hledger-lib-1.10: Core data types, parsers and functionality for the hledger accounting tools

Safe HaskellNone
LanguageHaskell2010

Hledger

Synopsis

Documentation

trace :: String -> a -> a #

The trace function outputs the trace message given as its first argument, before returning the second argument as its result.

For example, this returns the value of f x but first outputs the message.

>>> let x = 123; f = show
>>> trace ("calling f with x = " ++ show x) (f x)
"calling f with x = 123
123"

The trace function should only be used for debugging, or for monitoring execution. The function is not referentially transparent: its type indicates that it is a pure function but it has the side effect of outputting the trace message.

data Color #

ANSI colors: come in various intensities, which are controlled by ColorIntensity

Constructors

Black 
Red 
Green 
Yellow 
Blue 
Magenta 
Cyan 
White 
Instances
Bounded Color 
Instance details

Defined in System.Console.ANSI.Types

Enum Color 
Instance details

Defined in System.Console.ANSI.Types

Eq Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

(==) :: Color -> Color -> Bool #

(/=) :: Color -> Color -> Bool #

Ord Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

compare :: Color -> Color -> Ordering #

(<) :: Color -> Color -> Bool #

(<=) :: Color -> Color -> Bool #

(>) :: Color -> Color -> Bool #

(>=) :: Color -> Color -> Bool #

max :: Color -> Color -> Color #

min :: Color -> Color -> Color #

Read Color 
Instance details

Defined in System.Console.ANSI.Types

Show Color 
Instance details

Defined in System.Console.ANSI.Types

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Ix Color 
Instance details

Defined in System.Console.ANSI.Types

data ColorIntensity #

ANSI colors come in two intensities

Constructors

Dull 
Vivid 
Instances
Bounded ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Enum ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Eq ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Ord ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Read ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Show ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

Ix ColorIntensity 
Instance details

Defined in System.Console.ANSI.Types

traceMarkerIO :: String -> IO () #

The traceMarkerIO function emits a marker to the eventlog, if eventlog profiling is available and enabled at runtime.

Compared to traceMarker, traceMarkerIO sequences the event with respect to other IO actions.

Since: base-4.7.0.0

traceMarker :: String -> a -> a #

The traceMarker function emits a marker to the eventlog, if eventlog profiling is available and enabled at runtime. The String is the name of the marker. The name is just used in the profiling tools to help you keep clear which marker is which.

This function is suitable for use in pure code. In an IO context use traceMarkerIO instead.

Note that when using GHC's SMP runtime, it is possible (but rare) to get duplicate events emitted if two CPUs simultaneously evaluate the same thunk that uses traceMarker.

Since: base-4.7.0.0

traceEventIO :: String -> IO () #

The traceEventIO function emits a message to the eventlog, if eventlog profiling is available and enabled at runtime.

Compared to traceEvent, traceEventIO sequences the event with respect to other IO actions.

Since: base-4.5.0.0

traceEvent :: String -> a -> a #

The traceEvent function behaves like trace with the difference that the message is emitted to the eventlog, if eventlog profiling is available and enabled at runtime.

It is suitable for use in pure code. In an IO context use traceEventIO instead.

Note that when using GHC's SMP runtime, it is possible (but rare) to get duplicate events emitted if two CPUs simultaneously evaluate the same thunk that uses traceEvent.

Since: base-4.5.0.0

traceStack :: String -> a -> a #

like trace, but additionally prints a call stack if one is available.

In the current GHC implementation, the call stack is only available if the program was compiled with -prof; otherwise traceStack behaves exactly like trace. Entries in the call stack correspond to SCC annotations, so it is a good idea to use -fprof-auto or -fprof-auto-calls to add SCC annotations automatically.

Since: base-4.5.0.0

traceShowM :: (Show a, Applicative f) => a -> f () #

Like traceM, but uses show on the argument to convert it to a String.

>>> :{
do
    x <- Just 3
    traceShowM x
    y <- pure 12
    traceShowM y
    pure (x*2 + y)
:}
3
12
Just 18

Since: base-4.7.0.0

traceM :: Applicative f => String -> f () #

Like trace but returning unit in an arbitrary Applicative context. Allows for convenient use in do-notation.

Note that the application of traceM is not an action in the Applicative context, as traceIO is in the IO type. While the fresh bindings in the following example will force the traceM expressions to be reduced every time the do-block is executed, traceM "not crashed" would only be reduced once, and the message would only be printed once. If your monad is in MonadIO, liftIO . traceIO may be a better option.

>>> :{
do
    x <- Just 3
    traceM ("x: " ++ show x)
    y <- pure 12
    traceM ("y: " ++ show y)
    pure (x*2 + y)
:}
x: 3
y: 12
Just 18

Since: base-4.7.0.0

traceShowId :: Show a => a -> a #

Like traceShow but returns the shown value instead of a third value.

>>> traceShowId (1+2+3, "hello" ++ "world")
(6,"helloworld")
(6,"helloworld")

Since: base-4.7.0.0

traceShow :: Show a => a -> b -> b #

Like trace, but uses show on the argument to convert it to a String.

This makes it convenient for printing the values of interesting variables or expressions inside a function. For example here we print the value of the variables x and y:

>>> let f x y = traceShow (x,y) (x + y) in f (1+2) 5
(3,5)
8

traceId :: String -> String #

Like trace but returns the message instead of a third value.

>>> traceId "hello"
"hello
hello"

Since: base-4.7.0.0

putTraceMsg :: String -> IO () #

 

traceIO :: String -> IO () #

The traceIO function outputs the trace message from the IO monad. This sequences the output with respect to other IO actions.

Since: base-4.5.0.0

ppShow :: Show a => a -> String #

Convert a generic value into a pretty String, if possible.

color :: ColorIntensity -> Color -> String -> String Source #

Wrap a string in ANSI codes to set and reset foreground colour.

bgColor :: ColorIntensity -> Color -> String -> String Source #

Wrap a string in ANSI codes to set and reset background colour.

testName :: Test -> String Source #

Get a Test's label, or the empty string.

flattenTests :: Test -> [Test] Source #

Flatten a Test containing TestLists into a list of single tests.

filterTests :: (Test -> Bool) -> Test -> Test Source #

Filter TestLists in a Test, recursively, preserving the structure.

is :: (Eq a, Show a) => a -> a -> Assertion Source #

Simple way to assert something is some expected value, with no label.

assertParse :: (Show t, Show e) => Either (ParseError t e) a -> Assertion Source #

Assert a parse result is successful, printing the parse error on failure.

assertParseFailure :: Either (ParseError t e) a -> Assertion Source #

Assert a parse result is successful, printing the parse error on failure.

assertParseEqual :: (Show a, Eq a, Show t, Show e) => Either (ParseError t e) a -> a -> Assertion Source #

Assert a parse result is some expected value, printing the parse error on failure.

printParseError :: Show a => a -> IO () Source #

type SystemString = String Source #

A string received from or being passed to the operating system, such as a file path, command-line argument, or environment variable name or value. With GHC versions before 7.2 on some platforms (posix) these are typically encoded. When converting, we assume the encoding is UTF-8 (cf http://www.dwheeler.com/essays/fixing-unix-linux-filenames.html#UTF8).

fromSystemString :: SystemString -> String Source #

Convert a system string to an ordinary string, decoding from UTF-8 if it appears to be UTF8-encoded and GHC version is less than 7.2.

toSystemString :: String -> SystemString Source #

Convert a unicode string to a system string, encoding with UTF-8 if we are on a posix platform with GHC < 7.2.

error' :: String -> a Source #

A SystemString-aware version of error.

userError' :: String -> IOError Source #

A SystemString-aware version of userError.

usageError :: String -> a Source #

A SystemString-aware version of error that adds a usage hint.

type Replacement = String Source #

A replacement pattern. May include numeric backreferences (N).

type Regexp = String Source #

Regular expression. Extended regular expression-ish syntax ? But does not support eg (?i) syntax.

regexReplaceBy :: Regexp -> (String -> String) -> String -> String Source #

Replace all occurrences of the regexp, transforming each match with the given function.

regexReplace :: Regexp -> Replacement -> String -> String Source #

Replace all occurrences of the regexp with the replacement pattern. The replacement pattern supports numeric backreferences (N) but no other RE syntax.

regexReplaceMemo :: Regexp -> Replacement -> String -> String Source #

A memoising version of regexReplace. Caches the result for each search pattern, replacement pattern, target string tuple.

newtype FastTree a Source #

An efficient-to-build tree suggested by Cale Gibbard, probably better than accountNameTreeFrom.

Constructors

T (Map a (FastTree a)) 
Instances
Eq a => Eq (FastTree a) Source # 
Instance details

Defined in Hledger.Utils.Tree

Methods

(==) :: FastTree a -> FastTree a -> Bool #

(/=) :: FastTree a -> FastTree a -> Bool #

Ord a => Ord (FastTree a) Source # 
Instance details

Defined in Hledger.Utils.Tree

Methods

compare :: FastTree a -> FastTree a -> Ordering #

(<) :: FastTree a -> FastTree a -> Bool #

(<=) :: FastTree a -> FastTree a -> Bool #

(>) :: FastTree a -> FastTree a -> Bool #

(>=) :: FastTree a -> FastTree a -> Bool #

max :: FastTree a -> FastTree a -> FastTree a #

min :: FastTree a -> FastTree a -> FastTree a #

Show a => Show (FastTree a) Source # 
Instance details

Defined in Hledger.Utils.Tree

Methods

showsPrec :: Int -> FastTree a -> ShowS #

show :: FastTree a -> String #

showList :: [FastTree a] -> ShowS #

root :: Tree a -> a Source #

subs :: Tree a -> Forest a Source #

leaves :: Tree a -> [a] Source #

List just the leaf nodes of a tree

subtreeat :: Eq a => a -> Tree a -> Maybe (Tree a) Source #

get the sub-tree rooted at the first (left-most, depth-first) occurrence of the specified node value

subtreeinforest :: Eq a => a -> [Tree a] -> Maybe (Tree a) Source #

get the sub-tree for the specified node value in the first tree in forest in which it occurs.

treeprune :: Int -> Tree a -> Tree a Source #

remove all nodes past a certain depth

treemap :: (a -> b) -> Tree a -> Tree b Source #

apply f to all tree nodes

treefilter :: (a -> Bool) -> Tree a -> Tree a Source #

remove all subtrees whose nodes do not fulfill predicate

treeany :: (a -> Bool) -> Tree a -> Bool Source #

is predicate true in any node of tree ?

showtree :: Show a => Tree a -> String Source #

show a compact ascii representation of a tree

showforest :: Show a => Forest a -> String Source #

show a compact ascii representation of a forest

treeFromPaths :: Ord a => [[a]] -> FastTree a Source #

data Ledger Source #

A Ledger has the journal it derives from, and the accounts derived from that. Accounts are accessible both list-wise and tree-wise, since each one knows its parent and subs; the first account is the root of the tree and always exists.

Constructors

Ledger 
Instances
Show Ledger # 
Instance details

Defined in Hledger.Data.Ledger

data NormalSign Source #

Whether an account's balance is normally a positive number (in accounting terms, a debit balance) or a negative number (credit balance). Assets and expenses are normally positive (debit), while liabilities, equity and income are normally negative (credit). https://en.wikipedia.org/wiki/Normal_balance

Instances
Eq NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

Data NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NormalSign -> c NormalSign #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NormalSign #

toConstr :: NormalSign -> Constr #

dataTypeOf :: NormalSign -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NormalSign) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NormalSign) #

gmapT :: (forall b. Data b => b -> b) -> NormalSign -> NormalSign #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NormalSign -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NormalSign -> r #

gmapQ :: (forall d. Data d => d -> u) -> NormalSign -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NormalSign -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NormalSign -> m NormalSign #

Show NormalSign Source # 
Instance details

Defined in Hledger.Data.Types

data Account Source #

An account, with name, balances and links to parent/subaccounts which let you walk up or down the account tree.

Constructors

Account 

Fields

Instances
Eq Account # 
Instance details

Defined in Hledger.Data.Account

Methods

(==) :: Account -> Account -> Bool #

(/=) :: Account -> Account -> Bool #

Data Account Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account #

toConstr :: Account -> Constr #

dataTypeOf :: Account -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Account) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) #

gmapT :: (forall b. Data b => b -> b) -> Account -> Account #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r #

gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account #

Show Account # 
Instance details

Defined in Hledger.Data.Account

Generic Account Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Account :: * -> * #

Methods

from :: Account -> Rep Account x #

to :: Rep Account x -> Account #

type Rep Account Source # 
Instance details

Defined in Hledger.Data.Types

type StorageFormat = String Source #

The id of a data format understood by hledger, eg journal or csv. The --output-format option selects one of these for output.

type ParsedJournal = Journal Source #

A journal in the process of being parsed, not yet finalised. The data is partial, and list fields are in reverse order.

data Journal Source #

A Journal, containing transactions and various other things. The basic data model for hledger.

This is used during parsing (as the type alias ParsedJournal), and then finalised/validated for use as a Journal. Some extra parsing-related fields are included for convenience, at least for now. In a ParsedJournal these are updated as parsing proceeds, in a Journal they represent the final state at end of parsing (used eg by the add command).

Constructors

Journal 

Fields

Instances
Eq Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Journal -> Journal -> Bool #

(/=) :: Journal -> Journal -> Bool #

Data Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Journal -> c Journal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Journal #

toConstr :: Journal -> Constr #

dataTypeOf :: Journal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Journal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Journal) #

gmapT :: (forall b. Data b => b -> b) -> Journal -> Journal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Journal -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Journal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Journal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Journal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Journal -> m Journal #

Show Journal # 
Instance details

Defined in Hledger.Data.Journal

Generic Journal Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Journal :: * -> * #

Methods

from :: Journal -> Rep Journal x #

to :: Rep Journal x -> Journal #

Semigroup Journal # 
Instance details

Defined in Hledger.Data.Journal

Monoid Journal # 
Instance details

Defined in Hledger.Data.Journal

NFData Journal Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Journal -> () #

type Rep Journal Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 (MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "Journal" PrefixI True) (((S1 (MetaSel (Just "jparsedefaultyear") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Year)) :*: (S1 (MetaSel (Just "jparsedefaultcommodity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (CommoditySymbol, AmountStyle))) :*: S1 (MetaSel (Just "jparseparentaccounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AccountName]))) :*: ((S1 (MetaSel (Just "jparsealiases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [AccountAlias]) :*: S1 (MetaSel (Just "jparsetimeclockentries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TimeclockEntry])) :*: (S1 (MetaSel (Just "jaccounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(AccountName, Maybe AccountCode)]) :*: S1 (MetaSel (Just "jcommodities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map CommoditySymbol Commodity))))) :*: (((S1 (MetaSel (Just "jinferredcommodities") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)) :*: S1 (MetaSel (Just "jmarketprices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [MarketPrice])) :*: (S1 (MetaSel (Just "jmodifiertxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModifierTransaction]) :*: S1 (MetaSel (Just "jperiodictxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PeriodicTransaction]))) :*: ((S1 (MetaSel (Just "jtxns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Transaction]) :*: S1 (MetaSel (Just "jfinalcommentlines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :*: (S1 (MetaSel (Just "jfiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(FilePath, Text)]) :*: S1 (MetaSel (Just "jlastreadtime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ClockTime))))))

data MarketPrice Source #

Instances
Eq MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Data MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MarketPrice -> c MarketPrice #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MarketPrice #

toConstr :: MarketPrice -> Constr #

dataTypeOf :: MarketPrice -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MarketPrice) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MarketPrice) #

gmapT :: (forall b. Data b => b -> b) -> MarketPrice -> MarketPrice #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MarketPrice -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MarketPrice -> r #

gmapQ :: (forall d. Data d => d -> u) -> MarketPrice -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MarketPrice -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MarketPrice -> m MarketPrice #

Ord MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Show MarketPrice # 
Instance details

Defined in Hledger.Data.Amount

Generic MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MarketPrice :: * -> * #

NFData MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: MarketPrice -> () #

type Rep MarketPrice Source # 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice = D1 (MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "MarketPrice" PrefixI True) (S1 (MetaSel (Just "mpdate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day) :*: (S1 (MetaSel (Just "mpcommodity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CommoditySymbol) :*: S1 (MetaSel (Just "mpamount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Amount))))

data TimeclockEntry Source #

Instances
Eq TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Data TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeclockEntry -> c TimeclockEntry #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeclockEntry #

toConstr :: TimeclockEntry -> Constr #

dataTypeOf :: TimeclockEntry -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeclockEntry) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeclockEntry) #

