Safe Haskell | None |
---|---|
Language | Haskell2010 |
Stmt
Contents
Synopsis
- data Statement = Statement (DList Txn)
- getTxns :: Maybe Statement -> DList Txn
- getTxnComment :: Txn -> TxnComment
- getTxnAmt :: Txn -> Balance
- toDate :: String -> Date
- getTxnPrincipal :: Txn -> Balance
- getTxnAsOf :: [Txn] -> Date -> Maybe Txn
- getTxnBalance :: Txn -> Balance
- appendStmt :: Txn -> Maybe Statement -> Maybe Statement
- combineTxn :: Txn -> Txn -> Txn
- getTxnBegBalance :: Txn -> Balance
- getDate :: TimeSeries ts => ts -> Date
- getDates :: TimeSeries ts => [ts] -> [Date]
- data TxnComment
- = PayInt [BondName]
- | PayYield BondName
- | PayPrin [BondName]
- | PayGroupPrin [BondName]
- | PayGroupInt [BondName]
- | WriteOff BondName Balance
- | FundWith BondName Balance
- | PayPrinResidual [BondName]
- | PayFee FeeName
- | SeqPayFee [FeeName]
- | PayFeeYield FeeName
- | Transfer AccName AccName
- | TransferBy AccName AccName Limit
- | BookLedgerBy BookDirection String
- | PoolInflow (Maybe [PoolId]) PoolSource
- | LiquidationProceeds [PoolId]
- | LiquidationSupport String
- | LiquidationDraw
- | LiquidationRepay String
- | LiquidationSupportInt Balance Balance
- | BankInt
- | SupportDraw
- | Empty
- | Tag String
- | UsingDS DealStats
- | SwapAccrue
- | SwapInSettle String
- | SwapOutSettle String
- | PurchaseAsset String Balance
- | IssuanceProceeds String
- | TxnDirection BookDirection
- | TxnComments [TxnComment]
- class QueryByComment a where
- queryStmt :: a -> TxnComment -> [Txn]
- queryStmtAsOf :: a -> Date -> TxnComment -> [Txn]
- queryTxnAmt :: a -> TxnComment -> Balance
- queryTxnAmtAsOf :: a -> Date -> TxnComment -> Balance
- weightAvgBalanceByDates :: [Date] -> [Txn] -> [Balance]
- weightAvgBalance :: Date -> Date -> [Txn] -> Balance
- weightAvgBalance' :: Date -> Date -> [Txn] -> Balance
- sumTxn :: [Txn] -> Balance
- consolTxn :: [Txn] -> Txn -> [Txn]
- getFlow :: TxnComment -> FlowDirection
- data FlowDirection
- aggByTxnComment :: [Txn] -> Map TxnComment [Txn] -> Map TxnComment Balance
- scaleByFactor :: Rate -> [Txn] -> [Txn]
- scaleTxn :: Rate -> Txn -> Txn
- isEmptyTxn :: Txn -> Bool
- statementTxns :: Lens' Statement (DList Txn)
- viewBalanceAsOf :: Date -> [Txn] -> Balance
- filterTxn :: (TxnComment -> Bool) -> [Txn] -> [Txn]
- class HasStmt a where
- getAllTxns :: a -> [Txn]
- hasEmptyTxn :: a -> Bool
- data Txn
- = BondTxn Date Balance Interest Principal IRate Cash DueInt DueIoI (Maybe Float) TxnComment
- | AccTxn Date Balance Amount TxnComment
- | ExpTxn Date Balance Amount Balance TxnComment
- | SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment
- | IrsTxn Date Balance Amount IRate IRate Balance TxnComment
- | EntryTxn Date Balance Amount TxnComment
- | TrgTxn Date Bool TxnComment
- getAllTxns :: HasStmt a => a -> [Txn]
- hasEmptyTxn :: HasStmt a => a -> Bool
Documentation
Instances
getTxnComment :: Txn -> TxnComment Source #
getTxnPrincipal :: Txn -> Balance Source #
getTxnBalance :: Txn -> Balance Source #
getTxnBegBalance :: Txn -> Balance Source #
SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment
getDate :: TimeSeries ts => ts -> Date Source #
getDates :: TimeSeries ts => [ts] -> [Date] Source #
data TxnComment Source #
transaction record in each entity
Constructors
Instances
class QueryByComment a where Source #
Minimal complete definition
Methods
queryStmt :: a -> TxnComment -> [Txn] Source #
queryStmtAsOf :: a -> Date -> TxnComment -> [Txn] Source #
queryTxnAmt :: a -> TxnComment -> Balance Source #
queryTxnAmtAsOf :: a -> Date -> TxnComment -> Balance Source #
Instances
QueryByComment Account Source # | |
Defined in Accounts Methods queryStmt :: Account -> TxnComment -> [Txn] Source # queryStmtAsOf :: Account -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: Account -> TxnComment -> Balance Source # queryTxnAmtAsOf :: Account -> Date -> TxnComment -> Balance Source # | |
QueryByComment LiqFacility Source # | |
Defined in CreditEnhancement Methods queryStmt :: LiqFacility -> TxnComment -> [Txn] Source # queryStmtAsOf :: LiqFacility -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: LiqFacility -> TxnComment -> Balance Source # queryTxnAmtAsOf :: LiqFacility -> Date -> TxnComment -> Balance Source # | |
QueryByComment Fee Source # | |
Defined in Expense Methods queryStmt :: Fee -> TxnComment -> [Txn] Source # queryStmtAsOf :: Fee -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: Fee -> TxnComment -> Balance Source # queryTxnAmtAsOf :: Fee -> Date -> TxnComment -> Balance Source # | |
QueryByComment RateCap Source # | |
Defined in Hedge Methods queryStmt :: RateCap -> TxnComment -> [Txn] Source # queryStmtAsOf :: RateCap -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: RateCap -> TxnComment -> Balance Source # queryTxnAmtAsOf :: RateCap -> Date -> TxnComment -> Balance Source # | |
QueryByComment RateSwap Source # | |
Defined in Hedge Methods queryStmt :: RateSwap -> TxnComment -> [Txn] Source # queryStmtAsOf :: RateSwap -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: RateSwap -> TxnComment -> Balance Source # queryTxnAmtAsOf :: RateSwap -> Date -> TxnComment -> Balance Source # | |
QueryByComment Ledger Source # | |
Defined in Ledger Methods queryStmt :: Ledger -> TxnComment -> [Txn] Source # queryStmtAsOf :: Ledger -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: Ledger -> TxnComment -> Balance Source # queryTxnAmtAsOf :: Ledger -> Date -> TxnComment -> Balance Source # | |
QueryByComment Bond Source # | |
Defined in Liability Methods queryStmt :: Bond -> TxnComment -> [Txn] Source # queryStmtAsOf :: Bond -> Date -> TxnComment -> [Txn] Source # queryTxnAmt :: Bond -> TxnComment -> Balance Source # queryTxnAmtAsOf :: Bond -> Date -> TxnComment -> Balance Source # |
getFlow :: TxnComment -> FlowDirection Source #
filter transaction by apply a filter function on txn comment
data FlowDirection Source #
Instances
Generic FlowDirection Source # | |||||
Defined in Stmt Associated Types
| |||||
Show FlowDirection Source # | |||||
Defined in Stmt Methods showsPrec :: Int -> FlowDirection -> ShowS # show :: FlowDirection -> String # showList :: [FlowDirection] -> ShowS # | |||||
Eq FlowDirection Source # | |||||
Defined in Stmt Methods (==) :: FlowDirection -> FlowDirection -> Bool # (/=) :: FlowDirection -> FlowDirection -> Bool # | |||||
type Rep FlowDirection Source # | |||||
Defined in Stmt type Rep FlowDirection = D1 ('MetaData "FlowDirection" "Stmt" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "Inflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Outflow" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Interflow" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Noneflow" 'PrefixI 'False) (U1 :: Type -> Type))) |
aggByTxnComment :: [Txn] -> Map TxnComment [Txn] -> Map TxnComment Balance Source #
isEmptyTxn :: Txn -> Bool Source #
Constructors
BondTxn Date Balance Interest Principal IRate Cash DueInt DueIoI (Maybe Float) TxnComment | bond transaction record for interest and principal |
AccTxn Date Balance Amount TxnComment | account transaction record |
ExpTxn Date Balance Amount Balance TxnComment | expense transaction record |
SupportTxn Date (Maybe Balance) Balance DueInt DuePremium Cash TxnComment | liquidity provider transaction record |
IrsTxn Date Balance Amount IRate IRate Balance TxnComment | interest swap transaction record |
EntryTxn Date Balance Amount TxnComment | ledger book entry |
TrgTxn Date Bool TxnComment |
Instances
TimeSeries Txn Source # | |||||
Defined in Stmt Methods cmp :: Txn -> Txn -> Ordering Source # sameDate :: Txn -> Txn -> Bool Source # getDate :: Txn -> Date Source # getDates :: [Txn] -> [Date] Source # filterByDate :: [Txn] -> Date -> [Txn] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [Txn] -> [Txn] Source # cutBy :: CutoffType -> DateDirection -> Date -> [Txn] -> [Txn] Source # cmpWith :: Txn -> Date -> Ordering Source # isAfter :: Txn -> Date -> Bool Source # isOnAfter :: Txn -> Date -> Bool Source # isBefore :: Txn -> Date -> Bool Source # isOnBefore :: Txn -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [Txn] -> ([Txn], [Txn]) Source # | |||||
FromJSON Txn Source # | |||||
ToJSON Txn Source # | |||||
Generic Txn Source # | |||||
Defined in Types Associated Types
| |||||
Read Txn Source # | |||||
Show Txn Source # | |||||
Eq Txn Source # | |||||
Ord Txn Source # | |||||
type Rep Txn Source # | |||||
Defined in Types type Rep Txn = D1 ('MetaData "Txn" "Types" "Hastructure-0.50.0-9tFAxbqhtE23KiGoJqUlJG" 'False) ((C1 ('MetaCons "BondTxn" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Interest) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Principal) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueIoI) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "AccTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "ExpTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) :+: ((C1 ('MetaCons "SupportTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Balance)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DueInt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DuePremium)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))) :+: C1 ('MetaCons "IrsTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IRate)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))))) :+: (C1 ('MetaCons "EntryTxn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Balance)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment))) :+: C1 ('MetaCons "TrgTxn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Date) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxnComment)))))) |
getAllTxns :: HasStmt a => a -> [Txn] Source #
hasEmptyTxn :: HasStmt a => a -> Bool Source #
Orphan instances
TimeSeries Txn Source # | |
Methods cmp :: Txn -> Txn -> Ordering Source # sameDate :: Txn -> Txn -> Bool Source # getDate :: Txn -> Date Source # getDates :: [Txn] -> [Date] Source # filterByDate :: [Txn] -> Date -> [Txn] Source # sliceBy :: RangeType -> StartDate -> EndDate -> [Txn] -> [Txn] Source # cutBy :: CutoffType -> DateDirection -> Date -> [Txn] -> [Txn] Source # cmpWith :: Txn -> Date -> Ordering Source # isAfter :: Txn -> Date -> Bool Source # isOnAfter :: Txn -> Date -> Bool Source # isBefore :: Txn -> Date -> Bool Source # isOnBefore :: Txn -> Date -> Bool Source # splitBy :: Date -> CutoffType -> [Txn] -> ([Txn], [Txn]) Source # | |
Ord Txn Source # | |