haspara-0.0.0.1: A library providing definitions to work with monetary values.
Safe HaskellNone
LanguageHaskell2010

Haspara.Accounting.Ledger

Documentation

data Ledger a o (s :: Nat) Source #

Constructors

Ledger 

Instances

Instances details
(Eq a, Eq o) => Eq (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: Ledger a o s -> Ledger a o s -> Bool #

(/=) :: Ledger a o s -> Ledger a o s -> Bool #

(Ord a, Ord o) => Ord (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: Ledger a o s -> Ledger a o s -> Ordering #

(<) :: Ledger a o s -> Ledger a o s -> Bool #

(<=) :: Ledger a o s -> Ledger a o s -> Bool #

(>) :: Ledger a o s -> Ledger a o s -> Bool #

(>=) :: Ledger a o s -> Ledger a o s -> Bool #

max :: Ledger a o s -> Ledger a o s -> Ledger a o s #

min :: Ledger a o s -> Ledger a o s -> Ledger a o s #

(KnownNat s, Show a, Show o) => Show (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> Ledger a o s -> ShowS #

show :: Ledger a o s -> String #

showList :: [Ledger a o s] -> ShowS #

Generic (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (Ledger a o s) :: Type -> Type #

Methods

from :: Ledger a o s -> Rep (Ledger a o s) x #

to :: Rep (Ledger a o s) x -> Ledger a o s #

(ToJSON o, ToJSON a, KnownNat s) => ToJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

toJSON :: Ledger a o s -> Value #

toEncoding :: Ledger a o s -> Encoding #

toJSONList :: [Ledger a o s] -> Value #

toEncodingList :: [Ledger a o s] -> Encoding #

(KnownNat s, FromJSON a, FromJSON o) => FromJSON (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

parseJSON :: Value -> Parser (Ledger a o s) #

parseJSONList :: Value -> Parser [Ledger a o s] #

type Rep (Ledger a o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (Ledger a o s) = D1 ('MetaData "Ledger" "Haspara.Accounting.Ledger" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'False) (C1 ('MetaCons "Ledger" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ledgerAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Account a)) :*: S1 ('MetaSel ('Just "ledgerOpening") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))) :*: (S1 ('MetaSel ('Just "ledgerClosing") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s)) :*: S1 ('MetaSel ('Just "ledgerRunning") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [LedgerItem o s]))))

data LedgerItem o (s :: Nat) Source #

Constructors

LedgerItem 

Fields

Instances

Instances details
Eq o => Eq (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

(==) :: LedgerItem o s -> LedgerItem o s -> Bool #

(/=) :: LedgerItem o s -> LedgerItem o s -> Bool #

Ord o => Ord (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

compare :: LedgerItem o s -> LedgerItem o s -> Ordering #

(<) :: LedgerItem o s -> LedgerItem o s -> Bool #

(<=) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>) :: LedgerItem o s -> LedgerItem o s -> Bool #

(>=) :: LedgerItem o s -> LedgerItem o s -> Bool #

max :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

min :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s #

(Show o, KnownNat s) => Show (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Methods

showsPrec :: Int -> LedgerItem o s -> ShowS #

show :: LedgerItem o s -> String #

showList :: [LedgerItem o s] -> ShowS #

Generic (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

Associated Types

type Rep (LedgerItem o s) :: Type -> Type #

Methods

from :: LedgerItem o s -> Rep (LedgerItem o s) x #

to :: Rep (LedgerItem o s) x -> LedgerItem o s #

(KnownNat s, ToJSON o) => ToJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

(FromJSON o, KnownNat s) => FromJSON (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) Source # 
Instance details

Defined in Haspara.Accounting.Ledger

type Rep (LedgerItem o s) = D1 ('MetaData "LedgerItem" "Haspara.Accounting.Ledger" "haspara-0.0.0.1-GIZpgp6So3jGG6B29GnUaf" 'False) (C1 ('MetaCons "LedgerItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerItemEntry") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Entry o s)) :*: S1 ('MetaSel ('Just "ledgerItemBalance") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Quantity s))))

mkLedger :: KnownNat s => Account a -> Quantity s -> [Entry o s] -> Ledger a o s Source #

addEntry :: KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s Source #