module Penny.Lincoln.Bits.Open where
import Data.Text (Text)
import qualified Data.Text as X
import qualified Penny.Lincoln.Serial as S
import qualified Penny.Lincoln.Bits.Qty as Q
newtype SubAccount =
SubAccount { unSubAccount :: Text }
deriving (Eq, Ord, Show)
newtype Account = Account { unAccount :: [SubAccount] }
deriving (Eq, Show, Ord)
data Amount = Amount { qty :: Q.Qty
, commodity :: Commodity
, side :: Maybe Side
, spaceBetween :: Maybe SpaceBetween }
deriving (Eq, Show, Ord)
newtype Commodity =
Commodity { unCommodity :: Text }
deriving (Eq, Ord, Show)
data DrCr = Debit | Credit deriving (Eq, Show, Ord)
opposite :: DrCr -> DrCr
opposite d = case d of
Debit -> Credit
Credit -> Debit
data Entry = Entry { drCr :: DrCr
, amount :: Amount }
deriving (Eq, Show, Ord)
newtype Flag = Flag { unFlag :: Text }
deriving (Eq, Show, Ord)
newtype Memo = Memo { unMemo :: [Text] }
deriving (Eq, Show, Ord)
newtype Number = Number { unNumber :: Text }
deriving (Eq, Show, Ord)
newtype Payee = Payee { unPayee :: Text }
deriving (Eq, Show, Ord)
newtype Tag = Tag { unTag :: Text }
deriving (Eq, Show, Ord)
newtype Tags = Tags { unTags :: [Tag] }
deriving (Eq, Show, Ord)
newtype TopLineLine = TopLineLine { unTopLineLine :: Int }
deriving (Eq, Show)
newtype TopMemoLine = TopMemoLine { unTopMemoLine :: Int }
deriving (Eq, Show)
data Side
= CommodityOnLeft
| CommodityOnRight
deriving (Eq, Show, Ord)
data SpaceBetween
= SpaceBetween
| NoSpaceBetween
deriving (Eq, Show, Ord)
newtype Filename = Filename { unFilename :: X.Text }
deriving (Eq, Show)
newtype PriceLine = PriceLine { unPriceLine :: Int }
deriving (Eq, Show)
newtype PostingLine = PostingLine { unPostingLine :: Int }
deriving (Eq, Show)
newtype GlobalPosting =
GlobalPosting { unGlobalPosting :: S.Serial }
deriving (Eq, Show)
newtype FilePosting =
FilePosting { unFilePosting :: S.Serial }
deriving (Eq, Show)
newtype GlobalTransaction =
GlobalTransaction { unGlobalTransaction :: S.Serial }
deriving (Eq, Show)
newtype FileTransaction =
FileTransaction { unFileTransaction :: S.Serial }
deriving (Eq, Show)