{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Hcompta.Format.JCC ( module Hcompta.Format.JCC , module Hcompta.Format.JCC.Amount , module Hcompta.Format.JCC.Unit , module Hcompta.Format.JCC.Quantity ) where -- import Control.Applicative (Const(..)) import Control.DeepSeq (NFData(..)) import Data.Data (Data(..)) import Data.Eq (Eq(..)) import Data.Function (id) import Data.Functor (Functor(..)) import Data.Functor.Compose (Compose(..)) import qualified Data.List as List import Data.List.NonEmpty (NonEmpty(..)) import Data.Map.Strict (Map) import qualified Data.Map.Strict as Map import Data.Maybe (Maybe(..)) import Data.Monoid (Monoid(..)) import Data.Ord (Ord(..)) import Data.Text (Text) import Data.Tuple (fst, uncurry) import Data.Typeable (Typeable) import Prelude (($), (.), FilePath, flip, seq, undefined) import Text.Parsec.Pos (SourcePos, initialPos) import Text.Show (Show(..)) import Hcompta.Account (Account_Anchor, Account_Tags) -- import qualified Hcompta.Amount as Amount -- import Hcompta.Balance (Balance(..)) import qualified Hcompta.Balance as Balance import qualified Hcompta.Chart as Chart import Hcompta.Date (Date) import qualified Hcompta.Date as Date import qualified Hcompta.Filter as Filter import qualified Hcompta.Filter.Read as Filter.Read -- import Hcompta.GL (GL(..)) import qualified Hcompta.GL as GL import qualified Hcompta.Journal as Journal -- import Hcompta.Lib.Consable import Hcompta.Lib.Parsec () import Hcompta.Lib.Regex (Regex) import qualified Hcompta.Polarize as Polarize import Hcompta.Posting (Posting_Anchors, Posting_Tags) import qualified Hcompta.Posting as Posting -- import qualified Hcompta.Quantity as Quantity import qualified Hcompta.Stats as Stats import Hcompta.Transaction (Transaction_Anchors, Transaction_Tags) import Hcompta.Format.JCC.Amount import Hcompta.Format.JCC.Quantity import Hcompta.Format.JCC.Unit -- * Type 'Account' type Account_Section = Text type Account = NonEmpty Account_Section account :: Account_Section -> [Account_Section] -> Account account = (:|) -- ** Type 'Joker' type Account_Joker = [Account_Joker_Section] data Account_Joker_Section = Account_Joker_Any | Account_Joker_Section Text deriving (Data, Eq, Show, Typeable) -- ** Type 'Pattern' data Account_Pattern = Account_Pattern_Exact Account | Account_Pattern_Joker Account_Joker | Account_Pattern_Regex Regex deriving (Show, Typeable) -- * Type 'Chart' type Chart = Chart.Chart Account type Charted = Chart.Charted Account -- * Type 'Posting' data Posting = Posting { posting_account :: Account , posting_account_anchor :: Maybe (Account_Anchor, Maybe Account) , posting_amounts :: Map Unit Quantity , posting_anchors :: Posting_Anchors , posting_comments :: [Comment] , posting_dates :: [Date] , posting_sourcepos :: SourcePos , posting_tags :: Posting_Tags } deriving (Data, Eq, Show, Typeable) instance NFData Posting where rnf Posting { posting_account , posting_account_anchor , posting_amounts , posting_anchors , posting_comments , posting_dates -- , posting_sourcepos , posting_tags } = rnf posting_account `seq` rnf posting_account_anchor `seq` rnf posting_amounts `seq` rnf posting_anchors `seq` rnf posting_comments `seq` rnf posting_dates `seq` -- rnf posting_sourcepos rnf posting_tags posting :: Account -> Posting posting acct = Posting { posting_account = acct , posting_account_anchor = Nothing , posting_amounts = mempty , posting_anchors = mempty , posting_comments = mempty , posting_dates = mempty , posting_sourcepos = initialPos "" , posting_tags = mempty } map_Postings_by_Account :: [Posting] -> Map Account [Posting] map_Postings_by_Account = Map.fromListWith (flip mappend) . List.map (\p -> (posting_account p, [p])) instance Posting.Posting Posting where type Posting_Account Posting = Account type Posting_Amount Posting = Amount type Posting_Amounts Posting = [] posting_account = posting_account posting_amounts = List.map (uncurry Amount) . Map.toList . posting_amounts instance Posting.Posting (Charted Posting) where type Posting_Account (Charted Posting) = Charted Account type Posting_Amount (Charted Posting) = Posting.Posting_Amount Posting type Posting_Amounts (Charted Posting) = Posting.Posting_Amounts Posting posting_account (Chart.Charted c p) = Chart.Charted c $ Posting.posting_account p posting_amounts = Posting.posting_amounts . Chart.charted instance Balance.Posting Posting where type Posting_Account Posting = Account type Posting_Quantity Posting = Polarize.Polarized Quantity type Posting_Unit Posting = Unit posting_account = posting_account posting_amounts = Map.map Polarize.polarize . posting_amounts posting_set_amounts amounts p = p { posting_amounts=Map.map Polarize.depolarize amounts } instance Balance.Posting (Charted Posting) where type Posting_Account (Charted Posting) = Account type Posting_Quantity (Charted Posting) = Balance.Posting_Quantity Posting type Posting_Unit (Charted Posting) = Balance.Posting_Unit Posting posting_account = posting_account . Chart.charted posting_amounts = Map.map Polarize.polarize . posting_amounts . Chart.charted posting_set_amounts amounts (Chart.Charted c p) = Chart.Charted c p{ posting_amounts=Map.map Polarize.depolarize amounts } instance Show Filter.Read.Forall_Filter_Balance_Decimal where show t = show $ (Filter.Read.get_Forall_Filter_Balance_Decimal t :: Filter.Filter_Balance ( (Account_Tags, Account) , (Unit, Polarize.Polarized Quantity) )) instance Filter.Posting (Charted Posting) where posting_type = undefined -- NOTE: the posting_type will be given to Filter.test -- through instance Posting p => Posting (Posting_Typed p) -- by Filter.transaction_postings -- and Filter.transaction_postings_virtual instance GL.Posting Posting where type Posting_Account Posting = Account type Posting_Quantity Posting = Map Unit (Polarize.Polarized Quantity) posting_account = posting_account posting_quantity = Map.map Polarize.polarize . posting_amounts instance GL.Posting (Charted Posting) where type Posting_Account (Charted Posting) = Account type Posting_Quantity (Charted Posting) = GL.Posting_Quantity Posting posting_account = GL.posting_account . Chart.charted posting_quantity = GL.posting_quantity . Chart.charted instance Stats.Posting Posting where type Posting_Account Posting = Account type Posting_Quantity Posting = Quantity type Posting_Unit Posting = Unit posting_account = posting_account posting_amounts = posting_amounts instance Show Filter.Read.Forall_Filter_Posting_Decimal where show t = show $ (Filter.Read.get_Forall_Filter_Posting_Decimal t :: Filter.Filter_Posting (Charted Posting)) -- * Type 'Transaction' type Code = Text type Comment = Text type Comments = [Comment] type Wording = Text data Transaction = Transaction { transaction_anchors :: Transaction_Anchors , transaction_comments :: Comments , transaction_dates :: (Date, [Date]) , transaction_postings :: Map Account [Posting] , transaction_sourcepos :: SourcePos , transaction_tags :: Transaction_Tags , transaction_wording :: Wording } deriving (Data, Eq, Show, Typeable) instance NFData Transaction where rnf Transaction { transaction_tags , transaction_comments , transaction_dates , transaction_wording , transaction_postings -- , transaction_sourcepos } = rnf transaction_comments `seq` rnf transaction_dates `seq` rnf transaction_postings `seq` rnf transaction_tags `seq` -- rnf transaction_sourcepos `seq` rnf transaction_wording transaction :: Transaction transaction = Transaction { transaction_anchors = mempty , transaction_comments = [] , transaction_dates = (Date.nil, []) , transaction_postings = mempty , transaction_sourcepos = initialPos "" , transaction_tags = mempty , transaction_wording = "" } instance Filter.Transaction (Charted Transaction) where type Transaction_Posting (Charted Transaction) = Charted Posting type Transaction_Postings (Charted Transaction) = Compose (Map Account) [] transaction_date = fst . transaction_dates . Chart.charted transaction_wording = transaction_wording . Chart.charted transaction_postings (Chart.Charted c t) = fmap (Chart.Charted c) $ Compose $ transaction_postings t transaction_tags = transaction_tags . Chart.charted instance Show Filter.Read.Forall_Filter_Transaction_Decimal where show t = show $ (Filter.Read.get_Forall_Filter_Transaction_Decimal t :: Filter.Filter_Transaction (Charted Transaction)) instance Journal.Transaction Transaction where transaction_date = fst . transaction_dates instance Journal.Transaction (Charted Transaction) where transaction_date = Journal.transaction_date . Chart.charted instance Stats.Transaction Transaction where type Transaction_Posting Transaction = Posting type Transaction_Postings Transaction = Compose (Map Account) [] transaction_date = fst . transaction_dates transaction_postings = Compose . transaction_postings transaction_postings_size t = Map.size (transaction_postings t) transaction_tags = transaction_tags instance Stats.Transaction (Charted Transaction) where type Transaction_Posting (Charted Transaction) = Stats.Transaction_Posting Transaction type Transaction_Postings (Charted Transaction) = Stats.Transaction_Postings Transaction transaction_date = Stats.transaction_date . Chart.charted transaction_postings = Stats.transaction_postings . Chart.charted transaction_postings_size = Stats.transaction_postings_size . Chart.charted transaction_tags = Stats.transaction_tags . Chart.charted instance GL.Transaction Transaction where type Transaction_Line Transaction = Transaction type Transaction_Posting Transaction = Posting type Transaction_Postings Transaction = Compose (Map Account) [] transaction_line = id transaction_date = fst . transaction_dates transaction_postings = Compose . transaction_postings transaction_postings_filter f t = t{ transaction_postings = Map.mapMaybe (\p -> case List.filter f p of [] -> Nothing ps -> Just ps) (transaction_postings t) } instance GL.Transaction (Charted Transaction) where type Transaction_Line (Charted Transaction) = Transaction type Transaction_Posting (Charted Transaction) = Charted (GL.Transaction_Posting Transaction) type Transaction_Postings (Charted Transaction) = GL.Transaction_Postings Transaction transaction_line = Chart.charted transaction_date = GL.transaction_date . Chart.charted transaction_postings (Chart.Charted c t) = fmap (Chart.Charted c) $ GL.transaction_postings t transaction_postings_filter f (Chart.Charted c t) = Chart.Charted c t{ transaction_postings = Map.mapMaybe (\p -> case List.filter f $ fmap (Chart.Charted c) p of [] -> Nothing ps -> Just $ fmap Chart.charted ps) (transaction_postings t) } -- | Return a 'Map.Map' associating -- the given 'Transaction's with their respective 'Date'. transaction_by_Date :: [Transaction] -> (Compose (Map Date) []) Transaction transaction_by_Date = Compose . Map.fromListWith (flip mappend) . List.map (\t -> (fst $ transaction_dates t, [t])) -- * Type 'Journal' data Journal j = Journal { journal_amount_styles :: !Styles , journal_chart :: Chart , journal_file :: FilePath , journal_includes :: [Journal j] , journal_last_read_time :: Date , journal_content :: !j } deriving (Data, Eq, Show, Typeable) instance Functor Journal where fmap f j@Journal{journal_includes, journal_content} = j{ journal_content = f journal_content , journal_includes = fmap (fmap f) journal_includes } journal :: Monoid j => Journal j journal = Journal { journal_amount_styles = mempty , journal_chart = mempty , journal_file = mempty , journal_includes = mempty , journal_last_read_time = Date.nil , journal_content = mempty } instance Monoid j => Monoid (Journal j) where mempty = journal mappend x y = Journal { journal_amount_styles = journal_amount_styles x `mappend` journal_amount_styles y , journal_chart = journal_chart x `mappend` journal_chart y , journal_file = mempty , journal_includes = journal_includes x `mappend` journal_includes y , journal_last_read_time = journal_last_read_time x `min` journal_last_read_time y , journal_content = journal_content x `mappend` journal_content y } instance NFData j => NFData (Journal j) where rnf Journal { journal_amount_styles , journal_chart , journal_file , journal_includes , journal_last_read_time , journal_content } = rnf journal_amount_styles `seq` rnf journal_chart `seq` rnf journal_file `seq` rnf journal_includes `seq` rnf journal_last_read_time `seq` rnf journal_content