summaryrefslogtreecommitdiffstats
path: root/app/Data/Ledger.hs
diff options
context:
space:
mode:
authorRutger Broekhoff2025-07-23 12:05:08 +0200
committerRutger Broekhoff2025-07-23 12:05:08 +0200
commit56273cf3b371312f0e72fc2af95a9dcacc8228b8 (patch)
treeb4249523cab145fa32e2fdfb826cb592dcfdc127 /app/Data/Ledger.hs
parenta40d93a36f0dd9f493757d793321f38a58cbb21b (diff)
downloadrdcapsis-56273cf3b371312f0e72fc2af95a9dcacc8228b8.tar.gz
rdcapsis-56273cf3b371312f0e72fc2af95a9dcacc8228b8.zip
Slaying
Diffstat (limited to 'app/Data/Ledger.hs')
-rw-r--r--app/Data/Ledger.hs115
1 files changed, 115 insertions, 0 deletions
diff --git a/app/Data/Ledger.hs b/app/Data/Ledger.hs
new file mode 100644
index 0000000..ceca9da
--- /dev/null
+++ b/app/Data/Ledger.hs
@@ -0,0 +1,115 @@
1{-# LANGUAGE TemplateHaskell #-}
2{-# LANGUAGE TypeFamilies #-}
3
4module Data.Ledger where
5
6import Data.Constraint.Extras.TH (deriveArgDict)
7import Data.Dependent.Map (DMap, fromList, singleton, union, unionWithKey)
8import Data.Dependent.Sum ((==>))
9import Data.Functor.Identity
10import Data.Functor.Identity (Identity (..))
11import Data.GADT.Compare.TH (deriveGCompare, deriveGEq)
12import Data.GADT.Show.TH (deriveGShow)
13import Data.Iban
14import Data.Map qualified as M
15import Data.Text qualified as T
16import Data.Time.Calendar
17import Data.Time.Clock
18import Data.UUID
19import GHC.Generics
20
21data AccountType = Asset | Equity | Liability | Expense | Income
22
23data TxAction = Inc | Dec
24
25txaOpp :: TxAction -> TxAction
26txaOpp Inc = Dec
27txaOpp Dec = Inc
28
29onDebit :: AccountType -> TxAction
30onDebit Asset = Inc
31onDebit Equity = Dec
32onDebit Liability = Dec
33onDebit Expense = Inc
34onDebit Income = Dec
35
36onCredit :: AccountType -> TxAction
37onCredit = txaOpp . onDebit
38
39data TxType
40 = InterestCtx
41 | OnlineBankingTx
42 | RecurrentDirectTx
43 | PaymentTerminalTx
44 | CashPaymentTx
45 | AtmTx
46 | AutoSaveRoundingTx
47 | BatchTx
48 | DirectDebitTx
49 | PeriodicTx
50
51data IbanTag = AccountTag | CounterpartyIbanTag deriving (Eq, Enum, Ord, Show)
52
53data UnitTag = FiledTag | GooglePayTag deriving (Eq, Enum, Ord, Show)
54
55data TextTag = DescTag | UserTag | CounterpartyNameTag | ReferenceTag | MandateIdTag | CreditorIdTag | OtherPartyTag | TransactionTag | TerminalTag | CardSeqNoTag deriving (Eq, Enum, Ord, Show)
56
57data Label a where
58 TextLabel :: TextTag -> Label T.Text
59 IbanLabel :: IbanTag -> Label Iban
60 UnitLabel :: UnitTag -> Label ()
61 TimestampLabel :: Label UTCTime
62
63deriveGEq ''Label
64deriveGCompare ''Label
65deriveGShow ''Label
66deriveArgDict ''Label
67
68type Labels = DMap Label Identity
69
70data Money = Money Integer deriving (Show)
71
72infixl 6 +€, -€
73
74(+€) :: Money -> Money -> Money
75Money x +€ Money y = Money (x + y)
76
77(-€) :: Money -> Money -> Money
78Money x -€ Money y = Money (x - y)
79
80data Scalar = Amount Money | Rate Integer deriving (Show)
81
82data AccountId = AccountId [T.Text] deriving (Show)
83
84data CommodityId = CommodityId UUID deriving (Show)
85
86data Account = Account
87 { id :: AccountId,
88 description :: [T.Text],
89 commodityId :: CommodityId,
90 balance :: Money
91 }
92
93-- A balance assertion is only valid when all transactions before it have been
94-- cleared and the balance of the account agrees with the amount in the
95-- assertion.
96data BalAssert = BalAssert
97 { account :: Account,
98 amount :: Integer,
99 labels :: Labels
100 }
101
102data Tx = Tx
103 { cleared :: Maybe Day,
104 commodityId :: CommodityId, -- the commodity w.r.t. which rates are calculated
105 debit :: M.Map AccountId Scalar,
106 credit :: M.Map AccountId Scalar,
107 labels :: Labels
108 }
109 deriving (Show, Generic)
110
111data SeqTx = SeqTx [Integer] Tx
112
113data LedgerEntry = TxEntry SeqTx | BalAssertEntry BalAssert
114
115data Ledger = Ledger [LedgerEntry]