gmapT :: (forall b. Data b => b -> b) -> TimeclockEntry -> TimeclockEntry #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockEntry -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockEntry -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeclockEntry -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeclockEntry -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockEntry -> m TimeclockEntry #

Ord TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Show TimeclockEntry # 
Instance details

Defined in Hledger.Data.Timeclock

Generic TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockEntry :: * -> * #

NFData TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: TimeclockEntry -> () #

type Rep TimeclockEntry Source # 
Instance details

Defined in Hledger.Data.Types

data TimeclockCode Source #

Instances
Eq TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Data TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeclockCode -> c TimeclockCode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeclockCode #

toConstr :: TimeclockCode -> Constr #

dataTypeOf :: TimeclockCode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeclockCode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeclockCode) #

gmapT :: (forall b. Data b => b -> b) -> TimeclockCode -> TimeclockCode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockCode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeclockCode -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeclockCode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeclockCode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeclockCode -> m TimeclockCode #

Ord TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Read TimeclockCode # 
Instance details

Defined in Hledger.Data.Timeclock

Show TimeclockCode # 
Instance details

Defined in Hledger.Data.Timeclock

Generic TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockCode :: * -> * #

NFData TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: TimeclockCode -> () #

type Rep TimeclockCode Source # 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode = D1 (MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) ((C1 (MetaCons "SetBalance" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "SetRequiredHours" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "In" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Out" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FinalOut" PrefixI False) (U1 :: * -> *))))

data PeriodicTransaction Source #

Constructors

PeriodicTransaction 

Fields

Instances
Eq PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Data PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PeriodicTransaction -> c PeriodicTransaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PeriodicTransaction #

toConstr :: PeriodicTransaction -> Constr #

dataTypeOf :: PeriodicTransaction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PeriodicTransaction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PeriodicTransaction) #

gmapT :: (forall b. Data b => b -> b) -> PeriodicTransaction -> PeriodicTransaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PeriodicTransaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PeriodicTransaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> PeriodicTransaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PeriodicTransaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PeriodicTransaction -> m PeriodicTransaction #

Show PeriodicTransaction # 
Instance details

Defined in Hledger.Data.Transaction

Generic PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PeriodicTransaction :: * -> * #

NFData PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: PeriodicTransaction -> () #

type Rep PeriodicTransaction Source # 
Instance details

Defined in Hledger.Data.Types

data ModifierTransaction Source #

Constructors

ModifierTransaction 
Instances
Eq ModifierTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Data ModifierTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModifierTransaction -> c ModifierTransaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModifierTransaction #

toConstr :: ModifierTransaction -> Constr #

dataTypeOf :: ModifierTransaction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModifierTransaction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModifierTransaction) #

gmapT :: (forall b. Data b => b -> b) -> ModifierTransaction -> ModifierTransaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModifierTransaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModifierTransaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModifierTransaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModifierTransaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModifierTransaction -> m ModifierTransaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModifierTransaction -> m ModifierTransaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModifierTransaction -> m ModifierTransaction #

Show ModifierTransaction # 
Instance details

Defined in Hledger.Data.Transaction

Generic ModifierTransaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep ModifierTransaction :: * -> * #

NFData ModifierTransaction Source #

A periodic transaction rule, describing a transaction that recurs.

Instance details

Defined in Hledger.Data.Types

Methods

rnf :: ModifierTransaction -> () #

type Rep ModifierTransaction Source # 
Instance details

Defined in Hledger.Data.Types

type Rep ModifierTransaction = D1 (MetaData "ModifierTransaction" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "ModifierTransaction" PrefixI True) (S1 (MetaSel (Just "mtvalueexpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "mtpostings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Posting])))

data Transaction Source #

Constructors

Transaction 

Fields

Instances
Eq Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Data Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transaction -> c Transaction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transaction #

toConstr :: Transaction -> Constr #

dataTypeOf :: Transaction -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Transaction) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transaction) #

gmapT :: (forall b. Data b => b -> b) -> Transaction -> Transaction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transaction -> r #

gmapQ :: (forall d. Data d => d -> u) -> Transaction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Transaction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transaction -> m Transaction #

Show Transaction # 
Instance details

Defined in Hledger.Data.Transaction

Generic Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Transaction :: * -> * #

NFData Transaction Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Transaction -> () #

type Rep Transaction Source # 
Instance details

Defined in Hledger.Data.Types

data GenericSourcePos Source #

The position of parse errors (eg), like parsec's SourcePos but generic.

Constructors

GenericSourcePos FilePath Int Int

file path, 1-based line number and 1-based column number.

JournalSourcePos FilePath (Int, Int)

file path, inclusive range of 1-based line numbers (first, last).

Instances
Eq GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Data GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenericSourcePos -> c GenericSourcePos #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenericSourcePos #

toConstr :: GenericSourcePos -> Constr #

dataTypeOf :: GenericSourcePos -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c GenericSourcePos) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenericSourcePos) #

gmapT :: (forall b. Data b => b -> b) -> GenericSourcePos -> GenericSourcePos #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenericSourcePos -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenericSourcePos -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenericSourcePos -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenericSourcePos -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericSourcePos -> m GenericSourcePos #

Ord GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Read GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Show GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Generic GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep GenericSourcePos :: * -> * #

NFData GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: GenericSourcePos -> () #

type Rep GenericSourcePos Source # 
Instance details

Defined in Hledger.Data.Types

data Posting Source #

Constructors

Posting 

Fields

Instances
Eq Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Posting -> Posting -> Bool #

(/=) :: Posting -> Posting -> Bool #

Data Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Posting -> c Posting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Posting #

toConstr :: Posting -> Constr #

dataTypeOf :: Posting -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Posting) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Posting) #

gmapT :: (forall b. Data b => b -> b) -> Posting -> Posting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Posting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Posting -> r #

gmapQ :: (forall d. Data d => d -> u) -> Posting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Posting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Posting -> m Posting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Posting -> m Posting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Posting -> m Posting #

Show Posting # 
Instance details

Defined in Hledger.Data.Posting

Generic Posting Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Posting :: * -> * #

Methods

from :: Posting -> Rep Posting x #

to :: Rep Posting x -> Posting #

NFData Posting Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Posting -> () #

type Rep Posting Source # 
Instance details

Defined in Hledger.Data.Types

data Status Source #

The status of a transaction or posting, recorded with a status mark (nothing, !, or *). What these mean is ultimately user defined.

Constructors

Unmarked 
Pending 
Cleared 
Instances
Bounded Status Source # 
Instance details

Defined in Hledger.Data.Types

Enum Status Source # 
Instance details

Defined in Hledger.Data.Types

Eq Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Data Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Status -> c Status #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Status #

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Status) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Status) #

gmapT :: (forall b. Data b => b -> b) -> Status -> Status #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Status -> r #

gmapQ :: (forall d. Data d => d -> u) -> Status -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Status -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Status -> m Status #

Ord Status Source # 
Instance details

Defined in Hledger.Data.Types

Show Status Source # 
Instance details

Defined in Hledger.Data.Types

Generic Status Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

NFData Status Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Status -> () #

type Rep Status Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 (MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "Unmarked" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Pending" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Cleared" PrefixI False) (U1 :: * -> *)))

type Tag Source #

Arguments

 = (TagName, TagValue)

A tag name and (possibly empty) value.

data PostingType Source #

Instances
Eq PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Data PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PostingType -> c PostingType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PostingType #

toConstr :: PostingType -> Constr #

dataTypeOf :: PostingType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PostingType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PostingType) #

gmapT :: (forall b. Data b => b -> b) -> PostingType -> PostingType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PostingType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PostingType -> r #

gmapQ :: (forall d. Data d => d -> u) -> PostingType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PostingType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PostingType -> m PostingType #

Show PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Generic PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PostingType :: * -> * #

NFData PostingType Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: PostingType -> () #

type Rep PostingType Source # 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType = D1 (MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "RegularPosting" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "VirtualPosting" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "BalancedVirtualPosting" PrefixI False) (U1 :: * -> *)))

newtype MixedAmount Source #

Constructors

Mixed [Amount] 
Instances
Eq MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Data MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MixedAmount -> c MixedAmount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MixedAmount #

toConstr :: MixedAmount -> Constr #

dataTypeOf :: MixedAmount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MixedAmount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MixedAmount) #

gmapT :: (forall b. Data b => b -> b) -> MixedAmount -> MixedAmount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MixedAmount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MixedAmount -> r #

gmapQ :: (forall d. Data d => d -> u) -> MixedAmount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MixedAmount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MixedAmount -> m MixedAmount #

Num MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

Ord MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Show MixedAmount # 
Instance details

Defined in Hledger.Data.Amount

Generic MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmount :: * -> * #

NFData MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: MixedAmount -> () #

type Rep MixedAmount Source # 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount = D1 (MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" True) (C1 (MetaCons "Mixed" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Amount])))

data Amount Source #

Constructors

Amount 

Fields

Instances
Eq Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Amount -> Amount -> Bool #

(/=) :: Amount -> Amount -> Bool #

Data Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Amount -> c Amount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Amount #

toConstr :: Amount -> Constr #

dataTypeOf :: Amount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Amount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Amount) #

gmapT :: (forall b. Data b => b -> b) -> Amount -> Amount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQ :: (forall d. Data d => d -> u) -> Amount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Amount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

Num Amount # 
Instance details

Defined in Hledger.Data.Amount

Ord Amount Source # 
Instance details

Defined in Hledger.Data.Types

Show Amount # 
Instance details

Defined in Hledger.Data.Amount

Generic Amount Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Amount :: * -> * #

Methods

from :: Amount -> Rep Amount x #

to :: Rep Amount x -> Amount #

NFData Amount Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Amount -> () #

type Rep Amount Source # 
Instance details

Defined in Hledger.Data.Types

data Commodity Source #

Instances
Eq Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Data Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Commodity -> c Commodity #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Commodity #

toConstr :: Commodity -> Constr #

dataTypeOf :: Commodity -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Commodity) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Commodity) #

gmapT :: (forall b. Data b => b -> b) -> Commodity -> Commodity #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Commodity -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Commodity -> r #

gmapQ :: (forall d. Data d => d -> u) -> Commodity -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Commodity -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Commodity -> m Commodity #

Show Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Generic Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Commodity :: * -> * #

NFData Commodity Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Commodity -> () #

type Rep Commodity Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity = D1 (MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "Commodity" PrefixI True) (S1 (MetaSel (Just "csymbol") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CommoditySymbol) :*: S1 (MetaSel (Just "cformat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AmountStyle))))

data DigitGroupStyle Source #

A style for displaying digit groups in the integer part of a floating point number. It consists of the character used to separate groups (comma or period, whichever is not used as decimal point), and the size of each group, starting with the one nearest the decimal point. The last group size is assumed to repeat. Eg, comma between thousands is DigitGroups ',' [3].

Constructors

DigitGroups Char [Int] 
Instances
Eq DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Data DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DigitGroupStyle -> c DigitGroupStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DigitGroupStyle #

toConstr :: DigitGroupStyle -> Constr #

dataTypeOf :: DigitGroupStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DigitGroupStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DigitGroupStyle) #

gmapT :: (forall b. Data b => b -> b) -> DigitGroupStyle -> DigitGroupStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DigitGroupStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DigitGroupStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> DigitGroupStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DigitGroupStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DigitGroupStyle -> m DigitGroupStyle #

Ord DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Read DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Generic DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DigitGroupStyle :: * -> * #

NFData DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: DigitGroupStyle -> () #

type Rep DigitGroupStyle Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 (MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "DigitGroups" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Char) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])))

data AmountStyle Source #

Display style for an amount.

Constructors

AmountStyle 

Fields

Instances
Eq AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Data AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmountStyle -> c AmountStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AmountStyle #

toConstr :: AmountStyle -> Constr #

dataTypeOf :: AmountStyle -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AmountStyle) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AmountStyle) #

gmapT :: (forall b. Data b => b -> b) -> AmountStyle -> AmountStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmountStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmountStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> AmountStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AmountStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountStyle -> m AmountStyle #

Ord AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Read AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Show AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Generic AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountStyle :: * -> * #

NFData AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AmountStyle -> () #

type Rep AmountStyle Source # 
Instance details

Defined in Hledger.Data.Types

data Price Source #

An amount's price (none, per unit, or total) in another commodity. Note the price should be a positive number, although this is not enforced.

Instances
Eq Price Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Price -> Price -> Bool #

(/=) :: Price -> Price -> Bool #

Data Price Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Price -> c Price #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Price #

toConstr :: Price -> Constr #

dataTypeOf :: Price -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Price) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Price) #

gmapT :: (forall b. Data b => b -> b) -> Price -> Price #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Price -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Price -> r #

gmapQ :: (forall d. Data d => d -> u) -> Price -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Price -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Price -> m Price #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Price -> m Price #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Price -> m Price #

Ord Price Source # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Price -> Price -> Ordering #

(<) :: Price -> Price -> Bool #

(<=) :: Price -> Price -> Bool #

(>) :: Price -> Price -> Bool #

(>=) :: Price -> Price -> Bool #

max :: Price -> Price -> Price #

min :: Price -> Price -> Price #

Generic Price Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Price :: * -> * #

Methods

from :: Price -> Rep Price x #

to :: Rep Price x -> Price #

NFData Price Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Price -> () #

type Rep Price Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Price = D1 (MetaData "Price" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "NoPrice" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "UnitPrice" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Amount)) :+: C1 (MetaCons "TotalPrice" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Amount))))

type Quantity = Decimal Source #

The basic numeric type used in amounts.

data Side Source #

Constructors

L 
R 
Instances
Eq Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Side -> Side -> Bool #

(/=) :: Side -> Side -> Bool #

Data Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Side -> c Side #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Side #

toConstr :: Side -> Constr #

dataTypeOf :: Side -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Side) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Side) #

gmapT :: (forall b. Data b => b -> b) -> Side -> Side #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Side -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Side -> r #

gmapQ :: (forall d. Data d => d -> u) -> Side -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Side -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Side -> m Side #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Side -> m Side #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Side -> m Side #

Ord Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Side -> Side -> Ordering #

(<) :: Side -> Side -> Bool #

(<=) :: Side -> Side -> Bool #

(>) :: Side -> Side -> Bool #

(>=) :: Side -> Side -> Bool #

max :: Side -> Side -> Side #

min :: Side -> Side -> Side #

Read Side Source # 
Instance details

Defined in Hledger.Data.Types

Show Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Side -> ShowS #

show :: Side -> String #

showList :: [Side] -> ShowS #

Generic Side Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Side :: * -> * #

Methods

from :: Side -> Rep Side x #

to :: Rep Side x -> Side #

NFData Side Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Side -> () #

type Rep Side Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Side = D1 (MetaData "Side" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "L" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "R" PrefixI False) (U1 :: * -> *))

data AccountAlias Source #

Instances
Eq AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Data AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountAlias -> c AccountAlias #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountAlias #

toConstr :: AccountAlias -> Constr #

dataTypeOf :: AccountAlias -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountAlias) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountAlias) #

gmapT :: (forall b. Data b => b -> b) -> AccountAlias -> AccountAlias #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountAlias -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountAlias -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountAlias -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountAlias -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountAlias -> m AccountAlias #

Ord AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Read AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Show AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Generic AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountAlias :: * -> * #

NFData AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: AccountAlias -> () #

type Rep AccountAlias Source # 
Instance details

Defined in Hledger.Data.Types

data Interval Source #

Instances
Eq Interval Source # 
Instance details

Defined in Hledger.Data.Types

Data Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Interval -> c Interval #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Interval #

toConstr :: Interval -> Constr #

dataTypeOf :: Interval -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Interval) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Interval) #

gmapT :: (forall b. Data b => b -> b) -> Interval -> Interval #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r #

gmapQ :: (forall d. Data d => d -> u) -> Interval -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Interval -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval #

Ord Interval Source # 
Instance details

Defined in Hledger.Data.Types

Show Interval Source # 
Instance details

Defined in Hledger.Data.Types

Generic Interval Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Interval :: * -> * #

Methods

from :: Interval -> Rep Interval x #

to :: Rep Interval x -> Interval #

Default Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Interval #

NFData Interval Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: Interval -> () #

