2009-08-12 13:38:48 +04:00
|
|
|
{-# LANGUAGE DeriveDataTypeable #-}
|
2008-10-03 06:04:15 +04:00
|
|
|
{-|
|
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
Most data types are defined here to avoid import cycles.
|
2009-12-19 08:57:54 +03:00
|
|
|
Here is an overview of the hledger data model:
|
2009-12-16 10:00:43 +03:00
|
|
|
|
2009-12-19 04:56:12 +03:00
|
|
|
> Ledger -- hledger's ledger is a journal file plus cached/derived data
|
|
|
|
> Journal -- a representation of the journal file, containing..
|
2009-12-19 08:57:54 +03:00
|
|
|
> [Transaction] -- ..journal transactions, which have date, status, code, description and..
|
|
|
|
> [Posting] -- ..two or more account postings (account name and amount)
|
|
|
|
> Tree AccountName -- all account names as a tree
|
|
|
|
> Map AccountName Account -- a map from account name to account info (postings and balances)
|
2009-12-16 10:00:43 +03:00
|
|
|
|
|
|
|
For more detailed documentation on each type, see the corresponding modules.
|
|
|
|
|
2009-12-19 08:57:54 +03:00
|
|
|
Terminology has been in flux:
|
2009-12-16 10:00:43 +03:00
|
|
|
|
|
|
|
- ledger 2 had entries containing transactions.
|
|
|
|
|
|
|
|
- hledger 0.4 had Entrys containing RawTransactions, which were flattened to Transactions.
|
|
|
|
|
2009-12-19 04:56:12 +03:00
|
|
|
- ledger 3 has transactions containing postings.
|
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
- hledger 0.5 had LedgerTransactions containing Postings, which were flattened to Transactions.
|
|
|
|
|
2009-12-19 08:57:54 +03:00
|
|
|
- hledger 0.8 has Transactions containing Postings, and no flattened type.
|
2009-04-03 14:58:05 +04:00
|
|
|
|
2008-10-01 13:33:05 +04:00
|
|
|
-}
|
2008-10-03 06:04:15 +04:00
|
|
|
|
2008-10-03 04:12:59 +04:00
|
|
|
module Ledger.Types
|
2007-02-16 12:00:17 +03:00
|
|
|
where
|
2008-10-03 04:05:16 +04:00
|
|
|
import Ledger.Utils
|
2007-07-02 22:57:37 +04:00
|
|
|
import qualified Data.Map as Map
|
2009-08-12 13:21:46 +04:00
|
|
|
import System.Time (ClockTime)
|
2009-08-12 13:38:48 +04:00
|
|
|
import Data.Typeable (Typeable)
|
2007-02-16 12:00:17 +03:00
|
|
|
|
2008-10-10 05:53:39 +04:00
|
|
|
|
2008-11-27 03:35:00 +03:00
|
|
|
type SmartDate = (String,String,String)
|
|
|
|
|
2009-12-21 08:23:07 +03:00
|
|
|
data WhichDate = ActualDate | EffectiveDate deriving (Eq,Show)
|
2009-07-09 23:22:27 +04:00
|
|
|
|
2008-11-27 09:29:29 +03:00
|
|
|
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Show,Ord)
|
2008-11-27 07:31:01 +03:00
|
|
|
|
2008-12-04 02:20:38 +03:00
|
|
|
data Interval = NoInterval | Daily | Weekly | Monthly | Quarterly | Yearly
|
|
|
|
deriving (Eq,Show,Ord)
|
|
|
|
|
2008-10-18 14:38:01 +04:00
|
|
|
type AccountName = String
|
|
|
|
|
2008-11-22 23:30:43 +03:00
|
|
|
data Side = L | R deriving (Eq,Show,Ord)
|
2008-10-13 01:52:48 +04:00
|
|
|
|
|
|
|
data Commodity = Commodity {
|
2008-10-15 03:14:31 +04:00
|
|
|
symbol :: String, -- ^ the commodity's symbol
|
|
|
|
-- display preferences for amounts of this commodity
|
|
|
|
side :: Side, -- ^ should the symbol appear on the left or the right
|
|
|
|
spaced :: Bool, -- ^ should there be a space between symbol and quantity
|
|
|
|
comma :: Bool, -- ^ should thousands be comma-separated
|
2008-10-18 14:46:49 +04:00
|
|
|
precision :: Int -- ^ number of decimal places to display
|
2008-11-22 23:30:43 +03:00
|
|
|
} deriving (Eq,Show,Ord)
|
2007-07-02 20:43:14 +04:00
|
|
|
|
|
|
|
data Amount = Amount {
|
2008-10-13 01:52:48 +04:00
|
|
|
commodity :: Commodity,
|
2008-11-22 19:26:01 +03:00
|
|
|
quantity :: Double,
|
2009-11-25 20:44:51 +03:00
|
|
|
price :: Maybe MixedAmount -- ^ unit price/conversion rate for this amount at posting time
|
2007-07-02 20:43:14 +04:00
|
|
|
} deriving (Eq)
|
|
|
|
|
2008-10-18 14:38:01 +04:00
|
|
|
newtype MixedAmount = Mixed [Amount] deriving (Eq)
|
2007-07-02 20:43:14 +04:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
|
2009-04-04 00:04:51 +04:00
|
|
|
deriving (Eq,Show)
|
2008-10-16 10:00:46 +04:00
|
|
|
|
2009-04-03 14:58:05 +04:00
|
|
|
data Posting = Posting {
|
|
|
|
pstatus :: Bool,
|
|
|
|
paccount :: AccountName,
|
|
|
|
pamount :: MixedAmount,
|
|
|
|
pcomment :: String,
|
2009-12-19 06:44:52 +03:00
|
|
|
ptype :: PostingType,
|
|
|
|
ptransaction :: Maybe Transaction -- ^ this posting's parent transaction (co-recursive types).
|
|
|
|
-- Tying this knot gets tedious, Maybe makes it easier/optional.
|
2007-07-02 20:43:14 +04:00
|
|
|
} deriving (Eq)
|
|
|
|
|
2009-12-16 11:07:26 +03:00
|
|
|
data Transaction = Transaction {
|
2009-12-16 20:58:51 +03:00
|
|
|
tdate :: Day,
|
|
|
|
teffectivedate :: Maybe Day,
|
2009-12-21 08:23:07 +03:00
|
|
|
tstatus :: Bool, -- XXX tcleared ?
|
2009-12-16 20:58:51 +03:00
|
|
|
tcode :: String,
|
|
|
|
tdescription :: String,
|
|
|
|
tcomment :: String,
|
|
|
|
tpostings :: [Posting],
|
|
|
|
tpreceding_comment_lines :: String
|
2007-07-02 20:43:14 +04:00
|
|
|
} deriving (Eq)
|
|
|
|
|
2009-12-19 08:57:54 +03:00
|
|
|
data ModifierTransaction = ModifierTransaction {
|
|
|
|
mtvalueexpr :: String,
|
|
|
|
mtpostings :: [Posting]
|
|
|
|
} deriving (Eq)
|
|
|
|
|
|
|
|
data PeriodicTransaction = PeriodicTransaction {
|
|
|
|
ptperiodicexpr :: String,
|
|
|
|
ptpostings :: [Posting]
|
|
|
|
} deriving (Eq)
|
|
|
|
|
2009-04-04 00:04:51 +04:00
|
|
|
data TimeLogCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (Eq,Ord)
|
|
|
|
|
|
|
|
data TimeLogEntry = TimeLogEntry {
|
|
|
|
tlcode :: TimeLogCode,
|
|
|
|
tldatetime :: LocalTime,
|
|
|
|
tlcomment :: String
|
|
|
|
} deriving (Eq,Ord)
|
|
|
|
|
2008-12-16 13:54:20 +03:00
|
|
|
data HistoricalPrice = HistoricalPrice {
|
2009-04-03 14:58:05 +04:00
|
|
|
hdate :: Day,
|
2009-12-09 23:51:00 +03:00
|
|
|
hsymbol :: String,
|
|
|
|
hamount :: MixedAmount
|
|
|
|
} deriving (Eq) -- & Show (in Amount.hs)
|
2008-12-16 13:54:20 +03:00
|
|
|
|
2009-12-16 10:00:43 +03:00
|
|
|
data Journal = Journal {
|
2009-12-16 20:58:51 +03:00
|
|
|
jmodifiertxns :: [ModifierTransaction],
|
|
|
|
jperiodictxns :: [PeriodicTransaction],
|
|
|
|
jtxns :: [Transaction],
|
2008-12-08 04:48:03 +03:00
|
|
|
open_timelog_entries :: [TimeLogEntry],
|
2008-12-16 13:54:20 +03:00
|
|
|
historical_prices :: [HistoricalPrice],
|
2009-04-08 07:40:05 +04:00
|
|
|
final_comment_lines :: String,
|
2009-08-12 13:21:46 +04:00
|
|
|
filepath :: FilePath,
|
2009-12-21 08:43:10 +03:00
|
|
|
filereadtime :: ClockTime,
|
|
|
|
jtext :: String
|
2007-07-02 20:43:14 +04:00
|
|
|
} deriving (Eq)
|
|
|
|
|
|
|
|
data Account = Account {
|
2008-10-03 02:33:32 +04:00
|
|
|
aname :: AccountName,
|
2009-12-19 08:57:54 +03:00
|
|
|
apostings :: [Posting], -- ^ transactions in this account
|
|
|
|
abalance :: MixedAmount -- ^ sum of transactions in this account and subaccounts
|
2007-07-02 20:43:14 +04:00
|
|
|
}
|
|
|
|
|
2007-07-02 23:15:39 +04:00
|
|
|
data Ledger = Ledger {
|
2009-12-16 10:00:43 +03:00
|
|
|
journal :: Journal,
|
2007-07-03 03:41:07 +04:00
|
|
|
accountnametree :: Tree AccountName,
|
2008-10-13 01:52:48 +04:00
|
|
|
accountmap :: Map.Map AccountName Account
|
2009-08-12 13:38:48 +04:00
|
|
|
} deriving Typeable
|
2007-07-02 22:57:37 +04:00
|
|
|
|
2009-12-19 09:26:33 +03:00
|
|
|
-- | A generic, pure specification of how to filter transactions/postings.
|
2009-12-21 08:23:07 +03:00
|
|
|
-- This exists to keep app-specific options out of the hledger library.
|
2009-12-19 09:26:33 +03:00
|
|
|
data FilterSpec = FilterSpec {
|
|
|
|
datespan :: DateSpan -- ^ only include if in this date span
|
|
|
|
,cleared :: Maybe Bool -- ^ only include if cleared\/uncleared\/don't care
|
|
|
|
,real :: Bool -- ^ only include if real\/don't care
|
2009-12-21 08:23:07 +03:00
|
|
|
,empty :: Bool -- ^ include if empty (ie amount is zero)
|
2009-12-19 09:26:33 +03:00
|
|
|
,costbasis :: Bool -- ^ convert all amounts to cost basis
|
|
|
|
,acctpats :: [String] -- ^ only include if matching these account patterns
|
|
|
|
,descpats :: [String] -- ^ only include if matching these description patterns
|
|
|
|
,whichdate :: WhichDate -- ^ which dates to use (actual or effective)
|
2009-12-21 08:23:07 +03:00
|
|
|
,depth :: Maybe Int
|
|
|
|
} deriving (Show)
|
2009-12-19 09:26:33 +03:00
|
|
|
|