{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Hcompta.Model.Transaction where
import Data.Data
+import qualified Data.List
+import qualified Data.Map.Strict as Data.Map
+import Data.Text (Text)
import Data.Typeable ()
-import Text.Parsec.Pos (SourcePos)
+import Text.Parsec.Pos (SourcePos, initialPos)
-import qualified Hcompta.Model.Date as Date ()
-import Hcompta.Model.Date (Date)
+import qualified Hcompta.Model.Date as Date
+import Hcompta.Model.Date (Date)
import qualified Hcompta.Model.Transaction.Posting as Posting
-import qualified Hcompta.Model.Transaction.Tag as Tag
+import qualified Hcompta.Model.Transaction.Tag as Tag
-- * The 'Transaction' type
data Transaction
= Transaction
- { code :: String
- , comment :: String
- , date :: Date
- , date2 :: Maybe Date
- , description :: String
- , postings :: Posting.By_Account
- , preceding_comment_lines :: String
- , sourcepos :: SourcePos
- , status :: Bool
- , tags :: Tag.By_Name
+ { code :: Code
+ , comments_before :: [Comment]
+ , comments_after :: [Comment]
+ , dates :: (Date, [Date])
+ , description :: Description
+ , postings :: Posting.By_Account
+ , virtual_postings :: Posting.By_Account
+ , balanced_virtual_postings :: Posting.By_Account
+ , sourcepos :: SourcePos
+ , status :: Status
+ , tags :: Tag.By_Name
} deriving (Data, Eq, Read, Show, Typeable)
+type Code = Text
+type Comment = Posting.Comment
+type Description = Text
+type Status = Bool
+
+nil :: Transaction
+nil =
+ Transaction
+ { code = ""
+ , comments_before = []
+ , comments_after = []
+ , dates = (Date.nil, [])
+ , description = ""
+ , postings = Data.Map.empty
+ , virtual_postings = Data.Map.empty
+ , balanced_virtual_postings = Data.Map.empty
+ , sourcepos = initialPos ""
+ , status = False
+ , tags = Data.Map.empty
+ }
+
-- * Types to submodules
type Posting = Posting.Posting
type Tag = Tag.Tag
+
+-- * The 'By_Date' mapping
+
+type By_Date
+ = Data.Map.Map Date.UTC [Transaction]
+
+-- ** Convenient constructors
+
+-- | Return a tuple associating the given 'Transaction' with its 'Date'.
+by_date :: Transaction -> (Date.UTC, Transaction)
+by_date t = (Date.to_UTC $ fst $ dates t, t)
+
+-- | Return a Data.'Data.Map.Map' associating the given 'Transaction's with their respective 'Date'.
+from_List :: [Transaction] -> By_Date
+from_List =
+ Data.Map.fromListWith (flip (++)) .
+ Data.List.map (\t -> (Date.to_UTC $ fst $ dates t, [t]))