type Rep Interval Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 (MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (((C1 (MetaCons "NoInterval" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Days" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "Weeks" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "Months" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "Quarters" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))) :+: ((C1 (MetaCons "Years" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "DayOfMonth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "WeekdayOfMonth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: (C1 (MetaCons "DayOfWeek" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "DayOfYear" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))))

data Period Source #

Instances
Eq Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Period -> Period -> Bool #

(/=) :: Period -> Period -> Bool #

Data Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Period -> c Period #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Period #

toConstr :: Period -> Constr #

dataTypeOf :: Period -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Period) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period) #

gmapT :: (forall b. Data b => b -> b) -> Period -> Period #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r #

gmapQ :: (forall d. Data d => d -> u) -> Period -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Period -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Period -> m Period #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period #

Ord Period Source # 
Instance details

Defined in Hledger.Data.Types

Show Period Source # 
Instance details

Defined in Hledger.Data.Types

Generic Period Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Period :: * -> * #

Methods

from :: Period -> Rep Period x #

to :: Rep Period x -> Period #

Default Period Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Period #

type Rep Period Source # 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 (MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (((C1 (MetaCons "DayPeriod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)) :+: C1 (MetaCons "WeekPeriod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day))) :+: (C1 (MetaCons "MonthPeriod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Year) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Month)) :+: C1 (MetaCons "QuarterPeriod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Year) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Quarter)))) :+: ((C1 (MetaCons "YearPeriod" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Year)) :+: C1 (MetaCons "PeriodBetween" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day))) :+: (C1 (MetaCons "PeriodFrom" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)) :+: (C1 (MetaCons "PeriodTo" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Day)) :+: C1 (MetaCons "PeriodAll" PrefixI False) (U1 :: * -> *)))))

type Month = Int Source #

data DateSpan Source #

Constructors

DateSpan (Maybe Day) (Maybe Day) 
Instances
Eq DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Data DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateSpan -> c DateSpan #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateSpan #

toConstr :: DateSpan -> Constr #

dataTypeOf :: DateSpan -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DateSpan) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateSpan) #

gmapT :: (forall b. Data b => b -> b) -> DateSpan -> DateSpan #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateSpan -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateSpan -> r #

gmapQ :: (forall d. Data d => d -> u) -> DateSpan -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DateSpan -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateSpan -> m DateSpan #

Ord DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Show DateSpan # 
Instance details

Defined in Hledger.Data.Dates

Generic DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DateSpan :: * -> * #

Methods

from :: DateSpan -> Rep DateSpan x #

to :: Rep DateSpan x -> DateSpan #

Default DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

def :: DateSpan #

NFData DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

Methods

rnf :: DateSpan -> () #

type Rep DateSpan Source # 
Instance details

Defined in Hledger.Data.Types

type Rep DateSpan = D1 (MetaData "DateSpan" "Hledger.Data.Types" "hledger-lib-1.10-FqAYt0yboj6rHcXZ5x5Op" False) (C1 (MetaCons "DateSpan" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Day)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Day))))

data WhichDate Source #

Constructors

PrimaryDate 
SecondaryDate 
Instances
Eq WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

Show WhichDate Source # 
Instance details

Defined in Hledger.Data.Types

periodAsDateSpan :: Period -> DateSpan Source #

Convert Periods to DateSpans.

>>> periodAsDateSpan (MonthPeriod 2000 1) == DateSpan (Just $ fromGregorian 2000 1 1) (Just $ fromGregorian 2000 2 1)
True

dateSpanAsPeriod :: DateSpan -> Period Source #

Convert DateSpans to Periods.

>>> dateSpanAsPeriod $ DateSpan (Just $ fromGregorian 2000 1 1) (Just $ fromGregorian 2000 2 1)
MonthPeriod 2000 1

simplifyPeriod :: Period -> Period Source #

Convert PeriodBetweens to a more abstract period where possible.

>>> simplifyPeriod $ PeriodBetween (fromGregorian 1 1 1) (fromGregorian 2 1 1)
YearPeriod 1
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 10 1) (fromGregorian 2001 1 1)
QuarterPeriod 2000 4
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 2 1) (fromGregorian 2000 3 1)
MonthPeriod 2000 2
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2016 7 25) (fromGregorian 2016 8 1)
WeekPeriod 2016-07-25
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 1 1) (fromGregorian 2000 1 2)
DayPeriod 2000-01-01
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 2 28) (fromGregorian 2000 3 1)
PeriodBetween 2000-02-28 2000-03-01
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 2 29) (fromGregorian 2000 3 1)
DayPeriod 2000-02-29
>>> simplifyPeriod $ PeriodBetween (fromGregorian 2000 12 31) (fromGregorian 2001 1 1)
DayPeriod 2000-12-31

isLastDayOfMonth :: (Eq a1, Eq a2, Num a1, Num a2) => Integer -> a1 -> a2 -> Bool Source #

isStandardPeriod :: Period -> Bool Source #

Is this period a "standard" period, referencing a particular day, week, month, quarter, or year ? Periods of other durations, or infinite duration, or not starting on a standard period boundary, are not.

showPeriod :: Period -> String Source #

Render a period as a compact display string suitable for user output.

>>> showPeriod (WeekPeriod (fromGregorian 2016 7 25))
"2016/07/25w30"

showPeriodMonthAbbrev :: Period -> String Source #

Like showPeriod, but if it's a month period show just the 3 letter month name abbreviation for the current locale.

periodNext :: Period -> Period Source #

Move a standard period to the following period of same duration. Non-standard periods are unaffected.

periodPrevious :: Period -> Period Source #

Move a standard period to the preceding period of same duration. Non-standard periods are unaffected.

periodNextIn :: DateSpan -> Period -> Period Source #

Move a standard period to the following period of same duration, staying within enclosing dates. Non-standard periods are unaffected.

periodPreviousIn :: DateSpan -> Period -> Period Source #

Move a standard period to the preceding period of same duration, staying within enclosing dates. Non-standard periods are unaffected.

periodMoveTo :: Day -> Period -> Period Source #

Move a standard period stepwise so that it encloses the given date. Non-standard periods are unaffected.

periodGrow :: Period -> Period Source #

Enlarge a standard period to the next larger enclosing standard period, if there is one. Eg, a day becomes the enclosing week. A week becomes whichever month the week's thursday falls into. A year becomes all (unlimited). Non-standard periods (arbitrary dates, or open-ended) are unaffected.

periodShrink :: Day -> Period -> Period Source #

Shrink a period to the next smaller standard period inside it, choosing the subperiod which contains today's date if possible, otherwise the first subperiod. It goes like this: unbounded periods and nonstandard periods (between two arbitrary dates) -> current year -> current quarter if it's in selected year, otherwise first quarter of selected year -> current month if it's in selected quarter, otherwise first month of selected quarter -> current week if it's in selected month, otherwise first week of selected month -> today if it's in selected week, otherwise first day of selected week, unless that's in previous month, in which case first day of month containing selected week. Shrinking a day has no effect.

data CustomErr Source #

A custom error type for the parser. The type is specialized to parsers of Text streams.

type JournalParser m a = StateT Journal (ParsecT CustomErr Text m) a Source #

A parser of text in some monad, with a journal as state.

type TextParser m a = ParsecT CustomErr Text m a Source #

A parser of text in some monad.

type SimpleTextParser = Parsec CustomErr Text Source #

A parser of strict text to some type.

type SimpleStringParser a = Parsec CustomErr String a Source #

A parser of string to some type.

choice' :: [TextParser m a] -> TextParser m a Source #

Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.

choiceInState :: [StateT s (ParsecT CustomErr Text m) a] -> StateT s (ParsecT CustomErr Text m) a Source #

Backtracking choice, use this when alternatives share a prefix. Consumes no input if all choices fail.

surroundedBy :: Applicative m => m openclose -> m a -> m a Source #

parseWithState' :: Stream s => st -> StateT st (ParsecT e s Identity) a -> s -> Either (ParseError (Token s) e) a Source #

fromparse :: (Show t, Show e) => Either (ParseError t e) a -> a Source #

parseerror :: (Show t, Show e) => ParseError t e -> a Source #

strip :: String -> String Source #

Remove leading and trailing whitespace.

lstrip :: String -> String Source #

Remove leading whitespace.

rstrip :: String -> String Source #

Remove trailing whitespace.

chomp :: String -> String Source #

Remove trailing newlines/carriage returns.

formatString :: Bool -> Maybe Int -> Maybe Int -> String -> String Source #

Clip and pad a string to a minimum & maximum width, andor leftright justify it. Works on multi-line strings too (but will rewrite non-unix line endings).

quoteIfNeeded :: String -> String Source #

Double-quote this string if it contains whitespace, single quotes or double-quotes, escaping the quotes as needed.

singleQuoteIfNeeded :: String -> String Source #

Single-quote this string if it contains whitespace or double-quotes. No good for strings containing single quotes.

words' :: String -> [String] Source #

Quote-aware version of words - don't split on spaces which are inside quotes. NB correctly handles "a'b" but not "'a'". Can raise an error if parsing fails.

unwords' :: [String] -> String Source #

Quote-aware version of unwords - single-quote strings which contain whitespace

concatTopPadded :: [String] -> String Source #

Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded. Treats wide characters as double width.

concatBottomPadded :: [String] -> String Source #

Join several multi-line strings as side-by-side rectangular strings of the same height, bottom-padded. Treats wide characters as double width.

concatOneLine :: [String] -> String Source #

Join multi-line strings horizontally, after compressing each of them to a single line with a comma and space between each original line.

vConcatLeftAligned :: [String] -> String Source #

Join strings vertically, left-aligned and right-padded.

vConcatRightAligned :: [String] -> String Source #

Join strings vertically, right-aligned and left-padded.

padtop :: Int -> String -> String Source #

Convert a multi-line string to a rectangular string top-padded to the specified height.

padbottom :: Int -> String -> String Source #

Convert a multi-line string to a rectangular string bottom-padded to the specified height.

padleft :: Int -> String -> String Source #

Convert a multi-line string to a rectangular string left-padded to the specified width. Treats wide characters as double width.

padright :: Int -> String -> String Source #

Convert a multi-line string to a rectangular string right-padded to the specified width. Treats wide characters as double width.

cliptopleft :: Int -> Int -> String -> String Source #

Clip a multi-line string to the specified width and height from the top left.

fitto :: Int -> Int -> String -> String Source #

Clip and pad a multi-line string to fill the specified width and height.

fitString :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String Source #

General-purpose wide-char-aware single-line string layout function. It can left- or right-pad a short string to a minimum width. It can left- or right-clip a long string to a maximum width, optionally inserting an ellipsis (the third argument). It clips and pads on the right when the fourth argument is true, otherwise on the left. It treats wide characters as double width.

fitStringMulti :: Maybe Int -> Maybe Int -> Bool -> Bool -> String -> String Source #

A version of fitString that works on multi-line strings, separate for now to avoid breakage. This will rewrite any line endings to unix newlines.

padLeftWide :: Int -> String -> String Source #

Left-pad a string to the specified width. Treats wide characters as double width. Works on multi-line strings too (but will rewrite non-unix line endings).

padRightWide :: Int -> String -> String Source #

Right-pad a string to the specified width. Treats wide characters as double width. Works on multi-line strings too (but will rewrite non-unix line endings).

takeWidth :: Int -> String -> String Source #

Double-width-character-aware string truncation. Take as many characters as possible from a string without exceeding the specified width. Eg takeWidth 3 "りんご" = "り".

strWidth :: String -> Int Source #

Calculate the render width of a string, considering wide characters (counted as double width), ANSI escape codes (not counted), and line breaks (in a multi-line string, the longest line determines the width).

charWidth :: Char -> Int Source #

Get the designated render width of a character: 0 for a combining character, 1 for a regular character, 2 for a wide character. (Wide characters are rendered as exactly double width in apps and fonts that support it.) (From Pandoc.)

textstrip :: Text -> Text Source #

Remove leading and trailing whitespace.

textlstrip :: Text -> Text Source #

Remove leading whitespace.

textrstrip :: Text -> Text Source #

Remove trailing whitespace.

quoteIfSpaced :: Text -> Text Source #

Wrap a string in double quotes, and -prefix any embedded single quotes, if it contains whitespace and is not already single- or double-quoted.

stripquotes :: Text -> Text Source #

Strip one matching pair of single or double quotes on the ends of a string.

textConcatTopPadded :: [Text] -> Text Source #

Join several multi-line strings as side-by-side rectangular strings of the same height, top-padded. Treats wide characters as double width.

fitText :: Maybe Int -> Maybe Int -> Bool -> Bool -> Text -> Text Source #

General-purpose wide-char-aware single-line text layout function. It can left- or right-pad a short string to a minimum width. It can left- or right-clip a long string to a maximum width, optionally inserting an ellipsis (the third argument). It clips and pads on the right when the fourth argument is true, otherwise on the left. It treats wide characters as double width.

textPadLeftWide :: Int -> Text -> Text Source #

Left-pad a text to the specified width. Treats wide characters as double width. Works on multi-line texts too (but will rewrite non-unix line endings).

textPadRightWide :: Int -> Text -> Text Source #

Right-pad a string to the specified width. Treats wide characters as double width. Works on multi-line strings too (but will rewrite non-unix line endings).

textTakeWidth :: Int -> Text -> Text Source #

Double-width-character-aware string truncation. Take as many characters as possible from a string without exceeding the specified width. Eg textTakeWidth 3 "りんご" = "り".

textWidth :: Text -> Int Source #

Calculate the designated render width of a string, taking into account wide characters and line breaks (the longest line within a multi-line string determines the width ).

pprint :: Show a => a -> IO () Source #

traceWith :: (a -> String) -> a -> a Source #

Trace (print to stderr) a showable value using a custom show function.

ptrace :: String -> TextParser m () Source #

Parsec trace - show the current parsec position and next input, and the provided label if it's non-null.

debugLevel :: Int Source #

Global debug level, which controls the verbosity of debug output on the console. The default is 0 meaning no debug output. The --debug command line flag sets it to 1, or --debug=N sets it to a higher value (note: not --debug N for some reason). This uses unsafePerformIO and can be accessed from anywhere and before normal command-line processing. When running with :main in GHCI, you must touch and reload this module to see the effect of a new --debug option. After command-line processing, it is also available as the debug_ field of CliOpts. {--} {--}

dbg0 :: Show a => String -> a -> a Source #

Convenience aliases for tracePrettyAt.

dbg1 :: Show a => String -> a -> a Source #

Pretty-print a message and the showable value to the console when the debug level is >= 1, then return it. Uses unsafePerformIO.

dbg2 :: Show a => String -> a -> a Source #

dbg3 :: Show a => String -> a -> a Source #

dbg4 :: Show a => String -> a -> a Source #

dbg5 :: Show a => String -> a -> a Source #

dbg6 :: Show a => String -> a -> a Source #

dbg7 :: Show a => String -> a -> a Source #

dbg8 :: Show a => String -> a -> a Source #

dbg9 :: Show a => String -> a -> a Source #

dbg0IO :: (MonadIO m, Show a) => String -> a -> m () Source #

Convenience aliases for tracePrettyAtIO. Like dbg, but convenient to insert in an IO monad. XXX These have a bug; they should use traceIO, not trace, otherwise GHC can occasionally over-optimise (cf lpaste a few days ago where it killed/blocked a child thread).

dbg1IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg2IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg3IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg4IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg5IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg6IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg7IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg8IO :: (MonadIO m, Show a) => String -> a -> m () Source #

dbg9IO :: (MonadIO m, Show a) => String -> a -> m () Source #

tracePrettyAt :: Show a => Int -> String -> a -> a Source #

Pretty-print a message and a showable value to the console if the debug level is at or above the specified level. At level 0, always prints. Otherwise, uses unsafePerformIO.

tracePrettyAtIO :: (MonadIO m, Show a) => Int -> String -> a -> m () Source #

log0 :: Show a => String -> a -> a Source #

logPrettyAt :: Show a => Int -> String -> a -> a Source #

Log a message and a pretty-printed showable value to ./debug.log, if the debug level is at or above the specified level. At level 0, always logs. Otherwise, uses unsafePerformIO.

dbgppshow :: Show a => Int -> String -> a -> a Source #

print this string to the console before evaluating the expression, if the global debug level is at or above the specified level. Uses unsafePerformIO. dbgtrace :: Int -> String -> a -> a dbgtrace level | debugLevel >= level = trace | otherwise = flip const

