1{-|
2
3Most data types are defined here to avoid import cycles.
4Here is an overview of the hledger data model:
5
6> Journal                  -- a journal is read from one or more data files. It contains..
7>  [Transaction]           -- journal transactions (aka entries), which have date, cleared status, code, description and..
8>   [Posting]              -- multiple account postings, which have account name and amount
9>  [MarketPrice]           -- historical market prices for commodities
10>
11> Ledger                   -- a ledger is derived from a journal, by applying a filter specification and doing some further processing. It contains..
12>  Journal                 -- a filtered copy of the original journal, containing only the transactions and postings we are interested in
13>  [Account]               -- all accounts, in tree order beginning with a "root" account", with their balances and sub/parent accounts
14
15For more detailed documentation on each type, see the corresponding modules.
16
17-}
18
19-- {-# LANGUAGE DeriveAnyClass #-}  -- https://hackage.haskell.org/package/deepseq-1.4.4.0/docs/Control-DeepSeq.html#v:rnf
20{-# LANGUAGE DeriveGeneric #-}
21{-# LANGUAGE FlexibleInstances #-}
22{-# LANGUAGE OverloadedStrings #-}
23{-# LANGUAGE RecordWildCards #-}
24{-# LANGUAGE StandaloneDeriving #-}
25{-# LANGUAGE TypeSynonymInstances #-}
26
27module Hledger.Data.Types
28where
29
30import GHC.Generics (Generic)
31import Data.Decimal
32import Data.Default
33import Data.Functor (($>))
34import Data.List (intercalate)
35import Text.Blaze (ToMarkup(..))
36--XXX https://hackage.haskell.org/package/containers/docs/Data-Map.html
37--Note: You should use Data.Map.Strict instead of this module if:
38--You will eventually need all the values stored.
39--The stored values don't represent large virtual data structures to be lazily computed.
40import qualified Data.Map as M
41import Data.Text (Text)
42-- import qualified Data.Text as T
43import Data.Time.Calendar
44import Data.Time.LocalTime
45import Data.Word (Word8)
46import System.Time (ClockTime(..))
47import Text.Printf
48
49import Hledger.Utils.Regex
50
51
52-- | A possibly incomplete year-month-day date provided by the user, to be
53-- interpreted as either a date or a date span depending on context. Missing
54-- parts "on the left" will be filled from the provided reference date, e.g. if
55-- the year and month are missing, the reference date's year and month are used.
56-- Missing parts "on the right" are assumed, when interpreting as a date, to be
57-- 1, (e.g. if the year and month are present but the day is missing, it means
58-- first day of that month); or when interpreting as a date span, to be a
59-- wildcard (so it would mean all days of that month). See the `smartdate`
60-- parser for more examples.
61--
62-- Or, one of the standard periods and an offset relative to the reference date:
63-- (last|this|next) (day|week|month|quarter|year), where "this" means the period
64-- containing the reference date.
65data SmartDate
66  = SmartAssumeStart Year (Maybe (Month, Maybe MonthDay))
67  | SmartFromReference (Maybe Month) MonthDay
68  | SmartMonth Month
69  | SmartRelative SmartSequence SmartInterval
70  deriving (Show)
71
72data SmartSequence = Last | This | Next deriving (Show)
73data SmartInterval = Day | Week | Month | Quarter | Year deriving (Show)
74
75data WhichDate = PrimaryDate | SecondaryDate deriving (Eq,Show)
76
77data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Ord,Generic)
78
79instance Default DateSpan where def = DateSpan Nothing Nothing
80
81-- synonyms for various date-related scalars
82type Year = Integer
83type Month = Int     -- 1-12
84type Quarter = Int   -- 1-4
85type YearWeek = Int  -- 1-52
86type MonthWeek = Int -- 1-5
87type YearDay = Int   -- 1-366
88type MonthDay = Int  -- 1-31
89type WeekDay = Int   -- 1-7
90
91-- Typical report periods (spans of time), both finite and open-ended.
92-- A richer abstraction than DateSpan.
93data Period =
94    DayPeriod Day
95  | WeekPeriod Day
96  | MonthPeriod Year Month
97  | QuarterPeriod Year Quarter
98  | YearPeriod Year
99  | PeriodBetween Day Day
100  | PeriodFrom Day
101  | PeriodTo Day
102  | PeriodAll
103  deriving (Eq,Ord,Show,Generic)
104
105instance Default Period where def = PeriodAll
106
107---- Typical report period/subperiod durations, from a day to a year.
108--data Duration =
109--    DayLong
110--   WeekLong
111--   MonthLong
112--   QuarterLong
113--   YearLong
114--  deriving (Eq,Ord,Show,Generic)
115
116-- Ways in which a period can be divided into subperiods.
117data Interval =
118    NoInterval
119  | Days Int
120  | Weeks Int
121  | Months Int
122  | Quarters Int
123  | Years Int
124  | DayOfMonth Int
125  | WeekdayOfMonth Int Int
126  | DayOfWeek Int
127  | DayOfYear Int Int -- Month, Day
128  -- WeekOfYear Int
129  -- MonthOfYear Int
130  -- QuarterOfYear Int
131  deriving (Eq,Show,Ord,Generic)
132
133instance Default Interval where def = NoInterval
134
135type AccountName = Text
136
137data AccountType =
138    Asset
139  | Liability
140  | Equity
141  | Revenue
142  | Expense
143  | Cash  -- ^ a subtype of Asset - liquid assets to show in cashflow report
144  deriving (Show,Eq,Ord,Generic)
145
146-- not worth the trouble, letters defined in accountdirectivep for now
147--instance Read AccountType
148--  where
149--    readsPrec _ ('A' : xs) = [(Asset,     xs)]
150--    readsPrec _ ('L' : xs) = [(Liability, xs)]
151--    readsPrec _ ('E' : xs) = [(Equity,    xs)]
152--    readsPrec _ ('R' : xs) = [(Revenue,   xs)]
153--    readsPrec _ ('X' : xs) = [(Expense,   xs)]
154--    readsPrec _ _ = []
155
156data AccountAlias = BasicAlias AccountName AccountName
157                  | RegexAlias Regexp Replacement
158  deriving (Eq, Read, Show, Ord, Generic)
159
160data Side = L | R deriving (Eq,Show,Read,Ord,Generic)
161
162-- | The basic numeric type used in amounts.
163type Quantity = Decimal
164-- The following is for hledger-web, and requires blaze-markup.
165-- Doing it here avoids needing a matching flag on the hledger-web package.
166instance ToMarkup Quantity
167 where
168   toMarkup = toMarkup . show
169
170-- | An amount's per-unit or total cost/selling price in another
171-- commodity, as recorded in the journal entry eg with @ or @@.
172-- Docs call this "transaction price". The amount is always positive.
173data AmountPrice = UnitPrice Amount | TotalPrice Amount
174  deriving (Eq,Ord,Generic,Show)
175
176-- | Display style for an amount.
177data AmountStyle = AmountStyle {
178      ascommodityside   :: Side,                 -- ^ does the symbol appear on the left or the right ?
179      ascommodityspaced :: Bool,                 -- ^ space between symbol and quantity ?
180      asprecision       :: !AmountPrecision,     -- ^ number of digits displayed after the decimal point
181      asdecimalpoint    :: Maybe Char,           -- ^ character used as decimal point: period or comma. Nothing means "unspecified, use default"
182      asdigitgroups     :: Maybe DigitGroupStyle -- ^ style for displaying digit groups, if any
183} deriving (Eq,Ord,Read,Generic)
184
185instance Show AmountStyle where
186  show AmountStyle{..} =
187    printf "AmountStylePP \"%s %s %s %s %s..\""
188    (show ascommodityside)
189    (show ascommodityspaced)
190    (show asprecision)
191    (show asdecimalpoint)
192    (show asdigitgroups)
193
194data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (Eq,Ord,Read,Show,Generic)
195
196-- | A style for displaying digit groups in the integer part of a
197-- floating point number. It consists of the character used to
198-- separate groups (comma or period, whichever is not used as decimal
199-- point), and the size of each group, starting with the one nearest
200-- the decimal point. The last group size is assumed to repeat. Eg,
201-- comma between thousands is DigitGroups ',' [3].
202data DigitGroupStyle = DigitGroups Char [Word8]
203  deriving (Eq,Ord,Read,Show,Generic)
204
205type CommoditySymbol = Text
206
207data Commodity = Commodity {
208  csymbol :: CommoditySymbol,
209  cformat :: Maybe AmountStyle
210  } deriving (Show,Eq,Generic) --,Ord)
211
212data Amount = Amount {
213      acommodity  :: CommoditySymbol,   -- commodity symbol, or special value "AUTO"
214      aquantity   :: Quantity,          -- numeric quantity, or zero in case of "AUTO"
215      aismultiplier :: Bool,            -- ^ kludge: a flag marking this amount and posting as a multiplier
216                                        --   in a TMPostingRule. In a regular Posting, should always be false.
217      astyle      :: AmountStyle,
218      aprice      :: Maybe AmountPrice  -- ^ the (fixed, transaction-specific) price for this amount, if any
219    } deriving (Eq,Ord,Generic,Show)
220
221newtype MixedAmount = Mixed [Amount] deriving (Eq,Ord,Generic,Show)
222
223data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
224                   deriving (Eq,Show,Generic)
225
226type TagName = Text
227type TagValue = Text
228type Tag = (TagName, TagValue)  -- ^ A tag name and (possibly empty) value.
229type DateTag = (TagName, Day)
230
231-- | The status of a transaction or posting, recorded with a status mark
232-- (nothing, !, or *). What these mean is ultimately user defined.
233data Status = Unmarked | Pending | Cleared
234  deriving (Eq,Ord,Bounded,Enum,Generic)
235
236instance Show Status where -- custom show.. bad idea.. don't do it..
237  show Unmarked = ""
238  show Pending   = "!"
239  show Cleared   = "*"
240
241-- | A balance assertion is a declaration about an account's expected balance
242-- at a certain point (posting date and parse order). They provide additional
243-- error checking and readability to a journal file.
244--
245-- The 'BalanceAssertion' type is also used to represent balance assignments,
246-- which instruct hledger what an account's balance should become at a certain
247-- point.
248--
249-- Different kinds of balance assertions are discussed eg on #290.
250-- Variables include:
251--
252-- - which postings are to be summed (real/virtual; unmarked/pending/cleared; this account/this account including subs)
253--
254-- - which commodities within the balance are to be checked
255--
256-- - whether to do a partial or a total check (disallowing other commodities)
257--
258-- I suspect we want:
259--
260-- 1. partial, subaccount-exclusive, Ledger-compatible assertions. Because
261--    they're what we've always had, and removing them would break some
262--    journals unnecessarily.  Implemented with = syntax.
263--
264-- 2. total assertions. Because otherwise assertions are a bit leaky.
265--    Implemented with == syntax.
266--
267-- 3. subaccount-inclusive assertions. Because that's something folks need.
268--    Not implemented.
269--
270-- 4. flexible assertions allowing custom criteria (perhaps arbitrary
271--    queries). Because power users have diverse needs and want to try out
272--    different schemes (assert cleared balances, assert balance from real or
273--    virtual postings, etc.). Not implemented.
274--
275-- 5. multicommodity assertions, asserting the balance of multiple commodities
276--    at once. Not implemented, requires #934.
277--
278data BalanceAssertion = BalanceAssertion {
279      baamount    :: Amount,             -- ^ the expected balance in a particular commodity
280      batotal     :: Bool,               -- ^ disallow additional non-asserted commodities ?
281      bainclusive :: Bool,               -- ^ include subaccounts when calculating the actual balance ?
282      baposition  :: GenericSourcePos    -- ^ the assertion's file position, for error reporting
283    } deriving (Eq,Generic,Show)
284
285data Posting = Posting {
286      pdate             :: Maybe Day,         -- ^ this posting's date, if different from the transaction's
287      pdate2            :: Maybe Day,         -- ^ this posting's secondary date, if different from the transaction's
288      pstatus           :: Status,
289      paccount          :: AccountName,
290      pamount           :: MixedAmount,
291      pcomment          :: Text,              -- ^ this posting's comment lines, as a single non-indented multi-line string
292      ptype             :: PostingType,
293      ptags             :: [Tag],                   -- ^ tag names and values, extracted from the comment
294      pbalanceassertion :: Maybe BalanceAssertion,  -- ^ an expected balance in the account after this posting,
295                                                    --   in a single commodity, excluding subaccounts.
296      ptransaction      :: Maybe Transaction,       -- ^ this posting's parent transaction (co-recursive types).
297                                                    --   Tying this knot gets tedious, Maybe makes it easier/optional.
298      poriginal         :: Maybe Posting            -- ^ When this posting has been transformed in some way
299                                                    --   (eg its amount or price was inferred, or the account name was
300                                                    --   changed by a pivot or budget report), this references the original
301                                                    --   untransformed posting (which will have Nothing in this field).
302    } deriving (Generic)
303
304-- The equality test for postings ignores the parent transaction's
305-- identity, to avoid recurring ad infinitum.
306-- XXX could check that it's Just or Nothing.
307instance Eq Posting where
308    (==) (Posting a1 b1 c1 d1 e1 f1 g1 h1 i1 _ _) (Posting a2 b2 c2 d2 e2 f2 g2 h2 i2 _ _) =  a1==a2 && b1==b2 && c1==c2 && d1==d2 && e1==e2 && f1==f2 && g1==g2 && h1==h2 && i1==i2
309
310-- | Posting's show instance elides the parent transaction so as not to recurse forever.
311instance Show Posting where
312  show Posting{..} = "PostingPP {" ++ intercalate ", " [
313     "pdate="             ++ show (show pdate)
314    ,"pdate2="            ++ show (show pdate2)
315    ,"pstatus="           ++ show (show pstatus)
316    ,"paccount="          ++ show paccount
317    ,"pamount="           ++ show pamount
318    ,"pcomment="          ++ show pcomment
319    ,"ptype="             ++ show ptype
320    ,"ptags="             ++ show ptags
321    ,"pbalanceassertion=" ++ show pbalanceassertion
322    ,"ptransaction="      ++ show (ptransaction $> "txn")
323    ,"poriginal="         ++ show poriginal
324    ] ++ "}"
325
326-- TODO: needs renaming, or removal if no longer needed. See also TextPosition in Hledger.UI.Editor
327-- | The position of parse errors (eg), like parsec's SourcePos but generic.
328data GenericSourcePos = GenericSourcePos FilePath Int Int    -- ^ file path, 1-based line number and 1-based column number.
329                      | JournalSourcePos FilePath (Int, Int) -- ^ file path, inclusive range of 1-based line numbers (first, last).
330  deriving (Eq, Read, Show, Ord, Generic)
331
332--{-# ANN Transaction "HLint: ignore" #-}
333--    Ambiguous type variable ‘p0’ arising from an annotation
334--    prevents the constraint ‘(Data p0)’ from being solved.
335--    Probable fix: use a type annotation to specify what ‘p0’ should be.
336data Transaction = Transaction {
337      tindex                   :: Integer,   -- ^ this transaction's 1-based position in the transaction stream, or 0 when not available
338      tprecedingcomment        :: Text,      -- ^ any comment lines immediately preceding this transaction
339      tsourcepos               :: GenericSourcePos,  -- ^ the file position where the date starts
340      tdate                    :: Day,
341      tdate2                   :: Maybe Day,
342      tstatus                  :: Status,
343      tcode                    :: Text,
344      tdescription             :: Text,
345      tcomment                 :: Text,      -- ^ this transaction's comment lines, as a single non-indented multi-line string
346      ttags                    :: [Tag],     -- ^ tag names and values, extracted from the comment
347      tpostings                :: [Posting]  -- ^ this transaction's postings
348    } deriving (Eq,Generic,Show)
349
350-- | A transaction modifier rule. This has a query which matches postings
351-- in the journal, and a list of transformations to apply to those
352-- postings or their transactions. Currently there is one kind of transformation:
353-- the TMPostingRule, which adds a posting ("auto posting") to the transaction,
354-- optionally setting its amount to the matched posting's amount multiplied by a constant.
355data TransactionModifier = TransactionModifier {
356      tmquerytxt :: Text,
357      tmpostingrules :: [TMPostingRule]
358    } deriving (Eq,Generic,Show)
359
360nulltransactionmodifier = TransactionModifier{
361  tmquerytxt = ""
362 ,tmpostingrules = []
363}
364
365-- | A transaction modifier transformation, which adds an extra posting
366-- to the matched posting's transaction.
367-- Can be like a regular posting, or the amount can have the aismultiplier flag set,
368-- indicating that it's a multiplier for the matched posting's amount.
369type TMPostingRule = Posting
370
371-- | A periodic transaction rule, describing a transaction that recurs.
372data PeriodicTransaction = PeriodicTransaction {
373      ptperiodexpr   :: Text,     -- ^ the period expression as written
374      ptinterval     :: Interval, -- ^ the interval at which this transaction recurs
375      ptspan         :: DateSpan, -- ^ the (possibly unbounded) period during which this transaction recurs. Contains a whole number of intervals.
376      --
377      ptstatus       :: Status,   -- ^ some of Transaction's fields
378      ptcode         :: Text,
379      ptdescription  :: Text,
380      ptcomment      :: Text,
381      pttags         :: [Tag],
382      ptpostings     :: [Posting]
383    } deriving (Eq,Generic) -- , Show in PeriodicTransaction.hs
384
385nullperiodictransaction = PeriodicTransaction{
386      ptperiodexpr   = ""
387     ,ptinterval     = def
388     ,ptspan         = def
389     ,ptstatus       = Unmarked
390     ,ptcode         = ""
391     ,ptdescription  = ""
392     ,ptcomment      = ""
393     ,pttags         = []
394     ,ptpostings     = []
395}
396
397data TimeclockCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord,Generic)
398
399data TimeclockEntry = TimeclockEntry {
400      tlsourcepos   :: GenericSourcePos,
401      tlcode        :: TimeclockCode,
402      tldatetime    :: LocalTime,
403      tlaccount     :: AccountName,
404      tldescription :: Text
405    } deriving (Eq,Ord,Generic)
406
407-- | A market price declaration made by the journal format's P directive.
408-- It declares two things: a historical exchange rate between two commodities,
409-- and an amount display style for the second commodity.
410data PriceDirective = PriceDirective {
411   pddate      :: Day
412  ,pdcommodity :: CommoditySymbol
413  ,pdamount    :: Amount
414  } deriving (Eq,Ord,Generic,Show)
415        -- Show instance derived in Amount.hs (XXX why ?)
416
417-- | A historical market price (exchange rate) from one commodity to another.
418-- A more concise form of a PriceDirective, without the amount display info.
419data MarketPrice = MarketPrice {
420   mpdate :: Day                -- ^ Date on which this price becomes effective.
421  ,mpfrom :: CommoditySymbol    -- ^ The commodity being converted from.
422  ,mpto   :: CommoditySymbol    -- ^ The commodity being converted to.
423  ,mprate :: Quantity           -- ^ One unit of the "from" commodity is worth this quantity of the "to" commodity.
424  } deriving (Eq,Ord,Generic)
425        -- Show instance derived in Amount.hs (XXX why ?)
426
427-- additional valuation-related types in Valuation.hs
428
429-- | A Journal, containing transactions and various other things.
430-- The basic data model for hledger.
431--
432-- This is used during parsing (as the type alias ParsedJournal), and
433-- then finalised/validated for use as a Journal. Some extra
434-- parsing-related fields are included for convenience, at least for
435-- now. In a ParsedJournal these are updated as parsing proceeds, in a
436-- Journal they represent the final state at end of parsing (used eg
437-- by the add command).
438--
439data Journal = Journal {
440  -- parsing-related data
441   jparsedefaultyear      :: Maybe Year                            -- ^ the current default year, specified by the most recent Y directive (or current date)
442  ,jparsedefaultcommodity :: Maybe (CommoditySymbol,AmountStyle)   -- ^ the current default commodity and its format, specified by the most recent D directive
443  ,jparseparentaccounts   :: [AccountName]                         -- ^ the current stack of parent account names, specified by apply account directives
444  ,jparsealiases          :: [AccountAlias]                        -- ^ the current account name aliases in effect, specified by alias directives (& options ?)
445  -- ,jparsetransactioncount :: Integer                               -- ^ the current count of transactions parsed so far (only journal format txns, currently)
446  ,jparsetimeclockentries :: [TimeclockEntry]                       -- ^ timeclock sessions which have not been clocked out
447  ,jincludefilestack      :: [FilePath]
448  -- principal data
449  ,jdeclaredaccounts      :: [(AccountName,AccountDeclarationInfo)] -- ^ Accounts declared by account directives, in parse order (after journal finalisation)
450  ,jdeclaredaccounttypes  :: M.Map AccountType [AccountName]        -- ^ Accounts whose type has been declared in account directives (usually 5 top-level accounts)
451  ,jcommodities           :: M.Map CommoditySymbol Commodity        -- ^ commodities and formats declared by commodity directives
452  ,jinferredcommodities   :: M.Map CommoditySymbol AmountStyle      -- ^ commodities and formats inferred from journal amounts  TODO misnamed, should be eg jusedstyles
453  ,jpricedirectives       :: [PriceDirective]                       -- ^ Declarations of market prices by P directives, in parse order (after journal finalisation)
454  ,jinferredmarketprices  :: [MarketPrice]                          -- ^ Market prices implied by transactions, in parse order (after journal finalisation)
455  ,jtxnmodifiers          :: [TransactionModifier]
456  ,jperiodictxns          :: [PeriodicTransaction]
457  ,jtxns                  :: [Transaction]
458  ,jfinalcommentlines     :: Text                                   -- ^ any final trailing comments in the (main) journal file
459  ,jfiles                 :: [(FilePath, Text)]                     -- ^ the file path and raw text of the main and
460                                                                    --   any included journal files. The main file is first,
461                                                                    --   followed by any included files in the order encountered.
462  ,jlastreadtime          :: ClockTime                              -- ^ when this journal was last read from its file(s)
463  } deriving (Eq, Generic)
464
465deriving instance Generic ClockTime
466
467-- | A journal in the process of being parsed, not yet finalised.
468-- The data is partial, and list fields are in reverse order.
469type ParsedJournal = Journal
470
471-- | The id of a data format understood by hledger, eg @journal@ or @csv@.
472-- The --output-format option selects one of these for output.
473type StorageFormat = String
474
475-- | Extra information about an account that can be derived from
476-- its account directive (and the other account directives).
477data AccountDeclarationInfo = AccountDeclarationInfo {
478   adicomment          :: Text   -- ^ any comment lines following an account directive for this account
479  ,aditags             :: [Tag]  -- ^ tags extracted from the account comment, if any
480  ,adideclarationorder :: Int    -- ^ the order in which this account was declared,
481                                 --   relative to other account declarations, during parsing (1..)
482} deriving (Eq,Show,Generic)
483
484nullaccountdeclarationinfo = AccountDeclarationInfo {
485   adicomment          = ""
486  ,aditags             = []
487  ,adideclarationorder = 0
488}
489
490-- | An account, with its balances, parent/subaccount relationships, etc.
491-- Only the name is required; the other fields are added when needed.
492data Account = Account {
493   aname                     :: AccountName    -- ^ this account's full name
494  ,adeclarationinfo          :: Maybe AccountDeclarationInfo  -- ^ optional extra info from account directives
495  -- relationships in the tree
496  ,asubs                     :: [Account]      -- ^ this account's sub-accounts
497  ,aparent                   :: Maybe Account  -- ^ parent account
498  ,aboring                   :: Bool           -- ^ used in the accounts report to label elidable parents
499  -- balance information
500  ,anumpostings              :: Int            -- ^ the number of postings to this account
501  ,aebalance                 :: MixedAmount    -- ^ this account's balance, excluding subaccounts
502  ,aibalance                 :: MixedAmount    -- ^ this account's balance, including subaccounts
503  } deriving (Generic)
504
505-- | Whether an account's balance is normally a positive number (in
506-- accounting terms, a debit balance) or a negative number (credit balance).
507-- Assets and expenses are normally positive (debit), while liabilities, equity
508-- and income are normally negative (credit).
509-- https://en.wikipedia.org/wiki/Normal_balance
510data NormalSign = NormallyPositive | NormallyNegative deriving (Show, Eq)
511
512-- | A Ledger has the journal it derives from, and the accounts
513-- derived from that. Accounts are accessible both list-wise and
514-- tree-wise, since each one knows its parent and subs; the first
515-- account is the root of the tree and always exists.
516data Ledger = Ledger {
517  ljournal  :: Journal,
518  laccounts :: [Account]
519}
520
521