{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Hcompta.Model.Transaction.Posting where import Data.Data import qualified Data.Foldable import qualified Data.List import qualified Data.Map import Data.Map (Map) import Data.Typeable () import Text.Parsec.Pos (SourcePos, initialPos) import qualified Hcompta.Model.Account as Account () import Hcompta.Model.Account (Account) import qualified Hcompta.Model.Amount as Amount import qualified Hcompta.Model.Date as Date import Hcompta.Model.Date (Date) import qualified Hcompta.Model.Transaction.Tag as Tag -- * The 'Posting' type data Posting = Posting { account :: Account , amounts :: Amount.By_Unit , comment :: String , date :: Date , date2 :: Maybe Date , status :: Bool , sourcepos :: SourcePos , tags :: Tag.By_Name , type_ :: Type } deriving (Data, Eq, Read, Show, Typeable) instance Read SourcePos where readsPrec _ s = [(initialPos s, "")] data Type = Type_Regular | Type_Virtual | Type_Virtual_Balanced deriving (Data, Eq, Read, Show, Typeable) -- ** Convenient constructors nil :: Posting nil = Posting { account = [] , amounts = Data.Map.empty , comment = "" , date = Date.nil , date2 = Nothing , status = False , sourcepos = initialPos "" , tags = Data.Map.empty , type_ = Type_Regular } -- * The 'By_Account' mapping type By_Account = Map Account [Posting] -- ** Convenient constructors -- | Return a tuple associating the given posting with its account. by_account :: Posting -> (Account, Posting) by_account posting = (account posting, posting) -- | Return a 'Data.Map.Map' associating the given 'Posting's with their respective 'Unit'. from_List :: [Posting] -> By_Account from_List postings = Data.Map.fromListWith (++) $ Data.List.map (\posting -> (account posting, [posting])) postings -- * Collectors -- | Return the units in use within the given postings units :: Data.Foldable.Foldable m => m [Posting] -> [Amount.Unit] units = Data.Foldable.foldl (\acc -> Data.List.union acc . Data.List.concatMap (Data.Map.keys . amounts)) []