Print a showable value to the console, with a message, if the debug level is at or above the specified level (uses unsafePerformIO). Values are displayed with show, all on one line, which is hard to read. dbgshow :: Show a => Int -> String -> a -> a dbgshow level | debugLevel >= level = ltrace | otherwise = flip const

Print a showable value to the console, with a message, if the debug level is at or above the specified level (uses unsafePerformIO). Values are displayed with ppShow, each field/constructor on its own line.

dbgExit :: Show a => String -> a -> a Source #

Like dbg, then exit the program. Uses unsafePerformIO.

pdbg :: Int -> String -> TextParser m () Source #

Print a message and parsec debug info (parse position and next input) to the console when the debug level is at or above this level. Uses unsafePerformIO. pdbgAt :: GenParser m => Float -> String -> m ()

dbglog :: Show a => String -> a -> a Source #

Like dbg, but writes the output to "debug.log" in the current directory. Uses unsafePerformIO. Can fail due to log file contention if called too quickly ("*** Exception: debug.log: openFile: resource busy (file is locked)").

first3 :: (a, b, c) -> a Source #

second3 :: (a, b, c) -> b Source #

third3 :: (a, b, c) -> c Source #

first4 :: (a, b, c, d) -> a Source #

second4 :: (a, b, c, d) -> b Source #

third4 :: (a, b, c, d) -> c Source #

fourth4 :: (a, b, c, d) -> d Source #

first5 :: (a, b, c, d, e) -> a Source #

second5 :: (a, b, c, d, e) -> b Source #

third5 :: (a, b, c, d, e) -> c Source #

fourth5 :: (a, b, c, d, e) -> d Source #

fifth5 :: (a, b, c, d, e) -> e Source #

first6 :: (a, b, c, d, e, f) -> a Source #

second6 :: (a, b, c, d, e, f) -> b Source #

third6 :: (a, b, c, d, e, f) -> c Source #

fourth6 :: (a, b, c, d, e, f) -> d Source #

fifth6 :: (a, b, c, d, e, f) -> e Source #

sixth6 :: (a, b, c, d, e, f) -> f Source #

splitAtElement :: Eq a => a -> [a] -> [[a]] Source #

applyN :: Int -> (a -> a) -> a -> a Source #

Apply a function the specified number of times. Possibly uses O(n) stack ?

expandPath :: FilePath -> FilePath -> IO FilePath Source #

Convert a possibly relative, possibly tilde-containing file path to an absolute one, given the current directory. ~username is not supported. Leave "-" unchanged. Can raise an error.

firstJust :: Eq a => [Maybe a] -> Maybe a Source #

readFilePortably :: FilePath -> IO Text Source #

Read text from a file, handling any of the usual line ending conventions, using the system locale's text encoding, ignoring any utf8 BOM prefix (as seen in paypal's 2018 CSV, eg) if that encoding is utf8.

readFileOrStdinPortably :: String -> IO Text Source #

Like readFilePortably, but read from standard input if the path is "-".

maximum' :: Integral a => [a] -> a Source #

Total version of maximum, for integral types, giving 0 for an empty list.

sumStrict :: Num a => [a] -> a Source #

Strict version of sum that doesn’t leak space

maximumStrict :: Ord a => [a] -> a Source #

Strict version of maximum that doesn’t leak space

minimumStrict :: Ord a => [a] -> a Source #

Strict version of minimum that doesn’t leak space

sequence' :: Monad f => [f a] -> f [a] Source #

This is a version of sequence based on difference lists. It is slightly faster but we mostly use it because it uses the heap instead of the stack. This has the advantage that Neil Mitchell’s trick of limiting the stack size to discover space leaks doesn’t show this as a false positive.

mapM' :: Monad f => (a -> f b) -> [a] -> f [b] Source #

type RawOpts = [(String, String)] Source #

The result of running cmdargs: an association list of option names to string values.

inRawOpts :: String -> RawOpts -> Bool Source #

Is the named option present ?

showDateSpan :: DateSpan -> String Source #

Render a datespan as a display string, abbreviating into a compact form if possible.

showDateSpanMonthAbbrev :: DateSpan -> String Source #

Like showDateSpan, but show month spans as just the abbreviated month name in the current locale.

getCurrentDay :: IO Day Source #

Get the current local date.

getCurrentMonth :: IO Int Source #

Get the current local month number.

getCurrentYear :: IO Integer Source #

Get the current local year.

spansSpan :: [DateSpan] -> DateSpan Source #

Get overall span enclosing multiple sequentially ordered spans.

splitSpan :: Interval -> DateSpan -> [DateSpan] Source #

Split a DateSpan into consecutive whole spans of the specified interval which fully encompass the original span (and a little more when necessary). If no interval is specified, the original span is returned. If the original span is the null date span, ie unbounded, the null date span is returned. If the original span is empty, eg if the end date is <= the start date, no spans are returned.

Examples:

>>> let t i d1 d2 = splitSpan i $ mkdatespan d1 d2
>>> t NoInterval "2008/01/01" "2009/01/01"
[DateSpan 2008]
>>> t (Quarters 1) "2008/01/01" "2009/01/01"
[DateSpan 2008q1,DateSpan 2008q2,DateSpan 2008q3,DateSpan 2008q4]
>>> splitSpan (Quarters 1) nulldatespan
[DateSpan -]
>>> t (Days 1) "2008/01/01" "2008/01/01"  -- an empty datespan
[]
>>> t (Quarters 1) "2008/01/01" "2008/01/01"
[]
>>> t (Months 1) "2008/01/01" "2008/04/01"
[DateSpan 2008/01,DateSpan 2008/02,DateSpan 2008/03]
>>> t (Months 2) "2008/01/01" "2008/04/01"
[DateSpan 2008/01/01-2008/02/29,DateSpan 2008/03/01-2008/04/30]
>>> t (Weeks 1) "2008/01/01" "2008/01/15"
[DateSpan 2007/12/31w01,DateSpan 2008/01/07w02,DateSpan 2008/01/14w03]
>>> t (Weeks 2) "2008/01/01" "2008/01/15"
[DateSpan 2007/12/31-2008/01/13,DateSpan 2008/01/14-2008/01/27]
>>> t (DayOfMonth 2) "2008/01/01" "2008/04/01"
[DateSpan 2007/12/02-2008/01/01,DateSpan 2008/01/02-2008/02/01,DateSpan 2008/02/02-2008/03/01,DateSpan 2008/03/02-2008/04/01]
>>> t (WeekdayOfMonth 2 4) "2011/01/01" "2011/02/15"
[DateSpan 2010/12/09-2011/01/12,DateSpan 2011/01/13-2011/02/09,DateSpan 2011/02/10-2011/03/09]
>>> t (DayOfWeek 2) "2011/01/01" "2011/01/15"
[DateSpan 2010/12/28-2011/01/03,DateSpan 2011/01/04-2011/01/10,DateSpan 2011/01/11-2011/01/17]
>>> t (DayOfYear 11 29) "2011/10/01" "2011/10/15"
[DateSpan 2010/11/29-2011/11/28]
>>> t (DayOfYear 11 29) "2011/12/01" "2012/12/15"
[DateSpan 2011/11/29-2012/11/28,DateSpan 2012/11/29-2013/11/28]

daysInSpan :: DateSpan -> Maybe Integer Source #

Count the days in a DateSpan, or if it is open-ended return Nothing.

spanContainsDate :: DateSpan -> Day -> Bool Source #

Does the span include the given date ?

periodContainsDate :: Period -> Day -> Bool Source #

Does the period include the given date ? (Here to avoid import cycle).

spansIntersect :: [DateSpan] -> DateSpan Source #

Calculate the intersection of a number of datespans.

spanIntersect :: DateSpan -> DateSpan -> DateSpan Source #

Calculate the intersection of two datespans.

For non-intersecting spans, gives an empty span beginning on the second's start date: >>> mkdatespan "2018-01-01" "2018-01-03" spanIntersect mkdatespan "2018-01-03" "2018-01-05" DateSpan 20180103-20180102

spanIntervalIntersect :: Interval -> DateSpan -> DateSpan -> DateSpan Source #

Calculate the intersection of two DateSpans, adjusting the start date so the interval is preserved.

>>> let intervalIntersect = spanIntervalIntersect (Days 3)
>>> mkdatespan "2018-01-01" "2018-01-03" `intervalIntersect` mkdatespan "2018-01-01" "2018-01-05"
DateSpan 2018/01/01-2018/01/02
>>> mkdatespan "2018-01-01" "2018-01-05" `intervalIntersect` mkdatespan "2018-01-02" "2018-01-05"
DateSpan 2018/01/04
>>> mkdatespan "2018-01-01" "2018-01-05" `intervalIntersect` mkdatespan "2018-01-03" "2018-01-05"
DateSpan 2018/01/04
>>> mkdatespan "2018-01-01" "2018-01-05" `intervalIntersect` mkdatespan "2018-01-04" "2018-01-05"
DateSpan 2018/01/04
>>> mkdatespan "2018-01-01" "2018-01-05" `intervalIntersect` mkdatespan "2017-12-01" "2018-01-05"
DateSpan 2018/01/01-2018/01/04

spanDefaultsFrom :: DateSpan -> DateSpan -> DateSpan Source #

Fill any unspecified dates in the first span with the dates from the second one. Sort of a one-way spanIntersect.

spansUnion :: [DateSpan] -> DateSpan Source #

Calculate the union of a number of datespans.

spanUnion :: DateSpan -> DateSpan -> DateSpan Source #

Calculate the union of two datespans.

parsePeriodExpr :: Day -> Text -> Either (ParseError Char CustomErr) (Interval, DateSpan) Source #

Parse a period expression to an Interval and overall DateSpan using the provided reference date, or return a parse error.

parsePeriodExpr' :: Day -> Text -> (Interval, DateSpan) Source #

Like parsePeriodExpr, but call error' on failure.

fixSmartDateStr :: Day -> Text -> String Source #

Convert a smart date string to an explicit yyyy/mm/dd string using the provided reference date, or raise an error.

fixSmartDateStrEither :: Day -> Text -> Either (ParseError Char CustomErr) String Source #

A safe version of fixSmartDateStr.

fixSmartDate :: Day -> SmartDate -> Day Source #

Convert a SmartDate to an absolute date using the provided reference date.

Examples:

>>> :set -XOverloadedStrings
>>> let t = fixSmartDateStr (parsedate "2008/11/26")
>>> t "0000-01-01"
"0000/01/01"
>>> t "1999-12-02"
"1999/12/02"
>>> t "1999.12.02"
"1999/12/02"
>>> t "1999/3/2"
"1999/03/02"
>>> t "19990302"
"1999/03/02"
>>> t "2008/2"
"2008/02/01"
>>> t "0020/2"
"0020/02/01"
>>> t "1000"
"1000/01/01"
>>> t "4/2"
"2008/04/02"
>>> t "2"
"2008/11/02"
>>> t "January"
"2008/01/01"
>>> t "feb"
"2008/02/01"
>>> t "today"
"2008/11/26"
>>> t "yesterday"
"2008/11/25"
>>> t "tomorrow"
"2008/11/27"
>>> t "this day"
"2008/11/26"
>>> t "last day"
"2008/11/25"
>>> t "next day"
"2008/11/27"
>>> t "this week"  -- last monday
"2008/11/24"
>>> t "last week"  -- previous monday
"2008/11/17"
>>> t "next week"  -- next monday
"2008/12/01"
>>> t "this month"
"2008/11/01"
>>> t "last month"
"2008/10/01"
>>> t "next month"
"2008/12/01"
>>> t "this quarter"
"2008/10/01"
>>> t "last quarter"
"2008/07/01"
>>> t "next quarter"
"2009/01/01"
>>> t "this year"
"2008/01/01"
>>> t "last year"
"2007/01/01"
>>> t "next year"
"2009/01/01"

t "last wed" "20081119" t "next friday" "20081128" t "next january" "20090101"

parsedateM :: String -> Maybe Day Source #

Parse a couple of date string formats to a time type.

parsedate :: String -> Day Source #

Parse a YYYY-MM-DD or YYYYMMDD date string to a Day, or raise an error. For testing/debugging.

>>> parsedate "2008/02/03"
2008-02-03

smartdate :: TextParser m SmartDate Source #

Parse a date in any of the formats allowed in Ledger's period expressions, and some others. Assumes any text in the parse stream has been lowercased. Returns a SmartDate, to be converted to a full date later (see fixSmartDate).

Examples:

2004                                        (start of year, which must have 4+ digits)
2004/10                                     (start of month, which must be 1-12)
2004/10/1                                   (exact date, day must be 1-31)
10/1                                        (month and day in current year)
21                                          (day in current month)
october, oct                                (start of month in current year)
yesterday, today, tomorrow                  (-1, 0, 1 days from today)
last/this/next day/week/month/quarter/year  (-1, 0, 1 periods from the current period)
20181201                                    (8 digit YYYYMMDD with valid year month and day)
201812                                      (6 digit YYYYMM with valid year and month)

Note malformed digit sequences might give surprising results:

201813                                      (6 digits with an invalid month is parsed as start of 6-digit year)
20181301                                    (8 digits with an invalid month is parsed as start of 8-digit year)
20181232                                    (8 digits with an invalid day gives an error)
201801012                                   (9+ digits beginning with a valid YYYYMMDD gives an error)

Eg:

YYYYMMDD is parsed as year-month-date if those parts are valid (>=4 digits, 1-12, and 1-31 respectively): >>> parsewith (smartdate <* eof) "20181201" Right ("2018","12","01")

YYYYMM is parsed as year-month-01 if year and month are valid: >>> parsewith (smartdate <* eof) "201804" Right ("2018","04","01")

With an invalid month, it's parsed as a year: >>> parsewith (smartdate <* eof) "201813" Right ("201813","","")

A 9+ digit number beginning with valid YYYYMMDD gives an error: >>> parsewith (smartdate <* eof) "201801012" Left (...)

Big numbers not beginning with a valid YYYYMMDD are parsed as a year: >>> parsewith (smartdate <* eof) "201813012" Right ("201813012","","")

periodexprp :: Day -> TextParser m (Interval, DateSpan) Source #

>>> let p = parsePeriodExpr (parsedate "2008/11/26")
>>> p "from Aug to Oct"
Right (NoInterval,DateSpan 2008/08/01-2008/09/30)
>>> p "aug to oct"
Right (NoInterval,DateSpan 2008/08/01-2008/09/30)
>>> p "every 3 days in Aug"
Right (Days 3,DateSpan 2008/08)
>>> p "daily from aug"
Right (Days 1,DateSpan 2008/08/01-)
>>> p "every week to 2009"
Right (Weeks 1,DateSpan -2008/12/31)
>>> p "every 2nd day of month"
Right (DayOfMonth 2,DateSpan -)
>>> p "every 2nd day"
Right (DayOfMonth 2,DateSpan -)
>>> p "every 2nd day 2009-"
Right (DayOfMonth 2,DateSpan 2009/01/01-)  
>>> p "every 29th Nov"
Right (DayOfYear 11 29,DateSpan -)
>>> p "every 29th nov -2009"
Right (DayOfYear 11 29,DateSpan -2008/12/31)
>>> p "every nov 29th"
Right (DayOfYear 11 29,DateSpan -)
>>> p "every Nov 29th 2009-"
Right (DayOfYear 11 29,DateSpan 2009/01/01-)
>>> p "every 11/29 from 2009"
Right (DayOfYear 11 29,DateSpan 2009/01/01-)
>>> p "every 2nd Thursday of month to 2009"
Right (WeekdayOfMonth 2 4,DateSpan -2008/12/31)
>>> p "every 1st monday of month to 2009"
Right (WeekdayOfMonth 1 1,DateSpan -2008/12/31)
>>> p "every tue"
Right (DayOfWeek 2,DateSpan -)
>>> p "every 2nd day of week"
Right (DayOfWeek 2,DateSpan -)
>>> p "every 2nd day of month"
Right (DayOfMonth 2,DateSpan -)
>>> p "every 2nd day"
Right (DayOfMonth 2,DateSpan -)
>>> p "every 2nd day 2009-"
Right (DayOfMonth 2,DateSpan 2009/01/01-)
>>> p "every 2nd day of month 2009-"
Right (DayOfMonth 2,DateSpan 2009/01/01-)

mkdatespan :: String -> String -> DateSpan Source #

Make a datespan from two valid date strings parseable by parsedate (or raise an error). Eg: mkdatespan "201111" "20111231".

