hledger/hledger-lib/Ledger/Types.hs

154 lines
5.3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveDataTypeable #-}
{-|
2009-12-16 10:00:43 +03:00
Most data types are defined here to avoid import cycles.
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..
> [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.
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.
- hledger 0.8 has Transactions containing Postings, and no flattened type.
-}
2008-10-03 04:12:59 +04:00
module Ledger.Types
where
import Ledger.Utils
2007-07-02 22:57:37 +04:00
import qualified Data.Map as Map
import System.Time (ClockTime)
import Data.Typeable (Typeable)
type SmartDate = (String,String,String)
data WhichDate = ActualDate | EffectiveDate deriving (Eq,Show)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (Eq,Show,Ord)
2008-11-27 07:31:01 +03:00
data Interval = NoInterval | Daily | Weekly | Monthly | Quarterly | Yearly
deriving (Eq,Show,Ord)
type AccountName = String
data Side = L | R deriving (Eq,Show,Ord)
data Commodity = Commodity {
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
precision :: Int -- ^ number of decimal places to display
} deriving (Eq,Show,Ord)
2007-07-02 20:43:14 +04:00
data Amount = Amount {
commodity :: Commodity,
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)
newtype MixedAmount = Mixed [Amount] deriving (Eq)
2007-07-02 20:43:14 +04:00
data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
2009-04-04 00:04:51 +04:00
deriving (Eq,Show)
data Posting = Posting {
pstatus :: Bool,
paccount :: AccountName,
pamount :: MixedAmount,
pcomment :: String,
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)
data Transaction = Transaction {
tdate :: Day,
teffectivedate :: Maybe Day,
tstatus :: Bool, -- XXX tcleared ?
tcode :: String,
tdescription :: String,
tcomment :: String,
tpostings :: [Posting],
tpreceding_comment_lines :: String
2007-07-02 20:43:14 +04:00
} deriving (Eq)
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)
data HistoricalPrice = HistoricalPrice {
hdate :: Day,
hsymbol :: String,
hamount :: MixedAmount
} deriving (Eq) -- & Show (in Amount.hs)
2009-12-16 10:00:43 +03:00
data Journal = Journal {
jmodifiertxns :: [ModifierTransaction],
jperiodictxns :: [PeriodicTransaction],
jtxns :: [Transaction],
open_timelog_entries :: [TimeLogEntry],
historical_prices :: [HistoricalPrice],
2009-04-08 07:40:05 +04:00
final_comment_lines :: String,
filepath :: FilePath,
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,
apostings :: [Posting], -- ^ transactions in this account
abalance :: MixedAmount -- ^ sum of transactions in this account and subaccounts
2007-07-02 20:43:14 +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,
accountmap :: Map.Map AccountName Account
} 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.
-- 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
,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)
,depth :: Maybe Int
} deriving (Show)
2009-12-19 09:26:33 +03:00