hledger-1.41: Command-line interface for the hledger accounting system
Safe HaskellNone
LanguageHaskell2010

Hledger.Cli

Description

This is the root module of the hledger package, providing hledger's command-line interface. The main function, commands, command-line options, and utilities useful to other hledger command-line programs are exported. It also re-exports hledger-lib:Hledger and cmdargs:System.Concole.CmdArgs.Explicit

See also:

About

hledger - a fast, reliable, user-friendly plain text accounting tool. Copyright (c) 2007-2024 Simon Michael simon@joyful.com and contributors Released under GPL version 3 or later.

hledger is a Haskell rewrite of John Wiegley's "ledger". It generates financial reports from a plain text general journal. You can use the command line:

$ hledger

or ghci:

$ make ghci
ghci> Right j <- runExceptT $ readJournalFile definputopts "examples/sample.journal"  -- or: j <- defaultJournal
ghci> :t j
j :: Journal
ghci> stats defcliopts j
Main file                : examples/sample.journal
Included files           : 
Transactions span        : 2008-01-01 to 2009-01-01 (366 days)
Last transaction         : 2008-12-31 (733772 days from now)
Transactions             : 5 (0.0 per day)
Transactions last 30 days: 0 (0.0 per day)
Transactions last 7 days : 0 (0.0 per day)
Payees/descriptions      : 5
Accounts                 : 8 (depth 3)
Commodities              : 1 ($)
Market prices            : 0 ()

Run time (throughput)    : 1695276900.00s (0 txns/s)
ghci> balance defcliopts j
                  $1  assets:bank:saving
                 $-2  assets:cash
                  $1  expenses:food
                  $1  expenses:supplies
                 $-1  income:gifts
                 $-1  income:salary
                  $1  liabilities:debts
--------------------
                   0  
ghci> 

etc.

Synopsis

Documentation

main :: IO () Source #

hledger CLI's main procedure.

Here we will parse the command line, read any config file, and search for hledger-* addon executables in the user's PATH, then choose the appropriate builtin operation or addon operation to run, then run it in the right way, usually reading input data (eg a journal) first.

When making a CLI usable and robust with main command, builtin subcommands, various kinds of addon commands, and config files that add general and command-specific options, while balancing circular dependencies, environment, idioms, legacy, and libraries with their own requirements and limitations: things get crazy, and there is a tradeoff against complexity and bug risk. We try to provide the most intuitive, expressive and robust CLI that's feasible while keeping the CLI processing below sufficiently comprehensible, troubleshootable, and tested. It's an ongoing quest. See also: Hledger.Cli.CliOptions, cli.test, addons.test, --debug and --debug=8.

Probably the biggest source of complexity here is that cmdargs can't parse a command line containing undeclared flags, but this arises often with our addon commands and builtin/custom commands which haven't implemented all options, so we have to work hard to work around this. https://github.com/ndmitchell/cmdargs/issues/36 is the wishlist issue; implementing that would simplify hledger's CLI processing a lot.

mainmode :: [Name] -> Mode RawOpts Source #

The overall cmdargs mode describing hledger's command-line options and subcommands. The names of known addons are provided so they too can be recognised as commands.

argsToCliOpts :: [String] -> [String] -> IO CliOpts Source #

A helper for addons/scripts: this parses hledger CliOpts from these command line arguments and add-on command names, roughly how hledger main does. If option parsing/validating fails, it exits the program with usageError. Unlike main, this does not read extra args from a config file or search for addons; to do those things, mimic the code in main for now.

Re-exports

class HasReportOptsNoUpdate c where #

Minimal complete definition

reportOptsNoUpdate

Methods

reportOptsNoUpdate :: Lens' c ReportOpts #

accountlistmode :: Lens' c AccountListMode #

average :: Lens' c Bool #

balance_base_url :: Lens' c (Maybe Text) #

balanceaccum :: Lens' c BalanceAccumulation #

balancecalc :: Lens' c BalanceCalculation #

budgetpat :: Lens' c (Maybe Text) #

color__ :: Lens' c Bool #

conversionop :: Lens' c (Maybe ConversionOp) #

date2NoUpdate :: Lens' c Bool #

declared :: Lens' c Bool #

depthNoUpdate :: Lens' c DepthSpec #

drop__ :: Lens' c Int #

empty__ :: Lens' c Bool #

format :: Lens' c StringFormat #

infer_prices :: Lens' c Bool #

interval :: Lens' c Interval #

invert :: Lens' c Bool #

layout :: Lens' c Layout #

no_elide :: Lens' c Bool #

no_total :: Lens' c Bool #

normalbalance :: Lens' c (Maybe NormalSign) #

percent :: Lens' c Bool #

periodNoUpdate :: Lens' c Period #

pretty :: Lens' c Bool #

querystringNoUpdate :: Lens' c [Text] #

realNoUpdate :: Lens' c Bool #

related :: Lens' c Bool #

row_total :: Lens' c Bool #

show_costs :: Lens' c Bool #

sort_amount :: Lens' c Bool #

sortspec :: Lens' c SortSpec #

statusesNoUpdate :: Lens' c [Status] #

summary_only :: Lens' c Bool #

transpose__ :: Lens' c Bool #

txn_dates :: Lens' c Bool #

value :: Lens' c (Maybe ValuationType) #

Instances

Instances details
HasReportOptsNoUpdate CliOpts Source # 
Instance details

Defined in Hledger.Cli.CliOptions

HasReportOptsNoUpdate ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportOpts ReportOpts #

accountlistmode :: Lens' ReportOpts AccountListMode #

average :: Lens' ReportOpts Bool #

balance_base_url :: Lens' ReportOpts (Maybe Text) #

balanceaccum :: Lens' ReportOpts BalanceAccumulation #

balancecalc :: Lens' ReportOpts BalanceCalculation #

budgetpat :: Lens' ReportOpts (Maybe Text) #

color__ :: Lens' ReportOpts Bool #

conversionop :: Lens' ReportOpts (Maybe ConversionOp) #

date2NoUpdate :: Lens' ReportOpts Bool #

declared :: Lens' ReportOpts Bool #

depthNoUpdate :: Lens' ReportOpts DepthSpec #

drop__ :: Lens' ReportOpts Int #

empty__ :: Lens' ReportOpts Bool #

format :: Lens' ReportOpts StringFormat #

infer_prices :: Lens' ReportOpts Bool #

interval :: Lens' ReportOpts Interval #

invert :: Lens' ReportOpts Bool #

layout :: Lens' ReportOpts Layout #

no_elide :: Lens' ReportOpts Bool #

no_total :: Lens' ReportOpts Bool #

normalbalance :: Lens' ReportOpts (Maybe NormalSign) #

percent :: Lens' ReportOpts Bool #

periodNoUpdate :: Lens' ReportOpts Period #

pretty :: Lens' ReportOpts Bool #

querystringNoUpdate :: Lens' ReportOpts [Text] #

realNoUpdate :: Lens' ReportOpts Bool #

related :: Lens' ReportOpts Bool #

row_total :: Lens' ReportOpts Bool #

show_costs :: Lens' ReportOpts Bool #

sort_amount :: Lens' ReportOpts Bool #

sortspec :: Lens' ReportOpts SortSpec #

statusesNoUpdate :: Lens' ReportOpts [Status] #

summary_only :: Lens' ReportOpts Bool #

transpose__ :: Lens' ReportOpts Bool #

txn_dates :: Lens' ReportOpts Bool #

value :: Lens' ReportOpts (Maybe ValuationType) #

HasReportOptsNoUpdate ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportSpec ReportOpts #

accountlistmode :: Lens' ReportSpec AccountListMode #

average :: Lens' ReportSpec Bool #

balance_base_url :: Lens' ReportSpec (Maybe Text) #

balanceaccum :: Lens' ReportSpec BalanceAccumulation #

balancecalc :: Lens' ReportSpec BalanceCalculation #

budgetpat :: Lens' ReportSpec (Maybe Text) #

color__ :: Lens' ReportSpec Bool #

conversionop :: Lens' ReportSpec (Maybe ConversionOp) #

date2NoUpdate :: Lens' ReportSpec Bool #

declared :: Lens' ReportSpec Bool #

depthNoUpdate :: Lens' ReportSpec DepthSpec #

drop__ :: Lens' ReportSpec Int #

empty__ :: Lens' ReportSpec Bool #

format :: Lens' ReportSpec StringFormat #

infer_prices :: Lens' ReportSpec Bool #

interval :: Lens' ReportSpec Interval #

invert :: Lens' ReportSpec Bool #

layout :: Lens' ReportSpec Layout #

no_elide :: Lens' ReportSpec Bool #

no_total :: Lens' ReportSpec Bool #

normalbalance :: Lens' ReportSpec (Maybe NormalSign) #

percent :: Lens' ReportSpec Bool #

periodNoUpdate :: Lens' ReportSpec Period #

pretty :: Lens' ReportSpec Bool #

querystringNoUpdate :: Lens' ReportSpec [Text] #

realNoUpdate :: Lens' ReportSpec Bool #

related :: Lens' ReportSpec Bool #

row_total :: Lens' ReportSpec Bool #

show_costs :: Lens' ReportSpec Bool #

sort_amount :: Lens' ReportSpec Bool #

sortspec :: Lens' ReportSpec SortSpec #

statusesNoUpdate :: Lens' ReportSpec [Status] #

summary_only :: Lens' ReportSpec Bool #

transpose__ :: Lens' ReportSpec Bool #

txn_dates :: Lens' ReportSpec Bool #

value :: Lens' ReportSpec (Maybe ValuationType) #

class HasInputOpts c where #

Minimal complete definition

inputOpts

Methods

inputOpts :: Lens' c InputOpts #

aliases :: Lens' c [String] #

anon__ :: Lens' c Bool #

auto__ :: Lens' c Bool #

balancingopts :: Lens' c BalancingOpts #

defer :: Lens' c Bool #

forecast :: Lens' c (Maybe DateSpan) #

infer_costs :: Lens' c Bool #

infer_equity :: Lens' c Bool #

ioDay :: Lens' c Day #

mformat :: Lens' c (Maybe StorageFormat) #

mrules_file :: Lens' c (Maybe FilePath) #

new__ :: Lens' c Bool #

new_save :: Lens' c Bool #

pivot :: Lens' c String #

posting_account_tags :: Lens' c Bool #

reportspan :: Lens' c DateSpan #

strict :: Lens' c Bool #

verbose_tags :: Lens' c Bool #

Instances

Instances details
HasInputOpts CliOpts Source # 
Instance details

Defined in Hledger.Cli.CliOptions

Methods

inputOpts :: Lens' CliOpts InputOpts #

aliases :: Lens' CliOpts [String] #

anon__ :: Lens' CliOpts Bool #

auto__ :: Lens' CliOpts Bool #

balancingopts :: Lens' CliOpts BalancingOpts #

defer :: Lens' CliOpts Bool #

forecast :: Lens' CliOpts (Maybe DateSpan) #

infer_costs :: Lens' CliOpts Bool #

infer_equity :: Lens' CliOpts Bool #

ioDay :: Lens' CliOpts Day #

mformat :: Lens' CliOpts (Maybe StorageFormat) #

mrules_file :: Lens' CliOpts (Maybe FilePath) #

new__ :: Lens' CliOpts Bool #

new_save :: Lens' CliOpts Bool #

pivot :: Lens' CliOpts String #

posting_account_tags :: Lens' CliOpts Bool #

reportspan :: Lens' CliOpts DateSpan #

strict :: Lens' CliOpts Bool #

verbose_tags :: Lens' CliOpts Bool #

HasInputOpts InputOpts 
Instance details

Defined in Hledger.Read.InputOptions

Methods

inputOpts :: Lens' InputOpts InputOpts #

aliases :: Lens' InputOpts [String] #

anon__ :: Lens' InputOpts Bool #

auto__ :: Lens' InputOpts Bool #

balancingopts :: Lens' InputOpts BalancingOpts #

defer :: Lens' InputOpts Bool #

forecast :: Lens' InputOpts (Maybe DateSpan) #

infer_costs :: Lens' InputOpts Bool #

infer_equity :: Lens' InputOpts Bool #

ioDay :: Lens' InputOpts Day #

mformat :: Lens' InputOpts (Maybe StorageFormat) #

mrules_file :: Lens' InputOpts (Maybe FilePath) #

new__ :: Lens' InputOpts Bool #

new_save :: Lens' InputOpts Bool #

pivot :: Lens' InputOpts String #

posting_account_tags :: Lens' InputOpts Bool #

reportspan :: Lens' InputOpts DateSpan #

strict :: Lens' InputOpts Bool #

verbose_tags :: Lens' InputOpts Bool #

data SmartInterval #

Constructors

Day 
Week 
Month 
Quarter 
Year 

Instances

Instances details
Show SmartInterval 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> SmartInterval -> ShowS

show :: SmartInterval -> String

showList :: [SmartInterval] -> ShowS

data DateSpan #

Constructors

DateSpan (Maybe EFDay) (Maybe EFDay) 

Instances

Instances details
Default DateSpan 
Instance details

Defined in Hledger.Data.Types

Methods

def :: DateSpan

Generic DateSpan 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DateSpan 
Instance details

Defined in Hledger.Data.Types

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

Methods

from :: DateSpan -> Rep DateSpan x

to :: Rep DateSpan x -> DateSpan

Eq DateSpan 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: DateSpan -> DateSpan -> Bool

(/=) :: DateSpan -> DateSpan -> Bool

Ord DateSpan 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: DateSpan -> DateSpan -> Ordering #

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

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

(>) :: DateSpan -> DateSpan -> Bool #

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

max :: DateSpan -> DateSpan -> DateSpan #

min :: DateSpan -> DateSpan -> DateSpan #