comm :: String -> CommoditySymbol Source #

Look up one of the sample commodities' symbol by name.

conversionRate :: CommoditySymbol -> CommoditySymbol -> Double Source #

Find the conversion rate between two commodities. Currently returns 1.

amountstyle :: AmountStyle Source #

Default amount style

amount :: Amount Source #

The empty simple amount.

nullamt :: Amount Source #

The empty simple amount.

missingamt :: Amount Source #

A temporary value for parsed transactions which had no amount specified.

amountWithCommodity :: CommoditySymbol -> Amount -> Amount Source #

Convert an amount to the specified commodity, ignoring and discarding any assigned prices and assuming an exchange rate of 1.

costOfAmount :: Amount -> Amount Source #

Convert an amount to the commodity of its assigned price, if any. Notes:

  • price amounts must be MixedAmounts with exactly one component Amount (or there will be a runtime error) XXX
  • price amounts should be positive, though this is not currently enforced

divideAmount :: Amount -> Quantity -> Amount Source #

Divide an amount's quantity by a constant.

isNegativeAmount :: Amount -> Bool Source #

Is this amount negative ? The price is ignored.

isZeroAmount :: Amount -> Bool Source #

Does this amount appear to be zero when displayed with its given precision ?

isReallyZeroAmount :: Amount -> Bool Source #

Is this amount "really" zero, regardless of the display precision ?

setAmountPrecision :: Int -> Amount -> Amount Source #

Set an amount's display precision.

withPrecision :: Amount -> Int -> Amount Source #

Set an amount's display precision, flipped.

showAmountDebug :: Amount -> String Source #

Get a string representation of an amount for debugging, appropriate to the current debug level. 9 shows maximum detail.

showAmountWithoutPrice :: Amount -> String Source #

Get the string representation of an amount, without any @ price.

styleAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount Source #

Given a map of standard amount display styles, apply the appropriate one to this amount. If there's no standard style for this amount's commodity, return the amount unchanged.

showAmount :: Amount -> String Source #

Get the string representation of an amount, based on its commodity's display settings. String representations equivalent to zero are converted to just "0". The special "missing" amount is displayed as the empty string.

cshowAmount :: Amount -> String Source #

Colour version. For a negative amount, adds ANSI codes to change the colour, currently to hard-coded red.

showAmountWithZeroCommodity :: Amount -> String Source #

Like showAmount, but show a zero amount's commodity if it has one.

maxprecision :: Int Source #

For rendering: a special precision value which means show all available digits.

maxprecisionwithpoint :: Int Source #

For rendering: a special precision value which forces display of a decimal point.

canonicaliseAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount Source #

Canonicalise an amount's display style using the provided commodity style map.

amountValue :: Journal -> Day -> Amount -> Amount Source #

Find the market value of this amount on the given date, in it's default valuation commodity, based on recorded market prices. If no default valuation commodity can be found, the amount is left unchanged.

nullmixedamt :: MixedAmount Source #

The empty mixed amount.

missingmixedamt :: MixedAmount Source #

A temporary value for parsed transactions which had no amount specified.

mixed :: [Amount] -> MixedAmount Source #

Convert amounts in various commodities into a normalised MixedAmount.

normaliseMixedAmount :: MixedAmount -> MixedAmount Source #

Simplify a mixed amount's component amounts:

  • amounts in the same commodity are combined unless they have different prices or total prices
  • multiple zero amounts, all with the same non-null commodity, are replaced by just the last of them, preserving the commodity and amount style (all but the last zero amount are discarded)
  • multiple zero amounts with multiple commodities, or no commodities, are replaced by one commodity-less zero amount
  • an empty amount list is replaced by one commodity-less zero amount
  • the special "missing" mixed amount remains unchanged

normaliseMixedAmountSquashPricesForDisplay :: MixedAmount -> MixedAmount Source #

Like normaliseMixedAmount, but combine each commodity's amounts into just one by throwing away all prices except the first. This is only used as a rendering helper, and could show a misleading price.

amounts :: MixedAmount -> [Amount] Source #

Get a mixed amount's component amounts.

filterMixedAmount :: (Amount -> Bool) -> MixedAmount -> MixedAmount Source #

Filter a mixed amount's component amounts by a predicate.

filterMixedAmountByCommodity :: CommoditySymbol -> MixedAmount -> MixedAmount Source #

Return an unnormalised MixedAmount containing exactly one Amount with the specified commodity and the quantity of that commodity found in the original. NB if Amount's quantity is zero it will be discarded next time the MixedAmount gets normalised.

costOfMixedAmount :: MixedAmount -> MixedAmount Source #

Convert a mixed amount's component amounts to the commodity of their assigned price, if any.

divideMixedAmount :: MixedAmount -> Quantity -> MixedAmount Source #

Divide a mixed amount's quantities by a constant.

averageMixedAmounts :: [MixedAmount] -> MixedAmount Source #

Calculate the average of some mixed amounts.

isNegativeMixedAmount :: MixedAmount -> Maybe Bool Source #

Is this mixed amount negative, if it can be normalised to a single commodity ?

isZeroMixedAmount :: MixedAmount -> Bool Source #

Does this mixed amount appear to be zero when displayed with its given precision ?

isReallyZeroMixedAmount :: MixedAmount -> Bool Source #

Is this mixed amount "really" zero ? See isReallyZeroAmount.

isReallyZeroMixedAmountCost :: MixedAmount -> Bool Source #

Is this mixed amount "really" zero, after converting to cost commodities where possible ?

styleMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount Source #

Given a map of standard amount display styles, apply the appropriate ones to each individual amount.

showMixedAmount :: MixedAmount -> String Source #

Get the string representation of a mixed amount, after normalising it to one amount per commodity. Assumes amounts have no or similar prices, otherwise this can show misleading prices.

showMixedAmountWithZeroCommodity :: MixedAmount -> String Source #

Like showMixedAmount, but zero amounts are shown with their commodity if they have one.

showMixedAmountOneLine :: MixedAmount -> String Source #

Get the one-line string representation of a mixed amount.

ltraceamount :: String -> MixedAmount -> MixedAmount Source #

Compact labelled trace of a mixed amount, for debugging.

setMixedAmountPrecision :: Int -> MixedAmount -> MixedAmount Source #

Set the display precision in the amount's commodities.

showMixedAmountWithPrecision :: Int -> MixedAmount -> String Source #

Get the string representation of a mixed amount, showing each of its component amounts with the specified precision, ignoring their commoditys' display precision settings.

showMixedAmountDebug :: MixedAmount -> String Source #

Get an unambiguous string representation of a mixed amount for debugging.

showMixedAmountWithoutPrice :: MixedAmount -> String Source #

Get the string representation of a mixed amount, without showing any transaction prices.

cshowMixedAmountWithoutPrice :: MixedAmount -> String Source #

Colour version of showMixedAmountWithoutPrice. Any individual Amount which is negative is wrapped in ANSI codes to make it display in red.

showMixedAmountOneLineWithoutPrice :: MixedAmount -> String Source #

Get the one-line string representation of a mixed amount, but without any @ prices.

canonicaliseMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount Source #

Canonicalise a mixed amount's display styles using the provided commodity style map.

showMarketPrice :: MarketPrice -> String Source #

Get the string representation of an market price, based on its commodity's display settings.

accountSummarisedName :: AccountName -> Text Source #

Truncate all account name components but the last to two characters.

unbudgetedAccountName :: Text Source #

A top-level account prefixed to some accounts in budget reports. Defined here so it can be ignored by accountNameDrop.

accountNameDrop :: Int -> AccountName -> AccountName Source #

Remove some number of account name components from the front of the account name. If the special "unbudgeted" top-level account is present, it is preserved and dropping affects the rest of the account name.

expandAccountNames :: [AccountName] -> [AccountName] Source #

Sorted unique account names implied by these account names, ie these plus all their parent accounts up to the root. Eg: ["a:b:c","d:e"] -> ["a","a:b","a:b:c","d","d:e"]

expandAccountName :: AccountName -> [AccountName] Source #

"a:b:c" -> ["a","a:b","a:b:c"]

topAccountNames :: [AccountName] -> [AccountName] Source #

"a:b:c","d:e"
-> ["a","d"]

isAccountNamePrefixOf :: AccountName -> AccountName -> Bool Source #

Is the first account a parent or other ancestor of (and not the same as) the second ?

subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName] Source #

From a list of account names, select those which are direct subaccounts of the given account name.

accountNameTreeFrom :: [AccountName] -> Tree AccountName Source #

Convert a list of account names to a tree.

elideAccountName :: Int -> AccountName -> AccountName Source #

Elide an account name to fit in the specified width. From the ledger 2.6 news:

  What Ledger now does is that if an account name is too long, it will
  start abbreviating the first parts of the account name down to two
  letters in length.  If this results in a string that is still too
  long, the front will be elided -- not the end.  For example:

    Expenses:Cash           ; OK, not too long
    Ex:Wednesday:Cash       ; Expenses was abbreviated to fit
    Ex:We:Afternoon:Cash    ; Expenses and Wednesday abbreviated
    ; Expenses:Wednesday:Afternoon:Lunch:Snack:Candy:Chocolate:Cash
    ..:Af:Lu:Sn:Ca:Ch:Cash  ; Abbreviated and elided!

clipAccountName :: Int -> AccountName -> AccountName Source #

Keep only the first n components of an account name, where n is a positive integer. If n is 0, returns the empty string.

clipOrEllipsifyAccountName :: Int -> AccountName -> AccountName Source #

Keep only the first n components of an account name, where n is a positive integer. If n is 0, returns "...".

escapeName :: AccountName -> Regexp Source #

Escape an AccountName for use within a regular expression. >>> putStr $ escapeName "First?!*? %)*!#" First?!#$*?$(*) !^

accountNameToAccountRegex :: AccountName -> Regexp Source #

Convert an account name to a regular expression matching it and its subaccounts.

accountNameToAccountOnlyRegex :: AccountName -> Regexp Source #

Convert an account name to a regular expression matching it but not its subaccounts.

accountRegexToAccountName :: Regexp -> AccountName Source #

Convert an exact account-matching regular expression to a plain account name.

isAccountRegex :: String -> Bool Source #

Does this string look like an exact account-matching regular expression ?

accountNamesFromPostings :: [Posting] -> [AccountName] Source #

Sorted unique account names referenced by these postings.

removePrices :: Posting -> Posting Source #

Remove all prices of a posting

postingDate :: Posting -> Day Source #

Get a posting's (primary) date - it's own primary date if specified, otherwise the parent transaction's primary date, or the null date if there is no parent transaction.

postingDate2 :: Posting -> Day Source #

Get a posting's secondary (secondary) date, which is the first of: posting's secondary date, transaction's secondary date, posting's primary date, transaction's primary date, or the null date if there is no parent transaction.

postingStatus :: Posting -> Status Source #

Get a posting's status. This is cleared or pending if those are explicitly set on the posting, otherwise the status of its parent transaction, or unmarked if there is no parent transaction. (Note the ambiguity, unmarked can mean "posting and transaction are both unmarked" or "posting is unmarked and don't know about the transaction".

payeeAndNoteFromDescription :: Text -> (Text, Text) Source #

Parse a transaction's description into payee and note (aka narration) fields, assuming a convention of separating these with | (like Beancount). Ie, everything up to the first | is the payee, everything after it is the note. When there's no |, payee == note == description.

postingAllTags :: Posting -> [Tag] Source #

Tags for this posting including any inherited from its parent transaction.

transactionAllTags :: Transaction -> [Tag] Source #

Tags for this transaction including any from its postings.

isPostingInDateSpan :: DateSpan -> Posting -> Bool Source #

Does this posting fall within the given date span ?

postingsDateSpan :: [Posting] -> DateSpan Source #

Get the minimal date span which contains all the postings, or the null date span if there are none.

joinAccountNames :: AccountName -> AccountName -> AccountName Source #

Prefix one account name to another, preserving posting type indicators like concatAccountNames.

concatAccountNames :: [AccountName] -> AccountName Source #

Join account names into one. If any of them has () or [] posting type indicators, these (the first type encountered) will also be applied to the resulting account name.

accountNameApplyAliases :: [AccountAlias] -> AccountName -> AccountName Source #

Rewrite an account name using all matching aliases from the given list, in sequence. Each alias sees the result of applying the previous aliases.

accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> AccountName Source #

Memoising version of accountNameApplyAliases, maybe overkill.

showTransaction :: Transaction -> String Source #

Show a journal transaction, formatted for the print command. ledger 2.x's standard format looks like this:

yyyymmdd[ *][ CODE] description.........          [  ; comment...............]
    account name 1.....................  ...$amount1[  ; comment...............]
    account name 2.....................  ..$-amount1[  ; comment...............]

pcodewidth    = no limit -- 10          -- mimicking ledger layout.
pdescwidth    = no limit -- 20          -- I don't remember what these mean,
pacctwidth    = 35 minimum, no maximum  -- they were important at the time.
pamtwidth     = 11
pcommentwidth = no limit -- 22

showPostingLines :: Posting -> [String] Source #

Produce posting line with all comment lines associated with it

showAccountName :: Maybe Int -> PostingType -> AccountName -> String Source #

Show an account name, clipped to the given width if any, and appropriately bracketed/parenthesised for the given posting type.

transactionPostingBalances :: Transaction -> (MixedAmount, MixedAmount, MixedAmount) Source #

Get the sums of a transaction's real, virtual, and balanced virtual postings.

isTransactionBalanced :: Maybe (Map CommoditySymbol AmountStyle) -> Transaction -> Bool Source #

Is this transaction balanced ? A balanced transaction's real (non-virtual) postings sum to 0, and any balanced virtual postings also sum to 0.

balanceTransaction :: Maybe (Map CommoditySymbol AmountStyle) -> Transaction -> Either String Transaction Source #

Ensure this transaction is balanced, possibly inferring a missing amount or conversion price(s), or return an error message. Balancing is affected by commodity display precisions, so those can (optionally) be provided.

this fails for example, if there are several missing amounts (possibly with balance assignments)

balanceTransactionUpdate Source #

Arguments

:: MonadError String m 
=> (AccountName -> MixedAmount -> m ())

update function

-> Maybe (Map CommoditySymbol AmountStyle) 
-> Transaction 
-> m Transaction 

More general version of balanceTransaction that takes an update function

txnTieKnot :: Transaction -> Transaction Source #

Ensure a transaction's postings refer back to it, so that eg relatedPostings works right.

txnUntieKnot :: Transaction -> Transaction Source #

Ensure a transaction's postings do not refer back to it, so that eg recursiveSize and GHCI's :sprint work right.

data QueryOpt Source #

A query option changes a query's/report's behaviour and output in some way.

Constructors

QueryOptInAcctOnly AccountName

show an account register focussed on this account

QueryOptInAcct AccountName

as above but include sub-accounts in the account register | QueryOptCostBasis -- ^ show amounts converted to cost where possible | QueryOptDate2 -- ^ show secondary dates instead of primary dates

Instances
Eq QueryOpt Source # 
Instance details

Defined in Hledger.Query

Data QueryOpt Source # 
Instance details

Defined in Hledger.Query

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> QueryOpt -> c QueryOpt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c QueryOpt #

toConstr :: QueryOpt -> Constr #

dataTypeOf :: QueryOpt -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c QueryOpt) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c QueryOpt) #

gmapT :: (forall b. Data b => b -> b) -> QueryOpt -> QueryOpt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> QueryOpt -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> QueryOpt -> r #

gmapQ :: (forall d. Data d => d -> u) -> QueryOpt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> QueryOpt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> QueryOpt -> m QueryOpt #

Show QueryOpt Source # 
Instance details

Defined in Hledger.Query

data Query Source #

A query is a composition of search criteria, which can be used to match postings, transactions, accounts and more.

Constructors

Any

always match

None

never match

Not Query

negate this match

Or [Query]

match if any of these match

And [Query]

match if all of these match

Code Regexp

match if code matches this regexp

Desc Regexp

match if description matches this regexp

Acct Regexp

match postings whose account matches this regexp

Date DateSpan

match if primary date in this date span

Date2 DateSpan

match if secondary date in this date span

StatusQ Status

match txns/postings with this status

Real Bool

match if "realness" (involves a real non-virtual account ?) has this value

Amt OrdPlus Quantity

match if the amount's numeric quantity is less thangreater thanequal to/unsignedly equal to some value

