{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE KindSignatures #-} module Haspara.Accounting.Ledger where import Deriving.Aeson (CustomJSON(CustomJSON), FromJSON, Generic, ToJSON) import Deriving.Aeson.Stock (PrefixedSnake) import GHC.TypeLits (KnownNat, Nat) import Haspara (Quantity) import Haspara.Accounting.Account (Account) import Haspara.Accounting.Entry (Entry(..), entryQuantity) data Ledger a o (s :: Nat) = Ledger { Ledger a o s -> Account a ledgerAccount :: !(Account a) , Ledger a o s -> Quantity s ledgerOpening :: !(Quantity s) , Ledger a o s -> Quantity s ledgerClosing :: !(Quantity s) , Ledger a o s -> [LedgerItem o s] ledgerRunning :: ![LedgerItem o s] } deriving (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) -> Eq (Ledger a o s) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall a o (s :: Nat). (Eq a, Eq o) => Ledger a o s -> Ledger a o s -> Bool /= :: Ledger a o s -> Ledger a o s -> Bool $c/= :: forall a o (s :: Nat). (Eq a, Eq o) => Ledger a o s -> Ledger a o s -> Bool == :: Ledger a o s -> Ledger a o s -> Bool $c== :: forall a o (s :: Nat). (Eq a, Eq o) => Ledger a o s -> Ledger a o s -> Bool Eq, (forall x. Ledger a o s -> Rep (Ledger a o s) x) -> (forall x. Rep (Ledger a o s) x -> Ledger a o s) -> Generic (Ledger a o s) forall x. Rep (Ledger a o s) x -> Ledger a o s forall x. Ledger a o s -> Rep (Ledger a o s) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall a o (s :: Nat) x. Rep (Ledger a o s) x -> Ledger a o s forall a o (s :: Nat) x. Ledger a o s -> Rep (Ledger a o s) x $cto :: forall a o (s :: Nat) x. Rep (Ledger a o s) x -> Ledger a o s $cfrom :: forall a o (s :: Nat) x. Ledger a o s -> Rep (Ledger a o s) x Generic, Eq (Ledger a o s) Eq (Ledger a o s) -> (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) -> (Ledger a o s -> Ledger a o s -> Ledger a o s) -> (Ledger a o s -> Ledger a o s -> Ledger a o s) -> Ord (Ledger a o s) Ledger a o s -> Ledger a o s -> Bool Ledger a o s -> Ledger a o s -> Ordering Ledger a o s -> Ledger a o s -> Ledger a o s 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 forall a o (s :: Nat). (Ord a, Ord o) => Eq (Ledger a o s) forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Bool forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Ordering forall a o (s :: Nat). (Ord a, Ord o) => 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 $cmin :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Ledger a o s max :: Ledger a o s -> Ledger a o s -> Ledger a o s $cmax :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Ledger a o s >= :: Ledger a o s -> Ledger a o s -> Bool $c>= :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Bool > :: Ledger a o s -> Ledger a o s -> Bool $c> :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Bool <= :: Ledger a o s -> Ledger a o s -> Bool $c<= :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Bool < :: Ledger a o s -> Ledger a o s -> Bool $c< :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Bool compare :: Ledger a o s -> Ledger a o s -> Ordering $ccompare :: forall a o (s :: Nat). (Ord a, Ord o) => Ledger a o s -> Ledger a o s -> Ordering $cp1Ord :: forall a o (s :: Nat). (Ord a, Ord o) => Eq (Ledger a o s) Ord, Int -> Ledger a o s -> ShowS [Ledger a o s] -> ShowS Ledger a o s -> String (Int -> Ledger a o s -> ShowS) -> (Ledger a o s -> String) -> ([Ledger a o s] -> ShowS) -> Show (Ledger a o s) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall a o (s :: Nat). (KnownNat s, Show a, Show o) => Int -> Ledger a o s -> ShowS forall a o (s :: Nat). (KnownNat s, Show a, Show o) => [Ledger a o s] -> ShowS forall a o (s :: Nat). (KnownNat s, Show a, Show o) => Ledger a o s -> String showList :: [Ledger a o s] -> ShowS $cshowList :: forall a o (s :: Nat). (KnownNat s, Show a, Show o) => [Ledger a o s] -> ShowS show :: Ledger a o s -> String $cshow :: forall a o (s :: Nat). (KnownNat s, Show a, Show o) => Ledger a o s -> String showsPrec :: Int -> Ledger a o s -> ShowS $cshowsPrec :: forall a o (s :: Nat). (KnownNat s, Show a, Show o) => Int -> Ledger a o s -> ShowS Show) deriving (Value -> Parser [Ledger a o s] Value -> Parser (Ledger a o s) (Value -> Parser (Ledger a o s)) -> (Value -> Parser [Ledger a o s]) -> FromJSON (Ledger a o s) forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a forall a o (s :: Nat). (KnownNat s, FromJSON a, FromJSON o) => Value -> Parser [Ledger a o s] forall a o (s :: Nat). (KnownNat s, FromJSON a, FromJSON o) => Value -> Parser (Ledger a o s) parseJSONList :: Value -> Parser [Ledger a o s] $cparseJSONList :: forall a o (s :: Nat). (KnownNat s, FromJSON a, FromJSON o) => Value -> Parser [Ledger a o s] parseJSON :: Value -> Parser (Ledger a o s) $cparseJSON :: forall a o (s :: Nat). (KnownNat s, FromJSON a, FromJSON o) => Value -> Parser (Ledger a o s) FromJSON, [Ledger a o s] -> Encoding [Ledger a o s] -> Value Ledger a o s -> Encoding Ledger a o s -> Value (Ledger a o s -> Value) -> (Ledger a o s -> Encoding) -> ([Ledger a o s] -> Value) -> ([Ledger a o s] -> Encoding) -> ToJSON (Ledger a o s) forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => [Ledger a o s] -> Encoding forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => [Ledger a o s] -> Value forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => Ledger a o s -> Encoding forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => Ledger a o s -> Value toEncodingList :: [Ledger a o s] -> Encoding $ctoEncodingList :: forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => [Ledger a o s] -> Encoding toJSONList :: [Ledger a o s] -> Value $ctoJSONList :: forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => [Ledger a o s] -> Value toEncoding :: Ledger a o s -> Encoding $ctoEncoding :: forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => Ledger a o s -> Encoding toJSON :: Ledger a o s -> Value $ctoJSON :: forall a o (s :: Nat). (ToJSON o, ToJSON a, KnownNat s) => Ledger a o s -> Value ToJSON) via PrefixedSnake "ledger" (Ledger a o s) data LedgerItem o (s :: Nat) = LedgerItem { LedgerItem o s -> Entry o s ledgerItemEntry :: !(Entry o s) , LedgerItem o s -> Quantity s ledgerItemBalance :: !(Quantity s) } deriving (LedgerItem o s -> LedgerItem o s -> Bool (LedgerItem o s -> LedgerItem o s -> Bool) -> (LedgerItem o s -> LedgerItem o s -> Bool) -> Eq (LedgerItem o s) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a forall o (s :: Nat). Eq o => LedgerItem o s -> LedgerItem o s -> Bool /= :: LedgerItem o s -> LedgerItem o s -> Bool $c/= :: forall o (s :: Nat). Eq o => LedgerItem o s -> LedgerItem o s -> Bool == :: LedgerItem o s -> LedgerItem o s -> Bool $c== :: forall o (s :: Nat). Eq o => LedgerItem o s -> LedgerItem o s -> Bool Eq, (forall x. LedgerItem o s -> Rep (LedgerItem o s) x) -> (forall x. Rep (LedgerItem o s) x -> LedgerItem o s) -> Generic (LedgerItem o s) forall x. Rep (LedgerItem o s) x -> LedgerItem o s forall x. LedgerItem o s -> Rep (LedgerItem o s) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall o (s :: Nat) x. Rep (LedgerItem o s) x -> LedgerItem o s forall o (s :: Nat) x. LedgerItem o s -> Rep (LedgerItem o s) x $cto :: forall o (s :: Nat) x. Rep (LedgerItem o s) x -> LedgerItem o s $cfrom :: forall o (s :: Nat) x. LedgerItem o s -> Rep (LedgerItem o s) x Generic, Eq (LedgerItem o s) Eq (LedgerItem o s) -> (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) -> (LedgerItem o s -> LedgerItem o s -> LedgerItem o s) -> (LedgerItem o s -> LedgerItem o s -> LedgerItem o s) -> Ord (LedgerItem o s) LedgerItem o s -> LedgerItem o s -> Bool LedgerItem o s -> LedgerItem o s -> Ordering LedgerItem o s -> LedgerItem o s -> LedgerItem o s 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 forall o (s :: Nat). Ord o => Eq (LedgerItem o s) forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Bool forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Ordering forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> LedgerItem o s min :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s $cmin :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> LedgerItem o s max :: LedgerItem o s -> LedgerItem o s -> LedgerItem o s $cmax :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> LedgerItem o s >= :: LedgerItem o s -> LedgerItem o s -> Bool $c>= :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Bool > :: LedgerItem o s -> LedgerItem o s -> Bool $c> :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Bool <= :: LedgerItem o s -> LedgerItem o s -> Bool $c<= :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Bool < :: LedgerItem o s -> LedgerItem o s -> Bool $c< :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Bool compare :: LedgerItem o s -> LedgerItem o s -> Ordering $ccompare :: forall o (s :: Nat). Ord o => LedgerItem o s -> LedgerItem o s -> Ordering $cp1Ord :: forall o (s :: Nat). Ord o => Eq (LedgerItem o s) Ord, Int -> LedgerItem o s -> ShowS [LedgerItem o s] -> ShowS LedgerItem o s -> String (Int -> LedgerItem o s -> ShowS) -> (LedgerItem o s -> String) -> ([LedgerItem o s] -> ShowS) -> Show (LedgerItem o s) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a forall o (s :: Nat). (Show o, KnownNat s) => Int -> LedgerItem o s -> ShowS forall o (s :: Nat). (Show o, KnownNat s) => [LedgerItem o s] -> ShowS forall o (s :: Nat). (Show o, KnownNat s) => LedgerItem o s -> String showList :: [LedgerItem o s] -> ShowS $cshowList :: forall o (s :: Nat). (Show o, KnownNat s) => [LedgerItem o s] -> ShowS show :: LedgerItem o s -> String $cshow :: forall o (s :: Nat). (Show o, KnownNat s) => LedgerItem o s -> String showsPrec :: Int -> LedgerItem o s -> ShowS $cshowsPrec :: forall o (s :: Nat). (Show o, KnownNat s) => Int -> LedgerItem o s -> ShowS Show) deriving (Value -> Parser [LedgerItem o s] Value -> Parser (LedgerItem o s) (Value -> Parser (LedgerItem o s)) -> (Value -> Parser [LedgerItem o s]) -> FromJSON (LedgerItem o s) forall a. (Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a forall o (s :: Nat). (FromJSON o, KnownNat s) => Value -> Parser [LedgerItem o s] forall o (s :: Nat). (FromJSON o, KnownNat s) => Value -> Parser (LedgerItem o s) parseJSONList :: Value -> Parser [LedgerItem o s] $cparseJSONList :: forall o (s :: Nat). (FromJSON o, KnownNat s) => Value -> Parser [LedgerItem o s] parseJSON :: Value -> Parser (LedgerItem o s) $cparseJSON :: forall o (s :: Nat). (FromJSON o, KnownNat s) => Value -> Parser (LedgerItem o s) FromJSON, [LedgerItem o s] -> Encoding [LedgerItem o s] -> Value LedgerItem o s -> Encoding LedgerItem o s -> Value (LedgerItem o s -> Value) -> (LedgerItem o s -> Encoding) -> ([LedgerItem o s] -> Value) -> ([LedgerItem o s] -> Encoding) -> ToJSON (LedgerItem o s) forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a forall o (s :: Nat). (KnownNat s, ToJSON o) => [LedgerItem o s] -> Encoding forall o (s :: Nat). (KnownNat s, ToJSON o) => [LedgerItem o s] -> Value forall o (s :: Nat). (KnownNat s, ToJSON o) => LedgerItem o s -> Encoding forall o (s :: Nat). (KnownNat s, ToJSON o) => LedgerItem o s -> Value toEncodingList :: [LedgerItem o s] -> Encoding $ctoEncodingList :: forall o (s :: Nat). (KnownNat s, ToJSON o) => [LedgerItem o s] -> Encoding toJSONList :: [LedgerItem o s] -> Value $ctoJSONList :: forall o (s :: Nat). (KnownNat s, ToJSON o) => [LedgerItem o s] -> Value toEncoding :: LedgerItem o s -> Encoding $ctoEncoding :: forall o (s :: Nat). (KnownNat s, ToJSON o) => LedgerItem o s -> Encoding toJSON :: LedgerItem o s -> Value $ctoJSON :: forall o (s :: Nat). (KnownNat s, ToJSON o) => LedgerItem o s -> Value ToJSON) via PrefixedSnake "ledgerItem" (LedgerItem o s) mkLedger :: KnownNat s => Account a -> Quantity s -> [Entry o s] -> Ledger a o s mkLedger :: Account a -> Quantity s -> [Entry o s] -> Ledger a o s mkLedger Account a a Quantity s o = (Ledger a o s -> Entry o s -> Ledger a o s) -> Ledger a o s -> [Entry o s] -> Ledger a o s forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b foldl Ledger a o s -> Entry o s -> Ledger a o s forall (s :: Nat) a o. KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s addEntry (Account a -> Quantity s -> Quantity s -> [LedgerItem o s] -> Ledger a o s forall a o (s :: Nat). Account a -> Quantity s -> Quantity s -> [LedgerItem o s] -> Ledger a o s Ledger Account a a Quantity s o Quantity s o []) addEntry :: KnownNat s => Ledger a o s -> Entry o s -> Ledger a o s addEntry :: Ledger a o s -> Entry o s -> Ledger a o s addEntry l :: Ledger a o s l@(Ledger Account a _ Quantity s _ Quantity s c [LedgerItem o s] r) Entry o s e = Ledger a o s l { ledgerClosing :: Quantity s ledgerClosing = Quantity s balance, ledgerRunning :: [LedgerItem o s] ledgerRunning = [LedgerItem o s] r [LedgerItem o s] -> [LedgerItem o s] -> [LedgerItem o s] forall a. Semigroup a => a -> a -> a <> [LedgerItem o s item]} where balance :: Quantity s balance = Quantity s c Quantity s -> Quantity s -> Quantity s forall a. Num a => a -> a -> a + Entry o s -> Quantity s forall (s :: Nat) o. KnownNat s => Entry o s -> Quantity s entryQuantity Entry o s e item :: LedgerItem o s item = Entry o s -> Quantity s -> LedgerItem o s forall o (s :: Nat). Entry o s -> Quantity s -> LedgerItem o s LedgerItem Entry o s e Quantity s balance