1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveFunctor #-}
3 {-# LANGUAGE DeriveTraversable #-}
4 {-# LANGUAGE FlexibleInstances #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE TypeFamilies #-}
7 module Hcompta.Ledger.Chart where
9 import Control.DeepSeq (NFData(..))
12 import Data.Foldable (Foldable)
13 import Data.Function (on, (.))
14 import Data.Functor (Functor)
15 import Data.Monoid (Monoid(..))
16 import Data.Ord (Ord(..))
17 import Data.Traversable (Traversable)
18 import Data.TreeMap.Strict (TreeMap)
19 import Data.Typeable ()
20 import Text.Show (Show)
22 import qualified Hcompta.Account as H
23 import Hcompta.Ledger.Account
29 { chart_accounts :: TreeMap (H.Account_Section Account) H.Account_Tags
30 } deriving (Data, Eq, Show, Typeable)
31 instance NFData Chart where
34 instance Monoid Chart where
36 { chart_accounts = mempty
40 { chart_accounts = chart_accounts x `mappend` chart_accounts y
49 } deriving (Data, Eq, Foldable, Functor, Show, Traversable, Typeable)
51 instance Ord a => Ord (Charted a) where
52 compare = compare `on` charted
53 instance H.Account (Charted Account) where
54 type Account_Section (Charted Account) = H.Account_Section Account
55 account_path = H.account_path . charted