Sym Regexp

match if the entire commodity symbol is matched by this regexp

Empty Bool

if true, show zero-amount postings/accounts which are usually not shown more of a query option than a query criteria ?

Depth Int

match if account depth is less than or equal to this value. Depth is sometimes used like a query (for filtering report data) and sometimes like a query option (for controlling display)

Tag Regexp (Maybe Regexp)

match if a tag's name, and optionally its value, is matched by these respective regexps matching the regexp if provided, exists

Instances
Eq Query Source # 
Instance details

Defined in Hledger.Query

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Data Query Source # 
Instance details

Defined in Hledger.Query

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Query -> c Query #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Query #

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Query) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Query) #

gmapT :: (forall b. Data b => b -> b) -> Query -> Query #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Query -> r #

gmapQ :: (forall d. Data d => d -> u) -> Query -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Query -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Query -> m Query #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Query -> m Query #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Query -> m Query #

Show Query Source # 
Instance details

Defined in Hledger.Query

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

parseQuery :: Day -> Text -> (Query, [QueryOpt]) Source #

Convert a query expression containing zero or more space-separated terms to a query and zero or more query options. A query term is either:

  1. a search pattern, which matches on one or more fields, eg:

    acct:REGEXP - match the account name with a regular expression desc:REGEXP - match the transaction description date:PERIODEXP - match the date with a period expression

The prefix indicates the field to match, or if there is no prefix account name is assumed.

  1. a query option, which modifies the reporting behaviour in some way. There is currently one of these, which may appear only once:

    inacct:FULLACCTNAME

The usual shell quoting rules are assumed. When a pattern contains whitespace, it (or the whole term including prefix) should be enclosed in single or double quotes.

Period expressions may contain relative dates, so a reference date is required to fully parse these.

Multiple terms are combined as follows: 1. multiple account patterns are OR'd together 2. multiple description patterns are OR'd together 3. multiple status patterns are OR'd together 4. then all terms are AND'd together

words'' :: [Text] -> Text -> [Text] Source #

Quote-and-prefix-aware version of words - don't split on spaces which are inside quotes, including quotes which may have one of the specified prefixes in front, and maybe an additional not: prefix in front of that.

filterQuery :: (Query -> Bool) -> Query -> Query Source #

Remove query terms (or whole sub-expressions) not matching the given predicate from this query. XXX Semantics not completely clear.

queryIsNull :: Query -> Bool Source #

Does this query match everything ?

queryIsStartDateOnly :: Bool -> Query -> Bool Source #

Does this query specify a start date and nothing else (that would filter postings prior to the date) ? When the flag is true, look for a starting secondary date instead.

queryStartDate :: Bool -> Query -> Maybe Day Source #

What start date (or secondary date) does this query specify, if any ? For OR expressions, use the earliest of the dates. NOT is ignored.

queryEndDate :: Bool -> Query -> Maybe Day Source #

What end date (or secondary date) does this query specify, if any ? For OR expressions, use the latest of the dates. NOT is ignored.

queryDateSpan :: Bool -> Query -> DateSpan Source #

What date span (or secondary date span) does this query specify ? For OR expressions, use the widest possible span. NOT is ignored.

queryDateSpan' :: Query -> DateSpan Source #

What date span (or secondary date span) does this query specify ? For OR expressions, use the widest possible span. NOT is ignored.

queryDepth :: Query -> Int Source #

The depth limit this query specifies, or a large number if none.

inAccount :: [QueryOpt] -> Maybe (AccountName, Bool) Source #

The account we are currently focussed on, if any, and whether subaccounts are included. Just looks at the first query option.

inAccountQuery :: [QueryOpt] -> Maybe Query Source #

A query for the account(s) we are currently focussed on, if any. Just looks at the first query option.

matchesAccount :: Query -> AccountName -> Bool Source #

Does the match expression match this account ? A matching in: clause is also considered a match.

matchesAmount :: Query -> Amount -> Bool Source #

Does the match expression match this (simple) amount ?

matchesPosting :: Query -> Posting -> Bool Source #

Does the match expression match this posting ?

Note that for account match we try both original and effective account

matchesTransaction :: Query -> Transaction -> Bool Source #

Does the match expression match this transaction ?

timeclockEntriesToTransactions :: LocalTime -> [TimeclockEntry] -> [Transaction] Source #

Convert time log entries to journal transactions. When there is no clockout, add one with the provided current time. Sessions crossing midnight are split into days to give accurate per-day totals.

entryFromTimeclockInOut :: TimeclockEntry -> TimeclockEntry -> Transaction Source #

Convert a timeclock clockin and clockout entry to an equivalent journal transaction, representing the time expenditure. Note this entry is not balanced, since we omit the "assets:time" transaction for simpler output.

runModifierTransaction :: Query -> ModifierTransaction -> Transaction -> Transaction Source #

Builds a Transaction transformer based on ModifierTransaction.

Query parameter allows injection of additional restriction on posting match. Don't forget to call txnTieKnot.

>>> runModifierTransaction Any (ModifierTransaction "" ["pong" `post` usd 2]) nulltransaction{tpostings=["ping" `post` usd 1]}
0000/01/01
    ping           $1.00
    pong           $2.00


>>> runModifierTransaction Any (ModifierTransaction "miss" ["pong" `post` usd 2]) nulltransaction{tpostings=["ping" `post` usd 1]}
0000/01/01
    ping           $1.00


>>> runModifierTransaction None (ModifierTransaction "" ["pong" `post` usd 2]) nulltransaction{tpostings=["ping" `post` usd 1]}
0000/01/01
    ping           $1.00


>>> runModifierTransaction Any (ModifierTransaction "ping" ["pong" `post` amount{amultiplier=True, aquantity=3}]) nulltransaction{tpostings=["ping" `post` usd 2]}
0000/01/01
    ping           $2.00
    pong           $6.00


mtvaluequery :: ModifierTransaction -> Day -> Query Source #

Extract Query equivalent of mtvalueexpr from ModifierTransaction

>>> mtvaluequery (ModifierTransaction "" []) undefined
Any
>>> mtvaluequery (ModifierTransaction "ping" []) undefined
Acct "ping"
>>> mtvaluequery (ModifierTransaction "date:2016" []) undefined
Date (DateSpan 2016)
>>> mtvaluequery (ModifierTransaction "date:today" []) (read "2017-01-01")
Date (DateSpan 2017/01/01)

jdatespan :: Journal -> DateSpan Source #

DateSpan of all dates mentioned in Journal

>>> jdatespan nulljournal
DateSpan -
>>> jdatespan nulljournal{jtxns=[nulltransaction{tdate=read "2016-01-01"}] }
DateSpan 2016/01/01
>>> jdatespan nulljournal{jtxns=[nulltransaction{tdate=read "2016-01-01", tpostings=[nullposting{pdate=Just $ read "2016-02-01"}]}] }
DateSpan 2016/01/01-2016/02/01

runPeriodicTransaction :: PeriodicTransaction -> DateSpan -> [Transaction] Source #

Generate transactions from PeriodicTransaction within a DateSpan

Note that new transactions require txnTieKnot post-processing.

>>> _ptgen "monthly from 2017/1 to 2017/4"
2017/01/01
    ; recur: monthly from 2017/1 to 2017/4
    a           $1.00

2017/02/01
    ; recur: monthly from 2017/1 to 2017/4
    a           $1.00

2017/03/01
    ; recur: monthly from 2017/1 to 2017/4
    a           $1.00

>>> _ptgen "monthly from 2017/1 to 2017/5"
2017/01/01
    ; recur: monthly from 2017/1 to 2017/5
    a           $1.00

2017/02/01
    ; recur: monthly from 2017/1 to 2017/5
    a           $1.00

2017/03/01
    ; recur: monthly from 2017/1 to 2017/5
    a           $1.00

2017/04/01
    ; recur: monthly from 2017/1 to 2017/5
    a           $1.00

>>> _ptgen "every 2nd day of month from 2017/02 to 2017/04"
2017/01/02
    ; recur: every 2nd day of month from 2017/02 to 2017/04
    a           $1.00

2017/02/02
    ; recur: every 2nd day of month from 2017/02 to 2017/04
    a           $1.00

2017/03/02
    ; recur: every 2nd day of month from 2017/02 to 2017/04
    a           $1.00

>>> _ptgen "every 30th day of month from 2017/1 to 2017/5"
2016/12/30
    ; recur: every 30th day of month from 2017/1 to 2017/5
    a           $1.00

2017/01/30
    ; recur: every 30th day of month from 2017/1 to 2017/5
    a           $1.00

2017/02/28
    ; recur: every 30th day of month from 2017/1 to 2017/5
    a           $1.00

2017/03/30
    ; recur: every 30th day of month from 2017/1 to 2017/5
    a           $1.00

2017/04/30
    ; recur: every 30th day of month from 2017/1 to 2017/5
    a           $1.00

>>> _ptgen "every 2nd Thursday of month from 2017/1 to 2017/4"
2016/12/08
    ; recur: every 2nd Thursday of month from 2017/1 to 2017/4
    a           $1.00

2017/01/12
    ; recur: every 2nd Thursday of month from 2017/1 to 2017/4
    a           $1.00

2017/02/09
    ; recur: every 2nd Thursday of month from 2017/1 to 2017/4
    a           $1.00

2017/03/09
    ; recur: every 2nd Thursday of month from 2017/1 to 2017/4
    a           $1.00

>>> _ptgen "every nov 29th from 2017 to 2019"
2016/11/29
    ; recur: every nov 29th from 2017 to 2019
    a           $1.00

2017/11/29
    ; recur: every nov 29th from 2017 to 2019
    a           $1.00

2018/11/29
    ; recur: every nov 29th from 2017 to 2019
    a           $1.00

>>> _ptgen "2017/1"
2017/01/01
    ; recur: 2017/1
    a           $1.00

>>> _ptgen ""
*** Exception: failed to parse...
...
>>> _ptgen "weekly from 2017"
*** Exception: Unable to generate transactions according to "weekly from 2017" because 2017-01-01 is not a first day of the week
>>> _ptgen "monthly from 2017/5/4"
*** Exception: Unable to generate transactions according to "monthly from 2017/5/4" because 2017-05-04 is not a first day of the month        
>>> _ptgen "every quarter from 2017/1/2"
*** Exception: Unable to generate transactions according to "every quarter from 2017/1/2" because 2017-01-02 is not a first day of the quarter        
>>> _ptgen "yearly from 2017/1/14"
*** Exception: Unable to generate transactions according to "yearly from 2017/1/14" because 2017-01-14 is not a first day of the year        
>>> let reportperiod="daily from 2018/01/03" in let (i,s) = parsePeriodExpr' nulldate reportperiod in runPeriodicTransaction (nullperiodictransaction{ptperiodexpr=reportperiod, ptspan=s, ptinterval=i, ptpostings=["a" `post` usd 1]}) (DateSpan (Just $ parsedate "2018-01-01") (Just $ parsedate "2018-01-03"))
[]

checkPeriodicTransactionStartDate :: Interval -> DateSpan -> Text -> Maybe String Source #

Check that this date span begins at a boundary of this interval, or return an explanatory error message including the provided period expression (from which the span and interval are derived).

periodTransactionInterval :: PeriodicTransaction -> Maybe Interval Source #

What is the interval of this PeriodicTransactions period expression, if it can be parsed ?

journalTransactionAt :: Journal -> Integer -> Maybe Transaction Source #

Get the transaction with this index (its 1-based position in the input stream), if any.

journalNextTransaction :: Journal -> Transaction -> Maybe Transaction Source #

Get the transaction that appeared immediately after this one in the input stream, if any.

journalPrevTransaction :: Journal -> Transaction -> Maybe Transaction Source #

Get the transaction that appeared immediately before this one in the input stream, if any.

journalDescriptions :: Journal -> [Text] Source #

Unique transaction descriptions used in this journal.

journalPostings :: Journal -> [Posting] Source #

All postings from this journal's transactions, in order.

journalAccountNamesUsed :: Journal -> [AccountName] Source #

Sorted unique account names posted to by this journal's transactions.

journalAccountNamesImplied :: Journal -> [AccountName] Source #

Sorted unique account names implied by this journal's transactions - accounts posted to and all their implied parent accounts.

journalAccountNamesDeclared :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives in this journal.

journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives or posted to by transactions in this journal.

journalAccountNamesDeclaredOrImplied :: Journal -> [AccountName] Source #

Sorted unique account names declared by account directives, or posted to or implied as parents by transactions in this journal.

journalAccountNames :: Journal -> [AccountName] Source #

Convenience/compatibility alias for journalAccountNamesDeclaredOrImplied.

journalIncomeAccountQuery :: Journal -> Query Source #

A query for Income (Revenue) accounts in this journal. This is currently hard-coded to the case-insensitive regex ^(income|revenue)s?(:|$).

journalExpenseAccountQuery :: Journal -> Query Source #

A query for Expense accounts in this journal. This is currently hard-coded to the case-insensitive regex ^expenses?(:|$).

journalAssetAccountQuery :: Journal -> Query Source #

A query for Asset accounts in this journal. This is currently hard-coded to the case-insensitive regex ^assets?(:|$).

journalLiabilityAccountQuery :: Journal -> Query Source #

A query for Liability accounts in this journal. This is currently hard-coded to the case-insensitive regex ^(debts?|liabilit(y|ies))(:|$).

journalEquityAccountQuery :: Journal -> Query Source #

A query for Equity accounts in this journal. This is currently hard-coded to the case-insensitive regex ^equity(:|$).

journalCashAccountQuery :: Journal -> Query Source #

A query for Cash (-equivalent) accounts in this journal (ie, accounts which appear on the cashflow statement.) This is currently hard-coded to be all the Asset accounts except for those containing the case-insensitive regex (receivable|:A/R|:fixed).

filterJournalTransactions :: Query -> Journal -> Journal Source #

Keep only transactions matching the query expression.

filterJournalPostings :: Query -> Journal -> Journal Source #

Keep only postings matching the query expression. This can leave unbalanced transactions.

filterJournalAmounts :: Query -> Journal -> Journal Source #

Within each posting's amount, keep only the parts matching the query. This can leave unbalanced transactions.

filterTransactionAmounts :: Query -> Transaction -> Transaction Source #

Filter out all parts of this transaction's amounts which do not match the query. This can leave the transaction unbalanced.

filterPostingAmount :: Query -> Posting -> Posting Source #

Filter out all parts of this posting's amount which do not match the query.

journalFinalise :: ClockTime -> FilePath -> Text -> Bool -> ParsedJournal -> Either String Journal Source #

Do post-parse processing on a parsed journal to make it ready for use. Reverse parsed data to normal order, standardise amount formats, check/ensure that transactions are balanced, and maybe check balance assertions.

journalUntieTransactions :: Transaction -> Transaction Source #

Untie all transaction-posting knots in this journal, so that eg recursiveSize and GHCI's :sprint can work on it.

journalCheckBalanceAssertions :: Journal -> Either String Journal Source #

Check any balance assertions in the journal and return an error message if any of them fail.

journalBalanceTransactions :: Bool -> Journal -> Either String Journal Source #

Fill in any missing amounts and check that all journal transactions balance, or return an error message. This is done after parsing all amounts and applying canonical commodity styles, since balancing depends on display precision. Reports only the first error encountered.

journalApplyCommodityStyles :: Journal -> Journal Source #

Choose and apply a consistent display format to the posting amounts in each commodity. Each commodity's format is specified by a commodity format directive, or otherwise inferred from posting amounts as in hledger < 0.28.

journalCommodityStyles :: Journal -> Map CommoditySymbol AmountStyle Source #

Get all the amount styles defined in this journal, either declared by a commodity directive or inferred from amounts, as a map from symbol to style. Styles declared by commodity directives take precedence, and these also are guaranteed to know their decimal point character.

commodityStylesFromAmounts :: [Amount] -> Map CommoditySymbol AmountStyle Source #

Given a list of amounts in parse order, build a map from their commodity names to standard commodity display formats.

canonicalStyleFrom :: [AmountStyle] -> AmountStyle Source #

Given an ordered list of amount styles, choose a canonical style. That is: the style of the first, and the maximum precision of all.

journalConvertAmountsToCost :: Journal -> Journal Source #

Convert all this journal's amounts to cost by applying their prices, if any.

journalAmounts :: Journal -> [Amount] Source #

