]> Git — Sourcephile - comptalang.git/blob - lib/Hcompta/Posting.hs
Ajout : Hcompta.Format.JCC.
[comptalang.git] / lib / Hcompta / Posting.hs
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
4 {-# LANGUAGE TypeFamilies #-}
5 module Hcompta.Posting where
6
7 import Control.DeepSeq (NFData)
8 import Data.Data
9 import Data.Eq (Eq)
10 import Data.Foldable (Foldable(..))
11 import Data.Monoid (Monoid)
12 import Data.Ord (Ord)
13 import Data.Typeable ()
14 import Prelude (($), (.))
15 import Text.Show (Show)
16
17 import Hcompta.Account
18 import Hcompta.Amount
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
23
24 class
25 ( Account (Posting_Account p)
26 , Amount (Posting_Amount p)
27 , Foldable (Posting_Amounts p)
28 ) => Posting p where
29 type Posting_Account p
30 type Posting_Amount p
31 type Posting_Amounts p :: * -> *
32 posting_account :: p -> Posting_Account p
33 posting_amounts :: p -> Posting_Amounts p (Posting_Amount p)
34
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)
42
43 anchor :: Anchor.Path -> Posting_Anchor
44 anchor = Posting_Anchor . Anchor.anchor
45
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
50
51 -- * Type 'Posting_Tag'
52 newtype Posting_Tag
53 = Posting_Tag Tag
54 deriving (Data, Eq, NFData, Ord, Show, Typeable)
55 newtype Posting_Tags
56 = Posting_Tags Tags
57 deriving (Data, Eq, Monoid, NFData, Show, Typeable)
58
59 tag :: Tag.Path -> Tag.Value -> Posting_Tag
60 tag p v = Posting_Tag $ Tag.tag p v
61
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