{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Hledger.Data.Types
where
import GHC.Generics (Generic)
import Data.Decimal
import Data.Default
import Data.Functor (($>))
import Data.List (intercalate)
import Text.Blaze (ToMarkup(..))
import qualified Data.Map as M
import Data.Text (Text)
import Data.Time.Calendar
import Data.Time.LocalTime
import Data.Word (Word8)
import System.Time (ClockTime(..))
import Text.Printf
import Hledger.Utils.Regex
data SmartDate
= SmartAssumeStart Year (Maybe (Month, Maybe MonthDay))
| SmartFromReference (Maybe Month) MonthDay
| SmartMonth Month
| SmartRelative SmartSequence SmartInterval
deriving (Int -> SmartDate -> ShowS
[SmartDate] -> ShowS
SmartDate -> String
(Int -> SmartDate -> ShowS)
-> (SmartDate -> String)
-> ([SmartDate] -> ShowS)
-> Show SmartDate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SmartDate] -> ShowS
$cshowList :: [SmartDate] -> ShowS
show :: SmartDate -> String
$cshow :: SmartDate -> String
showsPrec :: Int -> SmartDate -> ShowS
$cshowsPrec :: Int -> SmartDate -> ShowS
Show)
data SmartSequence = Last | This | Next deriving (Int -> SmartSequence -> ShowS
[SmartSequence] -> ShowS
SmartSequence -> String
(Int -> SmartSequence -> ShowS)
-> (SmartSequence -> String)
-> ([SmartSequence] -> ShowS)
-> Show SmartSequence
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SmartSequence] -> ShowS
$cshowList :: [SmartSequence] -> ShowS
show :: SmartSequence -> String
$cshow :: SmartSequence -> String
showsPrec :: Int -> SmartSequence -> ShowS
$cshowsPrec :: Int -> SmartSequence -> ShowS
Show)
data SmartInterval = Day | Week | Month | Quarter | Year deriving (Int -> SmartInterval -> ShowS
[SmartInterval] -> ShowS
SmartInterval -> String
(Int -> SmartInterval -> ShowS)
-> (SmartInterval -> String)
-> ([SmartInterval] -> ShowS)
-> Show SmartInterval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SmartInterval] -> ShowS
$cshowList :: [SmartInterval] -> ShowS
show :: SmartInterval -> String
$cshow :: SmartInterval -> String
showsPrec :: Int -> SmartInterval -> ShowS
$cshowsPrec :: Int -> SmartInterval -> ShowS
Show)
data WhichDate = PrimaryDate | SecondaryDate deriving (WhichDate -> WhichDate -> Bool
(WhichDate -> WhichDate -> Bool)
-> (WhichDate -> WhichDate -> Bool) -> Eq WhichDate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhichDate -> WhichDate -> Bool
$c/= :: WhichDate -> WhichDate -> Bool
== :: WhichDate -> WhichDate -> Bool
$c== :: WhichDate -> WhichDate -> Bool
Eq,Int -> WhichDate -> ShowS
[WhichDate] -> ShowS
WhichDate -> String
(Int -> WhichDate -> ShowS)
-> (WhichDate -> String)
-> ([WhichDate] -> ShowS)
-> Show WhichDate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WhichDate] -> ShowS
$cshowList :: [WhichDate] -> ShowS
show :: WhichDate -> String
$cshow :: WhichDate -> String
showsPrec :: Int -> WhichDate -> ShowS
$cshowsPrec :: Int -> WhichDate -> ShowS
Show)
data DateSpan = DateSpan (Maybe Day) (Maybe Day) deriving (DateSpan -> DateSpan -> Bool
(DateSpan -> DateSpan -> Bool)
-> (DateSpan -> DateSpan -> Bool) -> Eq DateSpan
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateSpan -> DateSpan -> Bool
$c/= :: DateSpan -> DateSpan -> Bool
== :: DateSpan -> DateSpan -> Bool
$c== :: DateSpan -> DateSpan -> Bool
Eq,Eq DateSpan
Eq DateSpan
-> (DateSpan -> DateSpan -> Ordering)
-> (DateSpan -> DateSpan -> Bool)
-> (DateSpan -> DateSpan -> Bool)
-> (DateSpan -> DateSpan -> Bool)
-> (DateSpan -> DateSpan -> Bool)
-> (DateSpan -> DateSpan -> DateSpan)
-> (DateSpan -> DateSpan -> DateSpan)
-> Ord DateSpan
DateSpan -> DateSpan -> Bool
DateSpan -> DateSpan -> Ordering
DateSpan -> DateSpan -> DateSpan
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DateSpan -> DateSpan -> DateSpan
$cmin :: DateSpan -> DateSpan -> DateSpan
max :: DateSpan -> DateSpan -> DateSpan
$cmax :: DateSpan -> DateSpan -> DateSpan
>= :: DateSpan -> DateSpan -> Bool
$c>= :: DateSpan -> DateSpan -> Bool
> :: DateSpan -> DateSpan -> Bool
$c> :: DateSpan -> DateSpan -> Bool
<= :: DateSpan -> DateSpan -> Bool
$c<= :: DateSpan -> DateSpan -> Bool
< :: DateSpan -> DateSpan -> Bool
$c< :: DateSpan -> DateSpan -> Bool
compare :: DateSpan -> DateSpan -> Ordering
$ccompare :: DateSpan -> DateSpan -> Ordering
$cp1Ord :: Eq DateSpan
Ord,(forall x. DateSpan -> Rep DateSpan x)
-> (forall x. Rep DateSpan x -> DateSpan) -> Generic DateSpan
forall x. Rep DateSpan x -> DateSpan
forall x. DateSpan -> Rep DateSpan x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DateSpan x -> DateSpan
$cfrom :: forall x. DateSpan -> Rep DateSpan x
Generic)
instance Default DateSpan where def :: DateSpan
def = Maybe Day -> Maybe Day -> DateSpan
DateSpan Maybe Day
forall a. Maybe a
Nothing Maybe Day
forall a. Maybe a
Nothing
type Year = Integer
type Month = Int
type Quarter = Int
type YearWeek = Int
type MonthWeek = Int
type YearDay = Int
type MonthDay = Int
type WeekDay = Int
data Period =
DayPeriod Day
| WeekPeriod Day
| MonthPeriod Year Month
| QuarterPeriod Year Quarter
| YearPeriod Year
| PeriodBetween Day Day
| PeriodFrom Day
| PeriodTo Day
| PeriodAll
deriving (Period -> Period -> Bool
(Period -> Period -> Bool)
-> (Period -> Period -> Bool) -> Eq Period
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Period -> Period -> Bool
$c/= :: Period -> Period -> Bool
== :: Period -> Period -> Bool
$c== :: Period -> Period -> Bool
Eq,Eq Period
Eq Period
-> (Period -> Period -> Ordering)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Bool)
-> (Period -> Period -> Period)
-> (Period -> Period -> Period)
-> Ord Period
Period -> Period -> Bool
Period -> Period -> Ordering
Period -> Period -> Period
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Period -> Period -> Period
$cmin :: Period -> Period -> Period
max :: Period -> Period -> Period
$cmax :: Period -> Period -> Period
>= :: Period -> Period -> Bool
$c>= :: Period -> Period -> Bool
> :: Period -> Period -> Bool
$c> :: Period -> Period -> Bool
<= :: Period -> Period -> Bool
$c<= :: Period -> Period -> Bool
< :: Period -> Period -> Bool
$c< :: Period -> Period -> Bool
compare :: Period -> Period -> Ordering
$ccompare :: Period -> Period -> Ordering
$cp1Ord :: Eq Period
Ord,Int -> Period -> ShowS
[Period] -> ShowS
Period -> String
(Int -> Period -> ShowS)
-> (Period -> String) -> ([Period] -> ShowS) -> Show Period
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Period] -> ShowS
$cshowList :: [Period] -> ShowS
show :: Period -> String
$cshow :: Period -> String
showsPrec :: Int -> Period -> ShowS
$cshowsPrec :: Int -> Period -> ShowS
Show,(forall x. Period -> Rep Period x)
-> (forall x. Rep Period x -> Period) -> Generic Period
forall x. Rep Period x -> Period
forall x. Period -> Rep Period x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Period x -> Period
$cfrom :: forall x. Period -> Rep Period x
Generic)
instance Default Period where def :: Period
def = Period
PeriodAll
data Interval =
NoInterval
| Days Int
| Weeks Int
| Months Int
| Quarters Int
| Years Int
| DayOfMonth Int
| WeekdayOfMonth Int Int
| DayOfWeek Int
| DayOfYear Int Int
deriving (Interval -> Interval -> Bool
(Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool) -> Eq Interval
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Interval -> Interval -> Bool
$c/= :: Interval -> Interval -> Bool
== :: Interval -> Interval -> Bool
$c== :: Interval -> Interval -> Bool
Eq,Int -> Interval -> ShowS
[Interval] -> ShowS
Interval -> String
(Int -> Interval -> ShowS)
-> (Interval -> String) -> ([Interval] -> ShowS) -> Show Interval
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Interval] -> ShowS
$cshowList :: [Interval] -> ShowS
show :: Interval -> String
$cshow :: Interval -> String
showsPrec :: Int -> Interval -> ShowS
$cshowsPrec :: Int -> Interval -> ShowS
Show,Eq Interval
Eq Interval
-> (Interval -> Interval -> Ordering)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Bool)
-> (Interval -> Interval -> Interval)
-> (Interval -> Interval -> Interval)
-> Ord Interval
Interval -> Interval -> Bool
Interval -> Interval -> Ordering
Interval -> Interval -> Interval
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Interval -> Interval -> Interval
$cmin :: Interval -> Interval -> Interval
max :: Interval -> Interval -> Interval
$cmax :: Interval -> Interval -> Interval
>= :: Interval -> Interval -> Bool
$c>= :: Interval -> Interval -> Bool
> :: Interval -> Interval -> Bool
$c> :: Interval -> Interval -> Bool
<= :: Interval -> Interval -> Bool
$c<= :: Interval -> Interval -> Bool
< :: Interval -> Interval -> Bool
$c< :: Interval -> Interval -> Bool
compare :: Interval -> Interval -> Ordering
$ccompare :: Interval -> Interval -> Ordering
$cp1Ord :: Eq Interval
Ord,(forall x. Interval -> Rep Interval x)
-> (forall x. Rep Interval x -> Interval) -> Generic Interval
forall x. Rep Interval x -> Interval
forall x. Interval -> Rep Interval x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Interval x -> Interval
$cfrom :: forall x. Interval -> Rep Interval x
Generic)
instance Default Interval where def :: Interval
def = Interval
NoInterval
type Payee = Text
type AccountName = Text
data AccountType =
Asset
| Liability
| Equity
| Revenue
| Expense
| Cash
deriving (Int -> AccountType -> ShowS
[AccountType] -> ShowS
AccountType -> String
(Int -> AccountType -> ShowS)
-> (AccountType -> String)
-> ([AccountType] -> ShowS)
-> Show AccountType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountType] -> ShowS
$cshowList :: [AccountType] -> ShowS
show :: AccountType -> String
$cshow :: AccountType -> String
showsPrec :: Int -> AccountType -> ShowS
$cshowsPrec :: Int -> AccountType -> ShowS
Show,AccountType -> AccountType -> Bool
(AccountType -> AccountType -> Bool)
-> (AccountType -> AccountType -> Bool) -> Eq AccountType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountType -> AccountType -> Bool
$c/= :: AccountType -> AccountType -> Bool
== :: AccountType -> AccountType -> Bool
$c== :: AccountType -> AccountType -> Bool
Eq,Eq AccountType
Eq AccountType
-> (AccountType -> AccountType -> Ordering)
-> (AccountType -> AccountType -> Bool)
-> (AccountType -> AccountType -> Bool)
-> (AccountType -> AccountType -> Bool)
-> (AccountType -> AccountType -> Bool)
-> (AccountType -> AccountType -> AccountType)
-> (AccountType -> AccountType -> AccountType)
-> Ord AccountType
AccountType -> AccountType -> Bool
AccountType -> AccountType -> Ordering
AccountType -> AccountType -> AccountType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AccountType -> AccountType -> AccountType
$cmin :: AccountType -> AccountType -> AccountType
max :: AccountType -> AccountType -> AccountType
$cmax :: AccountType -> AccountType -> AccountType
>= :: AccountType -> AccountType -> Bool
$c>= :: AccountType -> AccountType -> Bool
> :: AccountType -> AccountType -> Bool
$c> :: AccountType -> AccountType -> Bool
<= :: AccountType -> AccountType -> Bool
$c<= :: AccountType -> AccountType -> Bool
< :: AccountType -> AccountType -> Bool
$c< :: AccountType -> AccountType -> Bool
compare :: AccountType -> AccountType -> Ordering
$ccompare :: AccountType -> AccountType -> Ordering
$cp1Ord :: Eq AccountType
Ord,(forall x. AccountType -> Rep AccountType x)
-> (forall x. Rep AccountType x -> AccountType)
-> Generic AccountType
forall x. Rep AccountType x -> AccountType
forall x. AccountType -> Rep AccountType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountType x -> AccountType
$cfrom :: forall x. AccountType -> Rep AccountType x
Generic)
data AccountAlias = BasicAlias AccountName AccountName
| RegexAlias Regexp Replacement
deriving (AccountAlias -> AccountAlias -> Bool
(AccountAlias -> AccountAlias -> Bool)
-> (AccountAlias -> AccountAlias -> Bool) -> Eq AccountAlias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountAlias -> AccountAlias -> Bool
$c/= :: AccountAlias -> AccountAlias -> Bool
== :: AccountAlias -> AccountAlias -> Bool
$c== :: AccountAlias -> AccountAlias -> Bool
Eq, ReadPrec [AccountAlias]
ReadPrec AccountAlias
Int -> ReadS AccountAlias
ReadS [AccountAlias]
(Int -> ReadS AccountAlias)
-> ReadS [AccountAlias]
-> ReadPrec AccountAlias
-> ReadPrec [AccountAlias]
-> Read AccountAlias
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AccountAlias]
$creadListPrec :: ReadPrec [AccountAlias]
readPrec :: ReadPrec AccountAlias
$creadPrec :: ReadPrec AccountAlias
readList :: ReadS [AccountAlias]
$creadList :: ReadS [AccountAlias]
readsPrec :: Int -> ReadS AccountAlias
$creadsPrec :: Int -> ReadS AccountAlias
Read, Int -> AccountAlias -> ShowS
[AccountAlias] -> ShowS
AccountAlias -> String
(Int -> AccountAlias -> ShowS)
-> (AccountAlias -> String)
-> ([AccountAlias] -> ShowS)
-> Show AccountAlias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountAlias] -> ShowS
$cshowList :: [AccountAlias] -> ShowS
show :: AccountAlias -> String
$cshow :: AccountAlias -> String
showsPrec :: Int -> AccountAlias -> ShowS
$cshowsPrec :: Int -> AccountAlias -> ShowS
Show, Eq AccountAlias
Eq AccountAlias
-> (AccountAlias -> AccountAlias -> Ordering)
-> (AccountAlias -> AccountAlias -> Bool)
-> (AccountAlias -> AccountAlias -> Bool)
-> (AccountAlias -> AccountAlias -> Bool)
-> (AccountAlias -> AccountAlias -> Bool)
-> (AccountAlias -> AccountAlias -> AccountAlias)
-> (AccountAlias -> AccountAlias -> AccountAlias)
-> Ord AccountAlias
AccountAlias -> AccountAlias -> Bool
AccountAlias -> AccountAlias -> Ordering
AccountAlias -> AccountAlias -> AccountAlias
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AccountAlias -> AccountAlias -> AccountAlias
$cmin :: AccountAlias -> AccountAlias -> AccountAlias
max :: AccountAlias -> AccountAlias -> AccountAlias
$cmax :: AccountAlias -> AccountAlias -> AccountAlias
>= :: AccountAlias -> AccountAlias -> Bool
$c>= :: AccountAlias -> AccountAlias -> Bool
> :: AccountAlias -> AccountAlias -> Bool
$c> :: AccountAlias -> AccountAlias -> Bool
<= :: AccountAlias -> AccountAlias -> Bool
$c<= :: AccountAlias -> AccountAlias -> Bool
< :: AccountAlias -> AccountAlias -> Bool
$c< :: AccountAlias -> AccountAlias -> Bool
compare :: AccountAlias -> AccountAlias -> Ordering
$ccompare :: AccountAlias -> AccountAlias -> Ordering
$cp1Ord :: Eq AccountAlias
Ord, (forall x. AccountAlias -> Rep AccountAlias x)
-> (forall x. Rep AccountAlias x -> AccountAlias)
-> Generic AccountAlias
forall x. Rep AccountAlias x -> AccountAlias
forall x. AccountAlias -> Rep AccountAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountAlias x -> AccountAlias
$cfrom :: forall x. AccountAlias -> Rep AccountAlias x
Generic)
data Side = L | R deriving (Side -> Side -> Bool
(Side -> Side -> Bool) -> (Side -> Side -> Bool) -> Eq Side
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Side -> Side -> Bool
$c/= :: Side -> Side -> Bool
== :: Side -> Side -> Bool
$c== :: Side -> Side -> Bool
Eq,Int -> Side -> ShowS
[Side] -> ShowS
Side -> String
(Int -> Side -> ShowS)
-> (Side -> String) -> ([Side] -> ShowS) -> Show Side
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Side] -> ShowS
$cshowList :: [Side] -> ShowS
show :: Side -> String
$cshow :: Side -> String
showsPrec :: Int -> Side -> ShowS
$cshowsPrec :: Int -> Side -> ShowS
Show,ReadPrec [Side]
ReadPrec Side
Int -> ReadS Side
ReadS [Side]
(Int -> ReadS Side)
-> ReadS [Side] -> ReadPrec Side -> ReadPrec [Side] -> Read Side
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Side]
$creadListPrec :: ReadPrec [Side]
readPrec :: ReadPrec Side
$creadPrec :: ReadPrec Side
readList :: ReadS [Side]
$creadList :: ReadS [Side]
readsPrec :: Int -> ReadS Side
$creadsPrec :: Int -> ReadS Side
Read,Eq Side
Eq Side
-> (Side -> Side -> Ordering)
-> (Side -> Side -> Bool)
-> (Side -> Side -> Bool)
-> (Side -> Side -> Bool)
-> (Side -> Side -> Bool)
-> (Side -> Side -> Side)
-> (Side -> Side -> Side)
-> Ord Side
Side -> Side -> Bool
Side -> Side -> Ordering
Side -> Side -> Side
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Side -> Side -> Side
$cmin :: Side -> Side -> Side
max :: Side -> Side -> Side
$cmax :: Side -> Side -> Side
>= :: Side -> Side -> Bool
$c>= :: Side -> Side -> Bool
> :: Side -> Side -> Bool
$c> :: Side -> Side -> Bool
<= :: Side -> Side -> Bool
$c<= :: Side -> Side -> Bool
< :: Side -> Side -> Bool
$c< :: Side -> Side -> Bool
compare :: Side -> Side -> Ordering
$ccompare :: Side -> Side -> Ordering
$cp1Ord :: Eq Side
Ord,(forall x. Side -> Rep Side x)
-> (forall x. Rep Side x -> Side) -> Generic Side
forall x. Rep Side x -> Side
forall x. Side -> Rep Side x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Side x -> Side
$cfrom :: forall x. Side -> Rep Side x
Generic)
type DecimalMark = Char
isDecimalMark :: Char -> Bool
isDecimalMark :: Char -> Bool
isDecimalMark Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
','
type Quantity = Decimal
instance ToMarkup Quantity
where
toMarkup :: Quantity -> Markup
toMarkup = String -> Markup
forall a. ToMarkup a => a -> Markup
toMarkup (String -> Markup) -> (Quantity -> String) -> Quantity -> Markup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Quantity -> String
forall a. Show a => a -> String
show
data AmountPrice = UnitPrice !Amount | TotalPrice !Amount
deriving (AmountPrice -> AmountPrice -> Bool
(AmountPrice -> AmountPrice -> Bool)
-> (AmountPrice -> AmountPrice -> Bool) -> Eq AmountPrice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AmountPrice -> AmountPrice -> Bool
$c/= :: AmountPrice -> AmountPrice -> Bool
== :: AmountPrice -> AmountPrice -> Bool
$c== :: AmountPrice -> AmountPrice -> Bool
Eq,Eq AmountPrice
Eq AmountPrice
-> (AmountPrice -> AmountPrice -> Ordering)
-> (AmountPrice -> AmountPrice -> Bool)
-> (AmountPrice -> AmountPrice -> Bool)
-> (AmountPrice -> AmountPrice -> Bool)
-> (AmountPrice -> AmountPrice -> Bool)
-> (AmountPrice -> AmountPrice -> AmountPrice)
-> (AmountPrice -> AmountPrice -> AmountPrice)
-> Ord AmountPrice
AmountPrice -> AmountPrice -> Bool
AmountPrice -> AmountPrice -> Ordering
AmountPrice -> AmountPrice -> AmountPrice
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AmountPrice -> AmountPrice -> AmountPrice
$cmin :: AmountPrice -> AmountPrice -> AmountPrice
max :: AmountPrice -> AmountPrice -> AmountPrice
$cmax :: AmountPrice -> AmountPrice -> AmountPrice
>= :: AmountPrice -> AmountPrice -> Bool
$c>= :: AmountPrice -> AmountPrice -> Bool
> :: AmountPrice -> AmountPrice -> Bool
$c> :: AmountPrice -> AmountPrice -> Bool
<= :: AmountPrice -> AmountPrice -> Bool
$c<= :: AmountPrice -> AmountPrice -> Bool
< :: AmountPrice -> AmountPrice -> Bool
$c< :: AmountPrice -> AmountPrice -> Bool
compare :: AmountPrice -> AmountPrice -> Ordering
$ccompare :: AmountPrice -> AmountPrice -> Ordering
$cp1Ord :: Eq AmountPrice
Ord,(forall x. AmountPrice -> Rep AmountPrice x)
-> (forall x. Rep AmountPrice x -> AmountPrice)
-> Generic AmountPrice
forall x. Rep AmountPrice x -> AmountPrice
forall x. AmountPrice -> Rep AmountPrice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AmountPrice x -> AmountPrice
$cfrom :: forall x. AmountPrice -> Rep AmountPrice x
Generic,Int -> AmountPrice -> ShowS
[AmountPrice] -> ShowS
AmountPrice -> String
(Int -> AmountPrice -> ShowS)
-> (AmountPrice -> String)
-> ([AmountPrice] -> ShowS)
-> Show AmountPrice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AmountPrice] -> ShowS
$cshowList :: [AmountPrice] -> ShowS
show :: AmountPrice -> String
$cshow :: AmountPrice -> String
showsPrec :: Int -> AmountPrice -> ShowS
$cshowsPrec :: Int -> AmountPrice -> ShowS
Show)
data AmountStyle = AmountStyle {
AmountStyle -> Side
ascommodityside :: !Side,
AmountStyle -> Bool
ascommodityspaced :: !Bool,
AmountStyle -> AmountPrecision
asprecision :: !AmountPrecision,
AmountStyle -> Maybe Char
asdecimalpoint :: !(Maybe Char),
AmountStyle -> Maybe DigitGroupStyle
asdigitgroups :: !(Maybe DigitGroupStyle)
} deriving (AmountStyle -> AmountStyle -> Bool
(AmountStyle -> AmountStyle -> Bool)
-> (AmountStyle -> AmountStyle -> Bool) -> Eq AmountStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AmountStyle -> AmountStyle -> Bool
$c/= :: AmountStyle -> AmountStyle -> Bool
== :: AmountStyle -> AmountStyle -> Bool
$c== :: AmountStyle -> AmountStyle -> Bool
Eq,Eq AmountStyle
Eq AmountStyle
-> (AmountStyle -> AmountStyle -> Ordering)
-> (AmountStyle -> AmountStyle -> Bool)
-> (AmountStyle -> AmountStyle -> Bool)
-> (AmountStyle -> AmountStyle -> Bool)
-> (AmountStyle -> AmountStyle -> Bool)
-> (AmountStyle -> AmountStyle -> AmountStyle)
-> (AmountStyle -> AmountStyle -> AmountStyle)
-> Ord AmountStyle
AmountStyle -> AmountStyle -> Bool
AmountStyle -> AmountStyle -> Ordering
AmountStyle -> AmountStyle -> AmountStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AmountStyle -> AmountStyle -> AmountStyle
$cmin :: AmountStyle -> AmountStyle -> AmountStyle
max :: AmountStyle -> AmountStyle -> AmountStyle
$cmax :: AmountStyle -> AmountStyle -> AmountStyle
>= :: AmountStyle -> AmountStyle -> Bool
$c>= :: AmountStyle -> AmountStyle -> Bool
> :: AmountStyle -> AmountStyle -> Bool
$c> :: AmountStyle -> AmountStyle -> Bool
<= :: AmountStyle -> AmountStyle -> Bool
$c<= :: AmountStyle -> AmountStyle -> Bool
< :: AmountStyle -> AmountStyle -> Bool
$c< :: AmountStyle -> AmountStyle -> Bool
compare :: AmountStyle -> AmountStyle -> Ordering
$ccompare :: AmountStyle -> AmountStyle -> Ordering
$cp1Ord :: Eq AmountStyle
Ord,ReadPrec [AmountStyle]
ReadPrec AmountStyle
Int -> ReadS AmountStyle
ReadS [AmountStyle]
(Int -> ReadS AmountStyle)
-> ReadS [AmountStyle]
-> ReadPrec AmountStyle
-> ReadPrec [AmountStyle]
-> Read AmountStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AmountStyle]
$creadListPrec :: ReadPrec [AmountStyle]
readPrec :: ReadPrec AmountStyle
$creadPrec :: ReadPrec AmountStyle
readList :: ReadS [AmountStyle]
$creadList :: ReadS [AmountStyle]
readsPrec :: Int -> ReadS AmountStyle
$creadsPrec :: Int -> ReadS AmountStyle
Read,(forall x. AmountStyle -> Rep AmountStyle x)
-> (forall x. Rep AmountStyle x -> AmountStyle)
-> Generic AmountStyle
forall x. Rep AmountStyle x -> AmountStyle
forall x. AmountStyle -> Rep AmountStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AmountStyle x -> AmountStyle
$cfrom :: forall x. AmountStyle -> Rep AmountStyle x
Generic)
instance Show AmountStyle where
show :: AmountStyle -> String
show AmountStyle{Bool
Maybe Char
Maybe DigitGroupStyle
AmountPrecision
Side
asdigitgroups :: Maybe DigitGroupStyle
asdecimalpoint :: Maybe Char
asprecision :: AmountPrecision
ascommodityspaced :: Bool
ascommodityside :: Side
asdigitgroups :: AmountStyle -> Maybe DigitGroupStyle
asdecimalpoint :: AmountStyle -> Maybe Char
asprecision :: AmountStyle -> AmountPrecision
ascommodityspaced :: AmountStyle -> Bool
ascommodityside :: AmountStyle -> Side
..} =
String -> String -> String -> String -> String -> ShowS
forall r. PrintfType r => String -> r
printf String
"AmountStylePP \"%s %s %s %s %s..\""
(Side -> String
forall a. Show a => a -> String
show Side
ascommodityside)
(Bool -> String
forall a. Show a => a -> String
show Bool
ascommodityspaced)
(AmountPrecision -> String
forall a. Show a => a -> String
show AmountPrecision
asprecision)
(Maybe Char -> String
forall a. Show a => a -> String
show Maybe Char
asdecimalpoint)
(Maybe DigitGroupStyle -> String
forall a. Show a => a -> String
show Maybe DigitGroupStyle
asdigitgroups)
data AmountPrecision = Precision !Word8 | NaturalPrecision deriving (AmountPrecision -> AmountPrecision -> Bool
(AmountPrecision -> AmountPrecision -> Bool)
-> (AmountPrecision -> AmountPrecision -> Bool)
-> Eq AmountPrecision
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AmountPrecision -> AmountPrecision -> Bool
$c/= :: AmountPrecision -> AmountPrecision -> Bool
== :: AmountPrecision -> AmountPrecision -> Bool
$c== :: AmountPrecision -> AmountPrecision -> Bool
Eq,Eq AmountPrecision
Eq AmountPrecision
-> (AmountPrecision -> AmountPrecision -> Ordering)
-> (AmountPrecision -> AmountPrecision -> Bool)
-> (AmountPrecision -> AmountPrecision -> Bool)
-> (AmountPrecision -> AmountPrecision -> Bool)
-> (AmountPrecision -> AmountPrecision -> Bool)
-> (AmountPrecision -> AmountPrecision -> AmountPrecision)
-> (AmountPrecision -> AmountPrecision -> AmountPrecision)
-> Ord AmountPrecision
AmountPrecision -> AmountPrecision -> Bool
AmountPrecision -> AmountPrecision -> Ordering
AmountPrecision -> AmountPrecision -> AmountPrecision
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AmountPrecision -> AmountPrecision -> AmountPrecision
$cmin :: AmountPrecision -> AmountPrecision -> AmountPrecision
max :: AmountPrecision -> AmountPrecision -> AmountPrecision
$cmax :: AmountPrecision -> AmountPrecision -> AmountPrecision
>= :: AmountPrecision -> AmountPrecision -> Bool
$c>= :: AmountPrecision -> AmountPrecision -> Bool
> :: AmountPrecision -> AmountPrecision -> Bool
$c> :: AmountPrecision -> AmountPrecision -> Bool
<= :: AmountPrecision -> AmountPrecision -> Bool
$c<= :: AmountPrecision -> AmountPrecision -> Bool
< :: AmountPrecision -> AmountPrecision -> Bool
$c< :: AmountPrecision -> AmountPrecision -> Bool
compare :: AmountPrecision -> AmountPrecision -> Ordering
$ccompare :: AmountPrecision -> AmountPrecision -> Ordering
$cp1Ord :: Eq AmountPrecision
Ord,ReadPrec [AmountPrecision]
ReadPrec AmountPrecision
Int -> ReadS AmountPrecision
ReadS [AmountPrecision]
(Int -> ReadS AmountPrecision)
-> ReadS [AmountPrecision]
-> ReadPrec AmountPrecision
-> ReadPrec [AmountPrecision]
-> Read AmountPrecision
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AmountPrecision]
$creadListPrec :: ReadPrec [AmountPrecision]
readPrec :: ReadPrec AmountPrecision
$creadPrec :: ReadPrec AmountPrecision
readList :: ReadS [AmountPrecision]
$creadList :: ReadS [AmountPrecision]
readsPrec :: Int -> ReadS AmountPrecision
$creadsPrec :: Int -> ReadS AmountPrecision
Read,Int -> AmountPrecision -> ShowS
[AmountPrecision] -> ShowS
AmountPrecision -> String
(Int -> AmountPrecision -> ShowS)
-> (AmountPrecision -> String)
-> ([AmountPrecision] -> ShowS)
-> Show AmountPrecision
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AmountPrecision] -> ShowS
$cshowList :: [AmountPrecision] -> ShowS
show :: AmountPrecision -> String
$cshow :: AmountPrecision -> String
showsPrec :: Int -> AmountPrecision -> ShowS
$cshowsPrec :: Int -> AmountPrecision -> ShowS
Show,(forall x. AmountPrecision -> Rep AmountPrecision x)
-> (forall x. Rep AmountPrecision x -> AmountPrecision)
-> Generic AmountPrecision
forall x. Rep AmountPrecision x -> AmountPrecision
forall x. AmountPrecision -> Rep AmountPrecision x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AmountPrecision x -> AmountPrecision
$cfrom :: forall x. AmountPrecision -> Rep AmountPrecision x
Generic)
data DigitGroupStyle = DigitGroups !Char ![Word8]
deriving (DigitGroupStyle -> DigitGroupStyle -> Bool
(DigitGroupStyle -> DigitGroupStyle -> Bool)
-> (DigitGroupStyle -> DigitGroupStyle -> Bool)
-> Eq DigitGroupStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c/= :: DigitGroupStyle -> DigitGroupStyle -> Bool
== :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c== :: DigitGroupStyle -> DigitGroupStyle -> Bool
Eq,Eq DigitGroupStyle
Eq DigitGroupStyle
-> (DigitGroupStyle -> DigitGroupStyle -> Ordering)
-> (DigitGroupStyle -> DigitGroupStyle -> Bool)
-> (DigitGroupStyle -> DigitGroupStyle -> Bool)
-> (DigitGroupStyle -> DigitGroupStyle -> Bool)
-> (DigitGroupStyle -> DigitGroupStyle -> Bool)
-> (DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle)
-> (DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle)
-> Ord DigitGroupStyle
DigitGroupStyle -> DigitGroupStyle -> Bool
DigitGroupStyle -> DigitGroupStyle -> Ordering
DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle
$cmin :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle
max :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle
$cmax :: DigitGroupStyle -> DigitGroupStyle -> DigitGroupStyle
>= :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c>= :: DigitGroupStyle -> DigitGroupStyle -> Bool
> :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c> :: DigitGroupStyle -> DigitGroupStyle -> Bool
<= :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c<= :: DigitGroupStyle -> DigitGroupStyle -> Bool
< :: DigitGroupStyle -> DigitGroupStyle -> Bool
$c< :: DigitGroupStyle -> DigitGroupStyle -> Bool
compare :: DigitGroupStyle -> DigitGroupStyle -> Ordering
$ccompare :: DigitGroupStyle -> DigitGroupStyle -> Ordering
$cp1Ord :: Eq DigitGroupStyle
Ord,ReadPrec [DigitGroupStyle]
ReadPrec DigitGroupStyle
Int -> ReadS DigitGroupStyle
ReadS [DigitGroupStyle]
(Int -> ReadS DigitGroupStyle)
-> ReadS [DigitGroupStyle]
-> ReadPrec DigitGroupStyle
-> ReadPrec [DigitGroupStyle]
-> Read DigitGroupStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DigitGroupStyle]
$creadListPrec :: ReadPrec [DigitGroupStyle]
readPrec :: ReadPrec DigitGroupStyle
$creadPrec :: ReadPrec DigitGroupStyle
readList :: ReadS [DigitGroupStyle]
$creadList :: ReadS [DigitGroupStyle]
readsPrec :: Int -> ReadS DigitGroupStyle
$creadsPrec :: Int -> ReadS DigitGroupStyle
Read,Int -> DigitGroupStyle -> ShowS
[DigitGroupStyle] -> ShowS
DigitGroupStyle -> String
(Int -> DigitGroupStyle -> ShowS)
-> (DigitGroupStyle -> String)
-> ([DigitGroupStyle] -> ShowS)
-> Show DigitGroupStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DigitGroupStyle] -> ShowS
$cshowList :: [DigitGroupStyle] -> ShowS
show :: DigitGroupStyle -> String
$cshow :: DigitGroupStyle -> String
showsPrec :: Int -> DigitGroupStyle -> ShowS
$cshowsPrec :: Int -> DigitGroupStyle -> ShowS
Show,(forall x. DigitGroupStyle -> Rep DigitGroupStyle x)
-> (forall x. Rep DigitGroupStyle x -> DigitGroupStyle)
-> Generic DigitGroupStyle
forall x. Rep DigitGroupStyle x -> DigitGroupStyle
forall x. DigitGroupStyle -> Rep DigitGroupStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DigitGroupStyle x -> DigitGroupStyle
$cfrom :: forall x. DigitGroupStyle -> Rep DigitGroupStyle x
Generic)
type CommoditySymbol = Text
data Commodity = Commodity {
Commodity -> CommoditySymbol
csymbol :: CommoditySymbol,
Commodity -> Maybe AmountStyle
cformat :: Maybe AmountStyle
} deriving (Int -> Commodity -> ShowS
[Commodity] -> ShowS
Commodity -> String
(Int -> Commodity -> ShowS)
-> (Commodity -> String)
-> ([Commodity] -> ShowS)
-> Show Commodity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Commodity] -> ShowS
$cshowList :: [Commodity] -> ShowS
show :: Commodity -> String
$cshow :: Commodity -> String
showsPrec :: Int -> Commodity -> ShowS
$cshowsPrec :: Int -> Commodity -> ShowS
Show,Commodity -> Commodity -> Bool
(Commodity -> Commodity -> Bool)
-> (Commodity -> Commodity -> Bool) -> Eq Commodity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Commodity -> Commodity -> Bool
$c/= :: Commodity -> Commodity -> Bool
== :: Commodity -> Commodity -> Bool
$c== :: Commodity -> Commodity -> Bool
Eq,(forall x. Commodity -> Rep Commodity x)
-> (forall x. Rep Commodity x -> Commodity) -> Generic Commodity
forall x. Rep Commodity x -> Commodity
forall x. Commodity -> Rep Commodity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Commodity x -> Commodity
$cfrom :: forall x. Commodity -> Rep Commodity x
Generic)
data Amount = Amount {
Amount -> CommoditySymbol
acommodity :: !CommoditySymbol,
Amount -> Quantity
aquantity :: !Quantity,
Amount -> Bool
aismultiplier :: !Bool,
Amount -> AmountStyle
astyle :: !AmountStyle,
Amount -> Maybe AmountPrice
aprice :: !(Maybe AmountPrice)
} deriving (Amount -> Amount -> Bool
(Amount -> Amount -> Bool)
-> (Amount -> Amount -> Bool) -> Eq Amount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Amount -> Amount -> Bool
$c/= :: Amount -> Amount -> Bool
== :: Amount -> Amount -> Bool
$c== :: Amount -> Amount -> Bool
Eq,Eq Amount
Eq Amount
-> (Amount -> Amount -> Ordering)
-> (Amount -> Amount -> Bool)
-> (Amount -> Amount -> Bool)
-> (Amount -> Amount -> Bool)
-> (Amount -> Amount -> Bool)
-> (Amount -> Amount -> Amount)
-> (Amount -> Amount -> Amount)
-> Ord Amount
Amount -> Amount -> Bool
Amount -> Amount -> Ordering
Amount -> Amount -> Amount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Amount -> Amount -> Amount
$cmin :: Amount -> Amount -> Amount
max :: Amount -> Amount -> Amount
$cmax :: Amount -> Amount -> Amount
>= :: Amount -> Amount -> Bool
$c>= :: Amount -> Amount -> Bool
> :: Amount -> Amount -> Bool
$c> :: Amount -> Amount -> Bool
<= :: Amount -> Amount -> Bool
$c<= :: Amount -> Amount -> Bool
< :: Amount -> Amount -> Bool
$c< :: Amount -> Amount -> Bool
compare :: Amount -> Amount -> Ordering
$ccompare :: Amount -> Amount -> Ordering
$cp1Ord :: Eq Amount
Ord,(forall x. Amount -> Rep Amount x)
-> (forall x. Rep Amount x -> Amount) -> Generic Amount
forall x. Rep Amount x -> Amount
forall x. Amount -> Rep Amount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Amount x -> Amount
$cfrom :: forall x. Amount -> Rep Amount x
Generic,Int -> Amount -> ShowS
[Amount] -> ShowS
Amount -> String
(Int -> Amount -> ShowS)
-> (Amount -> String) -> ([Amount] -> ShowS) -> Show Amount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Amount] -> ShowS
$cshowList :: [Amount] -> ShowS
show :: Amount -> String
$cshow :: Amount -> String
showsPrec :: Int -> Amount -> ShowS
$cshowsPrec :: Int -> Amount -> ShowS
Show)
newtype MixedAmount = Mixed [Amount] deriving (MixedAmount -> MixedAmount -> Bool
(MixedAmount -> MixedAmount -> Bool)
-> (MixedAmount -> MixedAmount -> Bool) -> Eq MixedAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MixedAmount -> MixedAmount -> Bool
$c/= :: MixedAmount -> MixedAmount -> Bool
== :: MixedAmount -> MixedAmount -> Bool
$c== :: MixedAmount -> MixedAmount -> Bool
Eq,Eq MixedAmount
Eq MixedAmount
-> (MixedAmount -> MixedAmount -> Ordering)
-> (MixedAmount -> MixedAmount -> Bool)
-> (MixedAmount -> MixedAmount -> Bool)
-> (MixedAmount -> MixedAmount -> Bool)
-> (MixedAmount -> MixedAmount -> Bool)
-> (MixedAmount -> MixedAmount -> MixedAmount)
-> (MixedAmount -> MixedAmount -> MixedAmount)
-> Ord MixedAmount
MixedAmount -> MixedAmount -> Bool
MixedAmount -> MixedAmount -> Ordering
MixedAmount -> MixedAmount -> MixedAmount
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MixedAmount -> MixedAmount -> MixedAmount
$cmin :: MixedAmount -> MixedAmount -> MixedAmount
max :: MixedAmount -> MixedAmount -> MixedAmount
$cmax :: MixedAmount -> MixedAmount -> MixedAmount
>= :: MixedAmount -> MixedAmount -> Bool
$c>= :: MixedAmount -> MixedAmount -> Bool
> :: MixedAmount -> MixedAmount -> Bool
$c> :: MixedAmount -> MixedAmount -> Bool
<= :: MixedAmount -> MixedAmount -> Bool
$c<= :: MixedAmount -> MixedAmount -> Bool
< :: MixedAmount -> MixedAmount -> Bool
$c< :: MixedAmount -> MixedAmount -> Bool
compare :: MixedAmount -> MixedAmount -> Ordering
$ccompare :: MixedAmount -> MixedAmount -> Ordering
$cp1Ord :: Eq MixedAmount
Ord,(forall x. MixedAmount -> Rep MixedAmount x)
-> (forall x. Rep MixedAmount x -> MixedAmount)
-> Generic MixedAmount
forall x. Rep MixedAmount x -> MixedAmount
forall x. MixedAmount -> Rep MixedAmount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MixedAmount x -> MixedAmount
$cfrom :: forall x. MixedAmount -> Rep MixedAmount x
Generic,Int -> MixedAmount -> ShowS
[MixedAmount] -> ShowS
MixedAmount -> String
(Int -> MixedAmount -> ShowS)
-> (MixedAmount -> String)
-> ([MixedAmount] -> ShowS)
-> Show MixedAmount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MixedAmount] -> ShowS
$cshowList :: [MixedAmount] -> ShowS
show :: MixedAmount -> String
$cshow :: MixedAmount -> String
showsPrec :: Int -> MixedAmount -> ShowS
$cshowsPrec :: Int -> MixedAmount -> ShowS
Show)
data PostingType = RegularPosting | VirtualPosting | BalancedVirtualPosting
deriving (PostingType -> PostingType -> Bool
(PostingType -> PostingType -> Bool)
-> (PostingType -> PostingType -> Bool) -> Eq PostingType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostingType -> PostingType -> Bool
$c/= :: PostingType -> PostingType -> Bool
== :: PostingType -> PostingType -> Bool
$c== :: PostingType -> PostingType -> Bool
Eq,Int -> PostingType -> ShowS
[PostingType] -> ShowS
PostingType -> String
(Int -> PostingType -> ShowS)
-> (PostingType -> String)
-> ([PostingType] -> ShowS)
-> Show PostingType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostingType] -> ShowS
$cshowList :: [PostingType] -> ShowS
show :: PostingType -> String
$cshow :: PostingType -> String
showsPrec :: Int -> PostingType -> ShowS
$cshowsPrec :: Int -> PostingType -> ShowS
Show,(forall x. PostingType -> Rep PostingType x)
-> (forall x. Rep PostingType x -> PostingType)
-> Generic PostingType
forall x. Rep PostingType x -> PostingType
forall x. PostingType -> Rep PostingType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PostingType x -> PostingType
$cfrom :: forall x. PostingType -> Rep PostingType x
Generic)
type TagName = Text
type TagValue = Text
type Tag = (TagName, TagValue)
type DateTag = (TagName, Day)
data Status = Unmarked | Pending | Cleared
deriving (Status -> Status -> Bool
(Status -> Status -> Bool)
-> (Status -> Status -> Bool) -> Eq Status
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Status -> Status -> Bool
$c/= :: Status -> Status -> Bool
== :: Status -> Status -> Bool
$c== :: Status -> Status -> Bool
Eq,Eq Status
Eq Status
-> (Status -> Status -> Ordering)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Bool)
-> (Status -> Status -> Status)
-> (Status -> Status -> Status)
-> Ord Status
Status -> Status -> Bool
Status -> Status -> Ordering
Status -> Status -> Status
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Status -> Status -> Status
$cmin :: Status -> Status -> Status
max :: Status -> Status -> Status
$cmax :: Status -> Status -> Status
>= :: Status -> Status -> Bool
$c>= :: Status -> Status -> Bool
> :: Status -> Status -> Bool
$c> :: Status -> Status -> Bool
<= :: Status -> Status -> Bool
$c<= :: Status -> Status -> Bool
< :: Status -> Status -> Bool
$c< :: Status -> Status -> Bool
compare :: Status -> Status -> Ordering
$ccompare :: Status -> Status -> Ordering
$cp1Ord :: Eq Status
Ord,Status
Status -> Status -> Bounded Status
forall a. a -> a -> Bounded a
maxBound :: Status
$cmaxBound :: Status
minBound :: Status
$cminBound :: Status
Bounded,Int -> Status
Status -> Int
Status -> [Status]
Status -> Status
Status -> Status -> [Status]
Status -> Status -> Status -> [Status]
(Status -> Status)
-> (Status -> Status)
-> (Int -> Status)
-> (Status -> Int)
-> (Status -> [Status])
-> (Status -> Status -> [Status])
-> (Status -> Status -> [Status])
-> (Status -> Status -> Status -> [Status])
-> Enum Status
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Status -> Status -> Status -> [Status]
$cenumFromThenTo :: Status -> Status -> Status -> [Status]
enumFromTo :: Status -> Status -> [Status]
$cenumFromTo :: Status -> Status -> [Status]
enumFromThen :: Status -> Status -> [Status]
$cenumFromThen :: Status -> Status -> [Status]
enumFrom :: Status -> [Status]
$cenumFrom :: Status -> [Status]
fromEnum :: Status -> Int
$cfromEnum :: Status -> Int
toEnum :: Int -> Status
$ctoEnum :: Int -> Status
pred :: Status -> Status
$cpred :: Status -> Status
succ :: Status -> Status
$csucc :: Status -> Status
Enum,(forall x. Status -> Rep Status x)
-> (forall x. Rep Status x -> Status) -> Generic Status
forall x. Rep Status x -> Status
forall x. Status -> Rep Status x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Status x -> Status
$cfrom :: forall x. Status -> Rep Status x
Generic)
instance Show Status where
show :: Status -> String
show Status
Unmarked = String
""
show Status
Pending = String
"!"
show Status
Cleared = String
"*"
data BalanceAssertion = BalanceAssertion {
BalanceAssertion -> Amount
baamount :: Amount,
BalanceAssertion -> Bool
batotal :: Bool,
BalanceAssertion -> Bool
bainclusive :: Bool,
BalanceAssertion -> GenericSourcePos
baposition :: GenericSourcePos
} deriving (BalanceAssertion -> BalanceAssertion -> Bool
(BalanceAssertion -> BalanceAssertion -> Bool)
-> (BalanceAssertion -> BalanceAssertion -> Bool)
-> Eq BalanceAssertion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BalanceAssertion -> BalanceAssertion -> Bool
$c/= :: BalanceAssertion -> BalanceAssertion -> Bool
== :: BalanceAssertion -> BalanceAssertion -> Bool
$c== :: BalanceAssertion -> BalanceAssertion -> Bool
Eq,(forall x. BalanceAssertion -> Rep BalanceAssertion x)
-> (forall x. Rep BalanceAssertion x -> BalanceAssertion)
-> Generic BalanceAssertion
forall x. Rep BalanceAssertion x -> BalanceAssertion
forall x. BalanceAssertion -> Rep BalanceAssertion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BalanceAssertion x -> BalanceAssertion
$cfrom :: forall x. BalanceAssertion -> Rep BalanceAssertion x
Generic,Int -> BalanceAssertion -> ShowS
[BalanceAssertion] -> ShowS
BalanceAssertion -> String
(Int -> BalanceAssertion -> ShowS)
-> (BalanceAssertion -> String)
-> ([BalanceAssertion] -> ShowS)
-> Show BalanceAssertion
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BalanceAssertion] -> ShowS
$cshowList :: [BalanceAssertion] -> ShowS
show :: BalanceAssertion -> String
$cshow :: BalanceAssertion -> String
showsPrec :: Int -> BalanceAssertion -> ShowS
$cshowsPrec :: Int -> BalanceAssertion -> ShowS
Show)
data Posting = Posting {
Posting -> Maybe Day
pdate :: Maybe Day,
Posting -> Maybe Day
pdate2 :: Maybe Day,
Posting -> Status
pstatus :: Status,
Posting -> CommoditySymbol
paccount :: AccountName,
Posting -> MixedAmount
pamount :: MixedAmount,
:: Text,
Posting -> PostingType
ptype :: PostingType,
Posting -> [Tag]
ptags :: [Tag],
Posting -> Maybe BalanceAssertion
pbalanceassertion :: Maybe BalanceAssertion,
Posting -> Maybe Transaction
ptransaction :: Maybe Transaction,
Posting -> Maybe Posting
poriginal :: Maybe Posting
} deriving ((forall x. Posting -> Rep Posting x)
-> (forall x. Rep Posting x -> Posting) -> Generic Posting
forall x. Rep Posting x -> Posting
forall x. Posting -> Rep Posting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Posting x -> Posting
$cfrom :: forall x. Posting -> Rep Posting x
Generic)
instance Eq Posting where
== :: Posting -> Posting -> Bool
(==) (Posting Maybe Day
a1 Maybe Day
b1 Status
c1 CommoditySymbol
d1 MixedAmount
e1 CommoditySymbol
f1 PostingType
g1 [Tag]
h1 Maybe BalanceAssertion
i1 Maybe Transaction
_ Maybe Posting
_) (Posting Maybe Day
a2 Maybe Day
b2 Status
c2 CommoditySymbol
d2 MixedAmount
e2 CommoditySymbol
f2 PostingType
g2 [Tag]
h2 Maybe BalanceAssertion
i2 Maybe Transaction
_ Maybe Posting
_) = Maybe Day
a1Maybe Day -> Maybe Day -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe Day
a2 Bool -> Bool -> Bool
&& Maybe Day
b1Maybe Day -> Maybe Day -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe Day
b2 Bool -> Bool -> Bool
&& Status
c1Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
==Status
c2 Bool -> Bool -> Bool
&& CommoditySymbol
d1CommoditySymbol -> CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
==CommoditySymbol
d2 Bool -> Bool -> Bool
&& MixedAmount
e1MixedAmount -> MixedAmount -> Bool
forall a. Eq a => a -> a -> Bool
==MixedAmount
e2 Bool -> Bool -> Bool
&& CommoditySymbol
f1CommoditySymbol -> CommoditySymbol -> Bool
forall a. Eq a => a -> a -> Bool
==CommoditySymbol
f2 Bool -> Bool -> Bool
&& PostingType
g1PostingType -> PostingType -> Bool
forall a. Eq a => a -> a -> Bool
==PostingType
g2 Bool -> Bool -> Bool
&& [Tag]
h1[Tag] -> [Tag] -> Bool
forall a. Eq a => a -> a -> Bool
==[Tag]
h2 Bool -> Bool -> Bool
&& Maybe BalanceAssertion
i1Maybe BalanceAssertion -> Maybe BalanceAssertion -> Bool
forall a. Eq a => a -> a -> Bool
==Maybe BalanceAssertion
i2
instance Show Posting where
show :: Posting -> String
show Posting{[Tag]
Maybe Day
Maybe Transaction
Maybe Posting
Maybe BalanceAssertion
CommoditySymbol
Status
PostingType
MixedAmount
poriginal :: Maybe Posting
ptransaction :: Maybe Transaction
pbalanceassertion :: Maybe BalanceAssertion
ptags :: [Tag]
ptype :: PostingType
pcomment :: CommoditySymbol
pamount :: MixedAmount
paccount :: CommoditySymbol
pstatus :: Status
pdate2 :: Maybe Day
pdate :: Maybe Day
poriginal :: Posting -> Maybe Posting
ptransaction :: Posting -> Maybe Transaction
pbalanceassertion :: Posting -> Maybe BalanceAssertion
ptags :: Posting -> [Tag]
ptype :: Posting -> PostingType
pcomment :: Posting -> CommoditySymbol
pamount :: Posting -> MixedAmount
paccount :: Posting -> CommoditySymbol
pstatus :: Posting -> Status
pdate2 :: Posting -> Maybe Day
pdate :: Posting -> Maybe Day
..} = String
"PostingPP {" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [
String
"pdate=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Maybe Day -> String
forall a. Show a => a -> String
show Maybe Day
pdate)
,String
"pdate2=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Maybe Day -> String
forall a. Show a => a -> String
show Maybe Day
pdate2)
,String
"pstatus=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Status -> String
forall a. Show a => a -> String
show Status
pstatus)
,String
"paccount=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ CommoditySymbol -> String
forall a. Show a => a -> String
show CommoditySymbol
paccount
,String
"pamount=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ MixedAmount -> String
forall a. Show a => a -> String
show MixedAmount
pamount
,String
"pcomment=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ CommoditySymbol -> String
forall a. Show a => a -> String
show CommoditySymbol
pcomment
,String
"ptype=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ PostingType -> String
forall a. Show a => a -> String
show PostingType
ptype
,String
"ptags=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Tag] -> String
forall a. Show a => a -> String
show [Tag]
ptags
,String
"pbalanceassertion=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe BalanceAssertion -> String
forall a. Show a => a -> String
show Maybe BalanceAssertion
pbalanceassertion
,String
"ptransaction=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe String -> String
forall a. Show a => a -> String
show (Maybe Transaction
ptransaction Maybe Transaction -> String -> Maybe String
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> String
"txn")
,String
"poriginal=" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Maybe Posting -> String
forall a. Show a => a -> String
show Maybe Posting
poriginal
] String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"}"
data GenericSourcePos = GenericSourcePos FilePath Int Int
| JournalSourcePos FilePath (Int, Int)
deriving (GenericSourcePos -> GenericSourcePos -> Bool
(GenericSourcePos -> GenericSourcePos -> Bool)
-> (GenericSourcePos -> GenericSourcePos -> Bool)
-> Eq GenericSourcePos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenericSourcePos -> GenericSourcePos -> Bool
$c/= :: GenericSourcePos -> GenericSourcePos -> Bool
== :: GenericSourcePos -> GenericSourcePos -> Bool
$c== :: GenericSourcePos -> GenericSourcePos -> Bool
Eq, ReadPrec [GenericSourcePos]
ReadPrec GenericSourcePos
Int -> ReadS GenericSourcePos
ReadS [GenericSourcePos]
(Int -> ReadS GenericSourcePos)
-> ReadS [GenericSourcePos]
-> ReadPrec GenericSourcePos
-> ReadPrec [GenericSourcePos]
-> Read GenericSourcePos
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GenericSourcePos]
$creadListPrec :: ReadPrec [GenericSourcePos]
readPrec :: ReadPrec GenericSourcePos
$creadPrec :: ReadPrec GenericSourcePos
readList :: ReadS [GenericSourcePos]
$creadList :: ReadS [GenericSourcePos]
readsPrec :: Int -> ReadS GenericSourcePos
$creadsPrec :: Int -> ReadS GenericSourcePos
Read, Int -> GenericSourcePos -> ShowS
[GenericSourcePos] -> ShowS
GenericSourcePos -> String
(Int -> GenericSourcePos -> ShowS)
-> (GenericSourcePos -> String)
-> ([GenericSourcePos] -> ShowS)
-> Show GenericSourcePos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenericSourcePos] -> ShowS
$cshowList :: [GenericSourcePos] -> ShowS
show :: GenericSourcePos -> String
$cshow :: GenericSourcePos -> String
showsPrec :: Int -> GenericSourcePos -> ShowS
$cshowsPrec :: Int -> GenericSourcePos -> ShowS
Show, Eq GenericSourcePos
Eq GenericSourcePos
-> (GenericSourcePos -> GenericSourcePos -> Ordering)
-> (GenericSourcePos -> GenericSourcePos -> Bool)
-> (GenericSourcePos -> GenericSourcePos -> Bool)
-> (GenericSourcePos -> GenericSourcePos -> Bool)
-> (GenericSourcePos -> GenericSourcePos -> Bool)
-> (GenericSourcePos -> GenericSourcePos -> GenericSourcePos)
-> (GenericSourcePos -> GenericSourcePos -> GenericSourcePos)
-> Ord GenericSourcePos
GenericSourcePos -> GenericSourcePos -> Bool
GenericSourcePos -> GenericSourcePos -> Ordering
GenericSourcePos -> GenericSourcePos -> GenericSourcePos
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GenericSourcePos -> GenericSourcePos -> GenericSourcePos
$cmin :: GenericSourcePos -> GenericSourcePos -> GenericSourcePos
max :: GenericSourcePos -> GenericSourcePos -> GenericSourcePos
$cmax :: GenericSourcePos -> GenericSourcePos -> GenericSourcePos
>= :: GenericSourcePos -> GenericSourcePos -> Bool
$c>= :: GenericSourcePos -> GenericSourcePos -> Bool
> :: GenericSourcePos -> GenericSourcePos -> Bool
$c> :: GenericSourcePos -> GenericSourcePos -> Bool
<= :: GenericSourcePos -> GenericSourcePos -> Bool
$c<= :: GenericSourcePos -> GenericSourcePos -> Bool
< :: GenericSourcePos -> GenericSourcePos -> Bool
$c< :: GenericSourcePos -> GenericSourcePos -> Bool
compare :: GenericSourcePos -> GenericSourcePos -> Ordering
$ccompare :: GenericSourcePos -> GenericSourcePos -> Ordering
$cp1Ord :: Eq GenericSourcePos
Ord, (forall x. GenericSourcePos -> Rep GenericSourcePos x)
-> (forall x. Rep GenericSourcePos x -> GenericSourcePos)
-> Generic GenericSourcePos
forall x. Rep GenericSourcePos x -> GenericSourcePos
forall x. GenericSourcePos -> Rep GenericSourcePos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenericSourcePos x -> GenericSourcePos
$cfrom :: forall x. GenericSourcePos -> Rep GenericSourcePos x
Generic)
data Transaction = Transaction {
Transaction -> Integer
tindex :: Integer,
:: Text,
Transaction -> GenericSourcePos
tsourcepos :: GenericSourcePos,
Transaction -> Day
tdate :: Day,
Transaction -> Maybe Day
tdate2 :: Maybe Day,
Transaction -> Status
tstatus :: Status,
Transaction -> CommoditySymbol
tcode :: Text,
Transaction -> CommoditySymbol
tdescription :: Text,
:: Text,
Transaction -> [Tag]
ttags :: [Tag],
Transaction -> [Posting]
tpostings :: [Posting]
} deriving (Transaction -> Transaction -> Bool
(Transaction -> Transaction -> Bool)
-> (Transaction -> Transaction -> Bool) -> Eq Transaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transaction -> Transaction -> Bool
$c/= :: Transaction -> Transaction -> Bool
== :: Transaction -> Transaction -> Bool
$c== :: Transaction -> Transaction -> Bool
Eq,(forall x. Transaction -> Rep Transaction x)
-> (forall x. Rep Transaction x -> Transaction)
-> Generic Transaction
forall x. Rep Transaction x -> Transaction
forall x. Transaction -> Rep Transaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic,Int -> Transaction -> ShowS
[Transaction] -> ShowS
Transaction -> String
(Int -> Transaction -> ShowS)
-> (Transaction -> String)
-> ([Transaction] -> ShowS)
-> Show Transaction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transaction] -> ShowS
$cshowList :: [Transaction] -> ShowS
show :: Transaction -> String
$cshow :: Transaction -> String
showsPrec :: Int -> Transaction -> ShowS
$cshowsPrec :: Int -> Transaction -> ShowS
Show)
data TransactionModifier = TransactionModifier {
TransactionModifier -> CommoditySymbol
tmquerytxt :: Text,
TransactionModifier -> [Posting]
tmpostingrules :: [TMPostingRule]
} deriving (TransactionModifier -> TransactionModifier -> Bool
(TransactionModifier -> TransactionModifier -> Bool)
-> (TransactionModifier -> TransactionModifier -> Bool)
-> Eq TransactionModifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransactionModifier -> TransactionModifier -> Bool
$c/= :: TransactionModifier -> TransactionModifier -> Bool
== :: TransactionModifier -> TransactionModifier -> Bool
$c== :: TransactionModifier -> TransactionModifier -> Bool
Eq,(forall x. TransactionModifier -> Rep TransactionModifier x)
-> (forall x. Rep TransactionModifier x -> TransactionModifier)
-> Generic TransactionModifier
forall x. Rep TransactionModifier x -> TransactionModifier
forall x. TransactionModifier -> Rep TransactionModifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionModifier x -> TransactionModifier
$cfrom :: forall x. TransactionModifier -> Rep TransactionModifier x
Generic,Int -> TransactionModifier -> ShowS
[TransactionModifier] -> ShowS
TransactionModifier -> String
(Int -> TransactionModifier -> ShowS)
-> (TransactionModifier -> String)
-> ([TransactionModifier] -> ShowS)
-> Show TransactionModifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionModifier] -> ShowS
$cshowList :: [TransactionModifier] -> ShowS
show :: TransactionModifier -> String
$cshow :: TransactionModifier -> String
showsPrec :: Int -> TransactionModifier -> ShowS
$cshowsPrec :: Int -> TransactionModifier -> ShowS
Show)
nulltransactionmodifier :: TransactionModifier
nulltransactionmodifier = TransactionModifier :: CommoditySymbol -> [Posting] -> TransactionModifier
TransactionModifier{
tmquerytxt :: CommoditySymbol
tmquerytxt = CommoditySymbol
""
,tmpostingrules :: [Posting]
tmpostingrules = []
}
type TMPostingRule = Posting
data PeriodicTransaction = PeriodicTransaction {
PeriodicTransaction -> CommoditySymbol
ptperiodexpr :: Text,
PeriodicTransaction -> Interval
ptinterval :: Interval,
PeriodicTransaction -> DateSpan
ptspan :: DateSpan,
PeriodicTransaction -> Status
ptstatus :: Status,
PeriodicTransaction -> CommoditySymbol
ptcode :: Text,
PeriodicTransaction -> CommoditySymbol
ptdescription :: Text,
:: Text,
PeriodicTransaction -> [Tag]
pttags :: [Tag],
PeriodicTransaction -> [Posting]
ptpostings :: [Posting]
} deriving (PeriodicTransaction -> PeriodicTransaction -> Bool
(PeriodicTransaction -> PeriodicTransaction -> Bool)
-> (PeriodicTransaction -> PeriodicTransaction -> Bool)
-> Eq PeriodicTransaction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PeriodicTransaction -> PeriodicTransaction -> Bool
$c/= :: PeriodicTransaction -> PeriodicTransaction -> Bool
== :: PeriodicTransaction -> PeriodicTransaction -> Bool
$c== :: PeriodicTransaction -> PeriodicTransaction -> Bool
Eq,(forall x. PeriodicTransaction -> Rep PeriodicTransaction x)
-> (forall x. Rep PeriodicTransaction x -> PeriodicTransaction)
-> Generic PeriodicTransaction
forall x. Rep PeriodicTransaction x -> PeriodicTransaction
forall x. PeriodicTransaction -> Rep PeriodicTransaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PeriodicTransaction x -> PeriodicTransaction
$cfrom :: forall x. PeriodicTransaction -> Rep PeriodicTransaction x
Generic)
nullperiodictransaction :: PeriodicTransaction
nullperiodictransaction = PeriodicTransaction :: CommoditySymbol
-> Interval
-> DateSpan
-> Status
-> CommoditySymbol
-> CommoditySymbol
-> CommoditySymbol
-> [Tag]
-> [Posting]
-> PeriodicTransaction
PeriodicTransaction{
ptperiodexpr :: CommoditySymbol
ptperiodexpr = CommoditySymbol
""
,ptinterval :: Interval
ptinterval = Interval
forall a. Default a => a
def
,ptspan :: DateSpan
ptspan = DateSpan
forall a. Default a => a
def
,ptstatus :: Status
ptstatus = Status
Unmarked
,ptcode :: CommoditySymbol
ptcode = CommoditySymbol
""
,ptdescription :: CommoditySymbol
ptdescription = CommoditySymbol
""
,ptcomment :: CommoditySymbol
ptcomment = CommoditySymbol
""
,pttags :: [Tag]
pttags = []
,ptpostings :: [Posting]
ptpostings = []
}
data TimeclockCode = SetBalance | SetRequiredHours | In | Out | FinalOut deriving (TimeclockCode -> TimeclockCode -> Bool
(TimeclockCode -> TimeclockCode -> Bool)
-> (TimeclockCode -> TimeclockCode -> Bool) -> Eq TimeclockCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeclockCode -> TimeclockCode -> Bool
$c/= :: TimeclockCode -> TimeclockCode -> Bool
== :: TimeclockCode -> TimeclockCode -> Bool
$c== :: TimeclockCode -> TimeclockCode -> Bool
Eq,Eq TimeclockCode
Eq TimeclockCode
-> (TimeclockCode -> TimeclockCode -> Ordering)
-> (TimeclockCode -> TimeclockCode -> Bool)
-> (TimeclockCode -> TimeclockCode -> Bool)
-> (TimeclockCode -> TimeclockCode -> Bool)
-> (TimeclockCode -> TimeclockCode -> Bool)
-> (TimeclockCode -> TimeclockCode -> TimeclockCode)
-> (TimeclockCode -> TimeclockCode -> TimeclockCode)
-> Ord TimeclockCode
TimeclockCode -> TimeclockCode -> Bool
TimeclockCode -> TimeclockCode -> Ordering
TimeclockCode -> TimeclockCode -> TimeclockCode
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TimeclockCode -> TimeclockCode -> TimeclockCode
$cmin :: TimeclockCode -> TimeclockCode -> TimeclockCode
max :: TimeclockCode -> TimeclockCode -> TimeclockCode
$cmax :: TimeclockCode -> TimeclockCode -> TimeclockCode
>= :: TimeclockCode -> TimeclockCode -> Bool
$c>= :: TimeclockCode -> TimeclockCode -> Bool
> :: TimeclockCode -> TimeclockCode -> Bool
$c> :: TimeclockCode -> TimeclockCode -> Bool
<= :: TimeclockCode -> TimeclockCode -> Bool
$c<= :: TimeclockCode -> TimeclockCode -> Bool
< :: TimeclockCode -> TimeclockCode -> Bool
$c< :: TimeclockCode -> TimeclockCode -> Bool
compare :: TimeclockCode -> TimeclockCode -> Ordering
$ccompare :: TimeclockCode -> TimeclockCode -> Ordering
$cp1Ord :: Eq TimeclockCode
Ord,(forall x. TimeclockCode -> Rep TimeclockCode x)
-> (forall x. Rep TimeclockCode x -> TimeclockCode)
-> Generic TimeclockCode
forall x. Rep TimeclockCode x -> TimeclockCode
forall x. TimeclockCode -> Rep TimeclockCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TimeclockCode x -> TimeclockCode
$cfrom :: forall x. TimeclockCode -> Rep TimeclockCode x
Generic)
data TimeclockEntry = TimeclockEntry {
TimeclockEntry -> GenericSourcePos
tlsourcepos :: GenericSourcePos,
TimeclockEntry -> TimeclockCode
tlcode :: TimeclockCode,
TimeclockEntry -> LocalTime
tldatetime :: LocalTime,
TimeclockEntry -> CommoditySymbol
tlaccount :: AccountName,
TimeclockEntry -> CommoditySymbol
tldescription :: Text
} deriving (TimeclockEntry -> TimeclockEntry -> Bool
(TimeclockEntry -> TimeclockEntry -> Bool)
-> (TimeclockEntry -> TimeclockEntry -> Bool) -> Eq TimeclockEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeclockEntry -> TimeclockEntry -> Bool
$c/= :: TimeclockEntry -> TimeclockEntry -> Bool
== :: TimeclockEntry -> TimeclockEntry -> Bool
$c== :: TimeclockEntry -> TimeclockEntry -> Bool
Eq,Eq TimeclockEntry
Eq TimeclockEntry
-> (TimeclockEntry -> TimeclockEntry -> Ordering)
-> (TimeclockEntry -> TimeclockEntry -> Bool)
-> (TimeclockEntry -> TimeclockEntry -> Bool)
-> (TimeclockEntry -> TimeclockEntry -> Bool)
-> (TimeclockEntry -> TimeclockEntry -> Bool)
-> (TimeclockEntry -> TimeclockEntry -> TimeclockEntry)
-> (TimeclockEntry -> TimeclockEntry -> TimeclockEntry)
-> Ord TimeclockEntry
TimeclockEntry -> TimeclockEntry -> Bool
TimeclockEntry -> TimeclockEntry -> Ordering
TimeclockEntry -> TimeclockEntry -> TimeclockEntry
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry
$cmin :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry
max :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry
$cmax :: TimeclockEntry -> TimeclockEntry -> TimeclockEntry
>= :: TimeclockEntry -> TimeclockEntry -> Bool
$c>= :: TimeclockEntry -> TimeclockEntry -> Bool
> :: TimeclockEntry -> TimeclockEntry -> Bool
$c> :: TimeclockEntry -> TimeclockEntry -> Bool
<= :: TimeclockEntry -> TimeclockEntry -> Bool
$c<= :: TimeclockEntry -> TimeclockEntry -> Bool
< :: TimeclockEntry -> TimeclockEntry -> Bool
$c< :: TimeclockEntry -> TimeclockEntry -> Bool
compare :: TimeclockEntry -> TimeclockEntry -> Ordering
$ccompare :: TimeclockEntry -> TimeclockEntry -> Ordering
$cp1Ord :: Eq TimeclockEntry
Ord,(forall x. TimeclockEntry -> Rep TimeclockEntry x)
-> (forall x. Rep TimeclockEntry x -> TimeclockEntry)
-> Generic TimeclockEntry
forall x. Rep TimeclockEntry x -> TimeclockEntry
forall x. TimeclockEntry -> Rep TimeclockEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TimeclockEntry x -> TimeclockEntry
$cfrom :: forall x. TimeclockEntry -> Rep TimeclockEntry x
Generic)
data PriceDirective = PriceDirective {
PriceDirective -> Day
pddate :: Day
,PriceDirective -> CommoditySymbol
pdcommodity :: CommoditySymbol
,PriceDirective -> Amount
pdamount :: Amount
} deriving (PriceDirective -> PriceDirective -> Bool
(PriceDirective -> PriceDirective -> Bool)
-> (PriceDirective -> PriceDirective -> Bool) -> Eq PriceDirective
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PriceDirective -> PriceDirective -> Bool
$c/= :: PriceDirective -> PriceDirective -> Bool
== :: PriceDirective -> PriceDirective -> Bool
$c== :: PriceDirective -> PriceDirective -> Bool
Eq,Eq PriceDirective
Eq PriceDirective
-> (PriceDirective -> PriceDirective -> Ordering)
-> (PriceDirective -> PriceDirective -> Bool)
-> (PriceDirective -> PriceDirective -> Bool)
-> (PriceDirective -> PriceDirective -> Bool)
-> (PriceDirective -> PriceDirective -> Bool)
-> (PriceDirective -> PriceDirective -> PriceDirective)
-> (PriceDirective -> PriceDirective -> PriceDirective)
-> Ord PriceDirective
PriceDirective -> PriceDirective -> Bool
PriceDirective -> PriceDirective -> Ordering
PriceDirective -> PriceDirective -> PriceDirective
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PriceDirective -> PriceDirective -> PriceDirective
$cmin :: PriceDirective -> PriceDirective -> PriceDirective
max :: PriceDirective -> PriceDirective -> PriceDirective
$cmax :: PriceDirective -> PriceDirective -> PriceDirective
>= :: PriceDirective -> PriceDirective -> Bool
$c>= :: PriceDirective -> PriceDirective -> Bool
> :: PriceDirective -> PriceDirective -> Bool
$c> :: PriceDirective -> PriceDirective -> Bool
<= :: PriceDirective -> PriceDirective -> Bool
$c<= :: PriceDirective -> PriceDirective -> Bool
< :: PriceDirective -> PriceDirective -> Bool
$c< :: PriceDirective -> PriceDirective -> Bool
compare :: PriceDirective -> PriceDirective -> Ordering
$ccompare :: PriceDirective -> PriceDirective -> Ordering
$cp1Ord :: Eq PriceDirective
Ord,(forall x. PriceDirective -> Rep PriceDirective x)
-> (forall x. Rep PriceDirective x -> PriceDirective)
-> Generic PriceDirective
forall x. Rep PriceDirective x -> PriceDirective
forall x. PriceDirective -> Rep PriceDirective x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PriceDirective x -> PriceDirective
$cfrom :: forall x. PriceDirective -> Rep PriceDirective x
Generic,Int -> PriceDirective -> ShowS
[PriceDirective] -> ShowS
PriceDirective -> String
(Int -> PriceDirective -> ShowS)
-> (PriceDirective -> String)
-> ([PriceDirective] -> ShowS)
-> Show PriceDirective
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PriceDirective] -> ShowS
$cshowList :: [PriceDirective] -> ShowS
show :: PriceDirective -> String
$cshow :: PriceDirective -> String
showsPrec :: Int -> PriceDirective -> ShowS
$cshowsPrec :: Int -> PriceDirective -> ShowS
Show)
data MarketPrice = MarketPrice {
MarketPrice -> Day
mpdate :: Day
,MarketPrice -> CommoditySymbol
mpfrom :: CommoditySymbol
,MarketPrice -> CommoditySymbol
mpto :: CommoditySymbol
,MarketPrice -> Quantity
mprate :: Quantity
} deriving (MarketPrice -> MarketPrice -> Bool
(MarketPrice -> MarketPrice -> Bool)
-> (MarketPrice -> MarketPrice -> Bool) -> Eq MarketPrice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MarketPrice -> MarketPrice -> Bool
$c/= :: MarketPrice -> MarketPrice -> Bool
== :: MarketPrice -> MarketPrice -> Bool
$c== :: MarketPrice -> MarketPrice -> Bool
Eq,Eq MarketPrice
Eq MarketPrice
-> (MarketPrice -> MarketPrice -> Ordering)
-> (MarketPrice -> MarketPrice -> Bool)
-> (MarketPrice -> MarketPrice -> Bool)
-> (MarketPrice -> MarketPrice -> Bool)
-> (MarketPrice -> MarketPrice -> Bool)
-> (MarketPrice -> MarketPrice -> MarketPrice)
-> (MarketPrice -> MarketPrice -> MarketPrice)
-> Ord MarketPrice
MarketPrice -> MarketPrice -> Bool
MarketPrice -> MarketPrice -> Ordering
MarketPrice -> MarketPrice -> MarketPrice
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MarketPrice -> MarketPrice -> MarketPrice
$cmin :: MarketPrice -> MarketPrice -> MarketPrice
max :: MarketPrice -> MarketPrice -> MarketPrice
$cmax :: MarketPrice -> MarketPrice -> MarketPrice
>= :: MarketPrice -> MarketPrice -> Bool
$c>= :: MarketPrice -> MarketPrice -> Bool
> :: MarketPrice -> MarketPrice -> Bool
$c> :: MarketPrice -> MarketPrice -> Bool
<= :: MarketPrice -> MarketPrice -> Bool
$c<= :: MarketPrice -> MarketPrice -> Bool
< :: MarketPrice -> MarketPrice -> Bool
$c< :: MarketPrice -> MarketPrice -> Bool
compare :: MarketPrice -> MarketPrice -> Ordering
$ccompare :: MarketPrice -> MarketPrice -> Ordering
$cp1Ord :: Eq MarketPrice
Ord,(forall x. MarketPrice -> Rep MarketPrice x)
-> (forall x. Rep MarketPrice x -> MarketPrice)
-> Generic MarketPrice
forall x. Rep MarketPrice x -> MarketPrice
forall x. MarketPrice -> Rep MarketPrice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MarketPrice x -> MarketPrice
$cfrom :: forall x. MarketPrice -> Rep MarketPrice x
Generic)
data Journal = Journal {
Journal -> Maybe Integer
jparsedefaultyear :: Maybe Year
,Journal -> Maybe (CommoditySymbol, AmountStyle)
jparsedefaultcommodity :: Maybe (CommoditySymbol,AmountStyle)
,Journal -> Maybe Char
jparsedecimalmark :: Maybe DecimalMark
,Journal -> [CommoditySymbol]
jparseparentaccounts :: [AccountName]
,Journal -> [AccountAlias]
jparsealiases :: [AccountAlias]
,Journal -> [TimeclockEntry]
jparsetimeclockentries :: [TimeclockEntry]
,Journal -> [String]
jincludefilestack :: [FilePath]
,Journal -> [(CommoditySymbol, PayeeDeclarationInfo)]
jdeclaredpayees :: [(Payee,PayeeDeclarationInfo)]
,Journal -> [(CommoditySymbol, AccountDeclarationInfo)]
jdeclaredaccounts :: [(AccountName,AccountDeclarationInfo)]
,Journal -> Map AccountType [CommoditySymbol]
jdeclaredaccounttypes :: M.Map AccountType [AccountName]
,Journal -> Map CommoditySymbol AmountStyle
jglobalcommoditystyles :: M.Map CommoditySymbol AmountStyle
,Journal -> Map CommoditySymbol Commodity
jcommodities :: M.Map CommoditySymbol Commodity
,Journal -> Map CommoditySymbol AmountStyle
jinferredcommodities :: M.Map CommoditySymbol AmountStyle
,Journal -> [PriceDirective]
jpricedirectives :: [PriceDirective]
,Journal -> [MarketPrice]
jinferredmarketprices :: [MarketPrice]
,Journal -> [TransactionModifier]
jtxnmodifiers :: [TransactionModifier]
,Journal -> [PeriodicTransaction]
jperiodictxns :: [PeriodicTransaction]
,Journal -> [Transaction]
jtxns :: [Transaction]
, :: Text
,Journal -> [(String, CommoditySymbol)]
jfiles :: [(FilePath, Text)]
,Journal -> ClockTime
jlastreadtime :: ClockTime
} deriving (Journal -> Journal -> Bool
(Journal -> Journal -> Bool)
-> (Journal -> Journal -> Bool) -> Eq Journal
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Journal -> Journal -> Bool
$c/= :: Journal -> Journal -> Bool
== :: Journal -> Journal -> Bool
$c== :: Journal -> Journal -> Bool
Eq, (forall x. Journal -> Rep Journal x)
-> (forall x. Rep Journal x -> Journal) -> Generic Journal
forall x. Rep Journal x -> Journal
forall x. Journal -> Rep Journal x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Journal x -> Journal
$cfrom :: forall x. Journal -> Rep Journal x
Generic)
deriving instance Generic ClockTime
type ParsedJournal = Journal
type StorageFormat = String
data PayeeDeclarationInfo = PayeeDeclarationInfo {
:: Text
,PayeeDeclarationInfo -> [Tag]
pditags :: [Tag]
} deriving (PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool
(PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool)
-> (PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool)
-> Eq PayeeDeclarationInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool
$c/= :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool
== :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool
$c== :: PayeeDeclarationInfo -> PayeeDeclarationInfo -> Bool
Eq,Int -> PayeeDeclarationInfo -> ShowS
[PayeeDeclarationInfo] -> ShowS
PayeeDeclarationInfo -> String
(Int -> PayeeDeclarationInfo -> ShowS)
-> (PayeeDeclarationInfo -> String)
-> ([PayeeDeclarationInfo] -> ShowS)
-> Show PayeeDeclarationInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PayeeDeclarationInfo] -> ShowS
$cshowList :: [PayeeDeclarationInfo] -> ShowS
show :: PayeeDeclarationInfo -> String
$cshow :: PayeeDeclarationInfo -> String
showsPrec :: Int -> PayeeDeclarationInfo -> ShowS
$cshowsPrec :: Int -> PayeeDeclarationInfo -> ShowS
Show,(forall x. PayeeDeclarationInfo -> Rep PayeeDeclarationInfo x)
-> (forall x. Rep PayeeDeclarationInfo x -> PayeeDeclarationInfo)
-> Generic PayeeDeclarationInfo
forall x. Rep PayeeDeclarationInfo x -> PayeeDeclarationInfo
forall x. PayeeDeclarationInfo -> Rep PayeeDeclarationInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PayeeDeclarationInfo x -> PayeeDeclarationInfo
$cfrom :: forall x. PayeeDeclarationInfo -> Rep PayeeDeclarationInfo x
Generic)
nullpayeedeclarationinfo :: PayeeDeclarationInfo
nullpayeedeclarationinfo = PayeeDeclarationInfo :: CommoditySymbol -> [Tag] -> PayeeDeclarationInfo
PayeeDeclarationInfo {
pdicomment :: CommoditySymbol
pdicomment = CommoditySymbol
""
,pditags :: [Tag]
pditags = []
}
data AccountDeclarationInfo = AccountDeclarationInfo {
:: Text
,AccountDeclarationInfo -> [Tag]
aditags :: [Tag]
,AccountDeclarationInfo -> Int
adideclarationorder :: Int
} deriving (AccountDeclarationInfo -> AccountDeclarationInfo -> Bool
(AccountDeclarationInfo -> AccountDeclarationInfo -> Bool)
-> (AccountDeclarationInfo -> AccountDeclarationInfo -> Bool)
-> Eq AccountDeclarationInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool
$c/= :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool
== :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool
$c== :: AccountDeclarationInfo -> AccountDeclarationInfo -> Bool
Eq,Int -> AccountDeclarationInfo -> ShowS
[AccountDeclarationInfo] -> ShowS
AccountDeclarationInfo -> String
(Int -> AccountDeclarationInfo -> ShowS)
-> (AccountDeclarationInfo -> String)
-> ([AccountDeclarationInfo] -> ShowS)
-> Show AccountDeclarationInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountDeclarationInfo] -> ShowS
$cshowList :: [AccountDeclarationInfo] -> ShowS
show :: AccountDeclarationInfo -> String
$cshow :: AccountDeclarationInfo -> String
showsPrec :: Int -> AccountDeclarationInfo -> ShowS
$cshowsPrec :: Int -> AccountDeclarationInfo -> ShowS
Show,(forall x. AccountDeclarationInfo -> Rep AccountDeclarationInfo x)
-> (forall x.
Rep AccountDeclarationInfo x -> AccountDeclarationInfo)
-> Generic AccountDeclarationInfo
forall x. Rep AccountDeclarationInfo x -> AccountDeclarationInfo
forall x. AccountDeclarationInfo -> Rep AccountDeclarationInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountDeclarationInfo x -> AccountDeclarationInfo
$cfrom :: forall x. AccountDeclarationInfo -> Rep AccountDeclarationInfo x
Generic)
nullaccountdeclarationinfo :: AccountDeclarationInfo
nullaccountdeclarationinfo = AccountDeclarationInfo :: CommoditySymbol -> [Tag] -> Int -> AccountDeclarationInfo
AccountDeclarationInfo {
adicomment :: CommoditySymbol
adicomment = CommoditySymbol
""
,aditags :: [Tag]
aditags = []
,adideclarationorder :: Int
adideclarationorder = Int
0
}
data Account = Account {
Account -> CommoditySymbol
aname :: AccountName
,Account -> Maybe AccountDeclarationInfo
adeclarationinfo :: Maybe AccountDeclarationInfo
,Account -> [Account]
asubs :: [Account]
,Account -> Maybe Account
aparent :: Maybe Account
,Account -> Bool
aboring :: Bool
,Account -> Int
anumpostings :: Int
,Account -> MixedAmount
aebalance :: MixedAmount
,Account -> MixedAmount
aibalance :: MixedAmount
} deriving ((forall x. Account -> Rep Account x)
-> (forall x. Rep Account x -> Account) -> Generic Account
forall x. Rep Account x -> Account
forall x. Account -> Rep Account x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Account x -> Account
$cfrom :: forall x. Account -> Rep Account x
Generic)
data NormalSign = NormallyPositive | NormallyNegative deriving (Int -> NormalSign -> ShowS
[NormalSign] -> ShowS
NormalSign -> String
(Int -> NormalSign -> ShowS)
-> (NormalSign -> String)
-> ([NormalSign] -> ShowS)
-> Show NormalSign
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NormalSign] -> ShowS
$cshowList :: [NormalSign] -> ShowS
show :: NormalSign -> String
$cshow :: NormalSign -> String
showsPrec :: Int -> NormalSign -> ShowS
$cshowsPrec :: Int -> NormalSign -> ShowS
Show, NormalSign -> NormalSign -> Bool
(NormalSign -> NormalSign -> Bool)
-> (NormalSign -> NormalSign -> Bool) -> Eq NormalSign
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NormalSign -> NormalSign -> Bool
$c/= :: NormalSign -> NormalSign -> Bool
== :: NormalSign -> NormalSign -> Bool
$c== :: NormalSign -> NormalSign -> Bool
Eq)
data Ledger = Ledger {
Ledger -> Journal
ljournal :: Journal,
Ledger -> [Account]
laccounts :: [Account]
}