Get an ordered list of the amounts in this journal which will influence amount style canonicalisation. These are:

  • amounts in market price directives (in parse order)
  • amounts in postings (in parse order)

Amounts in default commodity directives also influence canonicalisation, but earlier, as amounts are parsed. Amounts in posting prices are not used for canonicalisation.

overJournalAmounts :: (Amount -> Amount) -> Journal -> Journal Source #

Maps over all of the amounts in the journal

traverseJournalAmounts :: Applicative f => (Amount -> f Amount) -> Journal -> f Journal Source #

Traverses over all ofthe amounts in the journal, in the order indicated by journalAmounts.

journalDateSpan :: Bool -> Journal -> DateSpan Source #

The fully specified date span enclosing the dates (primary or secondary) of all this journal's transactions and postings, or DateSpan Nothing Nothing if there are none.

journalPivot :: Text -> Journal -> Journal Source #

Apply the pivot transformation to all postings in a journal, replacing their account name by their value for the given field or tag.

matchpats :: [String] -> String -> Bool Source #

Check if a set of hledger account/description filter patterns matches the given account name or entry description. Patterns are case-insensitive regular expressions. Prefixed with not:, they become anti-patterns.

accountsFromPostings :: [Posting] -> [Account] Source #

Derive 1. an account tree and 2. each account's total exclusive and inclusive changes from a list of postings. This is the core of the balance command (and of *ledger). The accounts are returned as a list in flattened tree order, and also reference each other as a tree. (The first account is the root of the tree.)

nameTreeToAccount :: AccountName -> FastTree AccountName -> Account Source #

Convert an AccountName tree to an Account tree

tieAccountParents :: Account -> Account Source #

Tie the knot so all subaccounts' parents are set correctly.

accountSetCodeFrom :: Journal -> Account -> Account Source #

Look up an account's numeric code, if any, from the Journal and set it.

parentAccounts :: Account -> [Account] Source #

Get this account's parent accounts, from the nearest up to the root.

accountsLevels :: Account -> [[Account]] Source #

List the accounts at each level of the account tree.

mapAccounts :: (Account -> Account) -> Account -> Account Source #

Map a (non-tree-structure-modifying) function over this and sub accounts.

anyAccounts :: (Account -> Bool) -> Account -> Bool Source #

Is the predicate true on any of this account or its subaccounts ?

sumAccounts :: Account -> Account Source #

Add subaccount-inclusive balances to an account tree.

clipAccounts :: Int -> Account -> Account Source #

Remove all subaccounts below a certain depth.

clipAccountsAndAggregate :: Int -> [Account] -> [Account] Source #

Remove subaccounts below the specified depth, aggregating their balance at the depth limit (accounts at the depth limit will have any sub-balances merged into their exclusive balance).

pruneAccounts :: (Account -> Bool) -> Account -> Maybe Account Source #

Remove all leaf accounts and subtrees matching a predicate.

flattenAccounts :: Account -> [Account] Source #

Flatten an account tree into a list, which is sometimes convenient. Note since accounts link to their parents/subs, the tree's structure remains intact and can still be used. It's a tree/list!

filterAccounts :: (Account -> Bool) -> Account -> [Account] Source #

Filter an account tree (to a list).

sortAccountTreeByAmount :: NormalSign -> Account -> Account Source #

Sort each level of an account tree by inclusive amount, so that the accounts with largest normal balances are listed first. The provided normal balance sign determines whether normal balances are negative or positive, affecting the sort order. Ie, if balances are normally negative, then the most negative balances sort first, and vice versa.

sortAccountTreeByAccountCodeAndName :: Account -> Account Source #

Sort each level of an account tree first by the account code if any, with the empty account code sorting last, and then by the account name.

lookupAccount :: AccountName -> [Account] -> Maybe Account Source #

Search an account list by name.

ledgerFromJournal :: Query -> Journal -> Ledger Source #

Filter a journal's transactions with the given query, then derive a ledger containing the chart of accounts and balances. If the query includes a depth limit, that will affect the ledger's journal but not the ledger's account tree.

ledgerAccountNames :: Ledger -> [AccountName] Source #

List a ledger's account names.

ledgerAccount :: Ledger -> AccountName -> Maybe Account Source #

Get the named account from a ledger.

ledgerRootAccount :: Ledger -> Account Source #

Get this ledger's root account, which is a dummy "root" account above all others. This should always be first in the account list, if somehow not this returns a null account.

ledgerTopAccounts :: Ledger -> [Account] Source #

List a ledger's top-level accounts (the ones below the root), in tree order.

ledgerLeafAccounts :: Ledger -> [Account] Source #

List a ledger's bottom-level (subaccount-less) accounts, in tree order.

ledgerAccountsMatching :: [String] -> Ledger -> [Account] Source #

Accounts in ledger whose name matches the pattern, in tree order.

ledgerPostings :: Ledger -> [Posting] Source #

List a ledger's postings, in the order parsed.

ledgerDateSpan :: Ledger -> DateSpan Source #

The (fully specified) date span containing all the ledger's (filtered) transactions, or DateSpan Nothing Nothing if there are none.

ledgerCommodities :: Ledger -> [CommoditySymbol] Source #

All commodities used in this ledger.

data ReportItemField Source #

An id identifying which report item field to interpolate. These are drawn from several hledger report types, so are not all applicable for a given report.

Constructors

AccountField

A posting or balance report item's account name

DefaultDateField

A posting or register or entry report item's date

DescriptionField

A posting or register or entry report item's description

TotalField

A balance or posting report item's balance or running total. Always rendered right-justified.

DepthSpacerField

A balance report item's indent level (which may be different from the account name depth). Rendered as this number of spaces, multiplied by the minimum width spec if any.

FieldNo Int

A report item's nth field. May be unimplemented.

data StringFormatComponent Source #

Constructors

FormatLiteral String

Literal text to be rendered as-is

FormatField Bool (Maybe Int) (Maybe Int) ReportItemField

A data field to be formatted and interpolated. Parameters:

  • Left justify ? Right justified if false
  • Minimum width ? Will be space-padded if narrower than this
  • Maximum width ? Will be clipped if wider than this
  • Which of the standard hledger report item fields to interpolate

data StringFormat Source #

A format specification/template to use when rendering a report line item as text.

A format is a sequence of components; each is either a literal string, or a hledger report item field with specified width and justification whose value will be interpolated at render time.

A component's value may be a multi-line string (or a multi-commodity amount), in which case the final string will be either single-line or a top or bottom-aligned multi-line string depending on the StringFormat variant used.

Currently this is only used in the balance command's single-column mode, which provides a limited StringFormat renderer.

Constructors

OneLine [StringFormatComponent]

multi-line values will be rendered on one line, comma-separated

TopAligned [StringFormatComponent]

values will be top-aligned (and bottom-padded to the same height)

BottomAligned [StringFormatComponent]

values will be bottom-aligned (and top-padded)

parseStringFormat :: String -> Either String StringFormat Source #

Parse a string format specification, or return a parse error.

data PeriodicReport a Source #

A generic tabular report of some value, where each row corresponds to an account and each column is a date period. The column periods are usually consecutive subperiods formed by splitting the overall report period by some report interval (daily, weekly, etc.) Depending on the value type, this can be a report of balance changes, ending balances, budget performance, etc. Successor to MultiBalanceReport.

Instances
Show a => Show (PeriodicReport a) Source # 
Instance details

Defined in Hledger.Reports.ReportTypes

type Average Source #

Arguments

 = MixedAmount

The average of Changes or Balances in a report or report row.

type Total Source #

Arguments

 = MixedAmount

The sum of Changes in a report or a report row. Does not make sense for Balances.

type Balance Source #

Arguments

 = MixedAmount

An ending balance as of some date.

type Change Source #

Arguments

 = MixedAmount

A change in balance during a certain period.

data ReportOpts Source #

Standard options for customising report filtering and output. Most of these correspond to standard hledger command-line options or query arguments, but not all. Some are used only by certain commands, as noted below.

Constructors

ReportOpts 

Fields

Instances
Data ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ReportOpts -> c ReportOpts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ReportOpts #

toConstr :: ReportOpts -> Constr #

dataTypeOf :: ReportOpts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ReportOpts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ReportOpts) #

gmapT :: (forall b. Data b => b -> b) -> ReportOpts -> ReportOpts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ReportOpts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ReportOpts -> r #

gmapQ :: (forall d. Data d => d -> u) -> ReportOpts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ReportOpts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ReportOpts -> m ReportOpts #

Show ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Default ReportOpts Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: ReportOpts #

data AccountListMode Source #

Should accounts be displayed: in the command's default style, hierarchically, or as a flat list ?

Constructors

ALDefault 
ALTree 
ALFlat 
Instances
Eq AccountListMode Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Data AccountListMode Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountListMode -> c AccountListMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountListMode #

toConstr :: AccountListMode -> Constr #

dataTypeOf :: AccountListMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountListMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountListMode) #

gmapT :: (forall b. Data b => b -> b) -> AccountListMode -> AccountListMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountListMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountListMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> AccountListMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountListMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountListMode -> m AccountListMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountListMode -> m AccountListMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountListMode -> m AccountListMode #

Show AccountListMode Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Default AccountListMode Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

data BalanceType Source #

Which "balance" is being shown in a balance report.

Constructors

PeriodChange

The change of balance in each period.

CumulativeChange

The accumulated change across multiple periods.

HistoricalBalance

The historical ending balance, including the effect of all postings before the report period. Unless altered by, a query, this is what you would see on a bank statement.

Instances
Eq BalanceType Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Data BalanceType Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BalanceType -> c BalanceType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BalanceType #

toConstr :: BalanceType -> Constr #

dataTypeOf :: BalanceType -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BalanceType) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BalanceType) #

gmapT :: (forall b. Data b => b -> b) -> BalanceType -> BalanceType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BalanceType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BalanceType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BalanceType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BalanceType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BalanceType -> m BalanceType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceType -> m BalanceType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BalanceType -> m BalanceType #

Show BalanceType Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Default BalanceType Source # 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: BalanceType #

checkReportOpts :: ReportOpts -> ReportOpts Source #

Do extra validation of report options, raising an error if there's a problem.

intervalFromRawOpts :: RawOpts -> Interval Source #

Get the report interval, if any, specified by the last of -p/--period, -D--daily, -W--weekly, -M/--monthly etc. options.

simplifyStatuses :: Ord a => [a] -> [a] Source #

Reduce a list of statuses to just one of each status, and if all statuses are present return the empty list.

reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts Source #

Add/remove this status from the status list. Used by hledger-ui.

transactionDateFn :: ReportOpts -> Transaction -> Day Source #

Select the Transaction date accessor based on --date2.

postingDateFn :: ReportOpts -> Posting -> Day Source #

Select the Posting date accessor based on --date2.

whichDateFromOpts :: ReportOpts -> WhichDate Source #

Report which date we will report on based on --date2.

tree_ :: ReportOpts -> Bool Source #

Legacy-compatible convenience aliases for accountlistmode_.

journalSelectingAmountFromOpts :: ReportOpts -> Journal -> Journal Source #

Convert this journal's postings' amounts to the cost basis amounts if specified by options.

queryFromOpts :: Day -> ReportOpts -> Query Source #

Convert report options and arguments to a query.

queryFromOptsOnly :: Day -> ReportOpts -> Query Source #

Convert report options to a query, ignoring any non-flag command line arguments.

queryOptsFromOpts :: Day -> ReportOpts -> [QueryOpt] Source #

Convert report options and arguments to query options.

reportSpan :: Journal -> ReportOpts -> IO DateSpan Source #

The effective report span is the start and end dates specified by options or queries, or otherwise the earliest and latest transaction or posting dates in the journal. If no dates are specified by options/queries and the journal is empty, returns the null date span. Needs IO to parse smart dates in options/queries.

specifiedStartEndDates :: ReportOpts -> IO (Maybe Day, Maybe Day) Source #

The specified report start/end dates are the dates specified by options or queries, if any. Needs IO to parse smart dates in options/queries.

type AccountTransactionsReport = (String, [AccountTransactionsReportItem]) Source #

An account transactions report represents transactions affecting a particular account (or possibly several accounts, but we don't use that). It is used eg by hledger-ui's and hledger-web's account register view, where we want to show one row per transaction, in the context of the current account. Report items consist of:

  • the transaction, unmodified
  • the transaction as seen in the context of the current account and query, which means:
  • the transaction date is set to the "transaction context date", which can be different from the transaction's general date: if postings to the current account (and matched by the report query) have their own dates, it's the earliest of these dates.
  • the transaction's postings are filtered, excluding any which are not matched by the report query
  • a text description of the other account(s) posted to/from
  • a flag indicating whether there's more than one other account involved
  • the total increase/decrease to the current account
  • the report transactions' running total after this transaction; or if historical balance is requested (-H), the historical running total. The historical running total includes transactions from before the report start date if one is specified, filtered by the report query. The historical running total may or may not be the account's historical running balance, depending on the report query.

Items are sorted by transaction register date (the earliest date the transaction posts to the current account), most recent first. Reporting intervals are currently ignored.

type TransactionsReport = (String, [TransactionsReportItem]) Source #

A transactions report includes a list of transactions (posting-filtered and unfiltered variants), a running balance, and some other information helpful for rendering a register view (a flag indicating multiple other accounts and a display string describing them) with or without a notion of current account(s). Two kinds of report use this data structure, see journalTransactionsReport and accountTransactionsReport below for detais.

triOrigTransaction :: (a, b, c, d, e, f) -> a Source #

triDate :: (a, Transaction, c, d, e, f) -> Day Source #

triAmount :: (a, b, c, d, e, f) -> e Source #

triBalance :: (a, b, c, d, e, f) -> f Source #

journalTransactionsReport :: ReportOpts -> Journal -> Query -> TransactionsReport Source #

Select transactions from the whole journal. This is similar to a "postingsReport" except with transaction-based report items which are ordered most recent first. XXX Or an EntriesReport - use that instead ? This is used by hledger-web's journal view.

transactionRegisterDate :: Query -> Query -> Transaction -> Day Source #

What is the transaction's date in the context of a particular account (specified with a query) and report query, as in an account register ? It's normally the transaction's general date, but if any posting(s) matched by the report query and affecting the matched account(s) have their own earlier dates, it's the earliest of these dates. Secondary transaction/posting dates are ignored.

transactionsReportByCommodity :: TransactionsReport -> [(CommoditySymbol, TransactionsReport)] Source #

Split a transactions report whose items may involve several commodities, into one or more single-commodity transactions reports.

type PostingsReport = (String, [PostingsReportItem]) Source #

A postings report is a list of postings with a running total, a label for the total field, and a little extra transaction info to help with rendering. This is used eg for the register command.

postingsReport :: ReportOpts -> Query -> Journal -> PostingsReport Source #

Select postings from the journal and add running balance and other information to make a postings report. Used by eg hledger's register command.

mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Day -> Posting -> MixedAmount -> PostingsReportItem Source #

Generate one postings report line item, containing the posting, the current running balance, and optionally the posting date and/or the transaction description.

type EntriesReport = [EntriesReportItem] Source #

A journal entries report is a list of whole transactions as originally entered in the journal (mostly). This is used by eg hledger's print command and hledger-web's journal entries view.

entriesReport :: ReportOpts -> Query -> Journal -> EntriesReport Source #

Select transactions for an entries report.

data InputOpts Source #

Various options to use when reading journal files. Similar to CliOptions.inputflags, simplifies the journal-reading functions.

Constructors

InputOpts 

Fields

Instances
Data InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputOpts -> c InputOpts #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputOpts #

toConstr :: InputOpts -> Constr #

dataTypeOf :: InputOpts -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputOpts) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputOpts) #

gmapT :: (forall b. Data b => b -> b) -> InputOpts -> InputOpts #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputOpts -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputOpts -> r #

gmapQ :: (forall d. Data d => d -> u) -> InputOpts -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InputOpts -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputOpts -> m InputOpts #

Show InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Default InputOpts Source # 
Instance details

Defined in Hledger.Read.Common

Methods

def :: InputOpts #

data Reader Source #

A hledger journal reader is a triple of storage format name, a detector of that format, and a parser from that format to Journal.

Instances
Show Reader Source # 
Instance details

Defined in Hledger.Read.Common

runTextParser :: TextParser Identity a -> Text -> Either (ParseError Char CustomErr) a Source #

Run a string parser with no state in the identity monad.

rtp :: TextParser Identity a -> Text -> Either (ParseError Char CustomErr) a Source #