type Rep DateSpan 
Instance details

Defined in Hledger.Data.Types

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

data Side #

Constructors

L 
R 

Instances

Instances details
Generic Side 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Side 
Instance details

Defined in Hledger.Data.Types

type Rep Side = D1 ('MetaData "Side" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Side -> Rep Side x

to :: Rep Side x -> Side

Read Side 
Instance details

Defined in Hledger.Data.Types

Methods

readsPrec :: Int -> ReadS Side

readList :: ReadS [Side]

readPrec :: ReadPrec Side

readListPrec :: ReadPrec [Side]

Show Side 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Side -> ShowS

show :: Side -> String

showList :: [Side] -> ShowS

Eq Side 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Side 
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 #

type Rep Side 
Instance details

Defined in Hledger.Data.Types

type Rep Side = D1 ('MetaData "Side" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "R" 'PrefixI 'False) (U1 :: Type -> Type))

data SepFormat #

Constructors

Csv 
Tsv 
Ssv 

Instances

Instances details
Show SepFormat 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> SepFormat -> ShowS

show :: SepFormat -> String

showList :: [SepFormat] -> ShowS

Eq SepFormat 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: SepFormat -> SepFormat -> Bool

(/=) :: SepFormat -> SepFormat -> Bool

data ReportOpts #

Instances

Instances details
Default ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: ReportOpts

Show ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> ReportOpts -> ShowS

show :: ReportOpts -> String

showList :: [ReportOpts] -> ShowS

HasReportOpts ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportOpts ReportOpts #

period :: ReportableLens' ReportOpts Period #

statuses :: ReportableLens' ReportOpts [Status] #

depth :: ReportableLens' ReportOpts DepthSpec #

date2 :: ReportableLens' ReportOpts Bool #

real :: ReportableLens' ReportOpts Bool #

querystring :: ReportableLens' ReportOpts [Text] #

HasReportOptsNoUpdate ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportOpts ReportOpts #

accountlistmode :: Lens' ReportOpts AccountListMode #

average :: Lens' ReportOpts Bool #

balance_base_url :: Lens' ReportOpts (Maybe Text) #

balanceaccum :: Lens' ReportOpts BalanceAccumulation #

balancecalc :: Lens' ReportOpts BalanceCalculation #

budgetpat :: Lens' ReportOpts (Maybe Text) #

color__ :: Lens' ReportOpts Bool #

conversionop :: Lens' ReportOpts (Maybe ConversionOp) #

date2NoUpdate :: Lens' ReportOpts Bool #

declared :: Lens' ReportOpts Bool #

depthNoUpdate :: Lens' ReportOpts DepthSpec #

drop__ :: Lens' ReportOpts Int #

empty__ :: Lens' ReportOpts Bool #

format :: Lens' ReportOpts StringFormat #

infer_prices :: Lens' ReportOpts Bool #

interval :: Lens' ReportOpts Interval #

invert :: Lens' ReportOpts Bool #

layout :: Lens' ReportOpts Layout #

no_elide :: Lens' ReportOpts Bool #

no_total :: Lens' ReportOpts Bool #

normalbalance :: Lens' ReportOpts (Maybe NormalSign) #

percent :: Lens' ReportOpts Bool #

periodNoUpdate :: Lens' ReportOpts Period #

pretty :: Lens' ReportOpts Bool #

querystringNoUpdate :: Lens' ReportOpts [Text] #

realNoUpdate :: Lens' ReportOpts Bool #

related :: Lens' ReportOpts Bool #

row_total :: Lens' ReportOpts Bool #

show_costs :: Lens' ReportOpts Bool #

sort_amount :: Lens' ReportOpts Bool #

sortspec :: Lens' ReportOpts SortSpec #

statusesNoUpdate :: Lens' ReportOpts [Status] #

summary_only :: Lens' ReportOpts Bool #

transpose__ :: Lens' ReportOpts Bool #

txn_dates :: Lens' ReportOpts Bool #

value :: Lens' ReportOpts (Maybe ValuationType) #

error' :: String -> a #

strip :: String -> String #

words' :: String -> [String] #

data RawOpts #

Instances

Instances details
Default RawOpts 
Instance details

Defined in Hledger.Data.RawOptions

Methods

def :: RawOpts

Show RawOpts 
Instance details

Defined in Hledger.Data.RawOptions

Methods

showsPrec :: Int -> RawOpts -> ShowS

show :: RawOpts -> String

showList :: [RawOpts] -> ShowS

collectopts :: ((String, String) -> Maybe a) -> RawOpts -> [a] #

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

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

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

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

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

class Assertable t where #

Methods

assert :: t -> Assertion #

Instances

Instances details
Assertable String 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assert :: String -> Assertion #

Assertable () 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assert :: () -> Assertion #

Assertable Bool 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assert :: Bool -> Assertion #

Assertable t => Assertable (IO t) 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assert :: IO t -> Assertion #

data Query #

Instances

Instances details
Default Query 
Instance details

Defined in Hledger.Query

Methods

def :: Query

Show Query 
Instance details

Defined in Hledger.Query

Methods

showsPrec :: Int -> Query -> ShowS

show :: Query -> String

showList :: [Query] -> ShowS

Eq Query 
Instance details

Defined in Hledger.Query

Methods

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

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

data OrdPlus #

Constructors

Lt 
LtEq 
Gt 
GtEq 
Eq 
AbsLt 
AbsLtEq 
AbsGt 
AbsGtEq 
AbsEq 

Instances

Instances details
Show OrdPlus 
Instance details

Defined in Hledger.Query

Methods

showsPrec :: Int -> OrdPlus -> ShowS

show :: OrdPlus -> String

showList :: [OrdPlus] -> ShowS

Eq OrdPlus 
Instance details

Defined in Hledger.Query

Methods

(==) :: OrdPlus -> OrdPlus -> Bool

(/=) :: OrdPlus -> OrdPlus -> Bool

takeEnd :: Int -> [a] -> [a] #

type HasCallStack = ?callStack :: CallStack #

data Period #

Instances

Instances details
Default Period 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Period

Generic Period 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Period 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 ('MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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 -> Type)))))

Methods

from :: Period -> Rep Period x

to :: Rep Period x -> Period

Show Period 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Period -> ShowS

show :: Period -> String

showList :: [Period] -> ShowS

Eq Period 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Period 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Period -> Period -> Ordering #

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

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

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

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

max :: Period -> Period -> Period #

min :: Period -> Period -> Period #

type Rep Period 
Instance details

Defined in Hledger.Data.Types

type Rep Period = D1 ('MetaData "Period" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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 -> Type)))))

type Year = Integer #

data AmountFormat #

Instances

Instances details
Default AmountFormat 
Instance details

Defined in Hledger.Data.Amount

Methods

def :: AmountFormat

Show AmountFormat 
Instance details

Defined in Hledger.Data.Amount

Methods

showsPrec :: Int -> AmountFormat -> ShowS

show :: AmountFormat -> String

showList :: [AmountFormat] -> ShowS

data Amount #

Instances

Instances details
Generic Amount 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Amount 
Instance details

Defined in Hledger.Data.Types

type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Amount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "acommodity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "aquantity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Quantity)) :*: (S1 ('MetaSel ('Just "astyle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountStyle) :*: S1 ('MetaSel ('Just "acost") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe AmountCost)))))

Methods

from :: Amount -> Rep Amount x

to :: Rep Amount x -> Amount

Show Amount 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Amount -> ShowS

show :: Amount -> String

showList :: [Amount] -> ShowS

Eq Amount 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Amount 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Amount -> Amount -> Ordering #

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

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

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

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

max :: Amount -> Amount -> Amount #

min :: Amount -> Amount -> Amount #

type Rep Amount 
Instance details

Defined in Hledger.Data.Types

type Rep Amount = D1 ('MetaData "Amount" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Amount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "acommodity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "aquantity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Quantity)) :*: (S1 ('MetaSel ('Just "astyle") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountStyle) :*: S1 ('MetaSel ('Just "acost") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe AmountCost)))))

data MixedAmount #

Instances

Instances details
Generic MixedAmount 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MixedAmount 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount = D1 ('MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'True) (C1 ('MetaCons "Mixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map MixedAmountKey Amount))))

Methods

from :: MixedAmount -> Rep MixedAmount x

to :: Rep MixedAmount x -> MixedAmount

Show MixedAmount 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> MixedAmount -> ShowS

show :: MixedAmount -> String

showList :: [MixedAmount] -> ShowS

Eq MixedAmount 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: MixedAmount -> MixedAmount -> Bool

(/=) :: MixedAmount -> MixedAmount -> Bool

Ord MixedAmount 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount 
Instance details

Defined in Hledger.Data.Types

type Rep MixedAmount = D1 ('MetaData "MixedAmount" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'True) (C1 ('MetaCons "Mixed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map MixedAmountKey Amount))))

data WideBuilder #

Constructors

WideBuilder 

Fields

Instances

Instances details
Monoid WideBuilder 
Instance details

Defined in Text.WideString

Semigroup WideBuilder 
Instance details

Defined in Text.WideString

Methods

(<>) :: WideBuilder -> WideBuilder -> WideBuilder

sconcat :: NonEmpty WideBuilder -> WideBuilder

stimes :: Integral b => b -> WideBuilder -> WideBuilder

Show WideBuilder 
Instance details

Defined in Text.WideString

Methods

showsPrec :: Int -> WideBuilder -> ShowS

show :: WideBuilder -> String

showList :: [WideBuilder] -> ShowS

wbUnpack :: WideBuilder -> String #

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

formatText :: Bool -> Maybe Int -> Maybe Int -> Text -> Text #

readDecimal :: Text -> Integer #

textElideRight :: Int -> Text -> Text #

textTakeWidth :: Int -> Text -> Text #

unlinesB :: [Builder] -> Builder #

wrap :: Text -> Text -> Text -> Text #

data TestTree #

data Interval #

Constructors

NoInterval 
Days Int 
Weeks Int 
Months Int 
Quarters Int 
Years Int 
NthWeekdayOfMonth Int Int 
MonthDay Int 
MonthAndDay Int Int 
DaysOfWeek [Int] 

Instances

Instances details
Default Interval 
Instance details

Defined in Hledger.Data.Types

Methods

def :: Interval

Generic Interval 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Interval 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 ('MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (((C1 ('MetaCons "NoInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: 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 "NthWeekdayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "MonthDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "MonthAndDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "DaysOfWeek" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]))))))

Methods

from :: Interval -> Rep Interval x

to :: Rep Interval x -> Interval

Show Interval 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Interval -> ShowS

show :: Interval -> String

showList :: [Interval] -> ShowS

Eq Interval 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Interval -> Interval -> Bool

(/=) :: Interval -> Interval -> Bool

Ord Interval 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Interval -> Interval -> Ordering #

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

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

(>) :: Interval -> Interval -> Bool #

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

max :: Interval -> Interval -> Interval #

min :: Interval -> Interval -> Interval #

type Rep Interval 
Instance details

Defined in Hledger.Data.Types

type Rep Interval = D1 ('MetaData "Interval" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (((C1 ('MetaCons "NoInterval" 'PrefixI 'False) (U1 :: Type -> Type) :+: 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 "NthWeekdayOfMonth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "MonthDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "MonthAndDay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "DaysOfWeek" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]))))))

data EFDay #

Constructors

Exact Day 
Flex Day 

Instances

Instances details
Generic EFDay 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep EFDay 
Instance details

Defined in Hledger.Data.Types

type Rep EFDay = D1 ('MetaData "EFDay" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Exact" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "Flex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)))

Methods

from :: EFDay -> Rep EFDay x

to :: Rep EFDay x -> EFDay

Show EFDay 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> EFDay -> ShowS

show :: EFDay -> String

showList :: [EFDay] -> ShowS

Eq EFDay 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: EFDay -> EFDay -> Bool

(/=) :: EFDay -> EFDay -> Bool

Ord EFDay 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: EFDay -> EFDay -> Ordering #

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

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

(>) :: EFDay -> EFDay -> Bool #

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

max :: EFDay -> EFDay -> EFDay #

min :: EFDay -> EFDay -> EFDay #

type Rep EFDay 
Instance details

Defined in Hledger.Data.Types

type Rep EFDay = D1 ('MetaData "EFDay" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Exact" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :+: C1 ('MetaCons "Flex" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)))

type Month = Int #

type MonthDay = Int #

type Quarter = Int #

data SmartDate #

Instances

Instances details
Show SmartDate 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> SmartDate -> ShowS

show :: SmartDate -> String

showList :: [SmartDate] -> ShowS

type WeekDay = Int #

modifyEFDay :: (Day -> Day) -> EFDay -> EFDay #

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

type TextParser (m :: Type -> Type) a = ParsecT HledgerParseErrorData Text m a #

choice' :: forall (m :: Type -> Type) a. [TextParser m a] -> TextParser m a #

parsewith :: Parsec e Text a -> Text -> Either (ParseErrorBundle Text e) a #

skipNonNewlineSpaces :: forall s (m :: Type -> Type). (Stream s, Token s ~ Char) => ParsecT HledgerParseErrorData s m () #

datesepchar :: forall (m :: Type -> Type). TextParser m Char #

datesepchars :: String #

daysInSpan :: DateSpan -> Maybe Integer #

elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a #

getCurrentYear :: IO Integer #

groupByDateSpan :: Bool -> (a -> Day) -> [DateSpan] -> [a] -> [(DateSpan, [a])] #

isDateSepChar :: Char -> Bool #

parsedateM :: String -> Maybe Day #

periodexprp :: forall (m :: Type -> Type). Day -> TextParser m (Interval, DateSpan) #

smartdate :: forall (m :: Type -> Type). TextParser m SmartDate #

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

yearp :: forall (m :: Type -> Type). TextParser m Integer #

data HledgerParseErrorData #

Instances

Instances details
Show HledgerParseErrorData 
Instance details

Defined in Hledger.Utils.Parse

Methods

showsPrec :: Int -> HledgerParseErrorData -> ShowS

show :: HledgerParseErrorData -> String

showList :: [HledgerParseErrorData] -> ShowS

Eq HledgerParseErrorData 
Instance details

Defined in Hledger.Utils.Parse

Ord HledgerParseErrorData 
Instance details

Defined in Hledger.Utils.Parse

ShowErrorComponent HledgerParseErrorData 
Instance details

Defined in Hledger.Utils.Parse

Ord (ParseError Text HledgerParseErrorData) 
Instance details

Defined in Hledger.Utils.Parse

Methods

compare :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> Ordering #

(<) :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> Bool #

(<=) :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> Bool #

(>) :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> Bool #

(>=) :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> Bool #

max :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData #

min :: ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData -> ParseError Text HledgerParseErrorData #

data SourcePos #

Constructors

SourcePos 

Fields

Instances

Instances details
NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnf :: SourcePos -> ()

Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr

dataTypeOf :: SourcePos -> DataType

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

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

gmapT :: (forall b. Data b => b -> b) -> SourcePos -> SourcePos

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

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

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

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

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

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

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

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.6.1-Fknd9Evn1rKGXk3RxCKRQR" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos))))

Methods

from :: SourcePos -> Rep SourcePos x

to :: Rep SourcePos x -> SourcePos

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

readsPrec :: Int -> ReadS SourcePos

readList :: ReadS [SourcePos]

readPrec :: ReadPrec SourcePos

readListPrec :: ReadPrec [SourcePos]

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

showsPrec :: Int -> SourcePos -> ShowS

show :: SourcePos -> String

showList :: [SourcePos] -> ShowS

Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

(==) :: SourcePos -> SourcePos -> Bool

(/=) :: SourcePos -> SourcePos -> Bool

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.6.1-Fknd9Evn1rKGXk3RxCKRQR" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos))))

data Regexp #

Instances

Instances details
ToJSON Regexp 
Instance details

Defined in Hledger.Utils.Regex

Methods

toJSON :: Regexp -> Value

toEncoding :: Regexp -> Encoding

toJSONList :: [Regexp] -> Value

toEncodingList :: [Regexp] -> Encoding

omitField :: Regexp -> Bool

Read Regexp 
Instance details

Defined in Hledger.Utils.Regex

Methods

readsPrec :: Int -> ReadS Regexp

readList :: ReadS [Regexp]

readPrec :: ReadPrec Regexp

readListPrec :: ReadPrec [Regexp]

Show Regexp 
Instance details

Defined in Hledger.Utils.Regex

Methods

showsPrec :: Int -> Regexp -> ShowS

show :: Regexp -> String

showList :: [Regexp] -> ShowS

Eq Regexp 
Instance details

Defined in Hledger.Utils.Regex

Methods

(==) :: Regexp -> Regexp -> Bool

(/=) :: Regexp -> Regexp -> Bool

Ord Regexp 
Instance details

Defined in Hledger.Utils.Regex

Methods

compare :: Regexp -> Regexp -> Ordering #

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

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

(>) :: Regexp -> Regexp -> Bool #

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

max :: Regexp -> Regexp -> Regexp #

min :: Regexp -> Regexp -> Regexp #

RegexLike Regexp String 
Instance details

Defined in Hledger.Utils.Regex

Methods

matchOnce :: Regexp -> String -> Maybe MatchArray

matchAll :: Regexp -> String -> [MatchArray]

matchCount :: Regexp -> String -> Int

matchTest :: Regexp -> String -> Bool

matchAllText :: Regexp -> String -> [MatchText String]

matchOnceText :: Regexp -> String -> Maybe (String, MatchText String, String)

RegexContext Regexp String String 
Instance details

Defined in Hledger.Utils.Regex

Methods

match :: Regexp -> String -> String

matchM :: MonadFail m => Regexp -> String -> m String

type Replacement = String #

data AccountAlias #

Instances

Instances details
Generic AccountAlias 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountAlias 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias = D1 ('MetaData "AccountAlias" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "BasicAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName)) :+: C1 ('MetaCons "RegexAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Regexp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Replacement)))
Read AccountAlias 
Instance details

Defined in Hledger.Data.Types

Methods

readsPrec :: Int -> ReadS AccountAlias

readList :: ReadS [AccountAlias]

readPrec :: ReadPrec AccountAlias

readListPrec :: ReadPrec [AccountAlias]

Show AccountAlias 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AccountAlias -> ShowS

show :: AccountAlias -> String

showList :: [AccountAlias] -> ShowS

Eq AccountAlias 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AccountAlias -> AccountAlias -> Bool

(/=) :: AccountAlias -> AccountAlias -> Bool

Ord AccountAlias 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias 
Instance details

Defined in Hledger.Data.Types

type Rep AccountAlias = D1 ('MetaData "AccountAlias" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "BasicAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName)) :+: C1 ('MetaCons "RegexAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Regexp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Replacement)))

data AccountDeclarationInfo #

Instances

Instances details
Generic AccountDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo = D1 ('MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "AccountDeclarationInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "adicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "aditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])) :*: (S1 ('MetaSel ('Just "adideclarationorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "adisourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))
Show AccountDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Eq AccountDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep AccountDeclarationInfo = D1 ('MetaData "AccountDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "AccountDeclarationInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "adicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "aditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])) :*: (S1 ('MetaSel ('Just "adideclarationorder") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "adisourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))

data AccountType #

Instances

Instances details
Generic AccountType 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AccountType 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType = D1 ('MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) ((C1 ('MetaCons "Asset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Liability" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Equity" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Revenue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Expense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Conversion" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: AccountType -> Rep AccountType x

to :: Rep AccountType x -> AccountType

Show AccountType 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AccountType -> ShowS

show :: AccountType -> String

showList :: [AccountType] -> ShowS

Eq AccountType 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AccountType -> AccountType -> Bool

(/=) :: AccountType -> AccountType -> Bool

Ord AccountType 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType 
Instance details

Defined in Hledger.Data.Types

type Rep AccountType = D1 ('MetaData "AccountType" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) ((C1 ('MetaCons "Asset" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Liability" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Equity" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Revenue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Expense" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Cash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Conversion" 'PrefixI 'False) (U1 :: Type -> Type))))

data Account #

Instances

Instances details
Generic Account 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Account 
Instance details

Defined in Hledger.Data.Types

type Rep Account = D1 ('MetaData "Account" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (((S1 ('MetaSel ('Just "aname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "adeclarationinfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AccountDeclarationInfo))) :*: (S1 ('MetaSel ('Just "asubs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account]) :*: S1 ('MetaSel ('Just "aparent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Account)))) :*: ((S1 ('MetaSel ('Just "aboring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "anumpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "aebalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount) :*: S1 ('MetaSel ('Just "aibalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))))

Methods

from :: Account -> Rep Account x

to :: Rep Account x -> Account

type Rep Account 
Instance details

Defined in Hledger.Data.Types

type Rep Account = D1 ('MetaData "Account" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Account" 'PrefixI 'True) (((S1 ('MetaSel ('Just "aname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "adeclarationinfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AccountDeclarationInfo))) :*: (S1 ('MetaSel ('Just "asubs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account]) :*: S1 ('MetaSel ('Just "aparent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Account)))) :*: ((S1 ('MetaSel ('Just "aboring") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "anumpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "aebalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount) :*: S1 ('MetaSel ('Just "aibalance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))))

data AmountCost #

Constructors

UnitCost !Amount 
TotalCost !Amount 

Instances

Instances details
Generic AmountCost 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountCost 
Instance details

Defined in Hledger.Data.Types

type Rep AmountCost = D1 ('MetaData "AmountCost" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "UnitCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)) :+: C1 ('MetaCons "TotalCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)))

Methods

from :: AmountCost -> Rep AmountCost x

to :: Rep AmountCost x -> AmountCost

Show AmountCost 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountCost -> ShowS

show :: AmountCost -> String

showList :: [AmountCost] -> ShowS

Eq AmountCost 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AmountCost -> AmountCost -> Bool

(/=) :: AmountCost -> AmountCost -> Bool

Ord AmountCost 
Instance details

Defined in Hledger.Data.Types

type Rep AmountCost 
Instance details

Defined in Hledger.Data.Types

type Rep AmountCost = D1 ('MetaData "AmountCost" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "UnitCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)) :+: C1 ('MetaCons "TotalCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Amount)))

data AmountPrecision #

Constructors

Precision !Word8 
NaturalPrecision 

Instances

Instances details
Generic AmountPrecision 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountPrecision 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision = D1 ('MetaData "AmountPrecision" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Precision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8)) :+: C1 ('MetaCons "NaturalPrecision" 'PrefixI 'False) (U1 :: Type -> Type))
Read AmountPrecision 
Instance details

Defined in Hledger.Data.Types

Show AmountPrecision 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountPrecision -> ShowS

show :: AmountPrecision -> String

showList :: [AmountPrecision] -> ShowS

Eq AmountPrecision 
Instance details

Defined in Hledger.Data.Types

Ord AmountPrecision 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision 
Instance details

Defined in Hledger.Data.Types

type Rep AmountPrecision = D1 ('MetaData "AmountPrecision" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Precision" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word8)) :+: C1 ('MetaCons "NaturalPrecision" 'PrefixI 'False) (U1 :: Type -> Type))

data AmountStyle #

Instances

Instances details
Generic AmountStyle 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep AmountStyle 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle = D1 ('MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "AmountStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ascommodityside") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Side) :*: (S1 ('MetaSel ('Just "ascommodityspaced") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "asdigitgroups") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DigitGroupStyle)))) :*: (S1 ('MetaSel ('Just "asdecimalmark") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Char)) :*: (S1 ('MetaSel ('Just "asprecision") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountPrecision) :*: S1 ('MetaSel ('Just "asrounding") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Rounding)))))

Methods

from :: AmountStyle -> Rep AmountStyle x

to :: Rep AmountStyle x -> AmountStyle

Read AmountStyle 
Instance details

Defined in Hledger.Data.Types

Methods

readsPrec :: Int -> ReadS AmountStyle

readList :: ReadS [AmountStyle]

readPrec :: ReadPrec AmountStyle

readListPrec :: ReadPrec [AmountStyle]

Show AmountStyle 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> AmountStyle -> ShowS

show :: AmountStyle -> String

showList :: [AmountStyle] -> ShowS

Eq AmountStyle 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: AmountStyle -> AmountStyle -> Bool

(/=) :: AmountStyle -> AmountStyle -> Bool

Ord AmountStyle 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle 
Instance details

Defined in Hledger.Data.Types

type Rep AmountStyle = D1 ('MetaData "AmountStyle" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "AmountStyle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ascommodityside") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Side) :*: (S1 ('MetaSel ('Just "ascommodityspaced") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "asdigitgroups") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe DigitGroupStyle)))) :*: (S1 ('MetaSel ('Just "asdecimalmark") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Char)) :*: (S1 ('MetaSel ('Just "asprecision") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AmountPrecision) :*: S1 ('MetaSel ('Just "asrounding") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Rounding)))))

data BalanceAssertion #

Constructors

BalanceAssertion 

Fields

Instances

Instances details
Generic BalanceAssertion 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep BalanceAssertion 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion = D1 ('MetaData "BalanceAssertion" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "BalanceAssertion" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Just "batotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "bainclusive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "baposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))
Show BalanceAssertion 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> BalanceAssertion -> ShowS

show :: BalanceAssertion -> String

showList :: [BalanceAssertion] -> ShowS

Eq BalanceAssertion 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion 
Instance details

Defined in Hledger.Data.Types

type Rep BalanceAssertion = D1 ('MetaData "BalanceAssertion" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "BalanceAssertion" 'PrefixI 'True) ((S1 ('MetaSel ('Just "baamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Just "batotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "bainclusive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "baposition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos))))

data Commodity #

Instances

Instances details
Generic Commodity 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Commodity 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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))))

Methods

from :: Commodity -> Rep Commodity x

to :: Rep Commodity x -> Commodity

Show Commodity 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Commodity -> ShowS

show :: Commodity -> String

showList :: [Commodity] -> ShowS

Eq Commodity 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Commodity -> Commodity -> Bool

(/=) :: Commodity -> Commodity -> Bool

type Rep Commodity 
Instance details

Defined in Hledger.Data.Types

type Rep Commodity = D1 ('MetaData "Commodity" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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 #

Constructors

DigitGroups !Char ![Word8] 

Instances

Instances details
Generic DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 ('MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "DigitGroups" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word8])))
Read DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

Show DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> DigitGroupStyle -> ShowS

show :: DigitGroupStyle -> String

showList :: [DigitGroupStyle] -> ShowS

Eq DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

Ord DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle 
Instance details

Defined in Hledger.Data.Types

type Rep DigitGroupStyle = D1 ('MetaData "DigitGroupStyle" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "DigitGroups" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word8])))

data Journal #

Instances

Instances details
Generic Journal 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Journal 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 ('MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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 "jparsedecimalmark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DecimalMark)))) :*: (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 "jincludefilestack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jdeclaredpayees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Payee, PayeeDeclarationInfo)]) :*: S1 ('MetaSel ('Just "jdeclaredtags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(TagName, TagDeclarationInfo)]))) :*: (S1 ('MetaSel ('Just "jdeclaredaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AccountName, AccountDeclarationInfo)]) :*: (S1 ('MetaSel ('Just "jdeclaredaccounttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName [Tag])) :*: S1 ('MetaSel ('Just "jdeclaredaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountType [AccountName])))))) :*: (((S1 ('MetaSel ('Just "jaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName AccountType)) :*: (S1 ('MetaSel ('Just "jdeclaredcommodities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol Commodity)) :*: S1 ('MetaSel ('Just "jinferredcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)))) :*: (S1 ('MetaSel ('Just "jglobalcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)) :*: (S1 ('MetaSel ('Just "jpricedirectives") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PriceDirective]) :*: S1 ('MetaSel ('Just "jinferredmarketprices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MarketPrice])))) :*: ((S1 ('MetaSel ('Just "jtxnmodifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TransactionModifier]) :*: (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 POSIXTime)))))))

Methods

from :: Journal -> Rep Journal x

to :: Rep Journal x -> Journal

Eq Journal 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Anon Journal Source # 
Instance details

Defined in Hledger.Cli.Anon

Methods

anon :: Journal -> Journal Source #

type Rep Journal 
Instance details

Defined in Hledger.Data.Types

type Rep Journal = D1 ('MetaData "Journal" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" '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 "jparsedecimalmark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DecimalMark)))) :*: (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 "jincludefilestack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "jdeclaredpayees") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Payee, PayeeDeclarationInfo)]) :*: S1 ('MetaSel ('Just "jdeclaredtags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(TagName, TagDeclarationInfo)]))) :*: (S1 ('MetaSel ('Just "jdeclaredaccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(AccountName, AccountDeclarationInfo)]) :*: (S1 ('MetaSel ('Just "jdeclaredaccounttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName [Tag])) :*: S1 ('MetaSel ('Just "jdeclaredaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountType [AccountName])))))) :*: (((S1 ('MetaSel ('Just "jaccounttypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AccountName AccountType)) :*: (S1 ('MetaSel ('Just "jdeclaredcommodities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol Commodity)) :*: S1 ('MetaSel ('Just "jinferredcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)))) :*: (S1 ('MetaSel ('Just "jglobalcommoditystyles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CommoditySymbol AmountStyle)) :*: (S1 ('MetaSel ('Just "jpricedirectives") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PriceDirective]) :*: S1 ('MetaSel ('Just "jinferredmarketprices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MarketPrice])))) :*: ((S1 ('MetaSel ('Just "jtxnmodifiers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TransactionModifier]) :*: (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 POSIXTime)))))))

data Ledger #

Constructors

Ledger 

Instances

Instances details
Generic Ledger 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Ledger 
Instance details

Defined in Hledger.Data.Types

type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account])))

Methods

from :: Ledger -> Rep Ledger x

to :: Rep Ledger x -> Ledger

type Rep Ledger 
Instance details

Defined in Hledger.Data.Types

type Rep Ledger = D1 ('MetaData "Ledger" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) (S1 ('MetaSel ('Just "ljournal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Journal) :*: S1 ('MetaSel ('Just "laccounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Account])))

data MarketPrice #

Instances

Instances details
Generic MarketPrice 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep MarketPrice 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice = D1 ('MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "MarketPrice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "mpfrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol)) :*: (S1 ('MetaSel ('Just "mpto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "mprate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity))))

Methods

from :: MarketPrice -> Rep MarketPrice x

to :: Rep MarketPrice x -> MarketPrice

Show MarketPrice 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> MarketPrice -> ShowS

show :: MarketPrice -> String

showList :: [MarketPrice] -> ShowS

Eq MarketPrice 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: MarketPrice -> MarketPrice -> Bool

(/=) :: MarketPrice -> MarketPrice -> Bool

Ord MarketPrice 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice 
Instance details

Defined in Hledger.Data.Types

type Rep MarketPrice = D1 ('MetaData "MarketPrice" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "MarketPrice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mpdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "mpfrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol)) :*: (S1 ('MetaSel ('Just "mpto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "mprate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Quantity))))

pattern MixedAmountKeyNoCost :: !CommoditySymbol -> MixedAmountKey #

pattern MixedAmountKeyTotalCost :: !CommoditySymbol -> !CommoditySymbol -> MixedAmountKey #

pattern MixedAmountKeyUnitCost :: !CommoditySymbol -> !CommoditySymbol -> !Quantity -> MixedAmountKey #

data PayeeDeclarationInfo #

Constructors

PayeeDeclarationInfo 

Fields

Instances

Instances details
Generic PayeeDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PayeeDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo = D1 ('MetaData "PayeeDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PayeeDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "pdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "pditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))
Show PayeeDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> PayeeDeclarationInfo -> ShowS

show :: PayeeDeclarationInfo -> String

showList :: [PayeeDeclarationInfo] -> ShowS

Eq PayeeDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep PayeeDeclarationInfo = D1 ('MetaData "PayeeDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PayeeDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "pdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "pditags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))

data PeriodicTransaction #

Instances

Instances details
Generic PeriodicTransaction 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PeriodicTransaction 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction = D1 ('MetaData "PeriodicTransaction" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicTransaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ptperiodexpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptinterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interval)) :*: (S1 ('MetaSel ('Just "ptspan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DateSpan) :*: (S1 ('MetaSel ('Just "ptsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: S1 ('MetaSel ('Just "ptstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :*: ((S1 ('MetaSel ('Just "ptcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "ptcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "pttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "ptpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))
Eq PeriodicTransaction 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction 
Instance details

Defined in Hledger.Data.Types

type Rep PeriodicTransaction = D1 ('MetaData "PeriodicTransaction" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicTransaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ptperiodexpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptinterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interval)) :*: (S1 ('MetaSel ('Just "ptspan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DateSpan) :*: (S1 ('MetaSel ('Just "ptsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: S1 ('MetaSel ('Just "ptstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status)))) :*: ((S1 ('MetaSel ('Just "ptcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "ptdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "ptcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "pttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "ptpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))

data PostingType #

Instances

Instances details
Generic PostingType 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PostingType 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType = D1 ('MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "RegularPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BalancedVirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: PostingType -> Rep PostingType x

to :: Rep PostingType x -> PostingType

Show PostingType 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> PostingType -> ShowS

show :: PostingType -> String

showList :: [PostingType] -> ShowS

Eq PostingType 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: PostingType -> PostingType -> Bool

(/=) :: PostingType -> PostingType -> Bool

type Rep PostingType 
Instance details

Defined in Hledger.Data.Types

type Rep PostingType = D1 ('MetaData "PostingType" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "RegularPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BalancedVirtualPosting" 'PrefixI 'False) (U1 :: Type -> Type)))

data Posting #

Instances

Instances details
Generic Posting 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Posting 
Instance details

Defined in Hledger.Data.Types

type Rep Posting = D1 ('MetaData "Posting" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Posting" 'PrefixI 'True) (((S1 ('MetaSel ('Just "pdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Just "pdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))) :*: (S1 ('MetaSel ('Just "pstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "paccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "pamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))) :*: ((S1 ('MetaSel ('Just "pcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ptype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PostingType) :*: S1 ('MetaSel ('Just "ptags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]))) :*: (S1 ('MetaSel ('Just "pbalanceassertion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BalanceAssertion)) :*: (S1 ('MetaSel ('Just "ptransaction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Transaction)) :*: S1 ('MetaSel ('Just "poriginal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Posting)))))))

Methods

from :: Posting -> Rep Posting x

to :: Rep Posting x -> Posting

Show Posting 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Posting -> ShowS

show :: Posting -> String

showList :: [Posting] -> ShowS

Eq Posting 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Anon Posting Source # 
Instance details

Defined in Hledger.Cli.Anon

Methods

anon :: Posting -> Posting Source #

type Rep Posting 
Instance details

Defined in Hledger.Data.Types

type Rep Posting = D1 ('MetaData "Posting" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Posting" 'PrefixI 'True) (((S1 ('MetaSel ('Just "pdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day)) :*: S1 ('MetaSel ('Just "pdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))) :*: (S1 ('MetaSel ('Just "pstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "paccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "pamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MixedAmount)))) :*: ((S1 ('MetaSel ('Just "pcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ptype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PostingType) :*: S1 ('MetaSel ('Just "ptags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]))) :*: (S1 ('MetaSel ('Just "pbalanceassertion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BalanceAssertion)) :*: (S1 ('MetaSel ('Just "ptransaction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Transaction)) :*: S1 ('MetaSel ('Just "poriginal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Posting)))))))

data PriceDirective #

Instances

Instances details
Generic PriceDirective 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep PriceDirective 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective = D1 ('MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PriceDirective" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pdsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "pddate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :*: (S1 ('MetaSel ('Just "pdcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "pdamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))))
Show PriceDirective 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> PriceDirective -> ShowS

show :: PriceDirective -> String

showList :: [PriceDirective] -> ShowS

Eq PriceDirective 
Instance details

Defined in Hledger.Data.Types

Ord PriceDirective 
Instance details

Defined in Hledger.Data.Types

HasAmounts PriceDirective Source # 
Instance details

Defined in Hledger.Cli.Commands.Prices

type Rep PriceDirective 
Instance details

Defined in Hledger.Data.Types

type Rep PriceDirective = D1 ('MetaData "PriceDirective" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PriceDirective" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pdsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "pddate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day)) :*: (S1 ('MetaSel ('Just "pdcommodity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommoditySymbol) :*: S1 ('MetaSel ('Just "pdamount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))))

data Rounding #

Instances

Instances details
Generic Rounding 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Rounding 
Instance details

Defined in Hledger.Data.Types

type Rep Rounding = D1 ('MetaData "Rounding" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) ((C1 ('MetaCons "NoRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SoftRounding" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HardRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllRounding" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Rounding -> Rep Rounding x

to :: Rep Rounding x -> Rounding

Read Rounding 
Instance details

Defined in Hledger.Data.Types

Methods

readsPrec :: Int -> ReadS Rounding

readList :: ReadS [Rounding]

readPrec :: ReadPrec Rounding

readListPrec :: ReadPrec [Rounding]

Show Rounding 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Rounding -> ShowS

show :: Rounding -> String

showList :: [Rounding] -> ShowS

Eq Rounding 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Rounding -> Rounding -> Bool

(/=) :: Rounding -> Rounding -> Bool

Ord Rounding 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Rounding -> Rounding -> Ordering #

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

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

(>) :: Rounding -> Rounding -> Bool #

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

max :: Rounding -> Rounding -> Rounding #

min :: Rounding -> Rounding -> Rounding #

type Rep Rounding 
Instance details

Defined in Hledger.Data.Types

type Rep Rounding = D1 ('MetaData "Rounding" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) ((C1 ('MetaCons "NoRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SoftRounding" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HardRounding" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllRounding" 'PrefixI 'False) (U1 :: Type -> Type)))

data Status #

Constructors

Unmarked 
Pending 
Cleared 

Instances

Instances details
Bounded Status 
Instance details

Defined in Hledger.Data.Types

Enum Status 
Instance details

Defined in Hledger.Data.Types

Generic Status 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Status 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Unmarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cleared" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Status -> Rep Status x

to :: Rep Status x -> Status

Show Status 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Status -> ShowS

show :: Status -> String

showList :: [Status] -> ShowS

Eq Status 
Instance details

Defined in Hledger.Data.Types

Methods

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

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

Ord Status 
Instance details

Defined in Hledger.Data.Types

Methods

compare :: Status -> Status -> Ordering #

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

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

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

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

max :: Status -> Status -> Status #

min :: Status -> Status -> Status #

type Rep Status 
Instance details

Defined in Hledger.Data.Types

type Rep Status = D1 ('MetaData "Status" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Unmarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cleared" 'PrefixI 'False) (U1 :: Type -> Type)))

data TMPostingRule #

Constructors

TMPostingRule 

Instances

Instances details
Generic TMPostingRule 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TMPostingRule 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule = D1 ('MetaData "TMPostingRule" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TMPostingRule" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmprPosting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Posting) :*: S1 ('MetaSel ('Just "tmprIsMultiplier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
Show TMPostingRule 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> TMPostingRule -> ShowS

show :: TMPostingRule -> String

showList :: [TMPostingRule] -> ShowS

Eq TMPostingRule 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule 
Instance details

Defined in Hledger.Data.Types

type Rep TMPostingRule = D1 ('MetaData "TMPostingRule" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TMPostingRule" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmprPosting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Posting) :*: S1 ('MetaSel ('Just "tmprIsMultiplier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

newtype TagDeclarationInfo #

Constructors

TagDeclarationInfo 

Fields

Instances

Instances details
Generic TagDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TagDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep TagDeclarationInfo = D1 ('MetaData "TagDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'True) (C1 ('MetaCons "TagDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "tdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
Show TagDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> TagDeclarationInfo -> ShowS

show :: TagDeclarationInfo -> String

showList :: [TagDeclarationInfo] -> ShowS

Eq TagDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep TagDeclarationInfo 
Instance details

Defined in Hledger.Data.Types

type Rep TagDeclarationInfo = D1 ('MetaData "TagDeclarationInfo" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'True) (C1 ('MetaCons "TagDeclarationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "tdicomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data TimeclockCode #

Instances

Instances details
Generic TimeclockCode 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockCode 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode = D1 ('MetaData "TimeclockCode" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) ((C1 ('MetaCons "SetBalance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SetRequiredHours" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Out" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FinalOut" 'PrefixI 'False) (U1 :: Type -> Type))))
Eq TimeclockCode 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockCode 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockCode 
Instance details

Defined in Hledger.Data.Types

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

data TimeclockEntry #

Instances

Instances details
Generic TimeclockEntry 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TimeclockEntry 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry = D1 ('MetaData "TimeclockEntry" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TimeclockEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tlsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "tlcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeclockCode) :*: S1 ('MetaSel ('Just "tldatetime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime))) :*: ((S1 ('MetaSel ('Just "tlaccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "tldescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tlcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tltags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))))
Eq TimeclockEntry 
Instance details

Defined in Hledger.Data.Types

Ord TimeclockEntry 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry 
Instance details

Defined in Hledger.Data.Types

type Rep TimeclockEntry = D1 ('MetaData "TimeclockEntry" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TimeclockEntry" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tlsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: (S1 ('MetaSel ('Just "tlcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeclockCode) :*: S1 ('MetaSel ('Just "tldatetime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LocalTime))) :*: ((S1 ('MetaSel ('Just "tlaccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AccountName) :*: S1 ('MetaSel ('Just "tldescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tlcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tltags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag])))))

data TransactionModifier #

Instances

Instances details
Generic TransactionModifier 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep TransactionModifier 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier = D1 ('MetaData "TransactionModifier" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TransactionModifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmquerytxt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tmpostingrules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TMPostingRule])))
Show TransactionModifier 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> TransactionModifier -> ShowS

show :: TransactionModifier -> String

showList :: [TransactionModifier] -> ShowS

Eq TransactionModifier 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier 
Instance details

Defined in Hledger.Data.Types

type Rep TransactionModifier = D1 ('MetaData "TransactionModifier" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "TransactionModifier" 'PrefixI 'True) (S1 ('MetaSel ('Just "tmquerytxt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tmpostingrules") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TMPostingRule])))

data Transaction #

Instances

Instances details
Generic Transaction 
Instance details

Defined in Hledger.Data.Types

Associated Types

type Rep Transaction 
Instance details

Defined in Hledger.Data.Types

type Rep Transaction = D1 ('MetaData "Transaction" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Transaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "tprecedingcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: (S1 ('MetaSel ('Just "tdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "tdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))))) :*: ((S1 ('MetaSel ('Just "tstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "tcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "tcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "tpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))

Methods

from :: Transaction -> Rep Transaction x

to :: Rep Transaction x -> Transaction

Show Transaction 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> Transaction -> ShowS

show :: Transaction -> String

showList :: [Transaction] -> ShowS

Eq Transaction 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: Transaction -> Transaction -> Bool

(/=) :: Transaction -> Transaction -> Bool

Anon Transaction Source # 
Instance details

Defined in Hledger.Cli.Anon

type Rep Transaction 
Instance details

Defined in Hledger.Data.Types

type Rep Transaction = D1 ('MetaData "Transaction" "Hledger.Data.Types" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "Transaction" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "tprecedingcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "tsourcepos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SourcePos, SourcePos)) :*: (S1 ('MetaSel ('Just "tdate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Day) :*: S1 ('MetaSel ('Just "tdate2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Day))))) :*: ((S1 ('MetaSel ('Just "tstatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Status) :*: (S1 ('MetaSel ('Just "tcode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "tdescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :*: (S1 ('MetaSel ('Just "tcomment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ttags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tag]) :*: S1 ('MetaSel ('Just "tpostings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Posting]))))))

class HasAmounts a where #

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a #

Instances

Instances details
HasAmounts PriceDirective Source # 
Instance details

Defined in Hledger.Cli.Commands.Prices

HasAmounts a => HasAmounts (Maybe a) 
Instance details

Defined in Hledger.Data.Types

HasAmounts a => HasAmounts [a] 
Instance details

Defined in Hledger.Data.Types

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> [a] -> [a] #

HasAmounts b => HasAmounts (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

HasAmounts b => HasAmounts (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

HasAmounts b => HasAmounts (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

(HasAmounts a, HasAmounts b) => HasAmounts (a, b) 
Instance details

Defined in Hledger.Data.Types

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> (a, b) -> (a, b) #

HasAmounts b => HasAmounts (Text, PeriodicReport a b, Bool) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> (Text, PeriodicReport a b, Bool) -> (Text, PeriodicReport a b, Bool) #

data DepthSpec #

Constructors

DepthSpec 

Fields

Instances

Instances details
Monoid DepthSpec 
Instance details

Defined in Hledger.Data.Types

Semigroup DepthSpec 
Instance details

Defined in Hledger.Data.Types

Methods

(<>) :: DepthSpec -> DepthSpec -> DepthSpec

sconcat :: NonEmpty DepthSpec -> DepthSpec

stimes :: Integral b => b -> DepthSpec -> DepthSpec

Show DepthSpec 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> DepthSpec -> ShowS

show :: DepthSpec -> String

showList :: [DepthSpec] -> ShowS

Eq DepthSpec 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: DepthSpec -> DepthSpec -> Bool

(/=) :: DepthSpec -> DepthSpec -> Bool

data NormalSign #

Instances

Instances details
Show NormalSign 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> NormalSign -> ShowS

show :: NormalSign -> String

showList :: [NormalSign] -> ShowS

Eq NormalSign 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: NormalSign -> NormalSign -> Bool

(/=) :: NormalSign -> NormalSign -> Bool

data StorageFormat #

Instances

Instances details
Show StorageFormat 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> StorageFormat -> ShowS

show :: StorageFormat -> String

showList :: [StorageFormat] -> ShowS

Eq StorageFormat 
Instance details

Defined in Hledger.Data.Types

data WhichDate #

Constructors

PrimaryDate 
SecondaryDate 

Instances

Instances details
Show WhichDate 
Instance details

Defined in Hledger.Data.Types

Methods

showsPrec :: Int -> WhichDate -> ShowS

show :: WhichDate -> String

showList :: [WhichDate] -> ShowS

Eq WhichDate 
Instance details

Defined in Hledger.Data.Types

Methods

(==) :: WhichDate -> WhichDate -> Bool

(/=) :: WhichDate -> WhichDate -> Bool

isDecimalMark :: Char -> Bool #

type DateTag = (TagName, Day) #

type HiddenTag = Tag #

type MonthWeek = Int #

type Payee = Text #

type Quantity = Decimal #

type Tag = (TagName, TagValue) #

type TagName = Text #

type TagValue = Text #

type YearDay = Int #

type YearWeek = Int #

numDigitsInt :: Integral a => Int -> a #

numDigitsInteger :: Integer -> Int #

colorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder #

amountIsZero :: Amount -> Bool #

cshowAmount :: Amount -> String #

eur :: DecimalRaw Integer -> Amount #

gbp :: DecimalRaw Integer -> Amount #

maAddAmounts :: Foldable t => MixedAmount -> t Amount -> MixedAmount #

maSum :: Foldable t => t MixedAmount -> MixedAmount #

mixed :: Foldable t => t Amount -> MixedAmount #

showAmount :: Amount -> String #

showAmountDebug :: Amount -> String #

showMixedAmountElided :: Int -> Bool -> MixedAmount -> String #

usd :: DecimalRaw Integer -> Amount #

charWidth :: Char -> Int #

chomp :: String -> String #

unPos :: Pos -> Int #

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

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

data DependencyType #

Constructors

AllSucceed 
AllFinish 

Instances

Instances details
Read DependencyType 
Instance details

Defined in Test.Tasty.Core

Methods

readsPrec :: Int -> ReadS DependencyType

readList :: ReadS [DependencyType]

readPrec :: ReadPrec DependencyType

readListPrec :: ReadPrec [DependencyType]

Show DependencyType 
Instance details

Defined in Test.Tasty.Core

Methods

showsPrec :: Int -> DependencyType -> ShowS

show :: DependencyType -> String

showList :: [DependencyType] -> ShowS

Eq DependencyType 
Instance details

Defined in Test.Tasty.Core

type TestName = String #

data InputOpts #

Constructors

InputOpts 

Fields

Instances

Instances details
Show InputOpts 
Instance details

Defined in Hledger.Read.InputOptions

Methods

showsPrec :: Int -> InputOpts -> ShowS

show :: InputOpts -> String

showList :: [InputOpts] -> ShowS

HasBalancingOpts InputOpts 
Instance details

Defined in Hledger.Read.InputOptions

HasInputOpts InputOpts 
Instance details

Defined in Hledger.Read.InputOptions

Methods

inputOpts :: Lens' InputOpts InputOpts #

aliases :: Lens' InputOpts [String] #

anon__ :: Lens' InputOpts Bool #

auto__ :: Lens' InputOpts Bool #

balancingopts :: Lens' InputOpts BalancingOpts #

defer :: Lens' InputOpts Bool #

forecast :: Lens' InputOpts (Maybe DateSpan) #

infer_costs :: Lens' InputOpts Bool #

infer_equity :: Lens' InputOpts Bool #

ioDay :: Lens' InputOpts Day #

mformat :: Lens' InputOpts (Maybe StorageFormat) #

mrules_file :: Lens' InputOpts (Maybe FilePath) #

new__ :: Lens' InputOpts Bool #

new_save :: Lens' InputOpts Bool #

pivot :: Lens' InputOpts String #

posting_account_tags :: Lens' InputOpts Bool #

reportspan :: Lens' InputOpts DateSpan #

strict :: Lens' InputOpts Bool #

verbose_tags :: Lens' InputOpts Bool #

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

filterAccounts :: (Account -> Bool) -> Account -> [Account] #

showAccounts :: Account -> String #

defaultBaseConversionAccount :: IsString a => a #

currencies :: [([Char], CurrencyCode, CurrencySymbol)] #

currencyCodeToSymbol :: CurrencyCode -> Maybe CurrencySymbol #

currencySymbolToCode :: CurrencySymbol -> Maybe CurrencyCode #

makePostingErrorExcerpt :: Posting -> (Posting -> Transaction -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) #

type ErroringJournalParser (m :: Type -> Type) a = StateT Journal (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m)) a #

type JournalParser (m :: Type -> Type) a = StateT Journal (ParsecT HledgerParseErrorData Text m) a #

journalDbg :: Journal -> String #

journalTransactionsSimilarTo :: Journal -> Text -> Query -> SimilarityScore -> Int -> [(DateWeightedSimilarityScore, Age, SimilarityScore, Transaction)] #

readJsonFile :: FromJSON a => FilePath -> IO a #

toJsonText :: ToJSON a => a -> Text #

writeJsonFile :: ToJSON a => FilePath -> a -> IO () #

firstMonthOfQuarter :: Num a => a -> a #

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

quarterContainingMonth :: Integral a => a -> a #

hasAmount :: Posting -> Bool #

isReal :: Posting -> Bool #

isVirtual :: Posting -> Bool #

postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int) #

postingsAsLines :: Bool -> [Posting] -> [Text] #

showPosting :: Posting -> String #

appendopts :: [(String, String)] -> RawOpts -> RawOpts #

boolopt :: String -> RawOpts -> Bool #

choiceopt :: (String -> Maybe a) -> RawOpts -> Maybe a #

intopt :: String -> RawOpts -> Int #

listofstringopt :: String -> RawOpts -> [String] #

maybecharopt :: String -> RawOpts -> Maybe Char #

maybeintopt :: String -> RawOpts -> Maybe Int #

maybeposintopt :: String -> RawOpts -> Maybe Int #

maybestringopt :: String -> RawOpts -> Maybe String #

maybeynaopt :: String -> RawOpts -> Maybe YNA #

maybeynopt :: String -> RawOpts -> Maybe Bool #

mkRawOpts :: [(String, String)] -> RawOpts #

overRawOpts :: ([(String, String)] -> [(String, String)]) -> RawOpts -> RawOpts #

posintopt :: String -> RawOpts -> Int #

setboolopt :: String -> RawOpts -> RawOpts #

setopt :: String -> String -> RawOpts -> RawOpts #

stringopt :: String -> RawOpts -> String #

toggleopt :: String -> RawOpts -> Bool #

unsetboolopt :: String -> RawOpts -> RawOpts #

data ReportItemField #

Instances

Instances details
Show ReportItemField 
Instance details

Defined in Hledger.Data.StringFormat

Methods

showsPrec :: Int -> ReportItemField -> ShowS

show :: ReportItemField -> String

showList :: [ReportItemField] -> ShowS

Eq ReportItemField 
Instance details

Defined in Hledger.Data.StringFormat

data StringFormat #

Instances

Instances details
Default StringFormat 
Instance details

Defined in Hledger.Data.StringFormat

Methods

def :: StringFormat

Show StringFormat 
Instance details

Defined in Hledger.Data.StringFormat

Methods

showsPrec :: Int -> StringFormat -> ShowS

show :: StringFormat -> String

showList :: [StringFormat] -> ShowS

Eq StringFormat 
Instance details

Defined in Hledger.Data.StringFormat

Methods

(==) :: StringFormat -> StringFormat -> Bool

(/=) :: StringFormat -> StringFormat -> Bool

data StringFormatComponent #

Constructors

FormatLiteral Text 
FormatField Bool (Maybe Int) (Maybe Int) ReportItemField 

Instances

Instances details
Show StringFormatComponent 
Instance details

Defined in Hledger.Data.StringFormat

Methods

showsPrec :: Int -> StringFormatComponent -> ShowS

show :: StringFormatComponent -> String

showList :: [StringFormatComponent] -> ShowS

Eq StringFormatComponent 
Instance details

Defined in Hledger.Data.StringFormat

partitionAndCheckConversionPostings :: Bool -> [AccountName] -> [IdxPosting] -> Either Text ([(IdxPosting, IdxPosting)], ([IdxPosting], [IdxPosting])) #

data ValuationType #

Instances

Instances details
Show ValuationType 
Instance details

Defined in Hledger.Data.Valuation

Methods

showsPrec :: Int -> ValuationType -> ShowS

show :: ValuationType -> String

showList :: [ValuationType] -> ShowS

Eq ValuationType 
Instance details

Defined in Hledger.Data.Valuation

data ConversionOp #

Constructors

NoConversionOp 
ToCost 

Instances

Instances details
Show ConversionOp 
Instance details

Defined in Hledger.Data.Valuation

Methods

showsPrec :: Int -> ConversionOp -> ShowS

show :: ConversionOp -> String

showList :: [ConversionOp] -> ShowS

Eq ConversionOp 
Instance details

Defined in Hledger.Data.Valuation

Methods

(==) :: ConversionOp -> ConversionOp -> Bool

(/=) :: ConversionOp -> ConversionOp -> Bool

matchesAmount :: Query -> Amount -> Bool #

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

treeLeaves :: Tree a -> [a] #

dbg1With :: Show a => (a -> String) -> a -> a #

dbg4With :: Show a => (a -> String) -> a -> a #

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

debugLevel :: Int #

traceOrLogAtWith :: Int -> (a -> String) -> a -> a #

type RegexError = String #

uppercase :: String -> String #

traceLog :: String -> a -> a #

mkPos :: Int -> Pos #

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

queryIsDepth :: Query -> Bool #

queryIsSym :: Query -> Bool #

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

dbg7With :: Show a => (a -> String) -> a -> a #

traceAt :: Int -> String -> a -> a #

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

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

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

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

spacenonewline :: forall s (m :: Type -> Type). (Stream s, Char ~ Token s) => ParsecT HledgerParseErrorData s m Char #

emptyorcommentlinep2 :: forall (m :: Type -> Type). [Char] -> TextParser m () #

data QueryOpt #

Instances

Instances details
Show QueryOpt 
Instance details

Defined in Hledger.Query

Methods

showsPrec :: Int -> QueryOpt -> ShowS

show :: QueryOpt -> String

showList :: [QueryOpt] -> ShowS

Eq QueryOpt 
Instance details

Defined in Hledger.Query

Methods

(==) :: QueryOpt -> QueryOpt -> Bool

(/=) :: QueryOpt -> QueryOpt -> Bool

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

matchesTags :: Regexp -> Maybe Regexp -> [Tag] -> Bool #

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

parseQueryList :: Day -> [Text] -> Either String (Query, [QueryOpt]) #

queryEndDate :: Bool -> Query -> Maybe Day #

queryIsAcct :: Query -> Bool #

queryIsAmt :: Query -> Bool #

queryIsCode :: Query -> Bool #

queryIsDate :: Query -> Bool #

queryIsDate2 :: Query -> Bool #

queryIsDesc :: Query -> Bool #

queryIsNull :: Query -> Bool #

queryIsReal :: Query -> Bool #

queryIsStartDateOnly :: Bool -> Query -> Bool #

queryIsStatus :: Query -> Bool #

queryIsTag :: Query -> Bool #

queryIsType :: Query -> Bool #

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

orDieTrying :: MonadIO m => ExceptT String m a -> m a #

readJournal :: InputOpts -> Maybe FilePath -> Text -> ExceptT String IO Journal #

readJournalFilesAndLatestDates :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO (Journal, [LatestDatesForFile]) #

saveLatestDates :: LatestDates -> FilePath -> IO () #

saveLatestDatesForFiles :: [LatestDatesForFile] -> IO () #

data Reader (m :: Type -> Type) #

Constructors

Reader 

Fields

Instances

Instances details
Show (Reader m) 
Instance details

Defined in Hledger.Read.Common

Methods

showsPrec :: Int -> Reader m -> ShowS

show :: Reader m -> String

showList :: [Reader m] -> ShowS

accountaliasp :: forall (m :: Type -> Type). TextParser m AccountAlias #

accountnamep :: forall (m :: Type -> Type). TextParser m AccountName #

addAccountAlias :: MonadState Journal m => AccountAlias -> m () #

addDeclaredAccountTags :: forall (m :: Type -> Type). AccountName -> [Tag] -> JournalParser m () #

addDeclaredAccountType :: forall (m :: Type -> Type). AccountName -> AccountType -> JournalParser m () #

amountp :: forall (m :: Type -> Type). JournalParser m Amount #

amountp' :: forall (m :: Type -> Type). Bool -> JournalParser m Amount #

balanceassertionp :: forall (m :: Type -> Type). JournalParser m BalanceAssertion #

bracketeddatetagsp :: forall (m :: Type -> Type). Maybe Year -> TextParser m [(TagName, Day)] #

clearAccountAliases :: MonadState Journal m => m () #

codep :: forall (m :: Type -> Type). TextParser m Text #

commentlinetagsp :: forall (m :: Type -> Type). TextParser m [Tag] #

commoditysymbolp :: forall (m :: Type -> Type). TextParser m CommoditySymbol #

costp :: forall (m :: Type -> Type). Amount -> JournalParser m AmountCost #

datep :: forall (m :: Type -> Type). JournalParser m Day #

datetimep :: forall (m :: Type -> Type). JournalParser m LocalTime #

descriptionp :: forall (m :: Type -> Type). TextParser m Text #

doublequotedtextp :: forall (m :: Type -> Type). TextParser m Text #

emptyorcommentlinep :: forall (m :: Type -> Type). TextParser m () #

followingcommentp :: forall (m :: Type -> Type). TextParser m Text #

fromRawNumber :: RawNumber -> Maybe Integer -> Either String (Quantity, Word8, Maybe Char, Maybe DigitGroupStyle) #

getAccountAliases :: MonadState Journal m => m [AccountAlias] #

getAmountStyle :: forall (m :: Type -> Type). CommoditySymbol -> JournalParser m (Maybe AmountStyle) #

getDefaultAmountStyle :: forall (m :: Type -> Type). JournalParser m (Maybe AmountStyle) #

getParentAccount :: forall (m :: Type -> Type). JournalParser m AccountName #

getYear :: forall (m :: Type -> Type). JournalParser m (Maybe Year) #

lotcostp :: forall (m :: Type -> Type). JournalParser m () #

modifiedaccountnamep :: forall (m :: Type -> Type). JournalParser m AccountName #

multilinecommentp :: forall (m :: Type -> Type). TextParser m () #

noncommenttext1p :: forall (m :: Type -> Type). TextParser m Text #

noncommenttextp :: forall (m :: Type -> Type). TextParser m Text #

numberp :: forall (m :: Type -> Type). Maybe AmountStyle -> TextParser m (Quantity, Word8, Maybe Char, Maybe DigitGroupStyle) #

parseamount' :: String -> Amount #

popParentAccount :: forall (m :: Type -> Type). JournalParser m () #

postingcommentp :: forall (m :: Type -> Type). Maybe Year -> TextParser m (Text, [Tag], Maybe Day, Maybe Day) #

pushParentAccount :: forall (m :: Type -> Type). AccountName -> JournalParser m () #

rawOptsToInputOpts :: Day -> Bool -> Bool -> RawOpts -> InputOpts #

rawnumberp :: forall (m :: Type -> Type). TextParser m (Either AmbiguousNumber RawNumber) #

secondarydatep :: forall (m :: Type -> Type). Day -> TextParser m Day #

setDefaultCommodityAndStyle :: forall (m :: Type -> Type). (CommoditySymbol, AmountStyle) -> JournalParser m () #

setYear :: forall (m :: Type -> Type). Year -> JournalParser m () #

singlespacednoncommenttext1p :: forall (m :: Type -> Type). TextParser m Text #

singlespacedtext1p :: forall (m :: Type -> Type). TextParser m Text #

singlespacedtextsatisfying1p :: forall (m :: Type -> Type). (Char -> Bool) -> TextParser m Text #

singlespacep :: forall (m :: Type -> Type). TextParser m () #

spaceandamountormissingp :: forall (m :: Type -> Type). JournalParser m MixedAmount #

statusp :: forall (m :: Type -> Type). TextParser m Status #

transactioncommentp :: forall (m :: Type -> Type). TextParser m (Text, [Tag]) #

findReader :: forall (m :: Type -> Type). MonadIO m => Maybe StorageFormat -> Maybe FilePath -> Maybe (Reader m) #

splitReaderPrefix :: PrefixedFilePath -> (Maybe StorageFormat, FilePath) #

tmpostingrulep :: forall (m :: Type -> Type). Maybe Year -> JournalParser m TMPostingRule #

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

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

triDate :: (a, Transaction, c, d, e, f) -> Day #

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

data AccountListMode #

Constructors

ALFlat 
ALTree 

Instances

Instances details
Default AccountListMode 
Instance details

Defined in Hledger.Reports.ReportOptions

Show AccountListMode 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> AccountListMode -> ShowS

show :: AccountListMode -> String

showList :: [AccountListMode] -> ShowS

Eq AccountListMode 
Instance details

Defined in Hledger.Reports.ReportOptions

data SortField #

Constructors

AbsAmount' Bool 
Account' Bool 
Amount' Bool 
Date' Bool 
Description' Bool 

Instances

Instances details
Show SortField 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> SortField -> ShowS

show :: SortField -> String

showList :: [SortField] -> ShowS

Eq SortField 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

(==) :: SortField -> SortField -> Bool

(/=) :: SortField -> SortField -> Bool

data BalanceAccumulation #

Instances

Instances details
Default BalanceAccumulation 
Instance details

Defined in Hledger.Reports.ReportOptions

Show BalanceAccumulation 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> BalanceAccumulation -> ShowS

show :: BalanceAccumulation -> String

showList :: [BalanceAccumulation] -> ShowS

Eq BalanceAccumulation 
Instance details

Defined in Hledger.Reports.ReportOptions

data BalanceCalculation #

Instances

Instances details
Default BalanceCalculation 
Instance details

Defined in Hledger.Reports.ReportOptions

Show BalanceCalculation 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> BalanceCalculation -> ShowS

show :: BalanceCalculation -> String

showList :: [BalanceCalculation] -> ShowS

Eq BalanceCalculation 
Instance details

Defined in Hledger.Reports.ReportOptions

class HasReportOptsNoUpdate a => HasReportOpts a where #

Minimal complete definition

Nothing

Methods

reportOpts :: ReportableLens' a ReportOpts #

period :: ReportableLens' a Period #

statuses :: ReportableLens' a [Status] #

depth :: ReportableLens' a DepthSpec #

date2 :: ReportableLens' a Bool #

real :: ReportableLens' a Bool #

querystring :: ReportableLens' a [Text] #

Instances

Instances details
HasReportOpts CliOpts Source # 
Instance details

Defined in Hledger.Cli.CliOptions

Methods

reportOpts :: ReportableLens' CliOpts ReportOpts #

period :: ReportableLens' CliOpts Period #

statuses :: ReportableLens' CliOpts [Status] #

depth :: ReportableLens' CliOpts DepthSpec #

date2 :: ReportableLens' CliOpts Bool #

real :: ReportableLens' CliOpts Bool #

querystring :: ReportableLens' CliOpts [Text] #

HasReportOpts ReportOpts 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportOpts ReportOpts #

period :: ReportableLens' ReportOpts Period #

statuses :: ReportableLens' ReportOpts [Status] #

depth :: ReportableLens' ReportOpts DepthSpec #

date2 :: ReportableLens' ReportOpts Bool #

real :: ReportableLens' ReportOpts Bool #

querystring :: ReportableLens' ReportOpts [Text] #

HasReportOpts ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportSpec ReportOpts #

period :: ReportableLens' ReportSpec Period #

statuses :: ReportableLens' ReportSpec [Status] #

depth :: ReportableLens' ReportSpec DepthSpec #

date2 :: ReportableLens' ReportSpec Bool #

real :: ReportableLens' ReportSpec Bool #

querystring :: ReportableLens' ReportSpec [Text] #

class HasReportSpec c where #

Minimal complete definition

reportSpec

Methods

reportSpec :: Lens' c ReportSpec #

rsDay :: Lens' c Day #

rsQuery :: Lens' c Query #

rsQueryOpts :: Lens' c [QueryOpt] #

rsReportOpts :: Lens' c ReportOpts #

data Layout #

Instances

Instances details
Show Layout 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> Layout -> ShowS

show :: Layout -> String

showList :: [Layout] -> ShowS

Eq Layout 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

(==) :: Layout -> Layout -> Bool

(/=) :: Layout -> Layout -> Bool

data ReportSpec #

Instances

Instances details
Default ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

def :: ReportSpec

Show ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

showsPrec :: Int -> ReportSpec -> ShowS

show :: ReportSpec -> String

showList :: [ReportSpec] -> ShowS

HasReportOpts ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOpts :: ReportableLens' ReportSpec ReportOpts #

period :: ReportableLens' ReportSpec Period #

statuses :: ReportableLens' ReportSpec [Status] #

depth :: ReportableLens' ReportSpec DepthSpec #

date2 :: ReportableLens' ReportSpec Bool #

real :: ReportableLens' ReportSpec Bool #

querystring :: ReportableLens' ReportSpec [Text] #

HasReportOptsNoUpdate ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

Methods

reportOptsNoUpdate :: Lens' ReportSpec ReportOpts #

accountlistmode :: Lens' ReportSpec AccountListMode #

average :: Lens' ReportSpec Bool #

balance_base_url :: Lens' ReportSpec (Maybe Text) #

balanceaccum :: Lens' ReportSpec BalanceAccumulation #

balancecalc :: Lens' ReportSpec BalanceCalculation #

budgetpat :: Lens' ReportSpec (Maybe Text) #

color__ :: Lens' ReportSpec Bool #

conversionop :: Lens' ReportSpec (Maybe ConversionOp) #

date2NoUpdate :: Lens' ReportSpec Bool #

declared :: Lens' ReportSpec Bool #

depthNoUpdate :: Lens' ReportSpec DepthSpec #

drop__ :: Lens' ReportSpec Int #

empty__ :: Lens' ReportSpec Bool #

format :: Lens' ReportSpec StringFormat #

infer_prices :: Lens' ReportSpec Bool #

interval :: Lens' ReportSpec Interval #

invert :: Lens' ReportSpec Bool #

layout :: Lens' ReportSpec Layout #

no_elide :: Lens' ReportSpec Bool #

no_total :: Lens' ReportSpec Bool #

normalbalance :: Lens' ReportSpec (Maybe NormalSign) #

percent :: Lens' ReportSpec Bool #

periodNoUpdate :: Lens' ReportSpec Period #

pretty :: Lens' ReportSpec Bool #

querystringNoUpdate :: Lens' ReportSpec [Text] #

realNoUpdate :: Lens' ReportSpec Bool #

related :: Lens' ReportSpec Bool #

row_total :: Lens' ReportSpec Bool #

show_costs :: Lens' ReportSpec Bool #

sort_amount :: Lens' ReportSpec Bool #

sortspec :: Lens' ReportSpec SortSpec #

statusesNoUpdate :: Lens' ReportSpec [Status] #

summary_only :: Lens' ReportSpec Bool #

transpose__ :: Lens' ReportSpec Bool #

txn_dates :: Lens' ReportSpec Bool #

value :: Lens' ReportSpec (Maybe ValuationType) #

HasReportSpec ReportSpec 
Instance details

Defined in Hledger.Reports.ReportOptions

flat_ :: ReportOpts -> Bool #

overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t #

setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t #

simplifyStatuses :: Ord a => [a] -> [a] #

tree_ :: ReportOpts -> Bool #

data CompoundPeriodicReport a b #

Instances

Instances details
Functor (CompoundPeriodicReport a) 
Instance details

Defined in Hledger.Reports.ReportTypes

(ToJSON b, ToJSON a) => ToJSON (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Generic (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (CompoundPeriodicReport a b) = D1 ('MetaData "CompoundPeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "CompoundPeriodicReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cbrTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cbrDates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DateSpan])) :*: (S1 ('MetaSel ('Just "cbrSubreports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, PeriodicReport a b, Bool)]) :*: S1 ('MetaSel ('Just "cbrTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PeriodicReportRow () b)))))
(Show a, Show b) => Show (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

showsPrec :: Int -> CompoundPeriodicReport a b -> ShowS

show :: CompoundPeriodicReport a b -> String

showList :: [CompoundPeriodicReport a b] -> ShowS

HasAmounts b => HasAmounts (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (CompoundPeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (CompoundPeriodicReport a b) = D1 ('MetaData "CompoundPeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "CompoundPeriodicReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cbrTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "cbrDates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DateSpan])) :*: (S1 ('MetaSel ('Just "cbrSubreports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, PeriodicReport a b, Bool)]) :*: S1 ('MetaSel ('Just "cbrTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PeriodicReportRow () b)))))

data DisplayName #

Constructors

DisplayName 

Fields

Instances

Instances details
ToJSON DisplayName 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

toJSON :: DisplayName -> Value

toEncoding :: DisplayName -> Encoding

toJSONList :: [DisplayName] -> Value

toEncodingList :: [DisplayName] -> Encoding

omitField :: DisplayName -> Bool

Show DisplayName 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

showsPrec :: Int -> DisplayName -> ShowS

show :: DisplayName -> String

showList :: [DisplayName] -> ShowS

Eq DisplayName 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

(==) :: DisplayName -> DisplayName -> Bool

(/=) :: DisplayName -> DisplayName -> Bool

Ord DisplayName 
Instance details

Defined in Hledger.Reports.ReportTypes

type Percentage = Decimal #

data PeriodicReport a b #

Instances

Instances details
Bifunctor PeriodicReport 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

bimap :: (a -> b) -> (c -> d) -> PeriodicReport a c -> PeriodicReport b d

first :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c

second :: (b -> c) -> PeriodicReport a b -> PeriodicReport a c

Functor (PeriodicReport a) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

fmap :: (a0 -> b) -> PeriodicReport a a0 -> PeriodicReport a b #

(<$) :: a0 -> PeriodicReport a b -> PeriodicReport a a0 #

(ToJSON a, ToJSON b) => ToJSON (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

toJSON :: PeriodicReport a b -> Value

toEncoding :: PeriodicReport a b -> Encoding

toJSONList :: [PeriodicReport a b] -> Value

toEncodingList :: [PeriodicReport a b] -> Encoding

omitField :: PeriodicReport a b -> Bool

Generic (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReport a b) = D1 ('MetaData "PeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicReport" 'PrefixI 'True) (S1 ('MetaSel ('Just "prDates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DateSpan]) :*: (S1 ('MetaSel ('Just "prRows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PeriodicReportRow a b]) :*: S1 ('MetaSel ('Just "prTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PeriodicReportRow () b)))))

Methods

from :: PeriodicReport a b -> Rep (PeriodicReport a b) x

to :: Rep (PeriodicReport a b) x -> PeriodicReport a b

(Show a, Show b) => Show (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

showsPrec :: Int -> PeriodicReport a b -> ShowS

show :: PeriodicReport a b -> String

showList :: [PeriodicReport a b] -> ShowS

HasAmounts b => HasAmounts (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

HasAmounts b => HasAmounts (Text, PeriodicReport a b, Bool) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

styleAmounts :: Map CommoditySymbol AmountStyle -> (Text, PeriodicReport a b, Bool) -> (Text, PeriodicReport a b, Bool) #

type Rep (PeriodicReport a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReport a b) = D1 ('MetaData "PeriodicReport" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicReport" 'PrefixI 'True) (S1 ('MetaSel ('Just "prDates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DateSpan]) :*: (S1 ('MetaSel ('Just "prRows") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PeriodicReportRow a b]) :*: S1 ('MetaSel ('Just "prTotals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PeriodicReportRow () b)))))

data PeriodicReportRow a b #

Constructors

PeriodicReportRow 

Fields

Instances

Instances details
Bifunctor PeriodicReportRow 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

bimap :: (a -> b) -> (c -> d) -> PeriodicReportRow a c -> PeriodicReportRow b d

first :: (a -> b) -> PeriodicReportRow a c -> PeriodicReportRow b c

second :: (b -> c) -> PeriodicReportRow a b -> PeriodicReportRow a c

Functor (PeriodicReportRow a) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

fmap :: (a0 -> b) -> PeriodicReportRow a a0 -> PeriodicReportRow a b #

(<$) :: a0 -> PeriodicReportRow a b -> PeriodicReportRow a a0 #

(ToJSON b, ToJSON a) => ToJSON (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

toJSON :: PeriodicReportRow a b -> Value

toEncoding :: PeriodicReportRow a b -> Encoding

toJSONList :: [PeriodicReportRow a b] -> Value

toEncodingList :: [PeriodicReportRow a b] -> Encoding

omitField :: PeriodicReportRow a b -> Bool

Semigroup b => Semigroup (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

(<>) :: PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b

sconcat :: NonEmpty (PeriodicReportRow a b) -> PeriodicReportRow a b

stimes :: Integral b0 => b0 -> PeriodicReportRow a b -> PeriodicReportRow a b

Generic (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Associated Types

type Rep (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReportRow a b) = D1 ('MetaData "PeriodicReportRow" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicReportRow" 'PrefixI 'True) ((S1 ('MetaSel ('Just "prrName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "prrAmounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [b])) :*: (S1 ('MetaSel ('Just "prrTotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Just "prrAverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

Methods

from :: PeriodicReportRow a b -> Rep (PeriodicReportRow a b) x

to :: Rep (PeriodicReportRow a b) x -> PeriodicReportRow a b

(Show a, Show b) => Show (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

Methods

showsPrec :: Int -> PeriodicReportRow a b -> ShowS

show :: PeriodicReportRow a b -> String

showList :: [PeriodicReportRow a b] -> ShowS

HasAmounts b => HasAmounts (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReportRow a b) 
Instance details

Defined in Hledger.Reports.ReportTypes

type Rep (PeriodicReportRow a b) = D1 ('MetaData "PeriodicReportRow" "Hledger.Reports.ReportTypes" "hledger-lib-1.41-LrpAgJIor4wKLtLkQw1YxH" 'False) (C1 ('MetaCons "PeriodicReportRow" 'PrefixI 'True) ((S1 ('MetaSel ('Just "prrName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "prrAmounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [b])) :*: (S1 ('MetaSel ('Just "prrTotal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Just "prrAverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))))

prMapName :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c #

prrAdd :: Semigroup b => PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b #

curry2 :: ((a, b) -> c) -> a -> b -> c #

curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d #

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

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

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

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

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

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

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

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

makeHledgerClassyLenses :: Name -> DecsQ #

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

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

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

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

multicol :: Int -> [String] -> String #

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

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

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

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

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

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

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

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

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

uncurry2 :: (a -> b -> c) -> (a, b) -> c #

uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d #

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

data GhcDebugMode #

Instances

Instances details
Show GhcDebugMode 
Instance details

Defined in Hledger.Utils.Debug

Methods

showsPrec :: Int -> GhcDebugMode -> ShowS

show :: GhcDebugMode -> String

showList :: [GhcDebugMode] -> ShowS

Eq GhcDebugMode 
Instance details

Defined in Hledger.Utils.Debug

Methods

(==) :: GhcDebugMode -> GhcDebugMode -> Bool

(/=) :: GhcDebugMode -> GhcDebugMode -> Bool

Ord GhcDebugMode 
Instance details

Defined in Hledger.Utils.Debug

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

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

dbg0With :: (a -> String) -> a -> a #

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

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

dbg2With :: Show a => (a -> String) -> a -> a #

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

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

dbg3With :: Show a => (a -> String) -> a -> a #

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

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

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

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

dbg5With :: Show a => (a -> String) -> a -> a #

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

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

dbg6With :: Show a => (a -> String) -> a -> a #

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

dbg8With :: Show a => (a -> String) -> a -> a #

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

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

dbg9With :: Show a => (a -> String) -> a -> a #

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

lbl_ :: String -> String -> String -> String #

progName :: String #

ptrace :: Show a => a -> a #

ptraceAt :: Show a => Int -> String -> a -> a #

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

ptraceLogAt :: Show a => Int -> String -> a -> a #

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

ptraceOrLogAt :: Show a => Int -> String -> a -> a #

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

traceAtWith :: Int -> (a -> String) -> a -> a #

traceLogAt :: Int -> String -> a -> a #

traceLogAtIO :: MonadIO m => Int -> String -> m () #

traceLogAtWith :: Int -> (a -> String) -> a -> a #

traceLogIO :: MonadIO m => String -> m () #

traceLogWith :: (a -> String) -> a -> a #

traceOrLog :: String -> a -> a #

traceOrLogAt :: Int -> String -> a -> a #

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

withGhcDebug' :: a -> a #

data YNA #

Constructors

Yes 
No 
Auto 

Instances

Instances details
Show YNA 
Instance details

Defined in Hledger.Utils.IO

Methods

showsPrec :: Int -> YNA -> ShowS

show :: YNA -> String

showList :: [YNA] -> ShowS

Eq YNA 
Instance details

Defined in Hledger.Utils.IO

Methods

(==) :: YNA -> YNA -> Bool

(/=) :: YNA -> YNA -> Bool

bgColorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder #

black' :: String -> String #

blue' :: String -> String #

bold' :: String -> String #

brightBlack' :: String -> String #

brightBlue' :: String -> String #

brightCyan' :: String -> String #

brightGreen' :: String -> String #

brightMagenta' :: String -> String #

brightRed' :: String -> String #

brightWhite' :: String -> String #

brightYellow' :: String -> String #

cyan' :: String -> String #

faint' :: String -> String #

getOpt :: [String] -> IO (Maybe String) #

green' :: String -> String #

magenta' :: String -> String #

parseYN :: String -> Bool #

parseYNA :: String -> YNA #

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

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

progArgs :: [String] #

pshow' :: Show a => a -> String #

red' :: String -> String #

rgb' :: Float -> Float -> Float -> String -> String #

runPager :: String -> IO () #

terminalBgColor :: Maybe (RGB Float) #

terminalFgColor :: Maybe (RGB Float) #

usageError :: String -> a #

warn :: String -> a -> a #

white' :: String -> String #

yellow' :: String -> String #

data FinalParseError' e #

Instances

Instances details
Monoid (FinalParseError' e) 
Instance details

Defined in Hledger.Utils.Parse

Semigroup (FinalParseError' e) 
Instance details

Defined in Hledger.Utils.Parse

Show e => Show (FinalParseError' e) 
Instance details

Defined in Hledger.Utils.Parse

Methods

showsPrec :: Int -> FinalParseError' e -> ShowS

show :: FinalParseError' e -> String

showList :: [FinalParseError' e] -> ShowS

data FinalParseErrorBundle' e #

Instances

Instances details
Show e => Show (FinalParseErrorBundle' e) 
Instance details

Defined in Hledger.Utils.Parse

Methods

showsPrec :: Int -> FinalParseErrorBundle' e -> ShowS

show :: FinalParseErrorBundle' e -> String

showList :: [FinalParseErrorBundle' e] -> ShowS

type SimpleStringParser a = Parsec HledgerParseErrorData String a #

choiceInState :: forall s (m :: Type -> Type) a. [StateT s (ParsecT HledgerParseErrorData Text m) a] -> StateT s (ParsecT HledgerParseErrorData Text m) a #

dbgparse :: forall (m :: Type -> Type). Int -> String -> TextParser m () #

eolof :: forall (m :: Type -> Type). TextParser m () #

excerpt_ :: MonadParsec HledgerParseErrorData Text m => m a -> m SourceExcerpt #

finalCustomFailure :: (MonadParsec e s m, MonadError (FinalParseError' e) m) => e -> m a #

finalError :: ParseError Text e -> FinalParseError' e #

finalFail :: (MonadParsec e s m, MonadError (FinalParseError' e) m) => String -> m a #

finalFancyFailure :: (MonadParsec e s m, MonadError (FinalParseError' e) m) => Set (ErrorFancy e) -> m a #

fromparse :: (Show t, Show (Token t), Show e) => Either (ParseErrorBundle t e) a -> a #

isNewline :: Char -> Bool #

nonspace :: forall (m :: Type -> Type). TextParser m Char #

parseErrorAtRegion :: Int -> Int -> String -> HledgerParseErrorData #

parseIncludeFile :: forall (m :: Type -> Type) st a. Monad m => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m)) a -> st -> FilePath -> Text -> StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError m)) a #

parseWithState :: Monad m => st -> StateT st (ParsecT HledgerParseErrorData Text m) a -> Text -> m (Either HledgerParseErrors a) #

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

parseerror :: (Show t, Show (Token t), Show e) => ParseErrorBundle t e -> a #

parsewithString :: Parsec e String a -> String -> Either (ParseErrorBundle String e) a #

reparseExcerpt :: forall (m :: Type -> Type) a. Monad m => SourceExcerpt -> ParsecT HledgerParseErrorData Text m a -> ParsecT HledgerParseErrorData Text m a #

restofline :: forall (m :: Type -> Type). TextParser m String #

showDateParseError :: (Show t, Show (Token t), Show e) => ParseErrorBundle t e -> String #

skipNonNewlineSpaces' :: forall s (m :: Type -> Type). (Stream s, Token s ~ Char) => ParsecT HledgerParseErrorData s m Bool #

skipNonNewlineSpaces1 :: forall s (m :: Type -> Type). (Stream s, Token s ~ Char) => ParsecT HledgerParseErrorData s m () #

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

traceOrLogParse :: forall (m :: Type -> Type). String -> TextParser m () #

regexMatch :: Regexp -> String -> Bool #

regexMatchText :: Regexp -> Text -> Bool #

regexReplace :: Regexp -> Replacement -> String -> Either RegexError String #

regexReplaceAllBy :: Regexp -> (String -> String) -> String -> String #

capitalise :: String -> String #

chomp1 :: String -> String #

elideLeft :: Int -> String -> String #

elideRight :: Int -> String -> String #

lowercase :: String -> String #

lstrip :: String -> String #

quoteForCommandLine :: String -> String #

quoteIfNeeded :: String -> String #

rstrip :: String -> String #

singleQuoteIfNeeded :: String -> String #

singleline :: String -> String #

strWidth :: String -> Int #

strWidthAnsi :: String -> Int #

strip1By :: (Char -> Bool) -> String -> String #

strip1Char :: Char -> Char -> String -> String #

stripAnsi :: String -> String #

stripBy :: (Char -> Bool) -> String -> String #

stripbrackets :: String -> String #

takeWidth :: Int -> String -> String #

underline :: String -> String #

unwords' :: [String] -> String #

assertLeft :: (HasCallStack, Eq b, Show b) => Either a b -> Assertion #

assertParse :: (HasCallStack, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> Assertion #

assertParseE :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> Assertion #

assertParseEq :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> a -> Assertion #

assertParseEqE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> a -> Assertion #

assertParseEqOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (a -> b) -> b -> Assertion #

assertParseError :: (HasCallStack, Eq a, Show a, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> String -> Assertion #

assertParseErrorE :: (Default st, Eq a, Show a, HasCallStack) => StateT st (ParsecT HledgerParseErrorData Text (ExceptT FinalParseError IO)) a -> Text -> String -> Assertion #

assertParseStateOn :: (HasCallStack, Eq b, Show b, Default st) => StateT st (ParsecT HledgerParseErrorData Text IO) a -> Text -> (st -> b) -> b -> Assertion #

assertRight :: (HasCallStack, Eq a, Show a) => Either a b -> Assertion #

traceIO :: String -> IO () #

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

adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree #

askOption :: IsOption v => (v -> TestTree) -> TestTree #

defaultIngredients :: [Ingredient] #

localOption :: IsOption v => v -> TestTree -> TestTree #

withResource :: IO a -> (a -> IO ()) -> (IO a -> TestTree) -> TestTree #

defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO () #

includingOptions :: [OptionDescription] -> Ingredient #

mkTimeout :: Integer -> Timeout #

(@=?) :: (Eq a, Show a, HasCallStack) => a -> a -> Assertion #

(@?) :: (AssertionPredicable t, HasCallStack) => t -> String -> Assertion #

(@?=) :: (Eq a, Show a, HasCallStack) => a -> a -> Assertion #

assertBool :: HasCallStack => String -> Bool -> Assertion #

assertEqual :: (Eq a, Show a, HasCallStack) => String -> a -> a -> Assertion #

assertFailure :: HasCallStack => String -> IO a #

testCaseSteps :: TestName -> ((String -> IO ()) -> Assertion) -> TestTree #

runExceptT :: ExceptT e m a -> m (Either e a) #

data Timeout #

Constructors

Timeout Integer String 
NoTimeout 

Instances

Instances details
Show Timeout 
Instance details

Defined in Test.Tasty.Options.Core

Methods

showsPrec :: Int -> Timeout -> ShowS

show :: Timeout -> String

showList :: [Timeout] -> ShowS

Eq Timeout 
Instance details

Defined in Test.Tasty.Options.Core

Methods

(==) :: Timeout -> Timeout -> Bool

(/=) :: Timeout -> Timeout -> Bool

Ord Timeout 
Instance details

Defined in Test.Tasty.Options.Core

Methods

compare :: Timeout -> Timeout -> Ordering #

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

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

(>) :: Timeout -> Timeout -> Bool #

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

max :: Timeout -> Timeout -> Timeout #

min :: Timeout -> Timeout -> Timeout #

IsOption Timeout 
Instance details

Defined in Test.Tasty.Options.Core

Methods

defaultValue :: Timeout

parseValue :: String -> Maybe Timeout

optionName :: Tagged Timeout String

optionHelp :: Tagged Timeout String

showDefaultValue :: Timeout -> Maybe String

optionCLParser :: Parser Timeout

type Assertion = IO () #

class AssertionPredicable t where #

Methods

assertionPredicate :: t -> IO Bool #

Instances

Instances details
AssertionPredicable Bool 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assertionPredicate :: Bool -> IO Bool #

AssertionPredicable t => AssertionPredicable (IO t) 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assertionPredicate :: IO t -> IO Bool #

type AssertionPredicate = IO Bool #

data HUnitFailure #

Constructors

HUnitFailure (Maybe SrcLoc) String 

Instances

Instances details
Exception HUnitFailure 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

toException :: HUnitFailure -> SomeException

fromException :: SomeException -> Maybe HUnitFailure

displayException :: HUnitFailure -> String

backtraceDesired :: HUnitFailure -> Bool

Show HUnitFailure 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

showsPrec :: Int -> HUnitFailure -> ShowS

show :: HUnitFailure -> String

showList :: [HUnitFailure] -> ShowS

Eq HUnitFailure 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

(==) :: HUnitFailure -> HUnitFailure -> Bool

(/=) :: HUnitFailure -> HUnitFailure -> Bool

trace :: String -> a -> a #

System.Console.CmdArgs.Explicit

process :: Mode a -> [String] -> Either String a #

type Help = String #

flagNone :: [Name] -> (a -> a) -> Help -> Flag a #

flagReq :: [Name] -> Update a -> FlagHelp -> Help -> Flag a #

flagOpt :: String -> [Name] -> Update a -> FlagHelp -> Help -> Flag a #

data Group a #

Constructors

Group 

Fields

Instances

Instances details
Functor Group 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

fmap :: (a -> b) -> Group a -> Group b #

(<$) :: a -> Group b -> Group a #

Packer a => Packer (Group a) 
Instance details

Defined in System.Console.CmdArgs.Helper

Methods

pack :: Group a -> Pack

unpack :: Pack -> Group a

Monoid (Group a) 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

mempty :: Group a

mappend :: Group a -> Group a -> Group a

mconcat :: [Group a] -> Group a

Semigroup (Group a) 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

(<>) :: Group a -> Group a -> Group a

sconcat :: NonEmpty (Group a) -> Group a

stimes :: Integral b => b -> Group a -> Group a

Show a => Show (Group a) 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

showsPrec :: Int -> Group a -> ShowS

show :: Group a -> String

showList :: [Group a] -> ShowS

data Mode a #

Constructors

Mode 

Fields

Instances

Instances details
Remap Mode 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Mode a -> Mode b #

Packer a => Packer (Mode a) 
Instance details

Defined in System.Console.CmdArgs.Helper

Methods

pack :: Mode a -> Pack

unpack :: Pack -> Mode a

data Arg a #

Constructors

Arg 

Fields

Instances

Instances details
Remap Arg 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Arg a -> Arg b #

Packer a => Packer (Arg a) 
Instance details

Defined in System.Console.CmdArgs.Helper

Methods

pack :: Arg a -> Pack

unpack :: Pack -> Arg a

data Complete #

Constructors

CompleteValue String 
CompleteFile String FilePath 
CompleteDir String FilePath 

Instances

Instances details
Show Complete 
Instance details

Defined in System.Console.CmdArgs.Explicit.Complete

Methods

showsPrec :: Int -> Complete -> ShowS

show :: Complete -> String

showList :: [Complete] -> ShowS

Eq Complete 
Instance details

Defined in System.Console.CmdArgs.Explicit.Complete

Methods

(==) :: Complete -> Complete -> Bool

(/=) :: Complete -> Complete -> Bool

Ord Complete 
Instance details

Defined in System.Console.CmdArgs.Explicit.Complete

Methods

compare :: Complete -> Complete -> Ordering #

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

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

(>) :: Complete -> Complete -> Bool #

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

max :: Complete -> Complete -> Complete #

min :: Complete -> Complete -> Complete #

mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode a #

data Flag a #

Constructors

Flag 

Instances

Instances details
Remap Flag 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Flag a -> Flag b #

Packer a => Packer (Flag a) 
Instance details

Defined in System.Console.CmdArgs.Helper

Methods

pack :: Flag a -> Pack

unpack :: Pack -> Flag a

type FlagHelp = String #

flagArg :: Update a -> FlagHelp -> Arg a #

toGroup :: [a] -> Group a #

helpText :: [String] -> HelpFormat -> Mode a -> [Text] #

data HelpFormat #

Instances

Instances details
Default HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Methods

def :: HelpFormat

Bounded HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Enum HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Read HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Methods

readsPrec :: Int -> ReadS HelpFormat

readList :: ReadS [HelpFormat]

readPrec :: ReadPrec HelpFormat

readListPrec :: ReadPrec [HelpFormat]

Show HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Methods

showsPrec :: Int -> HelpFormat -> ShowS

show :: HelpFormat -> String

showList :: [HelpFormat] -> ShowS

Eq HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

Methods

(==) :: HelpFormat -> HelpFormat -> Bool

(/=) :: HelpFormat -> HelpFormat -> Bool

Ord HelpFormat 
Instance details

Defined in System.Console.CmdArgs.Explicit.Help

expandArgsAt :: [String] -> IO [String] #

modes :: String -> a -> Help -> [Mode a] -> Mode a #

complete :: Mode a -> [String] -> (Int, Int) -> [Complete] #

joinArgs :: [String] -> String #

splitArgs :: String -> [String] #

data FlagInfo #

Constructors

FlagReq 
FlagOpt String 
FlagOptRare String 
FlagNone 

Instances

Instances details
Packer FlagInfo 
Instance details

Defined in System.Console.CmdArgs.Helper

Methods

pack :: FlagInfo -> Pack

unpack :: Pack -> FlagInfo

Show FlagInfo 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

showsPrec :: Int -> FlagInfo -> ShowS

show :: FlagInfo -> String

showList :: [FlagInfo] -> ShowS

Eq FlagInfo 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

(==) :: FlagInfo -> FlagInfo -> Bool

(/=) :: FlagInfo -> FlagInfo -> Bool

Ord FlagInfo 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

compare :: FlagInfo -> FlagInfo -> Ordering #

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

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

(>) :: FlagInfo -> FlagInfo -> Bool #

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

max :: FlagInfo -> FlagInfo -> FlagInfo #

min :: FlagInfo -> FlagInfo -> FlagInfo #

class Remap (m :: Type -> Type) where #

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> m a -> m b #

Instances

Instances details
Remap Arg 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Arg a -> Arg b #

Remap Flag 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Flag a -> Flag b #

Remap Mode 
Instance details

Defined in System.Console.CmdArgs.Explicit.Type

Methods

remap :: (a -> b) -> (b -> (a, a -> b)) -> Mode a -> Mode b #

type Update a = String -> a -> Either String a #

checkMode :: Mode a -> Maybe String #

flagBool :: [Name] -> (Bool -> a -> a) -> Help -> Flag a #

fromFlagOpt :: FlagInfo -> String #

fromGroup :: Group a -> [a] #

modeEmpty :: a -> Mode a #

modeFlags :: Mode a -> [Flag a] #

modeModes :: Mode a -> [Mode a] #

parseBool :: String -> Maybe Bool #

remap2 :: Remap m => (a -> b) -> (b -> a) -> m a -> m b #

remapUpdate :: (a -> b) -> (b -> (a, a -> b)) -> Update a -> Update b #

flagHelpFormat :: (HelpFormat -> TextFormat -> a -> a) -> Flag a #

flagHelpSimple :: (a -> a) -> Flag a #

flagNumericVersion :: (a -> a) -> Flag a #

flagVersion :: (a -> a) -> Flag a #

flagsVerbosity :: (Verbosity -> a -> a) -> [Flag a] #

processArgs :: Mode a -> IO a #

processValue :: Mode a -> [String] -> a #

processValueIO :: Mode a -> [String] -> IO a #