Safe Haskell | None |
---|---|
Language | Haskell2010 |
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:
- hledger-lib:Hledger
- The README files
- The high-level developer docs
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
- main :: IO ()
- mainmode :: [Name] -> Mode RawOpts
- argsToCliOpts :: [String] -> [String] -> IO CliOpts
- module Hledger.Cli.CliOptions
- module Hledger.Cli.Conf
- module Hledger.Cli.Commands
- module Hledger.Cli.DocFiles
- module Hledger.Cli.Utils
- module Hledger.Cli.Version
- class HasReportOptsNoUpdate c where
- 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)
- class HasInputOpts c where
- 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
- data SmartInterval
- quoteIfSpaced :: Text -> Text
- showDateSpan :: DateSpan -> Text
- showDate :: Day -> Text
- data DateSpan = DateSpan (Maybe EFDay) (Maybe EFDay)
- type Balance = MixedAmount
- data Side
- data SepFormat
- data ReportOpts = ReportOpts {
- period_ :: Period
- interval_ :: Interval
- statuses_ :: [Status]
- conversionop_ :: Maybe ConversionOp
- value_ :: Maybe ValuationType
- infer_prices_ :: Bool
- depth_ :: DepthSpec
- date2_ :: Bool
- empty_ :: Bool
- no_elide_ :: Bool
- real_ :: Bool
- format_ :: StringFormat
- balance_base_url_ :: Maybe Text
- pretty_ :: Bool
- querystring_ :: [Text]
- average_ :: Bool
- related_ :: Bool
- sortspec_ :: SortSpec
- txn_dates_ :: Bool
- balancecalc_ :: BalanceCalculation
- balanceaccum_ :: BalanceAccumulation
- budgetpat_ :: Maybe Text
- accountlistmode_ :: AccountListMode
- drop_ :: Int
- declared_ :: Bool
- row_total_ :: Bool
- no_total_ :: Bool
- summary_only_ :: Bool
- show_costs_ :: Bool
- sort_amount_ :: Bool
- percent_ :: Bool
- invert_ :: Bool
- normalbalance_ :: Maybe NormalSign
- color_ :: Bool
- transpose_ :: Bool
- layout_ :: Layout
- embedFileRelative :: FilePath -> Q Exp
- per :: Quantity -> Amount
- error' :: String -> a
- strip :: String -> String
- words' :: String -> [String]
- data RawOpts
- expandPath :: FilePath -> FilePath -> IO FilePath
- 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
- at :: Amount -> Amount -> Amount
- ghcDebugSupportedInLib :: Bool
- splitAtElement :: Eq a => a -> [a] -> [[a]]
- class Assertable t where
- data Query
- data OrdPlus
- takeEnd :: Int -> [a] -> [a]
- type HasCallStack = ?callStack :: CallStack
- data Period
- type Year = Integer
- data AmountFormat = AmountFormat {
- displayCommodity :: Bool
- displayZeroCommodity :: Bool
- displayCommodityOrder :: Maybe [CommoditySymbol]
- displayDigitGroups :: Bool
- displayForceDecimalMark :: Bool
- displayOneLine :: Bool
- displayMinWidth :: Maybe Int
- displayMaxWidth :: Maybe Int
- displayCost :: Bool
- displayColour :: Bool
- displayQuotes :: Bool
- showMixedAmountB :: AmountFormat -> MixedAmount -> WideBuilder
- showMixedAmountLinesPartsB :: AmountFormat -> MixedAmount -> [(WideBuilder, Amount)]
- unifyMixedAmount :: MixedAmount -> Maybe Amount
- data Amount = Amount {
- acommodity :: !CommoditySymbol
- aquantity :: !Quantity
- astyle :: !AmountStyle
- acost :: !(Maybe AmountCost)
- data MixedAmount
- data WideBuilder = WideBuilder {}
- type Total = MixedAmount
- amounts :: MixedAmount -> [Amount]
- nullamt :: Amount
- wbFromText :: Text -> WideBuilder
- wbToText :: WideBuilder -> Text
- wbUnpack :: WideBuilder -> String
- escapeBackslash :: Text -> Text
- escapeDoubleQuotes :: Text -> Text
- fitText :: Maybe Int -> Maybe Int -> Bool -> Bool -> Text -> Text
- formatText :: Bool -> Maybe Int -> Maybe Int -> Text -> Text
- linesPrepend :: Text -> Text -> Text
- linesPrepend2 :: Text -> Text -> Text -> Text
- readDecimal :: Text -> Integer
- stripquotes :: Text -> Text
- tests_Text :: TestTree
- textCapitalise :: Text -> Text
- textChomp :: Text -> Text
- textConcatBottomPadded :: [Text] -> Text
- textConcatTopPadded :: [Text] -> Text
- textElideRight :: Int -> Text -> Text
- textQuoteIfNeeded :: Text -> Text
- textTakeWidth :: Int -> Text -> Text
- textUnbracket :: Text -> Text
- unlinesB :: [Builder] -> Builder
- wrap :: Text -> Text -> Text -> Text
- data TestTree
- dateSpanAsPeriod :: DateSpan -> Period
- periodAsDateSpan :: Period -> DateSpan
- showPeriod :: Period -> Text
- showPeriodAbbrev :: Period -> Text
- data Interval
- = NoInterval
- | Days Int
- | Weeks Int
- | Months Int
- | Quarters Int
- | Years Int
- | NthWeekdayOfMonth Int Int
- | MonthDay Int
- | MonthAndDay Int Int
- | DaysOfWeek [Int]
- data EFDay
- type Month = Int
- type MonthDay = Int
- type Quarter = Int
- data SmartDate
- type WeekDay = Int
- fromEFDay :: EFDay -> Day
- modifyEFDay :: (Day -> Day) -> EFDay -> EFDay
- applyN :: Int -> (a -> a) -> a -> a
- type HledgerParseErrors = ParseErrorBundle Text HledgerParseErrorData
- type TextParser (m :: Type -> Type) a = ParsecT HledgerParseErrorData Text m a
- choice' :: forall (m :: Type -> Type) a. [TextParser m a] -> TextParser m a
- customErrorBundlePretty :: HledgerParseErrors -> String
- 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
- daysSpan :: [Day] -> DateSpan
- elapsedSeconds :: Fractional a => UTCTime -> UTCTime -> a
- emptydatespan :: DateSpan
- fixSmartDate :: Day -> SmartDate -> EFDay
- fixSmartDateStr :: Day -> Text -> Text
- fixSmartDateStrEither :: Day -> Text -> Either HledgerParseErrors Text
- fixSmartDateStrEither' :: Day -> Text -> Either HledgerParseErrors EFDay
- getCurrentDay :: IO Day
- getCurrentMonth :: IO Int
- getCurrentYear :: IO Integer
- groupByDateSpan :: Bool -> (a -> Day) -> [DateSpan] -> [a] -> [(DateSpan, [a])]
- intervalBoundaryBefore :: Interval -> Day -> Day
- isDateSepChar :: Char -> Bool
- latestSpanContaining :: [DateSpan] -> Day -> Maybe DateSpan
- nulldate :: Day
- nulldatespan :: DateSpan
- parsePeriodExpr :: Day -> Text -> Either HledgerParseErrors (Interval, DateSpan)
- parsePeriodExpr' :: Day -> Text -> (Interval, DateSpan)
- parsedateM :: String -> Maybe Day
- periodContainsDate :: Period -> Day -> Bool
- periodexprp :: forall (m :: Type -> Type). Day -> TextParser m (Interval, DateSpan)
- prevday :: Day -> Day
- showDateSpanAbbrev :: DateSpan -> Text
- showDateSpanDebug :: DateSpan -> String
- showEFDate :: EFDay -> Text
- smartdate :: forall (m :: Type -> Type). TextParser m SmartDate
- spanContainsDate :: DateSpan -> Day -> Bool
- spanDefaultsFrom :: DateSpan -> DateSpan -> DateSpan
- spanEnd :: DateSpan -> Maybe Day
- spanEndYear :: DateSpan -> Maybe Year
- spanExtend :: DateSpan -> DateSpan -> DateSpan
- spanIntersect :: DateSpan -> DateSpan -> DateSpan
- spanStart :: DateSpan -> Maybe Day
- spanStartYear :: DateSpan -> Maybe Year
- spanUnion :: DateSpan -> DateSpan -> DateSpan
- spanYears :: DateSpan -> [Year]
- spansFromBoundaries :: Day -> [Day] -> [DateSpan]
- spansIntersect :: [DateSpan] -> DateSpan
- spansSpan :: [DateSpan] -> DateSpan
- spansUnion :: [DateSpan] -> DateSpan
- splitSpan :: Bool -> Interval -> DateSpan -> [DateSpan]
- tests_Dates :: TestTree
- yearp :: forall (m :: Type -> Type). TextParser m Integer
- data HledgerParseErrorData
- isNonNewlineSpace :: Char -> Bool
- data SourcePos = SourcePos {
- sourceName :: FilePath
- sourceLine :: !Pos
- sourceColumn :: !Pos
- data Regexp
- type Replacement = String
- data AccountAlias
- data AccountDeclarationInfo = AccountDeclarationInfo {
- adicomment :: Text
- aditags :: [Tag]
- adideclarationorder :: Int
- adisourcepos :: SourcePos
- data AccountType
- data Account = Account {
- aname :: AccountName
- adeclarationinfo :: Maybe AccountDeclarationInfo
- asubs :: [Account]
- aparent :: Maybe Account
- aboring :: Bool
- anumpostings :: Int
- aebalance :: MixedAmount
- aibalance :: MixedAmount
- data AmountCost
- data AmountPrecision
- = Precision !Word8
- | NaturalPrecision
- data AmountStyle = AmountStyle {
- ascommodityside :: !Side
- ascommodityspaced :: !Bool
- asdigitgroups :: !(Maybe DigitGroupStyle)
- asdecimalmark :: !(Maybe Char)
- asprecision :: !AmountPrecision
- asrounding :: !Rounding
- data BalanceAssertion = BalanceAssertion {
- baamount :: Amount
- batotal :: Bool
- bainclusive :: Bool
- baposition :: SourcePos
- data Commodity = Commodity {}
- data DigitGroupStyle = DigitGroups !Char ![Word8]
- data Journal = Journal {
- jparsedefaultyear :: Maybe Year
- jparsedefaultcommodity :: Maybe (CommoditySymbol, AmountStyle)
- jparsedecimalmark :: Maybe DecimalMark
- jparseparentaccounts :: [AccountName]
- jparsealiases :: [AccountAlias]
- jparsetimeclockentries :: [TimeclockEntry]
- jincludefilestack :: [FilePath]
- jdeclaredpayees :: [(Payee, PayeeDeclarationInfo)]
- jdeclaredtags :: [(TagName, TagDeclarationInfo)]
- jdeclaredaccounts :: [(AccountName, AccountDeclarationInfo)]
- jdeclaredaccounttags :: Map AccountName [Tag]
- jdeclaredaccounttypes :: Map AccountType [AccountName]
- jaccounttypes :: Map AccountName AccountType
- jdeclaredcommodities :: Map CommoditySymbol Commodity
- jinferredcommoditystyles :: Map CommoditySymbol AmountStyle
- jglobalcommoditystyles :: Map CommoditySymbol AmountStyle
- jpricedirectives :: [PriceDirective]
- jinferredmarketprices :: [MarketPrice]
- jtxnmodifiers :: [TransactionModifier]
- jperiodictxns :: [PeriodicTransaction]
- jtxns :: [Transaction]
- jfinalcommentlines :: Text
- jfiles :: [(FilePath, Text)]
- jlastreadtime :: POSIXTime
- data Ledger = Ledger {}
- data MarketPrice = MarketPrice {
- mpdate :: Day
- mpfrom :: CommoditySymbol
- mpto :: CommoditySymbol
- mprate :: Quantity
- pattern MixedAmountKeyNoCost :: !CommoditySymbol -> MixedAmountKey
- pattern MixedAmountKeyTotalCost :: !CommoditySymbol -> !CommoditySymbol -> MixedAmountKey
- pattern MixedAmountKeyUnitCost :: !CommoditySymbol -> !CommoditySymbol -> !Quantity -> MixedAmountKey
- data PayeeDeclarationInfo = PayeeDeclarationInfo {
- pdicomment :: Text
- pditags :: [Tag]
- data PeriodicTransaction = PeriodicTransaction {
- ptperiodexpr :: Text
- ptinterval :: Interval
- ptspan :: DateSpan
- ptsourcepos :: (SourcePos, SourcePos)
- ptstatus :: Status
- ptcode :: Text
- ptdescription :: Text
- ptcomment :: Text
- pttags :: [Tag]
- ptpostings :: [Posting]
- data PostingType
- data Posting = Posting {
- pdate :: Maybe Day
- pdate2 :: Maybe Day
- pstatus :: Status
- paccount :: AccountName
- pamount :: MixedAmount
- pcomment :: Text
- ptype :: PostingType
- ptags :: [Tag]
- pbalanceassertion :: Maybe BalanceAssertion
- ptransaction :: Maybe Transaction
- poriginal :: Maybe Posting
- data PriceDirective = PriceDirective {}
- data Rounding
- data Status
- data TMPostingRule = TMPostingRule {
- tmprPosting :: Posting
- tmprIsMultiplier :: Bool
- newtype TagDeclarationInfo = TagDeclarationInfo {
- tdicomment :: Text
- data TimeclockCode
- = SetBalance
- | SetRequiredHours
- | In
- | Out
- | FinalOut
- data TimeclockEntry = TimeclockEntry {
- tlsourcepos :: SourcePos
- tlcode :: TimeclockCode
- tldatetime :: LocalTime
- tlaccount :: AccountName
- tldescription :: Text
- tlcomment :: Text
- tltags :: [Tag]
- data TransactionModifier = TransactionModifier {}
- data Transaction = Transaction {}
- class HasAmounts a where
- styleAmounts :: Map CommoditySymbol AmountStyle -> a -> a
- data DepthSpec = DepthSpec {
- dsFlatDepth :: Maybe Int
- dsRegexpDepths :: [(Regexp, Int)]
- data NormalSign
- data StorageFormat
- data WhichDate
- isAccountSubtypeOf :: AccountType -> AccountType -> Bool
- isBalanceSheetAccountType :: AccountType -> Bool
- isDecimalMark :: Char -> Bool
- isHiddenTagName :: TagName -> Bool
- isIncomeStatementAccountType :: AccountType -> Bool
- maCompare :: MixedAmount -> MixedAmount -> Ordering
- nullaccountdeclarationinfo :: AccountDeclarationInfo
- nullpayeedeclarationinfo :: PayeeDeclarationInfo
- nullperiodictransaction :: PeriodicTransaction
- nullsourcepos :: SourcePos
- nullsourcepospair :: (SourcePos, SourcePos)
- nulltagdeclarationinfo :: TagDeclarationInfo
- nulltransactionmodifier :: TransactionModifier
- showMarketPrice :: MarketPrice -> String
- showMarketPrices :: [MarketPrice] -> [Char]
- toHiddenTag :: Tag -> HiddenTag
- toHiddenTagName :: TagName -> TagName
- toVisibleTag :: HiddenTag -> Tag
- toVisibleTagName :: TagName -> TagName
- type AccountName = Text
- type CommoditySymbol = Text
- type DateTag = (TagName, Day)
- type DecimalMark = Char
- type HiddenTag = Tag
- type MonthWeek = Int
- type ParsedJournal = Journal
- 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
- mixedAmountSetStyles :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
- styleMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
- canonicaliseMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount
- amountSetStyles :: Map CommoditySymbol AmountStyle -> Amount -> Amount
- styleAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount
- canonicaliseAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount
- (@@) :: Amount -> Amount -> Amount
- amountCost :: Amount -> Amount
- amountDisplayPrecision :: Amount -> Word8
- amountInternalPrecision :: Amount -> Word8
- amountIsZero :: Amount -> Bool
- amountLooksZero :: Amount -> Bool
- amountSetFullPrecision :: Amount -> Amount
- amountSetFullPrecisionUpTo :: Maybe Word8 -> Amount -> Amount
- amountSetPrecision :: AmountPrecision -> Amount -> Amount
- amountSetPrecisionMax :: Word8 -> Amount -> Amount
- amountSetPrecisionMin :: Word8 -> Amount -> Amount
- amountStripCost :: Amount -> Amount
- amountStyleSetRounding :: Rounding -> AmountStyle -> AmountStyle
- amountStylesSetRounding :: Rounding -> Map CommoditySymbol AmountStyle -> Map CommoditySymbol AmountStyle
- amountUnstyled :: Amount -> Amount
- amountWithCommodity :: CommoditySymbol -> Amount -> Amount
- amountsPreservingZeros :: MixedAmount -> [Amount]
- amountsRaw :: MixedAmount -> [Amount]
- amountstyle :: AmountStyle
- averageMixedAmounts :: [MixedAmount] -> MixedAmount
- cshowAmount :: Amount -> String
- defaultFmt :: AmountFormat
- defaultMaxPrecision :: Word8
- divideAmount :: Quantity -> Amount -> Amount
- divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount
- eur :: DecimalRaw Integer -> Amount
- filterMixedAmount :: (Amount -> Bool) -> MixedAmount -> MixedAmount
- filterMixedAmountByCommodity :: CommoditySymbol -> MixedAmount -> MixedAmount
- fullZeroFmt :: AmountFormat
- gbp :: DecimalRaw Integer -> Amount
- hrs :: Quantity -> Amount
- invertAmount :: Amount -> Amount
- isMissingMixedAmount :: MixedAmount -> Bool
- isNegativeAmount :: Amount -> Bool
- isNegativeMixedAmount :: MixedAmount -> Maybe Bool
- isNonsimpleCommodityChar :: Char -> Bool
- maAddAmount :: MixedAmount -> Amount -> MixedAmount
- maAddAmounts :: Foldable t => MixedAmount -> t Amount -> MixedAmount
- maCommodities :: MixedAmount -> Set CommoditySymbol
- maIsNonZero :: MixedAmount -> Bool
- maIsZero :: MixedAmount -> Bool
- maMinus :: MixedAmount -> MixedAmount -> MixedAmount
- maNegate :: MixedAmount -> MixedAmount
- maPlus :: MixedAmount -> MixedAmount -> MixedAmount
- maSum :: Foldable t => t MixedAmount -> MixedAmount
- machineFmt :: AmountFormat
- mapMixedAmount :: (Amount -> Amount) -> MixedAmount -> MixedAmount
- missingamt :: Amount
- missingmixedamt :: MixedAmount
- mixed :: Foldable t => t Amount -> MixedAmount
- mixedAmount :: Amount -> MixedAmount
- mixedAmountCost :: MixedAmount -> MixedAmount
- mixedAmountIsZero :: MixedAmount -> Bool
- mixedAmountLooksZero :: MixedAmount -> Bool
- mixedAmountSetFullPrecision :: MixedAmount -> MixedAmount
- mixedAmountSetFullPrecisionUpTo :: Maybe Word8 -> MixedAmount -> MixedAmount
- mixedAmountSetPrecision :: AmountPrecision -> MixedAmount -> MixedAmount
- mixedAmountSetPrecisionMax :: Word8 -> MixedAmount -> MixedAmount
- mixedAmountSetPrecisionMin :: Word8 -> MixedAmount -> MixedAmount
- mixedAmountStripCosts :: MixedAmount -> MixedAmount
- mixedAmountUnstyled :: MixedAmount -> MixedAmount
- multiplyAmount :: Quantity -> Amount -> Amount
- multiplyMixedAmount :: Quantity -> MixedAmount -> MixedAmount
- noCostFmt :: AmountFormat
- nullmixedamt :: MixedAmount
- num :: Quantity -> Amount
- oneLineFmt :: AmountFormat
- oneLineNoCostFmt :: AmountFormat
- quoteCommoditySymbolIfNeeded :: Text -> Text
- setAmountDecimalPoint :: Maybe Char -> Amount -> Amount
- setAmountInternalPrecision :: Word8 -> Amount -> Amount
- showAmount :: Amount -> String
- showAmountB :: AmountFormat -> Amount -> WideBuilder
- showAmountCostB :: AmountFormat -> Amount -> WideBuilder
- showAmountDebug :: Amount -> String
- showAmountWith :: AmountFormat -> Amount -> String
- showAmountWithZeroCommodity :: Amount -> String
- showAmountWithoutCost :: Amount -> String
- showCommoditySymbol :: Text -> Text
- showMixedAmount :: MixedAmount -> String
- showMixedAmountDebug :: MixedAmount -> String
- showMixedAmountElided :: Int -> Bool -> MixedAmount -> String
- showMixedAmountLinesB :: AmountFormat -> MixedAmount -> [WideBuilder]
- showMixedAmountOneLine :: MixedAmount -> String
- showMixedAmountOneLineWithoutCost :: Bool -> MixedAmount -> String
- showMixedAmountWith :: AmountFormat -> MixedAmount -> String
- showMixedAmountWithZeroCommodity :: MixedAmount -> String
- showMixedAmountWithoutCost :: Bool -> MixedAmount -> String
- tests_Amount :: TestTree
- usd :: DecimalRaw Integer -> Amount
- withDecimalPoint :: Amount -> Maybe Char -> Amount
- withInternalPrecision :: Amount -> Word8 -> Amount
- withPrecision :: Amount -> AmountPrecision -> Amount
- post :: AccountName -> Amount -> Posting
- charWidth :: Char -> Int
- chomp :: String -> String
- sourcePosPretty :: SourcePos -> String
- unPos :: Pos -> Int
- color :: ColorIntensity -> Color -> String -> String
- bgColor :: ColorIntensity -> Color -> String -> String
- data DependencyType
- after :: DependencyType -> String -> TestTree -> TestTree
- after_ :: DependencyType -> Expr -> TestTree -> TestTree
- sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree
- testGroup :: TestName -> [TestTree] -> TestTree
- type TestName = String
- data InputOpts = InputOpts {
- mformat_ :: Maybe StorageFormat
- mrules_file_ :: Maybe FilePath
- aliases_ :: [String]
- anon_ :: Bool
- new_ :: Bool
- new_save_ :: Bool
- pivot_ :: String
- forecast_ :: Maybe DateSpan
- posting_account_tags_ :: Bool
- verbose_tags_ :: Bool
- reportspan_ :: DateSpan
- auto_ :: Bool
- infer_equity_ :: Bool
- infer_costs_ :: Bool
- balancingopts_ :: BalancingOpts
- strict_ :: Bool
- _defer :: Bool
- _ioDay :: Day
- txnTieKnot :: Transaction -> Transaction
- accountSetDeclarationInfo :: Journal -> Account -> Account
- accountTree :: AccountName -> [AccountName] -> Account
- accountsFromPostings :: [Posting] -> [Account]
- accountsLevels :: Account -> [[Account]]
- anyAccounts :: (Account -> Bool) -> Account -> Bool
- clipAccounts :: Int -> Account -> Account
- clipAccountsAndAggregate :: DepthSpec -> [Account] -> [Account]
- filterAccounts :: (Account -> Bool) -> Account -> [Account]
- flattenAccounts :: Account -> [Account]
- lookupAccount :: AccountName -> [Account] -> Maybe Account
- mapAccounts :: (Account -> Account) -> Account -> Account
- nullacct :: Account
- parentAccounts :: Account -> [Account]
- printAccounts :: Account -> IO ()
- pruneAccounts :: (Account -> Bool) -> Account -> Maybe Account
- showAccounts :: Account -> String
- showAccountsBoringFlag :: Account -> String
- sortAccountNamesByDeclaration :: Journal -> Bool -> [AccountName] -> [AccountName]
- sortAccountTreeByAmount :: NormalSign -> Account -> Account
- sumAccounts :: Account -> Account
- accountLeafName :: AccountName -> Text
- accountNameApplyAliases :: [AccountAlias] -> AccountName -> Either RegexError AccountName
- accountNameApplyAliasesMemo :: [AccountAlias] -> AccountName -> Either RegexError AccountName
- accountNameComponents :: AccountName -> [Text]
- accountNameDrop :: Int -> AccountName -> AccountName
- accountNameFromComponents :: [Text] -> AccountName
- accountNameInferType :: AccountName -> Maybe AccountType
- accountNameInferTypeExcept :: [AccountType] -> AccountName -> Maybe AccountType
- accountNameLevel :: AccountName -> Int
- accountNamePostingType :: AccountName -> PostingType
- accountNameToAccountOnlyRegex :: AccountName -> Regexp
- accountNameToAccountOnlyRegexCI :: AccountName -> Regexp
- accountNameToAccountRegex :: AccountName -> Regexp
- accountNameToAccountRegexCI :: AccountName -> Regexp
- accountNameTreeFrom :: [AccountName] -> Tree AccountName
- accountNameType :: Map AccountName AccountType -> AccountName -> Maybe AccountType
- accountNameWithPostingType :: PostingType -> AccountName -> AccountName
- accountNameWithoutPostingType :: AccountName -> AccountName
- accountSummarisedName :: AccountName -> Text
- acctsep :: Text
- acctsepchar :: Char
- assetAccountRegex :: Regexp
- cashAccountRegex :: Regexp
- clipAccountName :: DepthSpec -> AccountName -> AccountName
- clipOrEllipsifyAccountName :: DepthSpec -> AccountName -> AccountName
- concatAccountNames :: [AccountName] -> AccountName
- conversionAccountRegex :: Regexp
- defaultBaseConversionAccount :: IsString a => a
- elideAccountName :: Int -> AccountName -> AccountName
- equityAccountRegex :: Regexp
- escapeName :: AccountName -> Text
- expandAccountName :: AccountName -> [AccountName]
- expandAccountNames :: [AccountName] -> [AccountName]
- expenseAccountRegex :: Regexp
- getAccountNameClippedDepth :: DepthSpec -> AccountName -> Maybe Int
- isAccountNamePrefixOf :: AccountName -> AccountName -> Bool
- isSubAccountNameOf :: AccountName -> AccountName -> Bool
- joinAccountNames :: AccountName -> AccountName -> AccountName
- liabilityAccountRegex :: Regexp
- parentAccountName :: AccountName -> AccountName
- parentAccountNames :: AccountName -> [AccountName]
- revenueAccountRegex :: Regexp
- subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName]
- tests_AccountName :: TestTree
- topAccountName :: AccountName -> AccountName
- topAccountNames :: [AccountName] -> [AccountName]
- unbudgetedAccountName :: Text
- data BalancingOpts = BalancingOpts {
- ignore_assertions_ :: Bool
- infer_balancing_costs_ :: Bool
- commodity_styles_ :: Maybe (Map CommoditySymbol AmountStyle)
- class HasBalancingOpts c where
- balancingOpts :: Lens' c BalancingOpts
- commodity_styles :: Lens' c (Maybe (Map CommoditySymbol AmountStyle))
- ignore_assertions :: Lens' c Bool
- infer_balancing_costs :: Lens' c Bool
- balanceTransaction :: BalancingOpts -> Transaction -> Either String Transaction
- balanceTransactionHelper :: BalancingOpts -> Transaction -> Either String (Transaction, [(AccountName, MixedAmount)])
- defbalancingopts :: BalancingOpts
- isTransactionBalanced :: BalancingOpts -> Transaction -> Bool
- journalBalanceTransactions :: BalancingOpts -> Journal -> Either String Journal
- tests_Balancing :: TestTree
- currencies :: [([Char], CurrencyCode, CurrencySymbol)]
- currencyCodeToSymbol :: CurrencyCode -> Maybe CurrencySymbol
- currencySymbolToCode :: CurrencySymbol -> Maybe CurrencyCode
- makeAccountTagErrorExcerpt :: (AccountName, AccountDeclarationInfo) -> TagName -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- makeBalanceAssertionErrorExcerpt :: Posting -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- makePostingAccountErrorExcerpt :: Posting -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- makePostingErrorExcerpt :: Posting -> (Posting -> Transaction -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- makePriceDirectiveErrorExcerpt :: PriceDirective -> Maybe (PriceDirective -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- makeTransactionErrorExcerpt :: Transaction -> (Transaction -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text)
- transactionFindPostingIndex :: (Posting -> Bool) -> Transaction -> Maybe Int
- 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
- addPeriodicTransaction :: PeriodicTransaction -> Journal -> Journal
- addPriceDirective :: PriceDirective -> Journal -> Journal
- addTransaction :: Transaction -> Journal -> Journal
- addTransactionModifier :: TransactionModifier -> Journal -> Journal
- canonicalStyleFrom :: [AmountStyle] -> AmountStyle
- commodityStylesFromAmounts :: [Amount] -> Either String (Map CommoditySymbol AmountStyle)
- dbgJournalAcctDeclOrder :: String -> Journal -> Journal
- filterJournalAmounts :: Query -> Journal -> Journal
- filterJournalPostings :: Query -> Journal -> Journal
- filterJournalRelatedPostings :: Query -> Journal -> Journal
- filterJournalTransactions :: Query -> Journal -> Journal
- filterPostingAmount :: Query -> Posting -> Maybe Posting
- filterTransactionAmounts :: Query -> Transaction -> Transaction
- filterTransactionPostings :: Query -> Transaction -> Transaction
- filterTransactionPostingsExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> Transaction
- filterTransactionRelatedPostings :: Query -> Transaction -> Transaction
- journalAccountNameTree :: Journal -> Tree AccountName
- journalAccountNames :: Journal -> [AccountName]
- journalAccountNamesDeclared :: Journal -> [AccountName]
- journalAccountNamesDeclaredOrImplied :: Journal -> [AccountName]
- journalAccountNamesDeclaredOrUsed :: Journal -> [AccountName]
- journalAccountNamesImplied :: Journal -> [AccountName]
- journalAccountNamesUsed :: Journal -> [AccountName]
- journalAccountTags :: Journal -> AccountName -> [Tag]
- journalAccountType :: Journal -> AccountName -> Maybe AccountType
- journalAccountTypes :: Journal -> Map AccountName AccountType
- journalAddAccountTypes :: Journal -> Journal
- journalApplyAliases :: [AccountAlias] -> Journal -> Either RegexError Journal
- journalBaseConversionAccount :: Journal -> AccountName
- journalCommodities :: Journal -> Set CommoditySymbol
- journalCommoditiesDeclared :: Journal -> [CommoditySymbol]
- journalCommodityStyles :: Journal -> Map CommoditySymbol AmountStyle
- journalCommodityStylesWith :: Rounding -> Journal -> Map CommoditySymbol AmountStyle
- journalConcat :: Journal -> Journal -> Journal
- journalConversionAccounts :: Journal -> [AccountName]
- journalDateSpan :: Bool -> Journal -> DateSpan
- journalDateSpanBothDates :: Journal -> DateSpan
- journalDbg :: Journal -> String
- journalDescriptions :: Journal -> [Text]
- journalEndDate :: Bool -> Journal -> Maybe Day
- journalFilePath :: Journal -> FilePath
- journalFilePaths :: Journal -> [FilePath]
- journalInferCommodityStyles :: Journal -> Either String Journal
- journalInferEquityFromCosts :: Bool -> Journal -> Journal
- journalInferMarketPricesFromTransactions :: Journal -> Journal
- journalInheritedAccountTags :: Journal -> AccountName -> [Tag]
- journalLastDay :: Bool -> Journal -> Maybe Day
- journalLeafAccountNames :: Journal -> [AccountName]
- journalLeafAccountNamesDeclared :: Journal -> [AccountName]
- journalMapPostingAmounts :: (MixedAmount -> MixedAmount) -> Journal -> Journal
- journalMapPostings :: (Posting -> Posting) -> Journal -> Journal
- journalMapTransactions :: (Transaction -> Transaction) -> Journal -> Journal
- journalModifyTransactions :: Bool -> Day -> Journal -> Either String Journal
- journalNextTransaction :: Journal -> Transaction -> Maybe Transaction
- journalNumberAndTieTransactions :: Journal -> Journal
- journalNumberTransactions :: Journal -> Journal
- journalPayeesDeclared :: Journal -> [Payee]
- journalPayeesDeclaredOrUsed :: Journal -> [Payee]
- journalPayeesUsed :: Journal -> [Payee]
- journalPivot :: Text -> Journal -> Journal
- journalPostingAmounts :: Journal -> [MixedAmount]
- journalPostings :: Journal -> [Posting]
- journalPostingsAddAccountTags :: Journal -> Journal
- journalPrevTransaction :: Journal -> Transaction -> Maybe Transaction
- journalRenumberAccountDeclarations :: Journal -> Journal
- journalReverse :: Journal -> Journal
- journalSetLastReadTime :: POSIXTime -> Journal -> Journal
- journalStartDate :: Bool -> Journal -> Maybe Day
- journalStyleAmounts :: Journal -> Either String Journal
- journalTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> Journal -> Either String Journal
- journalTagsDeclared :: Journal -> [TagName]
- journalTagsDeclaredOrUsed :: Journal -> [TagName]
- journalTagsUsed :: Journal -> [TagName]
- journalToCost :: ConversionOp -> Journal -> Journal
- journalTransactionAt :: Journal -> Integer -> Maybe Transaction
- journalTransactionsSimilarTo :: Journal -> Text -> Query -> SimilarityScore -> Int -> [(DateWeightedSimilarityScore, Age, SimilarityScore, Transaction)]
- journalUntieTransactions :: Transaction -> Transaction
- nulljournal :: Journal
- samplejournal :: Journal
- samplejournalMaybeExplicit :: Bool -> Journal
- showJournalAmountsDebug :: Journal -> String
- tests_Journal :: TestTree
- journalCheckAccounts :: Journal -> Either String ()
- journalCheckBalanceAssertions :: Journal -> Either String ()
- journalCheckCommodities :: Journal -> Either String ()
- journalCheckPairedConversionPostings :: Journal -> Either String ()
- journalCheckPayees :: Journal -> Either String ()
- journalCheckRecentAssertions :: Journal -> Either String ()
- journalCheckTags :: Journal -> Either String ()
- journalStrictChecks :: Journal -> Either String ()
- journalCheckOrdereddates :: Journal -> Either String ()
- journalCheckUniqueleafnames :: Journal -> Either String ()
- readJsonFile :: FromJSON a => FilePath -> IO a
- toJsonText :: ToJSON a => a -> Text
- writeJsonFile :: ToJSON a => FilePath -> a -> IO ()
- ledgerAccount :: Ledger -> AccountName -> Maybe Account
- ledgerAccountNames :: Ledger -> [AccountName]
- ledgerCommodities :: Ledger -> [CommoditySymbol]
- ledgerDateSpan :: Ledger -> DateSpan
- ledgerFromJournal :: Query -> Journal -> Ledger
- ledgerLeafAccounts :: Ledger -> [Account]
- ledgerPostings :: Ledger -> [Posting]
- ledgerRootAccount :: Ledger -> Account
- ledgerTopAccounts :: Ledger -> [Account]
- nullledger :: Ledger
- tests_Ledger :: TestTree
- firstMonthOfQuarter :: Num a => a -> a
- isLastDayOfMonth :: (Eq a1, Eq a2, Num a1, Num a2) => Year -> a1 -> a2 -> Bool
- isStandardPeriod :: Period -> Bool
- mondayBefore :: Day -> Day
- periodEnd :: Period -> Maybe Day
- periodGrow :: Period -> Period
- periodMoveTo :: Day -> Period -> Period
- periodNext :: Period -> Period
- periodNextIn :: DateSpan -> Period -> Period
- periodPrevious :: Period -> Period
- periodPreviousIn :: DateSpan -> Period -> Period
- periodShrink :: Day -> Period -> Period
- periodStart :: Period -> Maybe Day
- periodTextWidth :: Period -> Int
- quarterContainingMonth :: Integral a => a -> a
- simplifyPeriod :: Period -> Period
- startOfFirstWeekInMonth :: Year -> MonthOfYear -> Day
- yearMonthContainingWeekStarting :: Day -> (Year, MonthOfYear)
- checkPeriodicTransactionStartDate :: Interval -> DateSpan -> Text -> Maybe String
- runPeriodicTransaction :: Bool -> PeriodicTransaction -> DateSpan -> [Transaction]
- accountNamesFromPostings :: [Posting] -> [AccountName]
- balassert :: Amount -> Maybe BalanceAssertion
- balassertParInc :: Amount -> Maybe BalanceAssertion
- balassertTot :: Amount -> Maybe BalanceAssertion
- balassertTotInc :: Amount -> Maybe BalanceAssertion
- commentAddTag :: Text -> Tag -> Text
- commentAddTagNextLine :: Text -> Tag -> Text
- commentAddTagUnspaced :: Text -> Tag -> Text
- commentJoin :: Text -> Text -> Text
- conversionPostingTagName :: TagName
- costPostingTagName :: TagName
- generatedPostingTagName :: TagName
- generatedTransactionTagName :: TagName
- hasAmount :: Posting -> Bool
- hasBalanceAssignment :: Posting -> Bool
- isBalancedVirtual :: Posting -> Bool
- isEmptyPosting :: Posting -> Bool
- isPostingInDateSpan :: DateSpan -> Posting -> Bool
- isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool
- isReal :: Posting -> Bool
- isVirtual :: Posting -> Bool
- modifiedTransactionTagName :: TagName
- negatePostingAmount :: Posting -> Posting
- nullassertion :: BalanceAssertion
- nullposting :: Posting
- originalPosting :: Posting -> Posting
- post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
- posting :: Posting
- postingAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Posting -> Posting
- postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting]
- postingAddTags :: Posting -> [Tag] -> Posting
- postingAllTags :: Posting -> [Tag]
- postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting
- postingApplyCommodityStyles :: Map CommoditySymbol AmountStyle -> Posting -> Posting
- postingApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting
- postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int)
- postingDate :: Posting -> Day
- postingDate2 :: Posting -> Day
- postingDateOrDate2 :: WhichDate -> Posting -> Day
- postingIndent :: Text -> Text
- postingPriceDirectivesFromCost :: Posting -> [PriceDirective]
- postingStatus :: Posting -> Status
- postingStripCosts :: Posting -> Posting
- postingStyleAmounts :: Map CommoditySymbol AmountStyle -> Posting -> Posting
- postingToCost :: ConversionOp -> Posting -> Maybe Posting
- postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting
- postingsAsLines :: Bool -> [Posting] -> [Text]
- relatedPostings :: Posting -> [Posting]
- renderCommentLines :: Text -> [Text]
- showAccountName :: Maybe Int -> PostingType -> AccountName -> Text
- showBalanceAssertion :: BalanceAssertion -> WideBuilder
- showPosting :: Posting -> String
- showPostingLines :: Posting -> [Text]
- sumPostings :: [Posting] -> MixedAmount
- tests_Posting :: TestTree
- transactionAllTags :: Transaction -> [Tag]
- vpost :: AccountName -> Amount -> Posting
- vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting
- 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
- data StringFormat
- data StringFormatComponent
- = FormatLiteral Text
- | FormatField Bool (Maybe Int) (Maybe Int) ReportItemField
- defaultBalanceLineFormat :: StringFormat
- defaultStringFormatStyle :: [StringFormatComponent] -> StringFormat
- parseStringFormat :: Text -> Either String StringFormat
- tests_StringFormat :: TestTree
- tests_Timeclock :: TestTree
- timeclockEntriesToTransactions :: LocalTime -> [TimeclockEntry] -> [Transaction]
- annotateErrorWithTransaction :: Transaction -> String -> String
- assignmentPostings :: Transaction -> [Posting]
- balancedVirtualPostings :: Transaction -> [Posting]
- hasRealPostings :: Transaction -> Bool
- nulltransaction :: Transaction
- partitionAndCheckConversionPostings :: Bool -> [AccountName] -> [IdxPosting] -> Either Text ([(IdxPosting, IdxPosting)], ([IdxPosting], [IdxPosting]))
- payeeAndNoteFromDescription :: Text -> (Text, Text)
- payeeAndNoteFromDescription' :: Text -> (Text, Text)
- realPostings :: Transaction -> [Posting]
- showTransaction :: Transaction -> Text
- showTransactionLineFirstPart :: Transaction -> Text
- showTransactionOneLineAmounts :: Transaction -> Text
- tests_Transaction :: TestTree
- transaction :: Day -> [Posting] -> Transaction
- transactionAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Transaction -> Transaction
- transactionAddTags :: Transaction -> [Tag] -> Transaction
- transactionAmounts :: Transaction -> [MixedAmount]
- transactionApplyAliases :: [AccountAlias] -> Transaction -> Either RegexError Transaction
- transactionApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction
- transactionDate2 :: Transaction -> Day
- transactionDateOrDate2 :: WhichDate -> Transaction -> Day
- transactionFile :: Transaction -> FilePath
- transactionInferEquityPostings :: Bool -> AccountName -> Transaction -> Transaction
- transactionMapPostingAmounts :: (MixedAmount -> MixedAmount) -> Transaction -> Transaction
- transactionMapPostings :: (Posting -> Posting) -> Transaction -> Transaction
- transactionNote :: Transaction -> Text
- transactionPayee :: Transaction -> Text
- transactionTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> [AccountName] -> Transaction -> Either String Transaction
- transactionToCost :: ConversionOp -> Transaction -> Transaction
- transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction
- transactionsPostings :: [Transaction] -> [Posting]
- txnUntieKnot :: Transaction -> Transaction
- virtualPostings :: Transaction -> [Posting]
- modifyTransactions :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Map CommoditySymbol AmountStyle -> Day -> Bool -> [TransactionModifier] -> [Transaction] -> Either String [Transaction]
- data ValuationType
- data ConversionOp
- type PriceOracle = (Day, CommoditySymbol, Maybe CommoditySymbol) -> Maybe (CommoditySymbol, Quantity)
- amountPriceDirectiveFromCost :: Day -> Amount -> Maybe PriceDirective
- journalPriceOracle :: Bool -> Journal -> PriceOracle
- marketPriceReverse :: MarketPrice -> MarketPrice
- mixedAmountApplyGain :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount
- mixedAmountApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount
- mixedAmountGainAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
- mixedAmountToCost :: Map CommoditySymbol AmountStyle -> ConversionOp -> MixedAmount -> MixedAmount
- mixedAmountValueAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount
- priceDirectiveToMarketPrice :: PriceDirective -> MarketPrice
- tests_Valuation :: TestTree
- valuationTypeValuationCommodity :: ValuationType -> Maybe CommoditySymbol
- tests_Data :: TestTree
- matchesAmount :: Query -> Amount -> Bool
- matchesPosting :: Query -> Posting -> Bool
- matchesPostingExtra :: (AccountName -> Maybe AccountType) -> Query -> Posting -> Bool
- matchesTransaction :: Query -> Transaction -> Bool
- matchesTransactionExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> 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 FinalParseError = FinalParseError' HledgerParseErrorData
- 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
- sourcePosPairPretty :: (SourcePos, SourcePos) -> String
- initialPos :: FilePath -> SourcePos
- 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
- filterQueryOrNotQuery :: (Query -> Bool) -> Query -> Query
- generatedTransactionTag :: Query
- inAccount :: [QueryOpt] -> Maybe (AccountName, Bool)
- inAccountQuery :: [QueryOpt] -> Maybe Query
- matchesAccount :: Query -> AccountName -> Bool
- matchesAccountExtra :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Query -> AccountName -> Bool
- matchesCommodity :: Query -> CommoditySymbol -> Bool
- matchesDescription :: Query -> Text -> Bool
- matchesMixedAmount :: Query -> MixedAmount -> Bool
- matchesPayeeWIP :: Query -> Payee -> Bool
- matchesPriceDirective :: Query -> PriceDirective -> Bool
- matchesQuery :: (Query -> Bool) -> Query -> Bool
- matchesTags :: Regexp -> Maybe Regexp -> [Tag] -> Bool
- noteTag :: Maybe Text -> Either RegexError Query
- parseAccountType :: Bool -> Text -> Either String AccountType
- parseDepthSpec :: Text -> Either RegexError DepthSpec
- parseQuery :: Day -> Text -> Either String (Query, [QueryOpt])
- parseQueryList :: Day -> [Text] -> Either String (Query, [QueryOpt])
- parseQueryTerm :: Day -> Text -> Either String (Query, [QueryOpt])
- payeeTag :: Maybe Text -> Either RegexError Query
- queryDateSpan :: Bool -> Query -> DateSpan
- queryDateSpan' :: Query -> DateSpan
- queryDepth :: Query -> DepthSpec
- queryEndDate :: Bool -> Query -> Maybe Day
- queryIsAcct :: Query -> Bool
- queryIsAmt :: Query -> Bool
- queryIsCode :: Query -> Bool
- queryIsDate :: Query -> Bool
- queryIsDate2 :: Query -> Bool
- queryIsDateOrDate2 :: Query -> Bool
- queryIsDesc :: Query -> Bool
- queryIsNull :: Query -> Bool
- queryIsReal :: Query -> Bool
- queryIsStartDateOnly :: Bool -> Query -> Bool
- queryIsStatus :: Query -> Bool
- queryIsTag :: Query -> Bool
- queryIsTransactionRelated :: Query -> Bool
- queryIsType :: Query -> Bool
- queryStartDate :: Bool -> Query -> Maybe Day
- queryprefixes :: [Text]
- simplifyQuery :: Query -> Query
- tests_Query :: TestTree
- words'' :: [Text] -> Text -> [Text]
- type PrefixedFilePath = FilePath
- defaultJournal :: IO Journal
- defaultJournalPath :: IO String
- ensureJournalFileExists :: FilePath -> IO ()
- orDieTrying :: MonadIO m => ExceptT String m a -> m a
- readJournal :: InputOpts -> Maybe FilePath -> Text -> ExceptT String IO Journal
- readJournal' :: Text -> IO Journal
- readJournalFile :: InputOpts -> PrefixedFilePath -> ExceptT String IO Journal
- readJournalFile' :: PrefixedFilePath -> IO Journal
- readJournalFiles :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO Journal
- readJournalFiles' :: [PrefixedFilePath] -> IO Journal
- readJournalFilesAndLatestDates :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO (Journal, [LatestDatesForFile])
- requireJournalFileExists :: FilePath -> IO ()
- saveLatestDates :: LatestDates -> FilePath -> IO ()
- saveLatestDatesForFiles :: [LatestDatesForFile] -> IO ()
- tests_Read :: TestTree
- data Reader (m :: Type -> Type) = Reader {
- rFormat :: StorageFormat
- rExtensions :: [String]
- rReadFn :: InputOpts -> FilePath -> Text -> ExceptT String IO Journal
- rParser :: MonadIO m => ErroringJournalParser m ParsedJournal
- 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 ()
- aliasesFromOpts :: InputOpts -> [AccountAlias]
- 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)
- getDefaultCommodityAndStyle :: forall (m :: Type -> Type). JournalParser m (Maybe (CommoditySymbol, AmountStyle))
- getParentAccount :: forall (m :: Type -> Type). JournalParser m AccountName
- getYear :: forall (m :: Type -> Type). JournalParser m (Maybe Year)
- initialiseAndParseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal
- isLineCommentStart :: Char -> Bool
- isSameLineCommentStart :: Char -> Bool
- journalAddAutoPostings :: Bool -> Day -> BalancingOpts -> Journal -> Either String Journal
- journalAddFile :: (FilePath, Text) -> Journal -> Journal
- journalAddForecast :: Bool -> Maybe DateSpan -> Journal -> Journal
- journalFinalise :: InputOpts -> FilePath -> Text -> ParsedJournal -> ExceptT String IO Journal
- 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)
- parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal
- parseamount :: String -> Either HledgerParseErrors Amount
- parseamount' :: String -> Amount
- parsemixedamount :: String -> Either HledgerParseErrors MixedAmount
- parsemixedamount' :: String -> MixedAmount
- 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
- tests_Common :: TestTree
- transactioncommentp :: forall (m :: Type -> Type). TextParser m (Text, [Tag])
- definputopts :: InputOpts
- forecastPeriod :: InputOpts -> Journal -> Maybe DateSpan
- findReader :: forall (m :: Type -> Type). MonadIO m => Maybe StorageFormat -> Maybe FilePath -> Maybe (Reader m)
- runJournalParser :: Monad m => JournalParser m a -> Text -> m (Either HledgerParseErrors a)
- splitReaderPrefix :: PrefixedFilePath -> (Maybe StorageFormat, FilePath)
- tmpostingrulep :: forall (m :: Type -> Type). Maybe Year -> JournalParser m TMPostingRule
- tests_Reports :: TestTree
- type AccountTransactionsReport = [AccountTransactionsReportItem]
- type AccountTransactionsReportItem = (Transaction, Transaction, Bool, Text, MixedAmount, MixedAmount)
- accountTransactionsReport :: ReportSpec -> Journal -> Query -> AccountTransactionsReport
- accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)]
- accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> (AccountName -> Maybe AccountType) -> [(Day, Transaction)] -> [AccountTransactionsReportItem]
- tests_AccountTransactionsReport :: TestTree
- transactionRegisterDate :: WhichDate -> Query -> Query -> Transaction -> Day
- triAmount :: (a, b, c, d, e, f) -> e
- triBalance :: (a, b, c, d, e, f) -> f
- triCommodityAmount :: CommoditySymbol -> (a, b, c, d, MixedAmount, f) -> MixedAmount
- triCommodityBalance :: CommoditySymbol -> (a, b, c, d, e, MixedAmount) -> MixedAmount
- triDate :: (a, Transaction, c, d, e, f) -> Day
- triOrigTransaction :: (a, b, c, d, e, f) -> a
- type BalanceReport = ([BalanceReportItem], MixedAmount)
- type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount)
- balanceReport :: ReportSpec -> Journal -> BalanceReport
- flatShowsExclusiveBalance :: Bool
- tests_BalanceReport :: TestTree
- type BudgetAverage = Average
- type BudgetCell = (Maybe Change, Maybe BudgetGoal)
- type BudgetGoal = Change
- type BudgetReport = PeriodicReport DisplayName BudgetCell
- type BudgetReportRow = PeriodicReportRow DisplayName BudgetCell
- type BudgetTotal = Total
- budgetReport :: ReportSpec -> BalancingOpts -> DateSpan -> Journal -> BudgetReport
- combineBudgetAndActual :: ReportOpts -> Journal -> MultiBalanceReport -> MultiBalanceReport -> BudgetReport
- tests_BudgetReport :: TestTree
- type EntriesReport = [EntriesReportItem]
- type EntriesReportItem = Transaction
- entriesReport :: ReportSpec -> Journal -> EntriesReport
- tests_EntriesReport :: TestTree
- type MultiBalanceReport = PeriodicReport DisplayName MixedAmount
- type MultiBalanceReportRow = PeriodicReportRow DisplayName MixedAmount
- compoundBalanceReport :: ReportSpec -> Journal -> [CBCSubreportSpec a] -> CompoundPeriodicReport a MixedAmount
- compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> [CBCSubreportSpec a] -> CompoundPeriodicReport a MixedAmount
- generateMultiBalanceReport :: ReportSpec -> Journal -> PriceOracle -> Set AccountName -> [(DateSpan, [Posting])] -> HashMap AccountName Account -> MultiBalanceReport
- getPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting]
- getPostingsByColumn :: ReportSpec -> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])]
- makeReportQuery :: ReportSpec -> DateSpan -> ReportSpec
- multiBalanceReport :: ReportSpec -> Journal -> MultiBalanceReport
- multiBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> Set AccountName -> MultiBalanceReport
- sortRows :: ReportOpts -> Journal -> [MultiBalanceReportRow] -> [MultiBalanceReportRow]
- sortRowsLike :: [AccountName] -> [PeriodicReportRow DisplayName b] -> [PeriodicReportRow DisplayName b]
- startingPostings :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting]
- tests_MultiBalanceReport :: TestTree
- type PostingsReport = [PostingsReportItem]
- type PostingsReportItem = (Maybe Day, Maybe Period, Maybe Text, Posting, MixedAmount)
- mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Period -> Posting -> MixedAmount -> PostingsReportItem
- postingsReport :: ReportSpec -> Journal -> PostingsReport
- tests_PostingsReport :: TestTree
- data AccountListMode
- data SortField
- = AbsAmount' Bool
- | Account' Bool
- | Amount' Bool
- | Date' Bool
- | Description' Bool
- data BalanceAccumulation
- data BalanceCalculation
- class HasReportOptsNoUpdate a => HasReportOpts a where
- 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]
- class HasReportSpec c where
- reportSpec :: Lens' c ReportSpec
- rsDay :: Lens' c Day
- rsQuery :: Lens' c Query
- rsQueryOpts :: Lens' c [QueryOpt]
- rsReportOpts :: Lens' c ReportOpts
- data Layout
- = LayoutWide (Maybe Int)
- | LayoutTall
- | LayoutBare
- | LayoutTidy
- data ReportSpec = ReportSpec {
- _rsReportOpts :: ReportOpts
- _rsDay :: Day
- _rsQuery :: Query
- _rsQueryOpts :: [QueryOpt]
- type SortSpec = [SortField]
- balanceAccumulationOverride :: RawOpts -> Maybe BalanceAccumulation
- defreportopts :: ReportOpts
- defreportspec :: ReportSpec
- defsortspec :: SortSpec
- flat_ :: ReportOpts -> Bool
- intervalFromRawOpts :: RawOpts -> Interval
- journalApplyValuationFromOpts :: ReportSpec -> Journal -> Journal
- journalApplyValuationFromOptsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
- journalValueAndFilterPostings :: ReportSpec -> Journal -> Journal
- journalValueAndFilterPostingsWith :: ReportSpec -> Journal -> PriceOracle -> Journal
- mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount
- overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t
- postingDateFn :: ReportOpts -> Posting -> Day
- queryFromFlags :: ReportOpts -> Query
- rawOptsToReportOpts :: Day -> Bool -> RawOpts -> ReportOpts
- rawOptsToReportSpec :: Day -> Bool -> RawOpts -> Either String ReportSpec
- reportEndDate :: Journal -> ReportSpec -> Maybe Day
- reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec
- reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts
- reportPeriodLastDay :: ReportSpec -> Maybe Day
- reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text
- reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day
- reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day
- reportPeriodStart :: ReportSpec -> Maybe Day
- reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
- reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan])
- reportStartDate :: Journal -> ReportSpec -> Maybe Day
- setDefaultConversionOp :: ConversionOp -> ReportSpec -> ReportSpec
- setEither :: ((a -> Either e b) -> s -> Either e t) -> b -> s -> Either e t
- simplifyStatuses :: Ord a => [a] -> [a]
- sortKeysDescription :: [Char]
- transactionDateFn :: ReportOpts -> Transaction -> Day
- tree_ :: ReportOpts -> Bool
- updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec
- updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec
- valuationAfterSum :: ReportOpts -> Maybe (Maybe CommoditySymbol)
- whichDate :: ReportOpts -> WhichDate
- type Average = MixedAmount
- data CBCSubreportSpec a = CBCSubreportSpec {}
- type Change = MixedAmount
- data CompoundPeriodicReport a b = CompoundPeriodicReport {
- cbrTitle :: Text
- cbrDates :: [DateSpan]
- cbrSubreports :: [(Text, PeriodicReport a b, Bool)]
- cbrTotals :: PeriodicReportRow () b
- data DisplayName = DisplayName {
- displayFull :: AccountName
- displayName :: AccountName
- displayIndent :: NumberOfIndents
- type Percentage = Decimal
- data PeriodicReport a b = PeriodicReport {
- prDates :: [DateSpan]
- prRows :: [PeriodicReportRow a b]
- prTotals :: PeriodicReportRow () b
- data PeriodicReportRow a b = PeriodicReportRow {
- prrName :: a
- prrAmounts :: [b]
- prrTotal :: b
- prrAverage :: b
- flatDisplayName :: AccountName -> DisplayName
- periodicReportSpan :: PeriodicReport a b -> DateSpan
- prMapMaybeName :: (a -> Maybe b) -> PeriodicReport a c -> PeriodicReport b c
- prMapName :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c
- prrAdd :: Semigroup b => PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b
- prrDisplayName :: PeriodicReportRow DisplayName a -> AccountName
- prrFullName :: PeriodicReportRow DisplayName a -> AccountName
- prrIndent :: PeriodicReportRow DisplayName a -> Int
- prrShowDebug :: PeriodicReportRow DisplayName MixedAmount -> String
- treeDisplayName :: AccountName -> DisplayName
- 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
- tests_Utils :: TestTree
- 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
- 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
- ghcDebugMode :: GhcDebugMode
- ghcDebugPause' :: IO ()
- 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
- 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
- colorOption :: IO YNA
- cyan' :: String -> String
- expandGlob :: FilePath -> FilePath -> IO [FilePath]
- expandHomePath :: FilePath -> IO FilePath
- faint' :: String -> String
- getCurrentLocalTime :: IO LocalTime
- getCurrentZonedTime :: IO ZonedTime
- getOpt :: [String] -> IO (Maybe String)
- getTerminalHeight :: IO (Maybe Int)
- getTerminalHeightWidth :: IO (Maybe (Int, Int))
- getTerminalWidth :: IO (Maybe Int)
- 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
- readFileOrStdinPortably :: String -> IO Text
- readFilePortably :: FilePath -> IO Text
- readFileStrictly :: FilePath -> IO Text
- readHandlePortably :: Handle -> IO Text
- red' :: String -> String
- rgb' :: Float -> Float -> Float -> String -> String
- runPager :: String -> IO ()
- setupPager :: IO ()
- sortByModTime :: [FilePath] -> IO [FilePath]
- terminalBgColor :: Maybe (RGB Float)
- terminalFgColor :: Maybe (RGB Float)
- terminalIsLight :: Maybe Bool
- terminalLightness :: Maybe Float
- usageError :: String -> a
- useColorOnStderr :: IO Bool
- useColorOnStderrUnsafe :: Bool
- useColorOnStdout :: IO Bool
- useColorOnStdoutUnsafe :: Bool
- warn :: String -> a -> a
- white' :: String -> String
- yellow' :: String -> String
- data FinalParseError' e
- type FinalParseErrorBundle = FinalParseErrorBundle' HledgerParseErrorData
- data FinalParseErrorBundle' e
- type SimpleStringParser a = Parsec HledgerParseErrorData String a
- type SimpleTextParser = Parsec HledgerParseErrorData Text
- data SourceExcerpt
- attachSource :: FilePath -> Text -> FinalParseError' e -> FinalParseErrorBundle' e
- 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
- finalErrorBundlePretty :: FinalParseErrorBundle' HledgerParseErrorData -> String
- 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
- getExcerptText :: SourceExcerpt -> Text
- isNewline :: Char -> Bool
- nonspace :: forall (m :: Type -> Type). TextParser m Char
- parseErrorAt :: Int -> String -> HledgerParseErrorData
- 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
- rtp :: TextParser Identity a -> Text -> Either HledgerParseErrors a
- runTextParser :: TextParser Identity a -> Text -> Either HledgerParseErrors a
- 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
- regexMatchTextGroups :: Regexp -> Text -> [Text]
- regexReplace :: Regexp -> Replacement -> String -> Either RegexError String
- regexReplaceAllBy :: Regexp -> (String -> String) -> String -> String
- regexReplaceUnmemo :: Regexp -> Replacement -> String -> Either RegexError String
- toRegex :: Text -> Either RegexError Regexp
- toRegex' :: Text -> Regexp
- toRegexCI :: Text -> Either RegexError Regexp
- toRegexCI' :: Text -> Regexp
- 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
- tests_Hledger :: TestTree
- 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
- testCase :: TestName -> Assertion -> TestTree
- testCaseInfo :: TestName -> IO String -> TestTree
- (@=?) :: (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
- assertString :: HasCallStack => String -> Assertion
- testCaseSteps :: TestName -> ((String -> IO ()) -> Assertion) -> TestTree
- runExceptT :: ExceptT e m a -> m (Either e a)
- data Timeout
- type Assertion = IO ()
- class AssertionPredicable t where
- assertionPredicate :: t -> IO Bool
- type AssertionPredicate = IO Bool
- data HUnitFailure = HUnitFailure (Maybe SrcLoc) String
- trace :: String -> a -> a
- 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 = Group {
- groupUnnamed :: [a]
- groupHidden :: [a]
- groupNamed :: [(Help, [a])]
- data Mode a = Mode {
- modeGroupModes :: Group (Mode a)
- modeNames :: [Name]
- modeValue :: a
- modeCheck :: a -> Either String a
- modeReform :: a -> Maybe [String]
- modeExpandAt :: Bool
- modeHelp :: Help
- modeHelpSuffix :: [String]
- modeArgs :: ([Arg a], Maybe (Arg a))
- modeGroupFlags :: Group (Flag a)
- data Arg a = Arg {
- argValue :: Update a
- argType :: FlagHelp
- argRequire :: Bool
- data Complete
- = CompleteValue String
- | CompleteFile String FilePath
- | CompleteDir String FilePath
- mode :: Name -> a -> Help -> Arg a -> [Flag a] -> Mode a
- data Flag a = Flag {}
- type FlagHelp = String
- flagArg :: Update a -> FlagHelp -> Arg a
- toGroup :: [a] -> Group a
- helpText :: [String] -> HelpFormat -> Mode a -> [Text]
- data HelpFormat
- 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
- = FlagReq
- | FlagOpt String
- | FlagOptRare String
- | FlagNone
- class Remap (m :: Type -> Type) where
- remap :: (a -> b) -> (b -> (a, a -> b)) -> m a -> m 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
Documentation
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
module Hledger.Cli.CliOptions
module Hledger.Cli.Conf
module Hledger.Cli.Commands
module Hledger.Cli.DocFiles
module Hledger.Cli.Utils
module Hledger.Cli.Version
class HasReportOptsNoUpdate c where #
Minimal complete definition
Methods
reportOptsNoUpdate :: Lens' c ReportOpts #
accountlistmode :: Lens' c AccountListMode #
balance_base_url :: Lens' c (Maybe Text) #
balanceaccum :: Lens' c BalanceAccumulation #
balancecalc :: Lens' c BalanceCalculation #
budgetpat :: Lens' c (Maybe Text) #
conversionop :: Lens' c (Maybe ConversionOp) #
date2NoUpdate :: Lens' c Bool #
depthNoUpdate :: Lens' c DepthSpec #
format :: Lens' c StringFormat #
infer_prices :: Lens' c Bool #
interval :: Lens' c Interval #
normalbalance :: Lens' c (Maybe NormalSign) #
periodNoUpdate :: Lens' c Period #
querystringNoUpdate :: Lens' c [Text] #
realNoUpdate :: 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 #
value :: Lens' c (Maybe ValuationType) #
Instances
class HasInputOpts c where #
Minimal complete definition
Methods
inputOpts :: Lens' c InputOpts #
balancingopts :: Lens' c BalancingOpts #
forecast :: Lens' c (Maybe DateSpan) #
infer_costs :: Lens' c Bool #
infer_equity :: Lens' c Bool #
mformat :: Lens' c (Maybe StorageFormat) #
mrules_file :: Lens' c (Maybe FilePath) #
posting_account_tags :: Lens' c Bool #
reportspan :: Lens' c DateSpan #
verbose_tags :: Lens' c Bool #
Instances
data SmartInterval #
Instances
Show SmartInterval | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> SmartInterval -> ShowS show :: SmartInterval -> String showList :: [SmartInterval] -> ShowS |
quoteIfSpaced :: Text -> Text #
showDateSpan :: DateSpan -> Text #
Instances
Default DateSpan | |||||
Defined in Hledger.Data.Types | |||||
Generic DateSpan | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Eq DateSpan | |||||
Ord DateSpan | |||||
Defined in Hledger.Data.Types | |||||
type Rep DateSpan | |||||
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)))) |
type Balance = MixedAmount #
Instances
Generic Side | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read Side | |||||
Defined in Hledger.Data.Types | |||||
Show Side | |||||
Eq Side | |||||
Ord Side | |||||
type Rep Side | |||||
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 ReportOpts #
Constructors
ReportOpts | |
Fields
|
Instances
embedFileRelative :: FilePath -> Q Exp #
collectopts :: ((String, String) -> Maybe a) -> RawOpts -> [a] #
formatString :: Bool -> Maybe Int -> Maybe Int -> String -> String #
ghcDebugSupportedInLib :: Bool #
splitAtElement :: Eq a => a -> [a] -> [[a]] #
class Assertable t where #
Instances
Assertable String | |
Defined in Test.Tasty.HUnit.Orig | |
Assertable () | |
Defined in Test.Tasty.HUnit.Orig | |
Assertable Bool | |
Defined in Test.Tasty.HUnit.Orig | |
Assertable t => Assertable (IO t) | |
Defined in Test.Tasty.HUnit.Orig |
type HasCallStack = ?callStack :: CallStack #
Constructors
DayPeriod Day | |
WeekPeriod Day | |
MonthPeriod Year Month | |
QuarterPeriod Year Quarter | |
YearPeriod Year | |
PeriodBetween Day Day | |
PeriodFrom Day | |
PeriodTo Day | |
PeriodAll |
Instances
Default Period | |||||
Defined in Hledger.Data.Types | |||||
Generic Period | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Period | |||||
Eq Period | |||||
Ord Period | |||||
type Rep Period | |||||
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))))) |
data AmountFormat #
Constructors
AmountFormat | |
Fields
|
Instances
Default AmountFormat | |
Defined in Hledger.Data.Amount Methods def :: AmountFormat | |
Show AmountFormat | |
Defined in Hledger.Data.Amount Methods showsPrec :: Int -> AmountFormat -> ShowS show :: AmountFormat -> String showList :: [AmountFormat] -> ShowS |
showMixedAmountB :: AmountFormat -> MixedAmount -> WideBuilder #
showMixedAmountLinesPartsB :: AmountFormat -> MixedAmount -> [(WideBuilder, Amount)] #
unifyMixedAmount :: MixedAmount -> Maybe Amount #
Constructors
Amount | |
Fields
|
Instances
Generic Amount | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Amount | |||||
Eq Amount | |||||
Ord Amount | |||||
type Rep Amount | |||||
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
Generic MixedAmount | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show MixedAmount | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> MixedAmount -> ShowS show :: MixedAmount -> String showList :: [MixedAmount] -> ShowS | |||||
Eq MixedAmount | |||||
Defined in Hledger.Data.Types | |||||
Ord MixedAmount | |||||
Defined in Hledger.Data.Types Methods compare :: MixedAmount -> MixedAmount -> Ordering # (<) :: MixedAmount -> MixedAmount -> Bool # (<=) :: MixedAmount -> MixedAmount -> Bool # (>) :: MixedAmount -> MixedAmount -> Bool # (>=) :: MixedAmount -> MixedAmount -> Bool # max :: MixedAmount -> MixedAmount -> MixedAmount # min :: MixedAmount -> MixedAmount -> MixedAmount # | |||||
type Rep MixedAmount | |||||
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 | |
Instances
Monoid WideBuilder | |
Defined in Text.WideString | |
Semigroup WideBuilder | |
Defined in Text.WideString Methods (<>) :: WideBuilder -> WideBuilder -> WideBuilder sconcat :: NonEmpty WideBuilder -> WideBuilder stimes :: Integral b => b -> WideBuilder -> WideBuilder | |
Show WideBuilder | |
Defined in Text.WideString Methods showsPrec :: Int -> WideBuilder -> ShowS show :: WideBuilder -> String showList :: [WideBuilder] -> ShowS |
type Total = MixedAmount #
amounts :: MixedAmount -> [Amount] #
wbFromText :: Text -> WideBuilder #
wbToText :: WideBuilder -> Text #
wbUnpack :: WideBuilder -> String #
escapeBackslash :: Text -> Text #
escapeDoubleQuotes :: Text -> Text #
linesPrepend :: Text -> Text -> Text #
readDecimal :: Text -> Integer #
stripquotes :: Text -> Text #
tests_Text :: TestTree #
textCapitalise :: Text -> Text #
textConcatBottomPadded :: [Text] -> Text #
textConcatTopPadded :: [Text] -> Text #
textElideRight :: Int -> Text -> Text #
textQuoteIfNeeded :: Text -> Text #
textTakeWidth :: Int -> Text -> Text #
textUnbracket :: Text -> Text #
dateSpanAsPeriod :: DateSpan -> Period #
periodAsDateSpan :: Period -> DateSpan #
showPeriod :: Period -> Text #
showPeriodAbbrev :: Period -> Text #
Constructors
NoInterval | |
Days Int | |
Weeks Int | |
Months Int | |
Quarters Int | |
Years Int | |
NthWeekdayOfMonth Int Int | |
MonthDay Int | |
MonthAndDay Int Int | |
DaysOfWeek [Int] |
Instances
Default Interval | |||||
Defined in Hledger.Data.Types | |||||
Generic Interval | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Interval | |||||
Eq Interval | |||||
Ord Interval | |||||
Defined in Hledger.Data.Types | |||||
type Rep Interval | |||||
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])))))) |
Instances
Generic EFDay | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show EFDay | |||||
Eq EFDay | |||||
Ord EFDay | |||||
type Rep EFDay | |||||
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))) |
Constructors
SmartCompleteDate Day | |
SmartAssumeStart Year (Maybe Month) | |
SmartFromReference (Maybe Month) MonthDay | |
SmartMonth Month | |
SmartRelative Integer SmartInterval |
type HledgerParseErrors = ParseErrorBundle Text HledgerParseErrorData #
type TextParser (m :: Type -> Type) a = ParsecT HledgerParseErrorData Text m a #
choice' :: forall (m :: Type -> Type) a. [TextParser m a] -> TextParser m a #
customErrorBundlePretty :: HledgerParseErrors -> String #
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 #
fixSmartDate :: Day -> SmartDate -> EFDay #
fixSmartDateStr :: Day -> Text -> Text #
fixSmartDateStrEither :: Day -> Text -> Either HledgerParseErrors Text #
fixSmartDateStrEither' :: Day -> Text -> Either HledgerParseErrors EFDay #
getCurrentDay :: IO Day #
getCurrentMonth :: IO Int #
getCurrentYear :: IO Integer #
groupByDateSpan :: Bool -> (a -> Day) -> [DateSpan] -> [a] -> [(DateSpan, [a])] #
intervalBoundaryBefore :: Interval -> Day -> Day #
isDateSepChar :: Char -> Bool #
parsePeriodExpr :: Day -> Text -> Either HledgerParseErrors (Interval, DateSpan) #
parsedateM :: String -> Maybe Day #
periodContainsDate :: Period -> Day -> Bool #
periodexprp :: forall (m :: Type -> Type). Day -> TextParser m (Interval, DateSpan) #
showDateSpanAbbrev :: DateSpan -> Text #
showDateSpanDebug :: DateSpan -> String #
showEFDate :: EFDay -> Text #
smartdate :: forall (m :: Type -> Type). TextParser m SmartDate #
spanContainsDate :: DateSpan -> Day -> Bool #
spanDefaultsFrom :: DateSpan -> DateSpan -> DateSpan #
spanEndYear :: DateSpan -> Maybe Year #
spanExtend :: DateSpan -> DateSpan -> DateSpan #
spanIntersect :: DateSpan -> DateSpan -> DateSpan #
spanStartYear :: DateSpan -> Maybe Year #
spansFromBoundaries :: Day -> [Day] -> [DateSpan] #
spansIntersect :: [DateSpan] -> DateSpan #
spansUnion :: [DateSpan] -> DateSpan #
tests_Dates :: TestTree #
yearp :: forall (m :: Type -> Type). TextParser m Integer #
data HledgerParseErrorData #
Instances
isNonNewlineSpace :: Char -> Bool #
Constructors
SourcePos | |
Fields
|
Instances
NFData SourcePos | |||||
Defined in Text.Megaparsec.Pos | |||||
Data SourcePos | |||||
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 | |||||
Defined in Text.Megaparsec.Pos Associated Types
| |||||
Read SourcePos | |||||
Defined in Text.Megaparsec.Pos | |||||
Show SourcePos | |||||
Eq SourcePos | |||||
Ord SourcePos | |||||
type Rep SourcePos | |||||
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)))) |
Instances
ToJSON Regexp | |
Defined in Hledger.Utils.Regex Methods toEncoding :: Regexp -> Encoding toJSONList :: [Regexp] -> Value toEncodingList :: [Regexp] -> Encoding | |
Read Regexp | |
Defined in Hledger.Utils.Regex | |
Show Regexp | |
Eq Regexp | |
Ord Regexp | |
RegexLike Regexp String | |
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 | |
type Replacement = String #
data AccountAlias #
Constructors
BasicAlias AccountName AccountName | |
RegexAlias Regexp Replacement |
Instances
Generic AccountAlias | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read AccountAlias | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AccountAlias readList :: ReadS [AccountAlias] readPrec :: ReadPrec AccountAlias readListPrec :: ReadPrec [AccountAlias] | |||||
Show AccountAlias | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountAlias -> ShowS show :: AccountAlias -> String showList :: [AccountAlias] -> ShowS | |||||
Eq AccountAlias | |||||
Defined in Hledger.Data.Types | |||||
Ord AccountAlias | |||||
Defined in Hledger.Data.Types Methods compare :: AccountAlias -> AccountAlias -> Ordering # (<) :: AccountAlias -> AccountAlias -> Bool # (<=) :: AccountAlias -> AccountAlias -> Bool # (>) :: AccountAlias -> AccountAlias -> Bool # (>=) :: AccountAlias -> AccountAlias -> Bool # max :: AccountAlias -> AccountAlias -> AccountAlias # min :: AccountAlias -> AccountAlias -> AccountAlias # | |||||
type Rep AccountAlias | |||||
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 #
Constructors
AccountDeclarationInfo | |
Fields
|
Instances
Generic AccountDeclarationInfo | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: AccountDeclarationInfo -> Rep AccountDeclarationInfo x to :: Rep AccountDeclarationInfo x -> AccountDeclarationInfo | |||||
Show AccountDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountDeclarationInfo -> ShowS show :: AccountDeclarationInfo -> String showList :: [AccountDeclarationInfo] -> ShowS | |||||
Eq AccountDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods (==) :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool (/=) :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool | |||||
type Rep AccountDeclarationInfo | |||||
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
Generic AccountType | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show AccountType | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AccountType -> ShowS show :: AccountType -> String showList :: [AccountType] -> ShowS | |||||
Eq AccountType | |||||
Defined in Hledger.Data.Types | |||||
Ord AccountType | |||||
Defined in Hledger.Data.Types Methods compare :: AccountType -> AccountType -> Ordering # (<) :: AccountType -> AccountType -> Bool # (<=) :: AccountType -> AccountType -> Bool # (>) :: AccountType -> AccountType -> Bool # (>=) :: AccountType -> AccountType -> Bool # max :: AccountType -> AccountType -> AccountType # min :: AccountType -> AccountType -> AccountType # | |||||
type Rep AccountType | |||||
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)))) |
Constructors
Account | |
Fields
|
Instances
Generic Account | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
type Rep Account | |||||
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 #
Instances
Generic AmountCost | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show AmountCost | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountCost -> ShowS show :: AmountCost -> String showList :: [AmountCost] -> ShowS | |||||
Eq AmountCost | |||||
Defined in Hledger.Data.Types | |||||
Ord AmountCost | |||||
Defined in Hledger.Data.Types Methods compare :: AmountCost -> AmountCost -> Ordering # (<) :: AmountCost -> AmountCost -> Bool # (<=) :: AmountCost -> AmountCost -> Bool # (>) :: AmountCost -> AmountCost -> Bool # (>=) :: AmountCost -> AmountCost -> Bool # max :: AmountCost -> AmountCost -> AmountCost # min :: AmountCost -> AmountCost -> AmountCost # | |||||
type Rep AmountCost | |||||
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
Generic AmountPrecision | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: AmountPrecision -> Rep AmountPrecision x to :: Rep AmountPrecision x -> AmountPrecision | |||||
Read AmountPrecision | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AmountPrecision readList :: ReadS [AmountPrecision] readPrec :: ReadPrec AmountPrecision readListPrec :: ReadPrec [AmountPrecision] | |||||
Show AmountPrecision | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountPrecision -> ShowS show :: AmountPrecision -> String showList :: [AmountPrecision] -> ShowS | |||||
Eq AmountPrecision | |||||
Defined in Hledger.Data.Types Methods (==) :: AmountPrecision -> AmountPrecision -> Bool (/=) :: AmountPrecision -> AmountPrecision -> Bool | |||||
Ord AmountPrecision | |||||
Defined in Hledger.Data.Types Methods compare :: AmountPrecision -> AmountPrecision -> Ordering # (<) :: AmountPrecision -> AmountPrecision -> Bool # (<=) :: AmountPrecision -> AmountPrecision -> Bool # (>) :: AmountPrecision -> AmountPrecision -> Bool # (>=) :: AmountPrecision -> AmountPrecision -> Bool # max :: AmountPrecision -> AmountPrecision -> AmountPrecision # min :: AmountPrecision -> AmountPrecision -> AmountPrecision # | |||||
type Rep AmountPrecision | |||||
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 #
Constructors
AmountStyle | |
Fields
|
Instances
Generic AmountStyle | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read AmountStyle | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS AmountStyle readList :: ReadS [AmountStyle] readPrec :: ReadPrec AmountStyle readListPrec :: ReadPrec [AmountStyle] | |||||
Show AmountStyle | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> AmountStyle -> ShowS show :: AmountStyle -> String showList :: [AmountStyle] -> ShowS | |||||
Eq AmountStyle | |||||
Defined in Hledger.Data.Types | |||||
Ord AmountStyle | |||||
Defined in Hledger.Data.Types Methods compare :: AmountStyle -> AmountStyle -> Ordering # (<) :: AmountStyle -> AmountStyle -> Bool # (<=) :: AmountStyle -> AmountStyle -> Bool # (>) :: AmountStyle -> AmountStyle -> Bool # (>=) :: AmountStyle -> AmountStyle -> Bool # max :: AmountStyle -> AmountStyle -> AmountStyle # min :: AmountStyle -> AmountStyle -> AmountStyle # | |||||
type Rep AmountStyle | |||||
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
Generic BalanceAssertion | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: BalanceAssertion -> Rep BalanceAssertion x to :: Rep BalanceAssertion x -> BalanceAssertion | |||||
Show BalanceAssertion | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> BalanceAssertion -> ShowS show :: BalanceAssertion -> String showList :: [BalanceAssertion] -> ShowS | |||||
Eq BalanceAssertion | |||||
Defined in Hledger.Data.Types Methods (==) :: BalanceAssertion -> BalanceAssertion -> Bool (/=) :: BalanceAssertion -> BalanceAssertion -> Bool | |||||
type Rep BalanceAssertion | |||||
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)))) |
Constructors
Commodity | |
Fields |
Instances
Generic Commodity | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Commodity | |||||
Eq Commodity | |||||
type Rep Commodity | |||||
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
Generic DigitGroupStyle | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: DigitGroupStyle -> Rep DigitGroupStyle x to :: Rep DigitGroupStyle x -> DigitGroupStyle | |||||
Read DigitGroupStyle | |||||
Defined in Hledger.Data.Types Methods readsPrec :: Int -> ReadS DigitGroupStyle readList :: ReadS [DigitGroupStyle] readPrec :: ReadPrec DigitGroupStyle readListPrec :: ReadPrec [DigitGroupStyle] | |||||
Show DigitGroupStyle | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> DigitGroupStyle -> ShowS show :: DigitGroupStyle -> String showList :: [DigitGroupStyle] -> ShowS | |||||
Eq DigitGroupStyle | |||||
Defined in Hledger.Data.Types Methods (==) :: DigitGroupStyle -> DigitGroupStyle -> Bool (/=) :: DigitGroupStyle -> DigitGroupStyle -> Bool | |||||
Ord DigitGroupStyle | |||||
Defined in Hledger.Data.Types Methods compare :: DigitGroupStyle -> DigitGroupStyle -> Ordering # (<) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (<=) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (>) :: DigitGroupStyle -> DigitGroupStyle -> Bool # (>=) :: DigitGroupStyle -> DigitGroupStyle -> Bool # max :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle # min :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle # | |||||
type Rep DigitGroupStyle | |||||
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]))) |
Constructors
Instances
Generic Journal | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Eq Journal | |||||
Anon Journal Source # | |||||
type Rep Journal | |||||
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))))))) |
Instances
Generic Ledger | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
type Rep Ledger | |||||
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 #
Constructors
MarketPrice | |
Fields
|
Instances
Generic MarketPrice | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show MarketPrice | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> MarketPrice -> ShowS show :: MarketPrice -> String showList :: [MarketPrice] -> ShowS | |||||
Eq MarketPrice | |||||
Defined in Hledger.Data.Types | |||||
Ord MarketPrice | |||||
Defined in Hledger.Data.Types Methods compare :: MarketPrice -> MarketPrice -> Ordering # (<) :: MarketPrice -> MarketPrice -> Bool # (<=) :: MarketPrice -> MarketPrice -> Bool # (>) :: MarketPrice -> MarketPrice -> Bool # (>=) :: MarketPrice -> MarketPrice -> Bool # max :: MarketPrice -> MarketPrice -> MarketPrice # min :: MarketPrice -> MarketPrice -> MarketPrice # | |||||
type Rep MarketPrice | |||||
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
Generic PayeeDeclarationInfo | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: PayeeDeclarationInfo -> Rep PayeeDeclarationInfo x to :: Rep PayeeDeclarationInfo x -> PayeeDeclarationInfo | |||||
Show PayeeDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PayeeDeclarationInfo -> ShowS show :: PayeeDeclarationInfo -> String showList :: [PayeeDeclarationInfo] -> ShowS | |||||
Eq PayeeDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods (==) :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool (/=) :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool | |||||
type Rep PayeeDeclarationInfo | |||||
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 #
Constructors
PeriodicTransaction | |
Fields
|
Instances
Generic PeriodicTransaction | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: PeriodicTransaction -> Rep PeriodicTransaction x to :: Rep PeriodicTransaction x -> PeriodicTransaction | |||||
Eq PeriodicTransaction | |||||
Defined in Hledger.Data.Types Methods (==) :: PeriodicTransaction -> PeriodicTransaction -> Bool (/=) :: PeriodicTransaction -> PeriodicTransaction -> Bool | |||||
type Rep PeriodicTransaction | |||||
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 #
Constructors
RegularPosting | |
VirtualPosting | |
BalancedVirtualPosting |
Instances
Generic PostingType | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show PostingType | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PostingType -> ShowS show :: PostingType -> String showList :: [PostingType] -> ShowS | |||||
Eq PostingType | |||||
Defined in Hledger.Data.Types | |||||
type Rep PostingType | |||||
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))) |
Constructors
Posting | |
Fields
|
Instances
Generic Posting | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Posting | |||||
Eq Posting | |||||
Anon Posting Source # | |||||
type Rep Posting | |||||
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 #
Constructors
PriceDirective | |
Fields
|
Instances
Generic PriceDirective | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show PriceDirective | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> PriceDirective -> ShowS show :: PriceDirective -> String showList :: [PriceDirective] -> ShowS | |||||
Eq PriceDirective | |||||
Defined in Hledger.Data.Types Methods (==) :: PriceDirective -> PriceDirective -> Bool (/=) :: PriceDirective -> PriceDirective -> Bool | |||||
Ord PriceDirective | |||||
Defined in Hledger.Data.Types Methods compare :: PriceDirective -> PriceDirective -> Ordering # (<) :: PriceDirective -> PriceDirective -> Bool # (<=) :: PriceDirective -> PriceDirective -> Bool # (>) :: PriceDirective -> PriceDirective -> Bool # (>=) :: PriceDirective -> PriceDirective -> Bool # max :: PriceDirective -> PriceDirective -> PriceDirective # min :: PriceDirective -> PriceDirective -> PriceDirective # | |||||
HasAmounts PriceDirective Source # | |||||
Defined in Hledger.Cli.Commands.Prices Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PriceDirective -> PriceDirective # | |||||
type Rep PriceDirective | |||||
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)))) |
Constructors
NoRounding | |
SoftRounding | |
HardRounding | |
AllRounding |
Instances
Generic Rounding | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Read Rounding | |||||
Defined in Hledger.Data.Types | |||||
Show Rounding | |||||
Eq Rounding | |||||
Ord Rounding | |||||
Defined in Hledger.Data.Types | |||||
type Rep Rounding | |||||
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))) |
Instances
Bounded Status | |||||
Defined in Hledger.Data.Types | |||||
Enum Status | |||||
Defined in Hledger.Data.Types | |||||
Generic Status | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Status | |||||
Eq Status | |||||
Ord Status | |||||
type Rep Status | |||||
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 | |
Fields
|
Instances
Generic TMPostingRule | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show TMPostingRule | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TMPostingRule -> ShowS show :: TMPostingRule -> String showList :: [TMPostingRule] -> ShowS | |||||
Eq TMPostingRule | |||||
Defined in Hledger.Data.Types | |||||
type Rep TMPostingRule | |||||
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
Generic TagDeclarationInfo | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: TagDeclarationInfo -> Rep TagDeclarationInfo x to :: Rep TagDeclarationInfo x -> TagDeclarationInfo | |||||
Show TagDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TagDeclarationInfo -> ShowS show :: TagDeclarationInfo -> String showList :: [TagDeclarationInfo] -> ShowS | |||||
Eq TagDeclarationInfo | |||||
Defined in Hledger.Data.Types Methods (==) :: TagDeclarationInfo -> TagDeclarationInfo -> Bool (/=) :: TagDeclarationInfo -> TagDeclarationInfo -> Bool | |||||
type Rep TagDeclarationInfo | |||||
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 #
Constructors
SetBalance | |
SetRequiredHours | |
In | |
Out | |
FinalOut |
Instances
Generic TimeclockCode | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Eq TimeclockCode | |||||
Defined in Hledger.Data.Types | |||||
Ord TimeclockCode | |||||
Defined in Hledger.Data.Types Methods compare :: TimeclockCode -> TimeclockCode -> Ordering # (<) :: TimeclockCode -> TimeclockCode -> Bool # (<=) :: TimeclockCode -> TimeclockCode -> Bool # (>) :: TimeclockCode -> TimeclockCode -> Bool # (>=) :: TimeclockCode -> TimeclockCode -> Bool # max :: TimeclockCode -> TimeclockCode -> TimeclockCode # min :: TimeclockCode -> TimeclockCode -> TimeclockCode # | |||||
type Rep TimeclockCode | |||||
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 #
Constructors
TimeclockEntry | |
Fields
|
Instances
Generic TimeclockEntry | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Eq TimeclockEntry | |||||
Defined in Hledger.Data.Types Methods (==) :: TimeclockEntry -> TimeclockEntry -> Bool (/=) :: TimeclockEntry -> TimeclockEntry -> Bool | |||||
Ord TimeclockEntry | |||||
Defined in Hledger.Data.Types Methods compare :: TimeclockEntry -> TimeclockEntry -> Ordering # (<) :: TimeclockEntry -> TimeclockEntry -> Bool # (<=) :: TimeclockEntry -> TimeclockEntry -> Bool # (>) :: TimeclockEntry -> TimeclockEntry -> Bool # (>=) :: TimeclockEntry -> TimeclockEntry -> Bool # max :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry # min :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry # | |||||
type Rep TimeclockEntry | |||||
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 #
Constructors
TransactionModifier | |
Fields
|
Instances
Generic TransactionModifier | |||||
Defined in Hledger.Data.Types Associated Types
Methods from :: TransactionModifier -> Rep TransactionModifier x to :: Rep TransactionModifier x -> TransactionModifier | |||||
Show TransactionModifier | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> TransactionModifier -> ShowS show :: TransactionModifier -> String showList :: [TransactionModifier] -> ShowS | |||||
Eq TransactionModifier | |||||
Defined in Hledger.Data.Types Methods (==) :: TransactionModifier -> TransactionModifier -> Bool (/=) :: TransactionModifier -> TransactionModifier -> Bool | |||||
type Rep TransactionModifier | |||||
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 #
Constructors
Transaction | |
Instances
Generic Transaction | |||||
Defined in Hledger.Data.Types Associated Types
| |||||
Show Transaction | |||||
Defined in Hledger.Data.Types Methods showsPrec :: Int -> Transaction -> ShowS show :: Transaction -> String showList :: [Transaction] -> ShowS | |||||
Eq Transaction | |||||
Defined in Hledger.Data.Types | |||||
Anon Transaction Source # | |||||
Defined in Hledger.Cli.Anon Methods anon :: Transaction -> Transaction Source # | |||||
type Rep Transaction | |||||
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
Constructors
DepthSpec | |
Fields
|
data NormalSign #
Constructors
NormallyPositive | |
NormallyNegative |
Instances
Show NormalSign | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> NormalSign -> ShowS show :: NormalSign -> String showList :: [NormalSign] -> ShowS | |
Eq NormalSign | |
Defined in Hledger.Data.Types |
data StorageFormat #
Instances
Show StorageFormat | |
Defined in Hledger.Data.Types Methods showsPrec :: Int -> StorageFormat -> ShowS show :: StorageFormat -> String showList :: [StorageFormat] -> ShowS | |
Eq StorageFormat | |
Defined in Hledger.Data.Types |
Constructors
PrimaryDate | |
SecondaryDate |
isAccountSubtypeOf :: AccountType -> AccountType -> Bool #
isBalanceSheetAccountType :: AccountType -> Bool #
isDecimalMark :: Char -> Bool #
isHiddenTagName :: TagName -> Bool #
isIncomeStatementAccountType :: AccountType -> Bool #
maCompare :: MixedAmount -> MixedAmount -> Ordering #
nullsourcepospair :: (SourcePos, SourcePos) #
showMarketPrice :: MarketPrice -> String #
showMarketPrices :: [MarketPrice] -> [Char] #
toHiddenTag :: Tag -> HiddenTag #
toHiddenTagName :: TagName -> TagName #
toVisibleTag :: HiddenTag -> Tag #
toVisibleTagName :: TagName -> TagName #
type AccountName = Text #
type CommoditySymbol = Text #
type DecimalMark = Char #
type ParsedJournal = Journal #
numDigitsInt :: Integral a => Int -> a #
numDigitsInteger :: Integer -> Int #
colorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder #
mixedAmountSetStyles :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount #
styleMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount #
canonicaliseMixedAmount :: Map CommoditySymbol AmountStyle -> MixedAmount -> MixedAmount #
amountSetStyles :: Map CommoditySymbol AmountStyle -> Amount -> Amount #
styleAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount #
canonicaliseAmount :: Map CommoditySymbol AmountStyle -> Amount -> Amount #
amountCost :: Amount -> Amount #
amountDisplayPrecision :: Amount -> Word8 #
amountInternalPrecision :: Amount -> Word8 #
amountIsZero :: Amount -> Bool #
amountLooksZero :: Amount -> Bool #
amountSetFullPrecision :: Amount -> Amount #
amountSetFullPrecisionUpTo :: Maybe Word8 -> Amount -> Amount #
amountSetPrecision :: AmountPrecision -> Amount -> Amount #
amountSetPrecisionMax :: Word8 -> Amount -> Amount #
amountSetPrecisionMin :: Word8 -> Amount -> Amount #
amountStripCost :: Amount -> Amount #
amountStylesSetRounding :: Rounding -> Map CommoditySymbol AmountStyle -> Map CommoditySymbol AmountStyle #
amountUnstyled :: Amount -> Amount #
amountWithCommodity :: CommoditySymbol -> Amount -> Amount #
amountsPreservingZeros :: MixedAmount -> [Amount] #
amountsRaw :: MixedAmount -> [Amount] #
averageMixedAmounts :: [MixedAmount] -> MixedAmount #
cshowAmount :: Amount -> String #
defaultMaxPrecision :: Word8 #
divideAmount :: Quantity -> Amount -> Amount #
divideMixedAmount :: Quantity -> MixedAmount -> MixedAmount #
filterMixedAmount :: (Amount -> Bool) -> MixedAmount -> MixedAmount #
invertAmount :: Amount -> Amount #
isMissingMixedAmount :: MixedAmount -> Bool #
isNegativeAmount :: Amount -> Bool #
isNegativeMixedAmount :: MixedAmount -> Maybe Bool #
isNonsimpleCommodityChar :: Char -> Bool #
maAddAmount :: MixedAmount -> Amount -> MixedAmount #
maAddAmounts :: Foldable t => MixedAmount -> t Amount -> MixedAmount #
maCommodities :: MixedAmount -> Set CommoditySymbol #
maIsNonZero :: MixedAmount -> Bool #
maIsZero :: MixedAmount -> Bool #
maMinus :: MixedAmount -> MixedAmount -> MixedAmount #
maNegate :: MixedAmount -> MixedAmount #
maPlus :: MixedAmount -> MixedAmount -> MixedAmount #
maSum :: Foldable t => t MixedAmount -> MixedAmount #
mapMixedAmount :: (Amount -> Amount) -> MixedAmount -> MixedAmount #
missingamt :: Amount #
mixed :: Foldable t => t Amount -> MixedAmount #
mixedAmount :: Amount -> MixedAmount #
mixedAmountIsZero :: MixedAmount -> Bool #
mixedAmountLooksZero :: MixedAmount -> Bool #
mixedAmountSetFullPrecisionUpTo :: Maybe Word8 -> MixedAmount -> MixedAmount #
mixedAmountSetPrecisionMax :: Word8 -> MixedAmount -> MixedAmount #
mixedAmountSetPrecisionMin :: Word8 -> MixedAmount -> MixedAmount #
multiplyAmount :: Quantity -> Amount -> Amount #
multiplyMixedAmount :: Quantity -> MixedAmount -> MixedAmount #
setAmountInternalPrecision :: Word8 -> Amount -> Amount #
showAmount :: Amount -> String #
showAmountB :: AmountFormat -> Amount -> WideBuilder #
showAmountCostB :: AmountFormat -> Amount -> WideBuilder #
showAmountDebug :: Amount -> String #
showAmountWith :: AmountFormat -> Amount -> String #
showAmountWithZeroCommodity :: Amount -> String #
showAmountWithoutCost :: Amount -> String #
showCommoditySymbol :: Text -> Text #
showMixedAmount :: MixedAmount -> String #
showMixedAmountDebug :: MixedAmount -> String #
showMixedAmountElided :: Int -> Bool -> MixedAmount -> String #
showMixedAmountLinesB :: AmountFormat -> MixedAmount -> [WideBuilder] #
showMixedAmountOneLine :: MixedAmount -> String #
showMixedAmountOneLineWithoutCost :: Bool -> MixedAmount -> String #
showMixedAmountWith :: AmountFormat -> MixedAmount -> String #
showMixedAmountWithZeroCommodity :: MixedAmount -> String #
showMixedAmountWithoutCost :: Bool -> MixedAmount -> String #
withInternalPrecision :: Amount -> Word8 -> Amount #
withPrecision :: Amount -> AmountPrecision -> Amount #
post :: AccountName -> Amount -> Posting #
sourcePosPretty :: SourcePos -> String #
data DependencyType #
Constructors
AllSucceed | |
AllFinish |
Instances
Read DependencyType | |
Defined in Test.Tasty.Core Methods readsPrec :: Int -> ReadS DependencyType readList :: ReadS [DependencyType] readPrec :: ReadPrec DependencyType readListPrec :: ReadPrec [DependencyType] | |
Show DependencyType | |
Defined in Test.Tasty.Core Methods showsPrec :: Int -> DependencyType -> ShowS show :: DependencyType -> String showList :: [DependencyType] -> ShowS | |
Eq DependencyType | |
Defined in Test.Tasty.Core Methods (==) :: DependencyType -> DependencyType -> Bool (/=) :: DependencyType -> DependencyType -> Bool |
after :: DependencyType -> String -> TestTree -> TestTree #
after_ :: DependencyType -> Expr -> TestTree -> TestTree #
sequentialTestGroup :: TestName -> DependencyType -> [TestTree] -> TestTree #
Constructors
InputOpts | |
Fields
|
Instances
txnTieKnot :: Transaction -> Transaction #
accountSetDeclarationInfo :: Journal -> Account -> Account #
accountTree :: AccountName -> [AccountName] -> Account #
accountsFromPostings :: [Posting] -> [Account] #
accountsLevels :: Account -> [[Account]] #
anyAccounts :: (Account -> Bool) -> Account -> Bool #
clipAccounts :: Int -> Account -> Account #
clipAccountsAndAggregate :: DepthSpec -> [Account] -> [Account] #
filterAccounts :: (Account -> Bool) -> Account -> [Account] #
flattenAccounts :: Account -> [Account] #
lookupAccount :: AccountName -> [Account] -> Maybe Account #
parentAccounts :: Account -> [Account] #
printAccounts :: Account -> IO () #
showAccounts :: Account -> String #
showAccountsBoringFlag :: Account -> String #
sortAccountNamesByDeclaration :: Journal -> Bool -> [AccountName] -> [AccountName] #
sortAccountTreeByAmount :: NormalSign -> Account -> Account #
sumAccounts :: Account -> Account #
accountLeafName :: AccountName -> Text #
accountNameComponents :: AccountName -> [Text] #
accountNameDrop :: Int -> AccountName -> AccountName #
accountNameFromComponents :: [Text] -> AccountName #
accountNameLevel :: AccountName -> Int #
accountNameTreeFrom :: [AccountName] -> Tree AccountName #
accountNameType :: Map AccountName AccountType -> AccountName -> Maybe AccountType #
acctsepchar :: Char #
clipAccountName :: DepthSpec -> AccountName -> AccountName #
concatAccountNames :: [AccountName] -> AccountName #
defaultBaseConversionAccount :: IsString a => a #
elideAccountName :: Int -> AccountName -> AccountName #
escapeName :: AccountName -> Text #
expandAccountName :: AccountName -> [AccountName] #
expandAccountNames :: [AccountName] -> [AccountName] #
getAccountNameClippedDepth :: DepthSpec -> AccountName -> Maybe Int #
isAccountNamePrefixOf :: AccountName -> AccountName -> Bool #
isSubAccountNameOf :: AccountName -> AccountName -> Bool #
joinAccountNames :: AccountName -> AccountName -> AccountName #
parentAccountNames :: AccountName -> [AccountName] #
subAccountNamesFrom :: [AccountName] -> AccountName -> [AccountName] #
topAccountNames :: [AccountName] -> [AccountName] #
data BalancingOpts #
Constructors
BalancingOpts | |
Fields
|
Instances
Show BalancingOpts | |
Defined in Hledger.Data.Balancing Methods showsPrec :: Int -> BalancingOpts -> ShowS show :: BalancingOpts -> String showList :: [BalancingOpts] -> ShowS | |
HasBalancingOpts BalancingOpts | |
Defined in Hledger.Data.Balancing Methods balancingOpts :: Lens' BalancingOpts BalancingOpts # commodity_styles :: Lens' BalancingOpts (Maybe (Map CommoditySymbol AmountStyle)) # ignore_assertions :: Lens' BalancingOpts Bool # infer_balancing_costs :: Lens' BalancingOpts Bool # |
class HasBalancingOpts c where #
Minimal complete definition
Methods
balancingOpts :: Lens' c BalancingOpts #
commodity_styles :: Lens' c (Maybe (Map CommoditySymbol AmountStyle)) #
ignore_assertions :: Lens' c Bool #
infer_balancing_costs :: Lens' c Bool #
Instances
HasBalancingOpts CliOpts Source # | |
Defined in Hledger.Cli.CliOptions Methods balancingOpts :: Lens' CliOpts BalancingOpts # commodity_styles :: Lens' CliOpts (Maybe (Map CommoditySymbol AmountStyle)) # ignore_assertions :: Lens' CliOpts Bool # infer_balancing_costs :: Lens' CliOpts Bool # | |
HasBalancingOpts BalancingOpts | |
Defined in Hledger.Data.Balancing Methods balancingOpts :: Lens' BalancingOpts BalancingOpts # commodity_styles :: Lens' BalancingOpts (Maybe (Map CommoditySymbol AmountStyle)) # ignore_assertions :: Lens' BalancingOpts Bool # infer_balancing_costs :: Lens' BalancingOpts Bool # | |
HasBalancingOpts InputOpts | |
Defined in Hledger.Read.InputOptions Methods balancingOpts :: Lens' InputOpts BalancingOpts # commodity_styles :: Lens' InputOpts (Maybe (Map CommoditySymbol AmountStyle)) # ignore_assertions :: Lens' InputOpts Bool # infer_balancing_costs :: Lens' InputOpts Bool # |
balanceTransaction :: BalancingOpts -> Transaction -> Either String Transaction #
balanceTransactionHelper :: BalancingOpts -> Transaction -> Either String (Transaction, [(AccountName, MixedAmount)]) #
isTransactionBalanced :: BalancingOpts -> Transaction -> Bool #
journalBalanceTransactions :: BalancingOpts -> Journal -> Either String Journal #
currencies :: [([Char], CurrencyCode, CurrencySymbol)] #
currencyCodeToSymbol :: CurrencyCode -> Maybe CurrencySymbol #
currencySymbolToCode :: CurrencySymbol -> Maybe CurrencyCode #
makeAccountTagErrorExcerpt :: (AccountName, AccountDeclarationInfo) -> TagName -> (FilePath, Int, Maybe (Int, Maybe Int), Text) #
makePostingErrorExcerpt :: Posting -> (Posting -> Transaction -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) #
makePriceDirectiveErrorExcerpt :: PriceDirective -> Maybe (PriceDirective -> Text -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) #
makeTransactionErrorExcerpt :: Transaction -> (Transaction -> Maybe (Int, Maybe Int)) -> (FilePath, Int, Maybe (Int, Maybe Int), Text) #
transactionFindPostingIndex :: (Posting -> Bool) -> Transaction -> Maybe Int #
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 #
addPriceDirective :: PriceDirective -> Journal -> Journal #
addTransaction :: Transaction -> Journal -> Journal #
canonicalStyleFrom :: [AmountStyle] -> AmountStyle #
commodityStylesFromAmounts :: [Amount] -> Either String (Map CommoditySymbol AmountStyle) #
dbgJournalAcctDeclOrder :: String -> Journal -> Journal #
filterJournalAmounts :: Query -> Journal -> Journal #
filterJournalPostings :: Query -> Journal -> Journal #
filterJournalRelatedPostings :: Query -> Journal -> Journal #
filterJournalTransactions :: Query -> Journal -> Journal #
filterTransactionAmounts :: Query -> Transaction -> Transaction #
filterTransactionPostingsExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> Transaction #
journalAccountNameTree :: Journal -> Tree AccountName #
journalAccountNames :: Journal -> [AccountName] #
journalAccountNamesUsed :: Journal -> [AccountName] #
journalAccountTags :: Journal -> AccountName -> [Tag] #
journalAccountType :: Journal -> AccountName -> Maybe AccountType #
journalAccountTypes :: Journal -> Map AccountName AccountType #
journalApplyAliases :: [AccountAlias] -> Journal -> Either RegexError Journal #
journalCommodities :: Journal -> Set CommoditySymbol #
journalCommodityStyles :: Journal -> Map CommoditySymbol AmountStyle #
journalCommodityStylesWith :: Rounding -> Journal -> Map CommoditySymbol AmountStyle #
journalConcat :: Journal -> Journal -> Journal #
journalConversionAccounts :: Journal -> [AccountName] #
journalDateSpan :: Bool -> Journal -> DateSpan #
journalDbg :: Journal -> String #
journalDescriptions :: Journal -> [Text] #
journalEndDate :: Bool -> Journal -> Maybe Day #
journalFilePath :: Journal -> FilePath #
journalFilePaths :: Journal -> [FilePath] #
journalInferCommodityStyles :: Journal -> Either String Journal #
journalInferEquityFromCosts :: Bool -> Journal -> Journal #
journalInheritedAccountTags :: Journal -> AccountName -> [Tag] #
journalLastDay :: Bool -> Journal -> Maybe Day #
journalLeafAccountNames :: Journal -> [AccountName] #
journalMapPostingAmounts :: (MixedAmount -> MixedAmount) -> Journal -> Journal #
journalMapTransactions :: (Transaction -> Transaction) -> Journal -> Journal #
journalPayeesDeclared :: Journal -> [Payee] #
journalPayeesDeclaredOrUsed :: Journal -> [Payee] #
journalPayeesUsed :: Journal -> [Payee] #
journalPivot :: Text -> Journal -> Journal #
journalPostingAmounts :: Journal -> [MixedAmount] #
journalPostings :: Journal -> [Posting] #
journalReverse :: Journal -> Journal #
journalSetLastReadTime :: POSIXTime -> Journal -> Journal #
journalStartDate :: Bool -> Journal -> Maybe Day #
journalStyleAmounts :: Journal -> Either String Journal #
journalTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> Journal -> Either String Journal #
journalTagsDeclared :: Journal -> [TagName] #
journalTagsDeclaredOrUsed :: Journal -> [TagName] #
journalTagsUsed :: Journal -> [TagName] #
journalToCost :: ConversionOp -> Journal -> Journal #
journalTransactionAt :: Journal -> Integer -> Maybe Transaction #
journalTransactionsSimilarTo :: Journal -> Text -> Query -> SimilarityScore -> Int -> [(DateWeightedSimilarityScore, Age, SimilarityScore, Transaction)] #
nulljournal :: Journal #
samplejournalMaybeExplicit :: Bool -> Journal #
showJournalAmountsDebug :: Journal -> String #
journalCheckAccounts :: Journal -> Either String () #
journalCheckBalanceAssertions :: Journal -> Either String () #
journalCheckCommodities :: Journal -> Either String () #
journalCheckPairedConversionPostings :: Journal -> Either String () #
journalCheckPayees :: Journal -> Either String () #
journalCheckRecentAssertions :: Journal -> Either String () #
journalCheckTags :: Journal -> Either String () #
journalStrictChecks :: Journal -> Either String () #
journalCheckOrdereddates :: Journal -> Either String () #
journalCheckUniqueleafnames :: Journal -> Either String () #
readJsonFile :: FromJSON a => FilePath -> IO a #
toJsonText :: ToJSON a => a -> Text #
writeJsonFile :: ToJSON a => FilePath -> a -> IO () #
ledgerAccount :: Ledger -> AccountName -> Maybe Account #
ledgerAccountNames :: Ledger -> [AccountName] #
ledgerCommodities :: Ledger -> [CommoditySymbol] #
ledgerDateSpan :: Ledger -> DateSpan #
ledgerFromJournal :: Query -> Journal -> Ledger #
ledgerLeafAccounts :: Ledger -> [Account] #
ledgerPostings :: Ledger -> [Posting] #
ledgerRootAccount :: Ledger -> Account #
ledgerTopAccounts :: Ledger -> [Account] #
nullledger :: Ledger #
firstMonthOfQuarter :: Num a => a -> a #
isLastDayOfMonth :: (Eq a1, Eq a2, Num a1, Num a2) => Year -> a1 -> a2 -> Bool #
isStandardPeriod :: Period -> Bool #
mondayBefore :: Day -> Day #
periodGrow :: Period -> Period #
periodMoveTo :: Day -> Period -> Period #
periodNext :: Period -> Period #
periodNextIn :: DateSpan -> Period -> Period #
periodPrevious :: Period -> Period #
periodPreviousIn :: DateSpan -> Period -> Period #
periodShrink :: Day -> Period -> Period #
periodStart :: Period -> Maybe Day #
periodTextWidth :: Period -> Int #
quarterContainingMonth :: Integral a => a -> a #
simplifyPeriod :: Period -> Period #
startOfFirstWeekInMonth :: Year -> MonthOfYear -> Day #
yearMonthContainingWeekStarting :: Day -> (Year, MonthOfYear) #
runPeriodicTransaction :: Bool -> PeriodicTransaction -> DateSpan -> [Transaction] #
accountNamesFromPostings :: [Posting] -> [AccountName] #
balassert :: Amount -> Maybe BalanceAssertion #
balassertTot :: Amount -> Maybe BalanceAssertion #
commentAddTag :: Text -> Tag -> Text #
commentAddTagNextLine :: Text -> Tag -> Text #
commentAddTagUnspaced :: Text -> Tag -> Text #
commentJoin :: Text -> Text -> Text #
hasBalanceAssignment :: Posting -> Bool #
isBalancedVirtual :: Posting -> Bool #
isEmptyPosting :: Posting -> Bool #
isPostingInDateSpan :: DateSpan -> Posting -> Bool #
isPostingInDateSpan' :: WhichDate -> DateSpan -> Posting -> Bool #
negatePostingAmount :: Posting -> Posting #
nullposting :: Posting #
originalPosting :: Posting -> Posting #
post' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting #
postingAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Posting -> Posting #
postingAddInferredEquityPostings :: Bool -> Text -> Posting -> [Posting] #
postingAddTags :: Posting -> [Tag] -> Posting #
postingAllTags :: Posting -> [Tag] #
postingApplyAliases :: [AccountAlias] -> Posting -> Either RegexError Posting #
postingApplyCommodityStyles :: Map CommoditySymbol AmountStyle -> Posting -> Posting #
postingApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Posting -> Posting #
postingAsLines :: Bool -> Bool -> Int -> Int -> Posting -> ([Text], Int, Int) #
postingDate :: Posting -> Day #
postingDate2 :: Posting -> Day #
postingDateOrDate2 :: WhichDate -> Posting -> Day #
postingIndent :: Text -> Text #
postingStatus :: Posting -> Status #
postingStripCosts :: Posting -> Posting #
postingStyleAmounts :: Map CommoditySymbol AmountStyle -> Posting -> Posting #
postingToCost :: ConversionOp -> Posting -> Maybe Posting #
postingTransformAmount :: (MixedAmount -> MixedAmount) -> Posting -> Posting #
postingsAsLines :: Bool -> [Posting] -> [Text] #
relatedPostings :: Posting -> [Posting] #
renderCommentLines :: Text -> [Text] #
showAccountName :: Maybe Int -> PostingType -> AccountName -> Text #
showPosting :: Posting -> String #
showPostingLines :: Posting -> [Text] #
sumPostings :: [Posting] -> MixedAmount #
transactionAllTags :: Transaction -> [Tag] #
vpost :: AccountName -> Amount -> Posting #
vpost' :: AccountName -> Amount -> Maybe BalanceAssertion -> Posting #
appendopts :: [(String, String)] -> RawOpts -> RawOpts #
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 #
overRawOpts :: ([(String, String)] -> [(String, String)]) -> RawOpts -> RawOpts #
setboolopt :: String -> RawOpts -> RawOpts #
unsetboolopt :: String -> RawOpts -> RawOpts #
data ReportItemField #
Constructors
AccountField | |
DefaultDateField | |
DescriptionField | |
TotalField | |
DepthSpacerField | |
FieldNo Int |
Instances
Show ReportItemField | |
Defined in Hledger.Data.StringFormat Methods showsPrec :: Int -> ReportItemField -> ShowS show :: ReportItemField -> String showList :: [ReportItemField] -> ShowS | |
Eq ReportItemField | |
Defined in Hledger.Data.StringFormat Methods (==) :: ReportItemField -> ReportItemField -> Bool (/=) :: ReportItemField -> ReportItemField -> Bool |
data StringFormat #
Constructors
OneLine [StringFormatComponent] | |
TopAligned [StringFormatComponent] | |
BottomAligned [StringFormatComponent] |
Instances
Default StringFormat | |
Defined in Hledger.Data.StringFormat Methods def :: StringFormat | |
Show StringFormat | |
Defined in Hledger.Data.StringFormat Methods showsPrec :: Int -> StringFormat -> ShowS show :: StringFormat -> String showList :: [StringFormat] -> ShowS | |
Eq StringFormat | |
Defined in Hledger.Data.StringFormat |
data StringFormatComponent #
Constructors
FormatLiteral Text | |
FormatField Bool (Maybe Int) (Maybe Int) ReportItemField |
Instances
Show StringFormatComponent | |
Defined in Hledger.Data.StringFormat Methods showsPrec :: Int -> StringFormatComponent -> ShowS show :: StringFormatComponent -> String showList :: [StringFormatComponent] -> ShowS | |
Eq StringFormatComponent | |
Defined in Hledger.Data.StringFormat Methods (==) :: StringFormatComponent -> StringFormatComponent -> Bool (/=) :: StringFormatComponent -> StringFormatComponent -> Bool |
parseStringFormat :: Text -> Either String StringFormat #
timeclockEntriesToTransactions :: LocalTime -> [TimeclockEntry] -> [Transaction] #
annotateErrorWithTransaction :: Transaction -> String -> String #
assignmentPostings :: Transaction -> [Posting] #
balancedVirtualPostings :: Transaction -> [Posting] #
hasRealPostings :: Transaction -> Bool #
partitionAndCheckConversionPostings :: Bool -> [AccountName] -> [IdxPosting] -> Either Text ([(IdxPosting, IdxPosting)], ([IdxPosting], [IdxPosting])) #
payeeAndNoteFromDescription :: Text -> (Text, Text) #
payeeAndNoteFromDescription' :: Text -> (Text, Text) #
realPostings :: Transaction -> [Posting] #
showTransaction :: Transaction -> Text #
transaction :: Day -> [Posting] -> Transaction #
transactionAddHiddenAndMaybeVisibleTag :: Bool -> HiddenTag -> Transaction -> Transaction #
transactionAddTags :: Transaction -> [Tag] -> Transaction #
transactionAmounts :: Transaction -> [MixedAmount] #
transactionApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> ValuationType -> Transaction -> Transaction #
transactionDate2 :: Transaction -> Day #
transactionDateOrDate2 :: WhichDate -> Transaction -> Day #
transactionFile :: Transaction -> FilePath #
transactionInferEquityPostings :: Bool -> AccountName -> Transaction -> Transaction #
transactionMapPostingAmounts :: (MixedAmount -> MixedAmount) -> Transaction -> Transaction #
transactionMapPostings :: (Posting -> Posting) -> Transaction -> Transaction #
transactionNote :: Transaction -> Text #
transactionPayee :: Transaction -> Text #
transactionTagCostsAndEquityAndMaybeInferCosts :: Bool -> Bool -> [AccountName] -> Transaction -> Either String Transaction #
transactionToCost :: ConversionOp -> Transaction -> Transaction #
transactionTransformPostings :: (Posting -> Posting) -> Transaction -> Transaction #
transactionsPostings :: [Transaction] -> [Posting] #
txnUntieKnot :: Transaction -> Transaction #
virtualPostings :: Transaction -> [Posting] #
modifyTransactions :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Map CommoditySymbol AmountStyle -> Day -> Bool -> [TransactionModifier] -> [Transaction] -> Either String [Transaction] #
data ValuationType #
Constructors
AtThen (Maybe CommoditySymbol) | |
AtEnd (Maybe CommoditySymbol) | |
AtNow (Maybe CommoditySymbol) | |
AtDate Day (Maybe CommoditySymbol) |
Instances
Show ValuationType | |
Defined in Hledger.Data.Valuation Methods showsPrec :: Int -> ValuationType -> ShowS show :: ValuationType -> String showList :: [ValuationType] -> ShowS | |
Eq ValuationType | |
Defined in Hledger.Data.Valuation |
data ConversionOp #
Constructors
NoConversionOp | |
ToCost |
Instances
Show ConversionOp | |
Defined in Hledger.Data.Valuation Methods showsPrec :: Int -> ConversionOp -> ShowS show :: ConversionOp -> String showList :: [ConversionOp] -> ShowS | |
Eq ConversionOp | |
Defined in Hledger.Data.Valuation |
type PriceOracle = (Day, CommoditySymbol, Maybe CommoditySymbol) -> Maybe (CommoditySymbol, Quantity) #
journalPriceOracle :: Bool -> Journal -> PriceOracle #
mixedAmountApplyGain :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount #
mixedAmountApplyValuation :: PriceOracle -> Map CommoditySymbol AmountStyle -> Day -> Day -> Day -> ValuationType -> MixedAmount -> MixedAmount #
mixedAmountGainAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount #
mixedAmountToCost :: Map CommoditySymbol AmountStyle -> ConversionOp -> MixedAmount -> MixedAmount #
mixedAmountValueAtDate :: PriceOracle -> Map CommoditySymbol AmountStyle -> Maybe CommoditySymbol -> Day -> MixedAmount -> MixedAmount #
tests_Data :: TestTree #
matchesAmount :: Query -> Amount -> Bool #
matchesPosting :: Query -> Posting -> Bool #
matchesPostingExtra :: (AccountName -> Maybe AccountType) -> Query -> Posting -> Bool #
matchesTransaction :: Query -> Transaction -> Bool #
matchesTransactionExtra :: (AccountName -> Maybe AccountType) -> Query -> Transaction -> Bool #
treeLeaves :: Tree a -> [a] #
debugLevel :: Int #
traceOrLogAtWith :: Int -> (a -> String) -> a -> a #
type RegexError = String #
filterQuery :: (Query -> Bool) -> Query -> Query #
queryIsDepth :: Query -> Bool #
queryIsSym :: Query -> Bool #
sourcePosPairPretty :: (SourcePos, SourcePos) -> String #
initialPos :: FilePath -> SourcePos #
spacenonewline :: forall s (m :: Type -> Type). (Stream s, Char ~ Token s) => ParsecT HledgerParseErrorData s m Char #
emptyorcommentlinep2 :: forall (m :: Type -> Type). [Char] -> TextParser m () #
Constructors
QueryOptInAcctOnly AccountName | |
QueryOptInAcct AccountName |
filterQueryOrNotQuery :: (Query -> Bool) -> Query -> Query #
inAccount :: [QueryOpt] -> Maybe (AccountName, Bool) #
inAccountQuery :: [QueryOpt] -> Maybe Query #
matchesAccount :: Query -> AccountName -> Bool #
matchesAccountExtra :: (AccountName -> Maybe AccountType) -> (AccountName -> [Tag]) -> Query -> AccountName -> Bool #
matchesCommodity :: Query -> CommoditySymbol -> Bool #
matchesDescription :: Query -> Text -> Bool #
matchesMixedAmount :: Query -> MixedAmount -> Bool #
matchesPayeeWIP :: Query -> Payee -> Bool #
matchesPriceDirective :: Query -> PriceDirective -> Bool #
matchesQuery :: (Query -> Bool) -> Query -> Bool #
parseAccountType :: Bool -> Text -> Either String AccountType #
parseDepthSpec :: Text -> Either RegexError DepthSpec #
queryDateSpan :: Bool -> Query -> DateSpan #
queryDateSpan' :: Query -> DateSpan #
queryDepth :: Query -> DepthSpec #
queryEndDate :: Bool -> Query -> Maybe Day #
queryIsAcct :: Query -> Bool #
queryIsAmt :: Query -> Bool #
queryIsCode :: Query -> Bool #
queryIsDate :: Query -> Bool #
queryIsDate2 :: Query -> Bool #
queryIsDateOrDate2 :: Query -> Bool #
queryIsDesc :: Query -> Bool #
queryIsNull :: Query -> Bool #
queryIsReal :: Query -> Bool #
queryIsStartDateOnly :: Bool -> Query -> Bool #
queryIsStatus :: Query -> Bool #
queryIsTag :: Query -> Bool #
queryIsTransactionRelated :: Query -> Bool #
queryIsType :: Query -> Bool #
queryStartDate :: Bool -> Query -> Maybe Day #
queryprefixes :: [Text] #
simplifyQuery :: Query -> Query #
tests_Query :: TestTree #
type PrefixedFilePath = FilePath #
defaultJournal :: IO Journal #
defaultJournalPath :: IO String #
ensureJournalFileExists :: FilePath -> IO () #
orDieTrying :: MonadIO m => ExceptT String m a -> m a #
readJournal' :: Text -> IO Journal #
readJournalFile :: InputOpts -> PrefixedFilePath -> ExceptT String IO Journal #
readJournalFiles :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO Journal #
readJournalFiles' :: [PrefixedFilePath] -> IO Journal #
readJournalFilesAndLatestDates :: InputOpts -> [PrefixedFilePath] -> ExceptT String IO (Journal, [LatestDatesForFile]) #
requireJournalFileExists :: FilePath -> IO () #
saveLatestDates :: LatestDates -> FilePath -> IO () #
saveLatestDatesForFiles :: [LatestDatesForFile] -> IO () #
tests_Read :: TestTree #
data Reader (m :: Type -> Type) #
Constructors
Reader | |
Fields
|
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 () #
aliasesFromOpts :: InputOpts -> [AccountAlias] #
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) #
getDefaultCommodityAndStyle :: forall (m :: Type -> Type). JournalParser m (Maybe (CommoditySymbol, AmountStyle)) #
getParentAccount :: forall (m :: Type -> Type). JournalParser m AccountName #
getYear :: forall (m :: Type -> Type). JournalParser m (Maybe Year) #
initialiseAndParseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal #
isLineCommentStart :: Char -> Bool #
isSameLineCommentStart :: Char -> Bool #
journalAddAutoPostings :: Bool -> Day -> BalancingOpts -> Journal -> Either String Journal #
journalFinalise :: InputOpts -> FilePath -> Text -> ParsedJournal -> ExceptT String IO Journal #
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) #
parseAndFinaliseJournal :: ErroringJournalParser IO ParsedJournal -> InputOpts -> FilePath -> Text -> ExceptT String IO Journal #
parseamount :: String -> Either HledgerParseErrors Amount #
parseamount' :: String -> Amount #
parsemixedamount :: String -> Either HledgerParseErrors MixedAmount #
parsemixedamount' :: String -> MixedAmount #
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) #
runJournalParser :: Monad m => JournalParser m a -> Text -> m (Either HledgerParseErrors a) #
splitReaderPrefix :: PrefixedFilePath -> (Maybe StorageFormat, FilePath) #
tmpostingrulep :: forall (m :: Type -> Type). Maybe Year -> JournalParser m TMPostingRule #
type AccountTransactionsReportItem = (Transaction, Transaction, Bool, Text, MixedAmount, MixedAmount) #
accountTransactionsReportByCommodity :: AccountTransactionsReport -> [(CommoditySymbol, AccountTransactionsReport)] #
accountTransactionsReportItems :: Query -> Query -> MixedAmount -> (MixedAmount -> MixedAmount) -> (AccountName -> Maybe AccountType) -> [(Day, Transaction)] -> [AccountTransactionsReportItem] #
transactionRegisterDate :: WhichDate -> Query -> Query -> Transaction -> Day #
triBalance :: (a, b, c, d, e, f) -> f #
triCommodityAmount :: CommoditySymbol -> (a, b, c, d, MixedAmount, f) -> MixedAmount #
triCommodityBalance :: CommoditySymbol -> (a, b, c, d, e, MixedAmount) -> MixedAmount #
triDate :: (a, Transaction, c, d, e, f) -> Day #
triOrigTransaction :: (a, b, c, d, e, f) -> a #
type BalanceReport = ([BalanceReportItem], MixedAmount) #
type BalanceReportItem = (AccountName, AccountName, Int, MixedAmount) #
balanceReport :: ReportSpec -> Journal -> BalanceReport #
flatShowsExclusiveBalance :: Bool #
type BudgetAverage = Average #
type BudgetCell = (Maybe Change, Maybe BudgetGoal) #
type BudgetGoal = Change #
type BudgetTotal = Total #
budgetReport :: ReportSpec -> BalancingOpts -> DateSpan -> Journal -> BudgetReport #
combineBudgetAndActual :: ReportOpts -> Journal -> MultiBalanceReport -> MultiBalanceReport -> BudgetReport #
type EntriesReport = [EntriesReportItem] #
type EntriesReportItem = Transaction #
entriesReport :: ReportSpec -> Journal -> EntriesReport #
compoundBalanceReport :: ReportSpec -> Journal -> [CBCSubreportSpec a] -> CompoundPeriodicReport a MixedAmount #
compoundBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> [CBCSubreportSpec a] -> CompoundPeriodicReport a MixedAmount #
generateMultiBalanceReport :: ReportSpec -> Journal -> PriceOracle -> Set AccountName -> [(DateSpan, [Posting])] -> HashMap AccountName Account -> MultiBalanceReport #
getPostings :: ReportSpec -> Journal -> PriceOracle -> [Posting] #
getPostingsByColumn :: ReportSpec -> Journal -> PriceOracle -> [DateSpan] -> [(DateSpan, [Posting])] #
makeReportQuery :: ReportSpec -> DateSpan -> ReportSpec #
multiBalanceReportWith :: ReportSpec -> Journal -> PriceOracle -> Set AccountName -> MultiBalanceReport #
sortRows :: ReportOpts -> Journal -> [MultiBalanceReportRow] -> [MultiBalanceReportRow] #
sortRowsLike :: [AccountName] -> [PeriodicReportRow DisplayName b] -> [PeriodicReportRow DisplayName b] #
startingPostings :: ReportSpec -> Journal -> PriceOracle -> DateSpan -> [Posting] #
type PostingsReport = [PostingsReportItem] #
type PostingsReportItem = (Maybe Day, Maybe Period, Maybe Text, Posting, MixedAmount) #
mkpostingsReportItem :: Bool -> Bool -> WhichDate -> Maybe Period -> Posting -> MixedAmount -> PostingsReportItem #
postingsReport :: ReportSpec -> Journal -> PostingsReport #
data AccountListMode #
Instances
Default AccountListMode | |
Defined in Hledger.Reports.ReportOptions Methods | |
Show AccountListMode | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> AccountListMode -> ShowS show :: AccountListMode -> String showList :: [AccountListMode] -> ShowS | |
Eq AccountListMode | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: AccountListMode -> AccountListMode -> Bool (/=) :: AccountListMode -> AccountListMode -> Bool |
Constructors
AbsAmount' Bool | |
Account' Bool | |
Amount' Bool | |
Date' Bool | |
Description' Bool |
Instances
data BalanceAccumulation #
Constructors
PerPeriod | |
Cumulative | |
Historical |
Instances
Default BalanceAccumulation | |
Defined in Hledger.Reports.ReportOptions Methods | |
Show BalanceAccumulation | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> BalanceAccumulation -> ShowS show :: BalanceAccumulation -> String showList :: [BalanceAccumulation] -> ShowS | |
Eq BalanceAccumulation | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: BalanceAccumulation -> BalanceAccumulation -> Bool (/=) :: BalanceAccumulation -> BalanceAccumulation -> Bool |
data BalanceCalculation #
Constructors
CalcChange | |
CalcBudget | |
CalcValueChange | |
CalcGain | |
CalcPostingsCount |
Instances
Default BalanceCalculation | |
Defined in Hledger.Reports.ReportOptions Methods | |
Show BalanceCalculation | |
Defined in Hledger.Reports.ReportOptions Methods showsPrec :: Int -> BalanceCalculation -> ShowS show :: BalanceCalculation -> String showList :: [BalanceCalculation] -> ShowS | |
Eq BalanceCalculation | |
Defined in Hledger.Reports.ReportOptions Methods (==) :: BalanceCalculation -> BalanceCalculation -> Bool (/=) :: BalanceCalculation -> BalanceCalculation -> Bool |
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
class HasReportSpec c where #
Minimal complete definition
Methods
reportSpec :: Lens' c ReportSpec #
rsQueryOpts :: Lens' c [QueryOpt] #
rsReportOpts :: Lens' c ReportOpts #
Instances
HasReportSpec CliOpts Source # | |
Defined in Hledger.Cli.CliOptions Methods reportSpec :: Lens' CliOpts ReportSpec # rsQuery :: Lens' CliOpts Query # rsQueryOpts :: Lens' CliOpts [QueryOpt] # rsReportOpts :: Lens' CliOpts ReportOpts # | |
HasReportSpec ReportSpec | |
Defined in Hledger.Reports.ReportOptions Methods reportSpec :: Lens' ReportSpec ReportSpec # rsDay :: Lens' ReportSpec Day # rsQuery :: Lens' ReportSpec Query # rsQueryOpts :: Lens' ReportSpec [QueryOpt] # rsReportOpts :: Lens' ReportSpec ReportOpts # |
Constructors
LayoutWide (Maybe Int) | |
LayoutTall | |
LayoutBare | |
LayoutTidy |
data ReportSpec #
Constructors
ReportSpec | |
Fields
|
Instances
defsortspec :: SortSpec #
flat_ :: ReportOpts -> Bool #
intervalFromRawOpts :: RawOpts -> Interval #
mixedAmountApplyValuationAfterSumFromOptsWith :: ReportOpts -> Journal -> PriceOracle -> DateSpan -> MixedAmount -> MixedAmount #
overEither :: ((a -> Either e b) -> s -> Either e t) -> (a -> b) -> s -> Either e t #
postingDateFn :: ReportOpts -> Posting -> Day #
queryFromFlags :: ReportOpts -> Query #
rawOptsToReportOpts :: Day -> Bool -> RawOpts -> ReportOpts #
rawOptsToReportSpec :: Day -> Bool -> RawOpts -> Either String ReportSpec #
reportEndDate :: Journal -> ReportSpec -> Maybe Day #
reportOptsToSpec :: Day -> ReportOpts -> Either String ReportSpec #
reportOptsToggleStatus :: Status -> ReportOpts -> ReportOpts #
reportPeriodLastDay :: ReportSpec -> Maybe Day #
reportPeriodName :: BalanceAccumulation -> [DateSpan] -> DateSpan -> Text #
reportPeriodOrJournalLastDay :: ReportSpec -> Journal -> Maybe Day #
reportPeriodOrJournalStart :: ReportSpec -> Journal -> Maybe Day #
reportPeriodStart :: ReportSpec -> Maybe Day #
reportSpan :: Journal -> ReportSpec -> (DateSpan, [DateSpan]) #
reportSpanBothDates :: Journal -> ReportSpec -> (DateSpan, [DateSpan]) #
reportStartDate :: Journal -> ReportSpec -> Maybe Day #
simplifyStatuses :: Ord a => [a] -> [a] #
sortKeysDescription :: [Char] #
transactionDateFn :: ReportOpts -> Transaction -> Day #
tree_ :: ReportOpts -> Bool #
updateReportSpec :: ReportOpts -> ReportSpec -> Either String ReportSpec #
updateReportSpecWith :: (ReportOpts -> ReportOpts) -> ReportSpec -> Either String ReportSpec #
whichDate :: ReportOpts -> WhichDate #
type Average = MixedAmount #
data CBCSubreportSpec a #
Constructors
CBCSubreportSpec | |
type Change = MixedAmount #
data CompoundPeriodicReport a b #
Constructors
CompoundPeriodicReport | |
Fields
|
Instances
Functor (CompoundPeriodicReport a) | |||||
Defined in Hledger.Reports.ReportTypes Methods fmap :: (a0 -> b) -> CompoundPeriodicReport a a0 -> CompoundPeriodicReport a b # (<$) :: a0 -> CompoundPeriodicReport a b -> CompoundPeriodicReport a a0 # | |||||
(ToJSON b, ToJSON a) => ToJSON (CompoundPeriodicReport a b) | |||||
Defined in Hledger.Reports.ReportTypes Methods toJSON :: CompoundPeriodicReport a b -> Value toEncoding :: CompoundPeriodicReport a b -> Encoding toJSONList :: [CompoundPeriodicReport a b] -> Value toEncodingList :: [CompoundPeriodicReport a b] -> Encoding omitField :: CompoundPeriodicReport a b -> Bool | |||||
Generic (CompoundPeriodicReport a b) | |||||
Defined in Hledger.Reports.ReportTypes Associated Types
Methods from :: CompoundPeriodicReport a b -> Rep (CompoundPeriodicReport a b) x to :: Rep (CompoundPeriodicReport a b) x -> CompoundPeriodicReport a b | |||||
(Show a, Show b) => Show (CompoundPeriodicReport a b) | |||||
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) | |||||
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> CompoundPeriodicReport a b -> CompoundPeriodicReport a b # | |||||
type Rep (CompoundPeriodicReport a b) | |||||
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
ToJSON DisplayName | |
Defined in Hledger.Reports.ReportTypes Methods toJSON :: DisplayName -> Value toEncoding :: DisplayName -> Encoding toJSONList :: [DisplayName] -> Value toEncodingList :: [DisplayName] -> Encoding omitField :: DisplayName -> Bool | |
Show DisplayName | |
Defined in Hledger.Reports.ReportTypes Methods showsPrec :: Int -> DisplayName -> ShowS show :: DisplayName -> String showList :: [DisplayName] -> ShowS | |
Eq DisplayName | |
Defined in Hledger.Reports.ReportTypes | |
Ord DisplayName | |
Defined in Hledger.Reports.ReportTypes Methods compare :: DisplayName -> DisplayName -> Ordering # (<) :: DisplayName -> DisplayName -> Bool # (<=) :: DisplayName -> DisplayName -> Bool # (>) :: DisplayName -> DisplayName -> Bool # (>=) :: DisplayName -> DisplayName -> Bool # max :: DisplayName -> DisplayName -> DisplayName # min :: DisplayName -> DisplayName -> DisplayName # |
type Percentage = Decimal #
data PeriodicReport a b #
Constructors
PeriodicReport | |
Fields
|
Instances
Bifunctor PeriodicReport | |||||
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) | |||||
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) | |||||
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) | |||||
Defined in Hledger.Reports.ReportTypes Associated Types
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) | |||||
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) | |||||
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PeriodicReport a b -> PeriodicReport a b # | |||||
HasAmounts b => HasAmounts (Text, PeriodicReport a b, Bool) | |||||
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) | |||||
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
Bifunctor PeriodicReportRow | |||||
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) | |||||
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) | |||||
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) | |||||
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) | |||||
Defined in Hledger.Reports.ReportTypes Associated Types
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) | |||||
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) | |||||
Defined in Hledger.Reports.ReportTypes Methods styleAmounts :: Map CommoditySymbol AmountStyle -> PeriodicReportRow a b -> PeriodicReportRow a b # | |||||
type Rep (PeriodicReportRow a b) | |||||
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)))) |
periodicReportSpan :: PeriodicReport a b -> DateSpan #
prMapMaybeName :: (a -> Maybe b) -> PeriodicReport a c -> PeriodicReport b c #
prMapName :: (a -> b) -> PeriodicReport a c -> PeriodicReport b c #
prrAdd :: Semigroup b => PeriodicReportRow a b -> PeriodicReportRow a b -> PeriodicReportRow a b #
prrIndent :: PeriodicReportRow DisplayName a -> Int #
prrShowDebug :: PeriodicReportRow DisplayName MixedAmount -> String #
makeHledgerClassyLenses :: Name -> DecsQ #
maximumStrict :: Ord a => [a] -> a #
minimumStrict :: Ord a => [a] -> a #
tests_Utils :: TestTree #
data GhcDebugMode #
Constructors
GDNotSupported | |
GDDisabled | |
GDNoPause | |
GDPauseAtStart | |
GDPauseAtEnd |
Instances
Show GhcDebugMode | |
Defined in Hledger.Utils.Debug Methods showsPrec :: Int -> GhcDebugMode -> ShowS show :: GhcDebugMode -> String showList :: [GhcDebugMode] -> ShowS | |
Eq GhcDebugMode | |
Defined in Hledger.Utils.Debug | |
Ord GhcDebugMode | |
Defined in Hledger.Utils.Debug Methods compare :: GhcDebugMode -> GhcDebugMode -> Ordering # (<) :: GhcDebugMode -> GhcDebugMode -> Bool # (<=) :: GhcDebugMode -> GhcDebugMode -> Bool # (>) :: GhcDebugMode -> GhcDebugMode -> Bool # (>=) :: GhcDebugMode -> GhcDebugMode -> Bool # max :: GhcDebugMode -> GhcDebugMode -> GhcDebugMode # min :: GhcDebugMode -> GhcDebugMode -> GhcDebugMode # |
ghcDebugPause' :: IO () #
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 #
withGhcDebug' :: a -> a #
bgColorB :: ColorIntensity -> Color -> WideBuilder -> WideBuilder #
brightBlack' :: String -> String #
brightBlue' :: String -> String #
brightCyan' :: String -> String #
brightGreen' :: String -> String #
brightMagenta' :: String -> String #
brightRed' :: String -> String #
brightWhite' :: String -> String #
brightYellow' :: String -> String #
colorOption :: IO YNA #
expandHomePath :: FilePath -> IO FilePath #
getTerminalHeight :: IO (Maybe Int) #
getTerminalHeightWidth :: IO (Maybe (Int, Int)) #
getTerminalWidth :: IO (Maybe Int) #
readFileOrStdinPortably :: String -> IO Text #
readFilePortably :: FilePath -> IO Text #
readFileStrictly :: FilePath -> IO Text #
readHandlePortably :: Handle -> IO Text #
setupPager :: IO () #
sortByModTime :: [FilePath] -> IO [FilePath] #
terminalBgColor :: Maybe (RGB Float) #
terminalFgColor :: Maybe (RGB Float) #
terminalIsLight :: Maybe Bool #
terminalLightness :: Maybe Float #
usageError :: String -> a #
useColorOnStderr :: IO Bool #
useColorOnStderrUnsafe :: Bool #
useColorOnStdout :: IO Bool #
useColorOnStdoutUnsafe :: Bool #
data FinalParseError' e #
Instances
Monoid (FinalParseError' e) | |
Defined in Hledger.Utils.Parse Methods mempty :: FinalParseError' e mappend :: FinalParseError' e -> FinalParseError' e -> FinalParseError' e mconcat :: [FinalParseError' e] -> FinalParseError' e | |
Semigroup (FinalParseError' e) | |
Defined in Hledger.Utils.Parse Methods (<>) :: FinalParseError' e -> FinalParseError' e -> FinalParseError' e sconcat :: NonEmpty (FinalParseError' e) -> FinalParseError' e stimes :: Integral b => b -> FinalParseError' e -> FinalParseError' e | |
Show e => Show (FinalParseError' e) | |
Defined in Hledger.Utils.Parse Methods showsPrec :: Int -> FinalParseError' e -> ShowS show :: FinalParseError' e -> String showList :: [FinalParseError' e] -> ShowS |
data FinalParseErrorBundle' e #
Instances
Show e => Show (FinalParseErrorBundle' e) | |
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 #
type SimpleTextParser = Parsec HledgerParseErrorData Text #
data SourceExcerpt #
attachSource :: FilePath -> Text -> FinalParseError' e -> FinalParseErrorBundle' e #
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 #
getExcerptText :: SourceExcerpt -> Text #
nonspace :: forall (m :: Type -> Type). TextParser m Char #
parseErrorAt :: Int -> String -> HledgerParseErrorData #
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 #
rtp :: TextParser Identity a -> Text -> Either HledgerParseErrors a #
runTextParser :: TextParser Identity a -> Text -> Either HledgerParseErrors a #
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 #
regexMatchTextGroups :: Regexp -> Text -> [Text] #
regexReplace :: Regexp -> Replacement -> String -> Either RegexError String #
regexReplaceAllBy :: Regexp -> (String -> String) -> String -> String #
regexReplaceUnmemo :: Regexp -> Replacement -> String -> Either RegexError String #
toRegexCI' :: Text -> Regexp #
capitalise :: String -> String #
elideRight :: Int -> String -> String #
quoteForCommandLine :: String -> String #
quoteIfNeeded :: String -> String #
singleQuoteIfNeeded :: String -> String #
singleline :: String -> String #
strWidthAnsi :: String -> Int #
strip1Char :: Char -> Char -> String -> String #
stripbrackets :: 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 #
traceShowId :: Show a => a -> a #
adjustOption :: IsOption v => (v -> v) -> TestTree -> TestTree #
defaultIngredients :: [Ingredient] #
localOption :: IsOption v => v -> TestTree -> TestTree #
defaultMainWithIngredients :: [Ingredient] -> TestTree -> IO () #
includingOptions :: [OptionDescription] -> Ingredient #
testCaseInfo :: TestName -> IO String -> TestTree #
(@=?) :: (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 #
assertString :: HasCallStack => String -> Assertion #
runExceptT :: ExceptT e m a -> m (Either e a) #
Instances
Show Timeout | |
Eq Timeout | |
Ord Timeout | |
Defined in Test.Tasty.Options.Core | |
IsOption Timeout | |
Defined in Test.Tasty.Options.Core Methods parseValue :: String -> Maybe Timeout optionName :: Tagged Timeout String optionHelp :: Tagged Timeout String showDefaultValue :: Timeout -> Maybe String optionCLParser :: Parser Timeout |
class AssertionPredicable t where #
Methods
assertionPredicate :: t -> IO Bool #
Instances
AssertionPredicable Bool | |
Defined in Test.Tasty.HUnit.Orig Methods assertionPredicate :: Bool -> IO Bool # | |
AssertionPredicable t => AssertionPredicable (IO t) | |
Defined in Test.Tasty.HUnit.Orig Methods assertionPredicate :: IO t -> IO Bool # |
type AssertionPredicate = IO Bool #
data HUnitFailure #
Constructors
HUnitFailure (Maybe SrcLoc) String |
Instances
Exception HUnitFailure | |
Defined in Test.Tasty.HUnit.Orig Methods toException :: HUnitFailure -> SomeException fromException :: SomeException -> Maybe HUnitFailure displayException :: HUnitFailure -> String backtraceDesired :: HUnitFailure -> Bool | |
Show HUnitFailure | |
Defined in Test.Tasty.HUnit.Orig Methods showsPrec :: Int -> HUnitFailure -> ShowS show :: HUnitFailure -> String showList :: [HUnitFailure] -> ShowS | |
Eq HUnitFailure | |
Defined in Test.Tasty.HUnit.Orig |
System.Console.CmdArgs.Explicit
Constructors
Group | |
Fields
|
Constructors
Mode | |
Fields
|
Constructors
CompleteValue String | |
CompleteFile String FilePath | |
CompleteDir String FilePath |
Instances
Show Complete | |
Eq Complete | |
Ord Complete | |
Defined in System.Console.CmdArgs.Explicit.Complete |
Constructors
Flag | |
helpText :: [String] -> HelpFormat -> Mode a -> [Text] #
data HelpFormat #
Instances
expandArgsAt :: [String] -> IO [String] #
Constructors
FlagReq | |
FlagOpt String | |
FlagOptRare String | |
FlagNone |
Instances
Packer FlagInfo | |
Defined in System.Console.CmdArgs.Helper | |
Show FlagInfo | |
Eq FlagInfo | |
Ord FlagInfo | |
Defined in System.Console.CmdArgs.Explicit.Type |
class Remap (m :: Type -> Type) where #
Instances
Remap Arg | |
Defined in System.Console.CmdArgs.Explicit.Type | |
Remap Flag | |
Defined in System.Console.CmdArgs.Explicit.Type | |
Remap Mode | |
Defined in System.Console.CmdArgs.Explicit.Type |
fromFlagOpt :: FlagInfo -> String #
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 #