Run a string parser with no state in the identity monad.

runJournalParser :: Monad m => JournalParser m a -> Text -> m (Either (ParseError Char CustomErr) a) Source #

Run a journal parser with a null journal-parsing state.

rjp :: Monad m => JournalParser m a -> Text -> m (Either (ParseError Char CustomErr) a) Source #

Run a journal parser with a null journal-parsing state.

journalSourcePos :: SourcePos -> SourcePos -> GenericSourcePos Source #

Construct a generic start & end line parse position from start and end megaparsec SourcePos's.

generateAutomaticPostings :: Journal -> Journal Source #

Generate Automatic postings and add them to the current journal.

parseAndFinaliseJournal :: JournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal Source #

Given a megaparsec ParsedJournal parser, input options, file path and file content: parse and post-process a Journal, or give an error.

getDefaultAmountStyle :: JournalParser m (Maybe AmountStyle) Source #

Get amount style associated with default currency.

Returns AmountStyle used to defined by a latest default commodity directive prior to current position within this file or its parents.

getAmountStyle :: CommoditySymbol -> JournalParser m (Maybe AmountStyle) Source #

Lookup currency-specific amount style.

Returns AmountStyle used in commodity directive within current journal prior to current position or in its parents files.

datep :: JournalParser m Day Source #

Parse a date in YYYYMMDD format. Hyphen (-) and period (.) are also allowed as separators. The year may be omitted if a default year has been set. Leading zeroes may be omitted.

datetimep :: JournalParser m LocalTime Source #

Parse a date and time in YYYYMMDD HH:MM[:SS][+-ZZZZ] format. Hyphen (-) and period (.) are also allowed as date separators. The year may be omitted if a default year has been set. Seconds are optional. The timezone is optional and ignored (the time is always interpreted as a local time). Leading zeroes may be omitted (except in a timezone).

modifiedaccountnamep :: JournalParser m AccountName Source #

Parse an account name (plus one following space if present), then apply any parent account prefix and/or account aliases currently in effect, in that order. (Ie first add the parent account prefix, then rewrite with aliases).

accountnamep :: TextParser m AccountName Source #

Parse an account name, plus one following space if present. Account names start with a non-space, may have single spaces inside them, and are terminated by two or more spaces (or end of input). (Also they have one or more components of at least one character, separated by the account separator character, but we don't check that here.)

singlespacedtextp :: TextParser m Text Source #

Parse any text beginning with a non-whitespace character, until a double space or the end of input. Consumes one of the following spaces, if present.

singlespacep :: ParsecT CustomErr Text m () Source #

Parse one non-newline whitespace character that is not followed by another one.

spaceandamountormissingp :: JournalParser m MixedAmount Source #

Parse whitespace then an amount, with an optional left or right currency symbol and optional price, or return the special "missing" marker amount.

amountp :: JournalParser m Amount Source #

Parse a single-commodity amount, with optional symbol on the left or right, optional unit or total price, and optional (ignored) ledger-style balance assertion or fixed lot price declaration.

amountp' :: String -> Amount Source #

Parse an amount from a string, or get an error.

mamountp' :: String -> MixedAmount Source #

Parse a mixed amount from a string, or get an error.

numberp :: Maybe AmountStyle -> TextParser m (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) Source #

Parse a string representation of a number for its value and display attributes.

Some international number formats are accepted, eg either period or comma may be used for the decimal point, and the other of these may be used for separating digit groups in the integer part. See http://en.wikipedia.org/wiki/Decimal_separator for more examples.

This returns: the parsed numeric value, the precision (number of digits seen following the decimal point), the decimal point character used if any, and the digit group style if any.

fromRawNumber :: RawNumber -> Maybe Int -> Either String (Quantity, Int, Maybe Char, Maybe DigitGroupStyle) Source #

Interpret a raw number as a decimal number.

Returns: - the decimal number - the precision (number of digits after the decimal point) - the decimal point character, if any - the digit group style, if any (digit group character and sizes of digit groups)

rawnumberp :: TextParser m (Either AmbiguousNumber RawNumber) Source #

Parse and interpret the structure of a number without external hints. Numbers are digit strings, possibly separated into digit groups by one of two types of separators. (1) Numbers may optionally have a decimal point, which may be either a period or comma. (2) Numbers may optionally contain digit group separators, which must all be either a period, a comma, or a space.

It is our task to deduce the identities of the decimal point and digit separator characters, based on the allowed syntax. For instance, we make use of the fact that a decimal point can occur at most once and must succeed all digit group separators.

>>> parseTest rawnumberp "1,234,567.89"
Right (WithSeparators ',' ["1","234","567"] (Just ('.',"89")))
>>> parseTest rawnumberp "1,000"
Left (AmbiguousNumber "1" ',' "000")
>>> parseTest rawnumberp "1 000"
Right (WithSeparators ' ' ["1","000"] Nothing)

followingcommentp :: TextParser m Text Source #

Parse the text of a (possibly multiline) comment following a journal item.

transactioncommentp :: TextParser m (Text, [Tag]) Source #

Parse a transaction comment and extract its tags.

The first line of a transaction may be followed by comments, which begin with semicolons and extend to the end of the line. Transaction comments may span multiple lines, but comment lines below the transaction must be preceeded by leading whitespace.

200011 ; a transaction comment starting on the same line ... ; extending to the next line account1 $1 account2

Tags are name-value pairs.

>>> let getTags (_,tags) = tags
>>> let parseTags = fmap getTags . rtp transactioncommentp
>>> parseTags "; name1: val1, name2:all this is value2"
Right [("name1","val1"),("name2","all this is value2")]

A tag's name must be immediately followed by a colon, without separating whitespace. The corresponding value consists of all the text following the colon up until the next colon or newline, stripped of leading and trailing whitespace.

postingcommentp :: Maybe Year -> TextParser m (Text, [Tag], Maybe Day, Maybe Day) Source #

Parse a posting comment and extract its tags and dates.

Postings may be followed by comments, which begin with semicolons and extend to the end of the line. Posting comments may span multiple lines, but comment lines below the posting must be preceeded by leading whitespace.

200011 account1 $1 ; a posting comment starting on the same line ... ; extending to the next line

account2 ; a posting comment beginning on the next line

Tags are name-value pairs.

>>> let getTags (_,tags,_,_) = tags
>>> let parseTags = fmap getTags . rtp (postingcommentp Nothing)
>>> parseTags "; name1: val1, name2:all this is value2"
Right [("name1","val1"),("name2","all this is value2")]

A tag's name must be immediately followed by a colon, without separating whitespace. The corresponding value consists of all the text following the colon up until the next colon or newline, stripped of leading and trailing whitespace.

Posting dates may be expressed with "date"/"date2" tags or with bracketed date syntax. Posting dates will inherit their year from the transaction date if the year is not specified. We throw parse errors on invalid dates.

>>> let getDates (_,_,d1,d2) = (d1, d2)
>>> let parseDates = fmap getDates . rtp (postingcommentp (Just 2000))
>>> parseDates "; date: 1/2, date2: 1999/12/31"
Right (Just 2000-01-02,Just 1999-12-31)
>>> parseDates "; [1/2=1999/12/31]"
Right (Just 2000-01-02,Just 1999-12-31)

Example: tags, date tags, and bracketed dates >>> rtp (postingcommentp (Just 2000)) "; a:b, date:34, [=56]" Right ("a:b, date:34, [=56]n",[("a","b"),("date","3/4")],Just 2000-03-04,Just 2000-05-06)

Example: extraction of dates from date tags ignores trailing text >>> rtp (postingcommentp (Just 2000)) "; date:34=56" Right ("date:34=56n",[("date","34=56")],Just 2000-03-04,Nothing)

bracketeddatetagsp :: Maybe Year -> TextParser m [(TagName, Day)] Source #

Parse Ledger-style bracketed posting dates ([DATE=DATE2]), as "date" and/or "date2" tags. Anything that looks like an attempt at this (a square-bracketed sequence of 0123456789/-.= containing at least one digit and one date separator) is also parsed, and will throw an appropriate error.

The dates are parsed in full here so that errors are reported in the right position. A missing year in DATE can be inferred if a default date is provided. A missing year in DATE2 will be inferred from DATE.

>>> either (Left . parseErrorPretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/2=3/4]"
Right [("date",2016-01-02),("date2",2016-03-04)]
>>> either (Left . parseErrorPretty) Right $ rtp (bracketeddatetagsp Nothing) "[1]"
Left ...not a bracketed date...
>>> either (Left . parseErrorPretty) Right $ rtp (bracketeddatetagsp Nothing) "[2016/1/32]"
Left ...1:11:...well-formed but invalid date: 2016/1/32...
>>> either (Left . parseErrorPretty) Right $ rtp (bracketeddatetagsp Nothing) "[1/31]"
Left ...1:6:...partial date 1/31 found, but the current year is unknown...
>>> either (Left . parseErrorPretty) Right $ rtp (bracketeddatetagsp Nothing) "[0123456789/-.=/-.=]"
Left ...1:13:...expecting month or day...

type PrefixedFilePath = FilePath Source #

A file path optionally prefixed by a reader name and colon (journal:, csv:, timedot:, etc.).

defaultJournal :: IO Journal Source #

Read the default journal file specified by the environment, or raise an error.

defaultJournalPath :: IO String Source #

Get the default journal file path specified by the environment. Like ledger, we look first for the LEDGER_FILE environment variable, and if that does not exist, for the legacy LEDGER environment variable. If neither is set, or the value is blank, return the hard-coded default, which is .hledger.journal in the users's home directory (or in the current directory, if we cannot determine a home directory).

splitReaderPrefix :: PrefixedFilePath -> (Maybe String, FilePath) Source #

If a filepath is prefixed by one of the reader names and a colon, split that off. Eg "csv:-" -> (Just "csv", "-").

requireJournalFileExists :: FilePath -> IO () Source #

If the specified journal file does not exist (and is not "-"), give a helpful error and quit.

ensureJournalFileExists :: FilePath -> IO () Source #

Ensure there is a journal file at the given path, creating an empty one if needed.

readJournal' :: Text -> IO Journal Source #

Read a Journal from the given text trying all readers in turn, or throw an error.

readJournalFiles :: InputOpts -> [FilePath] -> IO (Either String Journal) Source #

Read a Journal from each specified file path and combine them into one. Or, return the first error message.

Combining Journals means concatenating them, basically. The parse state resets at the start of each file, which means that directives & aliases do not affect subsequent sibling or parent files. They do affect included child files though. Also the final parse state saved in the Journal does span all files.

readJournalFile :: InputOpts -> PrefixedFilePath -> IO (Either String Journal) Source #

Read a Journal from this file, or from stdin if the file path is -, or return an error message. The file path can have a READER: prefix.

The reader (data format) to use is determined from (in priority order): the mformat_ specified in the input options, if any; the file path's READER: prefix, if any; a recognised file name extension. if none of these identify a known reader, all built-in readers are tried in turn.

The input options can also configure balance assertion checking, automated posting generation, a rules file for converting CSV data, etc.

readJournal :: InputOpts -> Maybe FilePath -> Text -> IO (Either String Journal) Source #

readJournal iopts mfile txt

Read a Journal from some text, or return an error message.

The reader (data format) is chosen based on a recognised file name extension in mfile (if provided). If it does not identify a known reader, all built-in readers are tried in turn (returning the first one's error message if none of them succeed).

Input ioptions (iopts) specify CSV conversion rules file to help convert CSV data, enable or disable balance assertion checking and automated posting generation.

type BalanceReport = ([BalanceReportItem], MixedAmount) Source #

A simple balance report. It has:

  1. a list of items, one per account, each containing:
  • the full account name
  • the Ledger-style elided short account name (the leaf account name, prefixed by any boring parents immediately above); or with --flat, the full account name again
  • the number of indentation steps for rendering a Ledger-style account tree, taking into account elided boring parents, --no-elide and --flat
  • an amount
  1. the total of all amounts

flatShowsExclusiveBalance :: Bool Source #

When true (the default), this makes balance --flat reports and their implementation clearer. Single/multi-col balance reports currently aren't all correct if this is false.

balanceReport :: ReportOpts -> Query -> Journal -> BalanceReport Source #

Enabling this makes balance --flat --empty also show parent accounts without postings, in addition to those with postings and a zero balance. Disabling it shows only the latter. No longer supported, but leave this here for a bit. flatShowsPostinglessAccounts = True

Generate a simple balance report, containing the matched accounts and their balances (change of balance) during the specified period. This is like PeriodChangeReport with a single column (but more mature, eg this can do hierarchical display).

newtype MultiBalanceReport Source #

A multi balance report is a balance report with one or more columns. It has:

  1. a list of each column's period (date span)
  2. a list of rows, each containing:
  • the full account name
  • the leaf account name
  • the account's depth
  • a list of amounts, one for each column
  • the total of the row's amounts
  • the average of the row's amounts
  1. the column totals and the overall total and average

The meaning of the amounts depends on the type of multi balance report, of which there are three: periodic, cumulative and historical (see BalanceType and Hledger.Cli.Commands.Balance).

Constructors

MultiBalanceReport ([DateSpan], [MultiBalanceReportRow], MultiBalanceReportTotals) 

multiBalanceReport :: ReportOpts -> Query -> Journal -> MultiBalanceReport Source #

Generate a multicolumn balance report for the matched accounts, showing the change of balance, accumulated balance, or historical balance in each of the specified periods. Does not support tree-mode boring parent eliding. If the normalbalance_ option is set, it adjusts the sorting and sign of amounts (see ReportOpts and CompoundBalanceCommand).

mbrNormaliseSign :: NormalSign -> MultiBalanceReport -> MultiBalanceReport Source #

Given a MultiBalanceReport and its normal balance sign, if it is known to be normally negative, convert it to normally positive.

mbrNegate :: MultiBalanceReport -> MultiBalanceReport Source #

Flip the sign of all amounts in a MultiBalanceReport.

multiBalanceReportSpan :: MultiBalanceReport -> DateSpan Source #

Figure out the overall date span of a multicolumn balance report.

balanceReportFromMultiBalanceReport :: ReportOpts -> Query -> Journal -> BalanceReport Source #

Generates a simple non-columnar BalanceReport, but using multiBalanceReport, in order to support --historical. Does not support tree-mode boring parent eliding. If the normalbalance_ option is set, it adjusts the sorting and sign of amounts (see ReportOpts and CompoundBalanceCommand).

type BudgetReport = PeriodicReport (Maybe Change, Maybe BudgetGoal) Source #

A budget report tracks expected and actual changes per account and subperiod.

budgetReport :: ReportOpts -> Bool -> Bool -> DateSpan -> Day -> Journal -> BudgetReport Source #

Calculate budget goals from all periodic transactions, actual balance changes from the regular transactions, and compare these to get a BudgetReport. Unbudgeted accounts may be hidden or renamed (see budgetRollup).

budgetJournal :: Bool -> ReportOpts -> DateSpan -> Journal -> Journal Source #

Use all periodic transactions in the journal to generate budget transactions in the specified report period. Budget transactions are similar to forecast transactions except their purpose is to set goal amounts (of change) per account and period.

budgetRollUp :: [AccountName] -> Bool -> Journal -> Journal Source #

Adjust a journal's account names for budget reporting, in two ways:

  1. accounts with no budget goal anywhere in their ancestry are moved under the "unbudgeted" top level account.
  2. subaccounts with no budget goal are merged with their closest parent account with a budget goal, so that only budgeted accounts are shown. This can be disabled by --show-unbudgeted.

combineBudgetAndActual :: MultiBalanceReport -> MultiBalanceReport -> BudgetReport Source #

Combine a per-account-and-subperiod report of budget goals, and one of actual change amounts, into a budget performance report. The two reports should have the same report interval, but need not have exactly the same account rows or date columns. (Cells in the combined budget report can be missing a budget goal, an actual amount, or both.) The combined report will include:

  • consecutive subperiods at the same interval as the two reports, spanning the period of both reports
  • all accounts mentioned in either report, sorted by account code or account name or amount as appropriate.

budgetReportSpan :: BudgetReport -> DateSpan Source #

Figure out the overall period of a BudgetReport.

budgetReportAsText :: ReportOpts -> BudgetReport -> String Source #

Render a budget report as plain text suitable for console output.

maybeAccountNameDrop :: ReportOpts -> AccountName -> AccountName Source #

Drop leading components of accounts names as specified by --drop, but only in --flat mode.