1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
4 {-# LANGUAGE TypeFamilies #-}
5 module Hcompta.Posting where
7 import Control.DeepSeq (NFData)
10 import Data.Foldable (Foldable(..))
11 import Data.Monoid (Monoid)
13 import Data.Typeable ()
14 import Prelude (($), (.))
15 import Text.Show (Show)
17 import Hcompta.Account
19 import Hcompta.Anchor (Anchor, Anchors)
20 import qualified Hcompta.Anchor as Anchor
21 import Hcompta.Tag (Tag, Tags)
22 import qualified Hcompta.Tag as Tag
25 ( Account (Posting_Account p)
26 , Amount (Posting_Amount p)
27 , Foldable (Posting_Amounts p)
29 type Posting_Account p
31 type Posting_Amounts p :: * -> *
32 posting_account :: p -> Posting_Account p
33 posting_amounts :: p -> Posting_Amounts p (Posting_Amount p)
35 -- * Type 'Posting_Anchor'
36 newtype Posting_Anchor
37 = Posting_Anchor Anchor
38 deriving (Data, Eq, NFData, Ord, Show, Typeable)
39 newtype Posting_Anchors
40 = Posting_Anchors Anchors
41 deriving (Data, Eq, Monoid, NFData, Show, Typeable)
43 anchor :: Anchor.Path -> Posting_Anchor
44 anchor = Posting_Anchor . Anchor.anchor
46 -- | Return the given 'Posting_Anchors' with the given 'Posting_Anchor' incorporated.
47 anchor_cons :: Posting_Anchor -> Posting_Anchors -> Posting_Anchors
48 anchor_cons (Posting_Anchor t) (Posting_Anchors ts) =
49 Posting_Anchors $ Anchor.cons t ts
51 -- * Type 'Posting_Tag'
54 deriving (Data, Eq, NFData, Ord, Show, Typeable)
57 deriving (Data, Eq, Monoid, NFData, Show, Typeable)
59 tag :: Tag.Path -> Tag.Value -> Posting_Tag
60 tag p v = Posting_Tag $ Tag.tag p v
62 -- | Return the given 'Posting_Tags' with the given 'Posting_Tag' incorporated.
63 tag_cons :: Posting_Tag -> Posting_Tags -> Posting_Tags
64 tag_cons (Posting_Tag t) (Posting_Tags ts) =
65 Posting_Tags $ Tag.cons t ts