{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveAnyClass #-}
module Accounts (Account(..),ReserveAmount(..),draw,deposit
,transfer,depositInt ,InterestInfo(..),buildEarnIntAction
,accBalLens,tryDraw,buildRateResetDates,accrueInt,accTypeLens)
where
import qualified Data.Time as T
import Stmt (Statement(..),appendStmt,getTxnBegBalance,getDate
,TxnComment(..),QueryByComment(..),getTxnComment,getTxnAmt,weightAvgBalanceByDates)
import Types
import Lib
import Util
import DateUtil
import Data.Aeson hiding (json)
import Language.Haskell.TH
import Data.Aeson.TH
import Data.Aeson.Types
import GHC.Generics
import Control.Lens.Tuple
import Control.Lens hiding (Index)
import qualified InterestRate as IR
import qualified Data.DList as DL
import Debug.Trace
debug :: c -> [Char] -> c
debug = ([Char] -> c -> c) -> c -> [Char] -> c
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Char] -> c -> c
forall a. [Char] -> a -> a
trace
data InterestInfo = BankAccount IRate DatePattern Date
| InvestmentAccount Types.Index Spread DatePattern DatePattern Date IRate
deriving (Int -> InterestInfo -> ShowS
[InterestInfo] -> ShowS
InterestInfo -> [Char]
(Int -> InterestInfo -> ShowS)
-> (InterestInfo -> [Char])
-> ([InterestInfo] -> ShowS)
-> Show InterestInfo
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InterestInfo -> ShowS
showsPrec :: Int -> InterestInfo -> ShowS
$cshow :: InterestInfo -> [Char]
show :: InterestInfo -> [Char]
$cshowList :: [InterestInfo] -> ShowS
showList :: [InterestInfo] -> ShowS
Show, (forall x. InterestInfo -> Rep InterestInfo x)
-> (forall x. Rep InterestInfo x -> InterestInfo)
-> Generic InterestInfo
forall x. Rep InterestInfo x -> InterestInfo
forall x. InterestInfo -> Rep InterestInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. InterestInfo -> Rep InterestInfo x
from :: forall x. InterestInfo -> Rep InterestInfo x
$cto :: forall x. Rep InterestInfo x -> InterestInfo
to :: forall x. Rep InterestInfo x -> InterestInfo
Generic,InterestInfo -> InterestInfo -> Bool
(InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool) -> Eq InterestInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterestInfo -> InterestInfo -> Bool
== :: InterestInfo -> InterestInfo -> Bool
$c/= :: InterestInfo -> InterestInfo -> Bool
/= :: InterestInfo -> InterestInfo -> Bool
Eq,Eq InterestInfo
Eq InterestInfo =>
(InterestInfo -> InterestInfo -> Ordering)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> Bool)
-> (InterestInfo -> InterestInfo -> InterestInfo)
-> (InterestInfo -> InterestInfo -> InterestInfo)
-> Ord InterestInfo
InterestInfo -> InterestInfo -> Bool
InterestInfo -> InterestInfo -> Ordering
InterestInfo -> InterestInfo -> InterestInfo
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
$ccompare :: InterestInfo -> InterestInfo -> Ordering
compare :: InterestInfo -> InterestInfo -> Ordering
$c< :: InterestInfo -> InterestInfo -> Bool
< :: InterestInfo -> InterestInfo -> Bool
$c<= :: InterestInfo -> InterestInfo -> Bool
<= :: InterestInfo -> InterestInfo -> Bool
$c> :: InterestInfo -> InterestInfo -> Bool
> :: InterestInfo -> InterestInfo -> Bool
$c>= :: InterestInfo -> InterestInfo -> Bool
>= :: InterestInfo -> InterestInfo -> Bool
$cmax :: InterestInfo -> InterestInfo -> InterestInfo
max :: InterestInfo -> InterestInfo -> InterestInfo
$cmin :: InterestInfo -> InterestInfo -> InterestInfo
min :: InterestInfo -> InterestInfo -> InterestInfo
Ord)
data ReserveAmount = PctReserve DealStats Rate
| FixReserve Balance
| Either Pre ReserveAmount ReserveAmount
| Max [ReserveAmount]
| Min [ReserveAmount]
deriving (Int -> ReserveAmount -> ShowS
[ReserveAmount] -> ShowS
ReserveAmount -> [Char]
(Int -> ReserveAmount -> ShowS)
-> (ReserveAmount -> [Char])
-> ([ReserveAmount] -> ShowS)
-> Show ReserveAmount
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReserveAmount -> ShowS
showsPrec :: Int -> ReserveAmount -> ShowS
$cshow :: ReserveAmount -> [Char]
show :: ReserveAmount -> [Char]
$cshowList :: [ReserveAmount] -> ShowS
showList :: [ReserveAmount] -> ShowS
Show, ReserveAmount -> ReserveAmount -> Bool
(ReserveAmount -> ReserveAmount -> Bool)
-> (ReserveAmount -> ReserveAmount -> Bool) -> Eq ReserveAmount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReserveAmount -> ReserveAmount -> Bool
== :: ReserveAmount -> ReserveAmount -> Bool
$c/= :: ReserveAmount -> ReserveAmount -> Bool
/= :: ReserveAmount -> ReserveAmount -> Bool
Eq, (forall x. ReserveAmount -> Rep ReserveAmount x)
-> (forall x. Rep ReserveAmount x -> ReserveAmount)
-> Generic ReserveAmount
forall x. Rep ReserveAmount x -> ReserveAmount
forall x. ReserveAmount -> Rep ReserveAmount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReserveAmount -> Rep ReserveAmount x
from :: forall x. ReserveAmount -> Rep ReserveAmount x
$cto :: forall x. Rep ReserveAmount x -> ReserveAmount
to :: forall x. Rep ReserveAmount x -> ReserveAmount
Generic, Eq ReserveAmount
Eq ReserveAmount =>
(ReserveAmount -> ReserveAmount -> Ordering)
-> (ReserveAmount -> ReserveAmount -> Bool)
-> (ReserveAmount -> ReserveAmount -> Bool)
-> (ReserveAmount -> ReserveAmount -> Bool)
-> (ReserveAmount -> ReserveAmount -> Bool)
-> (ReserveAmount -> ReserveAmount -> ReserveAmount)
-> (ReserveAmount -> ReserveAmount -> ReserveAmount)
-> Ord ReserveAmount
ReserveAmount -> ReserveAmount -> Bool
ReserveAmount -> ReserveAmount -> Ordering
ReserveAmount -> ReserveAmount -> ReserveAmount
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
$ccompare :: ReserveAmount -> ReserveAmount -> Ordering
compare :: ReserveAmount -> ReserveAmount -> Ordering
$c< :: ReserveAmount -> ReserveAmount -> Bool
< :: ReserveAmount -> ReserveAmount -> Bool
$c<= :: ReserveAmount -> ReserveAmount -> Bool
<= :: ReserveAmount -> ReserveAmount -> Bool
$c> :: ReserveAmount -> ReserveAmount -> Bool
> :: ReserveAmount -> ReserveAmount -> Bool
$c>= :: ReserveAmount -> ReserveAmount -> Bool
>= :: ReserveAmount -> ReserveAmount -> Bool
$cmax :: ReserveAmount -> ReserveAmount -> ReserveAmount
max :: ReserveAmount -> ReserveAmount -> ReserveAmount
$cmin :: ReserveAmount -> ReserveAmount -> ReserveAmount
min :: ReserveAmount -> ReserveAmount -> ReserveAmount
Ord)
data Account = Account {
Account -> Balance
accBalance :: Balance
,Account -> [Char]
accName :: String
,Account -> Maybe InterestInfo
accInterest :: Maybe InterestInfo
,Account -> Maybe ReserveAmount
accType :: Maybe ReserveAmount
,Account -> Maybe Statement
accStmt :: Maybe Statement
} deriving (Int -> Account -> ShowS
[Account] -> ShowS
Account -> [Char]
(Int -> Account -> ShowS)
-> (Account -> [Char]) -> ([Account] -> ShowS) -> Show Account
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Account -> ShowS
showsPrec :: Int -> Account -> ShowS
$cshow :: Account -> [Char]
show :: Account -> [Char]
$cshowList :: [Account] -> ShowS
showList :: [Account] -> ShowS
Show, (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
$cfrom :: forall x. Account -> Rep Account x
from :: forall x. Account -> Rep Account x
$cto :: forall x. Rep Account x -> Account
to :: forall x. Rep Account x -> Account
Generic,Account -> Account -> Bool
(Account -> Account -> Bool)
-> (Account -> Account -> Bool) -> Eq Account
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Account -> Account -> Bool
== :: Account -> Account -> Bool
$c/= :: Account -> Account -> Bool
/= :: Account -> Account -> Bool
Eq, Eq Account
Eq Account =>
(Account -> Account -> Ordering)
-> (Account -> Account -> Bool)
-> (Account -> Account -> Bool)
-> (Account -> Account -> Bool)
-> (Account -> Account -> Bool)
-> (Account -> Account -> Account)
-> (Account -> Account -> Account)
-> Ord Account
Account -> Account -> Bool
Account -> Account -> Ordering
Account -> Account -> Account
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
$ccompare :: Account -> Account -> Ordering
compare :: Account -> Account -> Ordering
$c< :: Account -> Account -> Bool
< :: Account -> Account -> Bool
$c<= :: Account -> Account -> Bool
<= :: Account -> Account -> Bool
$c> :: Account -> Account -> Bool
> :: Account -> Account -> Bool
$c>= :: Account -> Account -> Bool
>= :: Account -> Account -> Bool
$cmax :: Account -> Account -> Account
max :: Account -> Account -> Account
$cmin :: Account -> Account -> Account
min :: Account -> Account -> Account
Ord)
buildEarnIntAction :: [Account] -> Date -> [(String,Dates)] -> [(String,Dates)]
buildEarnIntAction :: [Account] -> Date -> [([Char], Dates)] -> [([Char], Dates)]
buildEarnIntAction [] Date
ed [([Char], Dates)]
r = [([Char], Dates)]
r
buildEarnIntAction (Account
acc:[Account]
accs) Date
ed [([Char], Dates)]
r =
case Account -> Maybe InterestInfo
accInterest Account
acc of
Maybe InterestInfo
Nothing -> [Account] -> Date -> [([Char], Dates)] -> [([Char], Dates)]
buildEarnIntAction [Account]
accs Date
ed [([Char], Dates)]
r
Just (BankAccount IRate
_ DatePattern
dp Date
lastAccDate )
-> [Account] -> Date -> [([Char], Dates)] -> [([Char], Dates)]
buildEarnIntAction [Account]
accs Date
ed [(Account -> [Char]
accName Account
acc, RangeType -> Date -> DatePattern -> Date -> Dates
genSerialDatesTill2 RangeType
NO_IE Date
lastAccDate DatePattern
dp Date
ed)][([Char], Dates)] -> [([Char], Dates)] -> [([Char], Dates)]
forall a. [a] -> [a] -> [a]
++[([Char], Dates)]
r
Just (InvestmentAccount Index
_ IRate
_ DatePattern
dp DatePattern
_ Date
lastAccDate IRate
_)
-> [Account] -> Date -> [([Char], Dates)] -> [([Char], Dates)]
buildEarnIntAction [Account]
accs Date
ed [(Account -> [Char]
accName Account
acc, RangeType -> Date -> DatePattern -> Date -> Dates
genSerialDatesTill2 RangeType
NO_IE Date
lastAccDate DatePattern
dp Date
ed)][([Char], Dates)] -> [([Char], Dates)] -> [([Char], Dates)]
forall a. [a] -> [a] -> [a]
++[([Char], Dates)]
r
accrueInt :: Date -> Account -> Balance
accrueInt :: Date -> Account -> Balance
accrueInt Date
_ (Account Balance
_ [Char]
_ Maybe InterestInfo
Nothing Maybe ReserveAmount
_ Maybe Statement
_) = Balance
0
accrueInt Date
endDate a :: Account
a@(Account Balance
bal [Char]
_ (Just InterestInfo
interestType) Maybe ReserveAmount
_ Maybe Statement
stmt)
= case Maybe Statement
stmt of
Maybe Statement
Nothing -> Balance -> Rate -> Balance
mulBR (Balance -> IRate -> Balance
mulBI Balance
bal IRate
rateToUse) (DayCount -> Date -> Date -> Rate
yearCountFraction DayCount
defaultDc Date
lastDay Date
endDate)
Just (Statement DList Txn
txns) ->
let
accrueTxns :: [Txn]
accrueTxns = RangeType -> Date -> Date -> [Txn] -> [Txn]
forall ts.
TimeSeries ts =>
RangeType -> Date -> Date -> [ts] -> [ts]
sliceBy RangeType
IE Date
lastDay Date
endDate (DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
bals :: [Balance]
bals = (Txn -> Balance) -> [Txn] -> [Balance]
forall a b. (a -> b) -> [a] -> [b]
map Txn -> Balance
getTxnBegBalance [Txn]
accrueTxns [Balance] -> [Balance] -> [Balance]
forall a. [a] -> [a] -> [a]
++ [Balance
bal]
ds :: Dates
ds = [Date
lastDay] Dates -> Dates -> Dates
forall a. [a] -> [a] -> [a]
++ [Txn] -> Dates
forall ts. TimeSeries ts => [ts] -> Dates
getDates [Txn]
accrueTxns Dates -> Dates -> Dates
forall a. [a] -> [a] -> [a]
++ [Date
endDate]
avgBal :: Balance
avgBal = DayCount -> [Balance] -> Dates -> Balance
calcWeightBalanceByDates DayCount
defaultDc [Balance]
bals Dates
ds
in
Balance -> IRate -> Balance
mulBI Balance
avgBal IRate
rateToUse
where
defaultDc :: DayCount
defaultDc = DayCount
DC_30E_360
(Date
lastDay,IRate
rateToUse) = case InterestInfo
interestType of
(BankAccount IRate
r DatePattern
dp Date
lastCollectDate) -> (Date
lastCollectDate, IRate
r)
(InvestmentAccount Index
idx IRate
spd DatePattern
dp DatePattern
_ Date
lastCollectDate IRate
lastRate) -> (Date
lastCollectDate, IRate
lastRate)
depositInt :: Date -> Account -> Account
depositInt :: Date -> Account -> Account
depositInt Date
_ a :: Account
a@(Account Balance
_ [Char]
_ Maybe InterestInfo
Nothing Maybe ReserveAmount
_ Maybe Statement
_) = Account
a
depositInt Date
ed a :: Account
a@(Account Balance
bal [Char]
_ (Just InterestInfo
intType) Maybe ReserveAmount
_ Maybe Statement
stmt)
= Account
a {accBalance = newBal ,accStmt= appendStmt newTxn stmt ,accInterest = Just (newIntInfoType intType)}
where
accruedInt :: Balance
accruedInt = Date -> Account -> Balance
accrueInt Date
ed Account
a
newIntInfoType :: InterestInfo -> InterestInfo
newIntInfoType (BankAccount IRate
x DatePattern
y Date
_d) = IRate -> DatePattern -> Date -> InterestInfo
BankAccount IRate
x DatePattern
y Date
ed
newIntInfoType (InvestmentAccount Index
x IRate
y DatePattern
z DatePattern
z1 Date
_d IRate
z2) = Index
-> IRate
-> DatePattern
-> DatePattern
-> Date
-> IRate
-> InterestInfo
InvestmentAccount Index
x IRate
y DatePattern
z DatePattern
z1 Date
ed IRate
z2
newBal :: Balance
newBal = Balance
accruedInt Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
bal
newTxn :: Txn
newTxn = Date -> Balance -> Balance -> TxnComment -> Txn
AccTxn Date
ed Balance
newBal Balance
accruedInt TxnComment
BankInt
transfer :: (Account,Account) -> Date -> Amount -> (Account, Account)
transfer :: (Account, Account) -> Date -> Balance -> (Account, Account)
transfer (sourceAcc :: Account
sourceAcc@(Account Balance
sBal [Char]
san Maybe InterestInfo
_ Maybe ReserveAmount
_ Maybe Statement
sStmt), targetAcc :: Account
targetAcc@(Account Balance
tBal [Char]
tan Maybe InterestInfo
_ Maybe ReserveAmount
_ Maybe Statement
tStmt))
Date
d
Balance
amount
= (Account
sourceAcc {accBalance = newSBal, accStmt = sourceNewStmt}
,Account
targetAcc {accBalance = newTBal, accStmt = targetNewStmt})
where
newSBal :: Balance
newSBal = Balance
sBal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
amount
newTBal :: Balance
newTBal = Balance
tBal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
amount
sourceNewStmt :: Maybe Statement
sourceNewStmt = Txn -> Maybe Statement -> Maybe Statement
appendStmt (Date -> Balance -> Balance -> TxnComment -> Txn
AccTxn Date
d Balance
newSBal (- Balance
amount) ([Char] -> [Char] -> TxnComment
Transfer [Char]
san [Char]
tan)) Maybe Statement
sStmt
targetNewStmt :: Maybe Statement
targetNewStmt = Txn -> Maybe Statement -> Maybe Statement
appendStmt (Date -> Balance -> Balance -> TxnComment -> Txn
AccTxn Date
d Balance
newTBal Balance
amount ([Char] -> [Char] -> TxnComment
Transfer [Char]
san [Char]
tan)) Maybe Statement
tStmt
deposit :: Amount -> Date -> TxnComment -> Account -> Account
deposit :: Balance -> Date -> TxnComment -> Account -> Account
deposit Balance
amount Date
d TxnComment
source acc :: Account
acc@(Account Balance
bal [Char]
_ Maybe InterestInfo
_ Maybe ReserveAmount
_ Maybe Statement
maybeStmt) =
Account
acc {accBalance = newBal, accStmt = newStmt}
where
newBal :: Balance
newBal = Balance
bal Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
+ Balance
amount
newStmt :: Maybe Statement
newStmt = Txn -> Maybe Statement -> Maybe Statement
appendStmt (Date -> Balance -> Balance -> TxnComment -> Txn
AccTxn Date
d Balance
newBal Balance
amount TxnComment
source) Maybe Statement
maybeStmt
draw :: Amount -> Date -> TxnComment -> Account -> Account
draw :: Balance -> Date -> TxnComment -> Account -> Account
draw Balance
amount Date
d TxnComment
txn acc :: Account
acc@Account{ accBalance :: Account -> Balance
accBalance = Balance
bal ,accName :: Account -> [Char]
accName = [Char]
an}
| Balance
bal Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
>= Balance
amount = Balance -> Date -> TxnComment -> Account -> Account
deposit (- Balance
amount) Date
d TxnComment
txn Account
acc
| Bool
otherwise = [Char] -> Account
forall a. HasCallStack => [Char] -> a
error ([Char] -> Account) -> [Char] -> Account
forall a b. (a -> b) -> a -> b
$ [Char]
"Date:"[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Date -> [Char]
forall a. Show a => a -> [Char]
show Date
d [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
" Failed to draw "[Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ Balance -> [Char]
forall a. Show a => a -> [Char]
show Balance
amount [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++[Char]
" from account" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
an
tryDraw :: Amount -> Date -> TxnComment -> Account -> ((Amount,Amount),Account)
tryDraw :: Balance
-> Date -> TxnComment -> Account -> ((Balance, Balance), Account)
tryDraw Balance
amt Date
d TxnComment
tc acc :: Account
acc@(Account Balance
bal [Char]
_ Maybe InterestInfo
_ Maybe ReserveAmount
_ Maybe Statement
maybeStmt)
| Balance
amt Balance -> Balance -> Bool
forall a. Ord a => a -> a -> Bool
> Balance
bal = ((Balance
amt Balance -> Balance -> Balance
forall a. Num a => a -> a -> a
- Balance
bal, Balance
bal), Account
acc {accBalance = 0})
| Bool
otherwise = ((Balance
0, Balance
amt), Balance -> Date -> TxnComment -> Account -> Account
draw Balance
amt Date
d TxnComment
tc Account
acc)
instance QueryByComment Account where
queryStmt :: Account -> TxnComment -> [Txn]
queryStmt (Account Balance
_ [Char]
_ Maybe InterestInfo
_ Maybe ReserveAmount
_ Maybe Statement
Nothing) TxnComment
tc = []
queryStmt (Account Balance
_ [Char]
_ Maybe InterestInfo
_ Maybe ReserveAmount
_ (Just (Statement DList Txn
txns))) TxnComment
tc = (Txn -> Bool) -> [Txn] -> [Txn]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Txn
x -> Txn -> TxnComment
getTxnComment Txn
x TxnComment -> TxnComment -> Bool
forall a. Eq a => a -> a -> Bool
== TxnComment
tc) (DList Txn -> [Txn]
forall a. DList a -> [a]
DL.toList DList Txn
txns)
buildRateResetDates :: Date -> Account -> Maybe (String,Dates)
buildRateResetDates :: Date -> Account -> Maybe ([Char], Dates)
buildRateResetDates Date
ed Account{accName :: Account -> [Char]
accName = [Char]
n, accInterest :: Account -> Maybe InterestInfo
accInterest = Just (InvestmentAccount Index
_ IRate
_ DatePattern
_ DatePattern
dp Date
sd IRate
_) }
= ([Char], Dates) -> Maybe ([Char], Dates)
forall a. a -> Maybe a
Just ([Char]
n, RangeType -> Date -> DatePattern -> Date -> Dates
genSerialDatesTill2 RangeType
NO_IE Date
sd DatePattern
dp Date
ed)
buildRateResetDates Date
_ Account
_ = Maybe ([Char], Dates)
forall a. Maybe a
Nothing
makeLensesFor [("accBalance","accBalLens") ,("accName","accNameLens")
,("accType","accTypeLens") ,("accStmt","accStmtLens"),("accInterest","accIntLens")] ''Account
instance IR.UseRate Account where
isAdjustbleRate :: Account -> Bool
isAdjustbleRate (Account Balance
_ [Char]
an (Just (InvestmentAccount Index
_ IRate
_ DatePattern
_ DatePattern
_ Date
_ IRate
_)) Maybe ReserveAmount
_ Maybe Statement
_) = Bool
True
isAdjustbleRate Account
_ = Bool
False
getIndex :: Account -> Maybe Index
getIndex (Account Balance
_ [Char]
an (Just (InvestmentAccount Index
idx IRate
_ DatePattern
_ DatePattern
_ Date
_ IRate
_)) Maybe ReserveAmount
_ Maybe Statement
_) = Index -> Maybe Index
forall a. a -> Maybe a
Just Index
idx
getIndex Account
_ = Maybe Index
forall a. Maybe a
Nothing
makePrisms ''InterestInfo
$(deriveJSON defaultOptions ''InterestInfo)
$(deriveJSON defaultOptions ''ReserveAmount)
$(deriveJSON defaultOptions ''Account)