{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE TypeFamilies #-} module Hcompta.Posting where import Control.DeepSeq (NFData) import Data.Data import Data.Eq (Eq) import Data.Foldable (Foldable(..)) import Data.Monoid (Monoid) import Data.Ord (Ord) import Data.Typeable () import Prelude (($), (.)) import Text.Show (Show) import Hcompta.Account import Hcompta.Amount import Hcompta.Anchor (Anchor, Anchors) import qualified Hcompta.Anchor as Anchor import Hcompta.Tag (Tag, Tags) import qualified Hcompta.Tag as Tag class ( Account (Posting_Account p) , Amount (Posting_Amount p) , Foldable (Posting_Amounts p) ) => Posting p where type Posting_Account p type Posting_Amount p type Posting_Amounts p :: * -> * posting_account :: p -> Posting_Account p posting_amounts :: p -> Posting_Amounts p (Posting_Amount p) -- * Type 'Posting_Anchor' newtype Posting_Anchor = Posting_Anchor Anchor deriving (Data, Eq, NFData, Ord, Show, Typeable) newtype Posting_Anchors = Posting_Anchors Anchors deriving (Data, Eq, Monoid, NFData, Show, Typeable) anchor :: Anchor.Path -> Posting_Anchor anchor = Posting_Anchor . Anchor.anchor -- | Return the given 'Posting_Anchors' with the given 'Posting_Anchor' incorporated. anchor_cons :: Posting_Anchor -> Posting_Anchors -> Posting_Anchors anchor_cons (Posting_Anchor t) (Posting_Anchors ts) = Posting_Anchors $ Anchor.cons t ts -- * Type 'Posting_Tag' newtype Posting_Tag = Posting_Tag Tag deriving (Data, Eq, NFData, Ord, Show, Typeable) newtype Posting_Tags = Posting_Tags Tags deriving (Data, Eq, Monoid, NFData, Show, Typeable) tag :: Tag.Path -> Tag.Value -> Posting_Tag tag p v = Posting_Tag $ Tag.tag p v -- | Return the given 'Posting_Tags' with the given 'Posting_Tag' incorporated. tag_cons :: Posting_Tag -> Posting_Tags -> Posting_Tags tag_cons (Posting_Tag t) (Posting_Tags ts) = Posting_Tags $ Tag.cons t ts