-- | This module provides definitions for acccounts and types of accounts as
-- they are used in accounting reporting.

{-# LANGUAGE DataKinds   #-}
{-# LANGUAGE DerivingVia #-}

module Haspara.Accounting.Account where

import qualified Data.Aeson             as Aeson
import           Data.Hashable          (Hashable)
import qualified Data.Text              as T
import           GHC.Generics           (Generic)
import           Haspara.Internal.Aeson (aesonOptionsForSingleTag, commonAesonOptions)


-- * Account Kind
-- $accountKind


-- | Type encoding for ledger account type.
--
-- This type covers both balance sheet and income statement account types:
--
-- 1. For balance sheet accounts:
--     1. Asset ('AccountKindAsset')
--     2. Liability ('AccountKindLiability')
--     3. Equity ('AccountKindEquity')
-- 2. For income statement accounts:
--     1. Revenue ('AccountKindRevenue')
--     2. Expense ('AccountKindExpense')
--
-- 'Data.Aeson.FromJSON' and 'Data.Aeson.ToJSON' instances, too:
--
-- >>> Data.Aeson.decode @AccountKind "\"ASSET\""
-- Just AccountKindAsset
-- >>> Data.Aeson.decode @AccountKind "\"LIABILITY\""
-- Just AccountKindLiability
-- >>> Data.Aeson.decode @AccountKind "\"EQUITY\""
-- Just AccountKindEquity
-- >>> Data.Aeson.decode @AccountKind "\"REVENUE\""
-- Just AccountKindRevenue
-- >>> Data.Aeson.decode @AccountKind "\"EXPENSE\""
-- Just AccountKindExpense
-- >>> Data.Aeson.encode AccountKindAsset
-- "\"ASSET\""
-- >>> Data.Aeson.encode AccountKindLiability
-- "\"LIABILITY\""
-- >>> Data.Aeson.encode AccountKindEquity
-- "\"EQUITY\""
-- >>> Data.Aeson.encode AccountKindRevenue
-- "\"REVENUE\""
-- >>> Data.Aeson.encode AccountKindExpense
-- "\"EXPENSE\""
data AccountKind =
    AccountKindAsset
  | AccountKindLiability
  | AccountKindEquity
  | AccountKindRevenue
  | AccountKindExpense
  deriving (AccountKind
AccountKind -> AccountKind -> Bounded AccountKind
forall a. a -> a -> Bounded a
maxBound :: AccountKind
$cmaxBound :: AccountKind
minBound :: AccountKind
$cminBound :: AccountKind
Bounded, Int -> AccountKind
AccountKind -> Int
AccountKind -> [AccountKind]
AccountKind -> AccountKind
AccountKind -> AccountKind -> [AccountKind]
AccountKind -> AccountKind -> AccountKind -> [AccountKind]
(AccountKind -> AccountKind)
-> (AccountKind -> AccountKind)
-> (Int -> AccountKind)
-> (AccountKind -> Int)
-> (AccountKind -> [AccountKind])
-> (AccountKind -> AccountKind -> [AccountKind])
-> (AccountKind -> AccountKind -> [AccountKind])
-> (AccountKind -> AccountKind -> AccountKind -> [AccountKind])
-> Enum AccountKind
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: AccountKind -> AccountKind -> AccountKind -> [AccountKind]
$cenumFromThenTo :: AccountKind -> AccountKind -> AccountKind -> [AccountKind]
enumFromTo :: AccountKind -> AccountKind -> [AccountKind]
$cenumFromTo :: AccountKind -> AccountKind -> [AccountKind]
enumFromThen :: AccountKind -> AccountKind -> [AccountKind]
$cenumFromThen :: AccountKind -> AccountKind -> [AccountKind]
enumFrom :: AccountKind -> [AccountKind]
$cenumFrom :: AccountKind -> [AccountKind]
fromEnum :: AccountKind -> Int
$cfromEnum :: AccountKind -> Int
toEnum :: Int -> AccountKind
$ctoEnum :: Int -> AccountKind
pred :: AccountKind -> AccountKind
$cpred :: AccountKind -> AccountKind
succ :: AccountKind -> AccountKind
$csucc :: AccountKind -> AccountKind
Enum, AccountKind -> AccountKind -> Bool
(AccountKind -> AccountKind -> Bool)
-> (AccountKind -> AccountKind -> Bool) -> Eq AccountKind
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountKind -> AccountKind -> Bool
$c/= :: AccountKind -> AccountKind -> Bool
== :: AccountKind -> AccountKind -> Bool
$c== :: AccountKind -> AccountKind -> Bool
Eq, (forall x. AccountKind -> Rep AccountKind x)
-> (forall x. Rep AccountKind x -> AccountKind)
-> Generic AccountKind
forall x. Rep AccountKind x -> AccountKind
forall x. AccountKind -> Rep AccountKind x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountKind x -> AccountKind
$cfrom :: forall x. AccountKind -> Rep AccountKind x
Generic, Eq AccountKind
Eq AccountKind
-> (AccountKind -> AccountKind -> Ordering)
-> (AccountKind -> AccountKind -> Bool)
-> (AccountKind -> AccountKind -> Bool)
-> (AccountKind -> AccountKind -> Bool)
-> (AccountKind -> AccountKind -> Bool)
-> (AccountKind -> AccountKind -> AccountKind)
-> (AccountKind -> AccountKind -> AccountKind)
-> Ord AccountKind
AccountKind -> AccountKind -> Bool
AccountKind -> AccountKind -> Ordering
AccountKind -> AccountKind -> AccountKind
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
min :: AccountKind -> AccountKind -> AccountKind
$cmin :: AccountKind -> AccountKind -> AccountKind
max :: AccountKind -> AccountKind -> AccountKind
$cmax :: AccountKind -> AccountKind -> AccountKind
>= :: AccountKind -> AccountKind -> Bool
$c>= :: AccountKind -> AccountKind -> Bool
> :: AccountKind -> AccountKind -> Bool
$c> :: AccountKind -> AccountKind -> Bool
<= :: AccountKind -> AccountKind -> Bool
$c<= :: AccountKind -> AccountKind -> Bool
< :: AccountKind -> AccountKind -> Bool
$c< :: AccountKind -> AccountKind -> Bool
compare :: AccountKind -> AccountKind -> Ordering
$ccompare :: AccountKind -> AccountKind -> Ordering
$cp1Ord :: Eq AccountKind
Ord, Int -> AccountKind -> ShowS
[AccountKind] -> ShowS
AccountKind -> String
(Int -> AccountKind -> ShowS)
-> (AccountKind -> String)
-> ([AccountKind] -> ShowS)
-> Show AccountKind
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountKind] -> ShowS
$cshowList :: [AccountKind] -> ShowS
show :: AccountKind -> String
$cshow :: AccountKind -> String
showsPrec :: Int -> AccountKind -> ShowS
$cshowsPrec :: Int -> AccountKind -> ShowS
Show)


instance Hashable AccountKind


instance Aeson.FromJSON AccountKind where
  parseJSON :: Value -> Parser AccountKind
parseJSON = Options -> Value -> Parser AccountKind
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON (Options -> Value -> Parser AccountKind)
-> Options -> Value -> Parser AccountKind
forall a b. (a -> b) -> a -> b
$ String -> Options
aesonOptionsForSingleTag String
"AccountKind"


instance Aeson.ToJSON AccountKind where
  toJSON :: AccountKind -> Value
toJSON = Options -> AccountKind -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON (Options -> AccountKind -> Value)
-> Options -> AccountKind -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
aesonOptionsForSingleTag String
"AccountKind"


-- | Provides textual representation of a given 'AccountKind'.
--
-- >>> accountKindText AccountKindAsset
-- "Asset"
-- >>> accountKindText AccountKindLiability
-- "Liability"
-- >>> accountKindText AccountKindEquity
-- "Equity"
-- >>> accountKindText AccountKindRevenue
-- "Revenue"
-- >>> accountKindText AccountKindExpense
-- "Expense"
accountKindText :: AccountKind -> T.Text
accountKindText :: AccountKind -> Text
accountKindText AccountKind
AccountKindAsset     = Text
"Asset"
accountKindText AccountKind
AccountKindLiability = Text
"Liability"
accountKindText AccountKind
AccountKindEquity    = Text
"Equity"
accountKindText AccountKind
AccountKindRevenue   = Text
"Revenue"
accountKindText AccountKind
AccountKindExpense   = Text
"Expense"


-- * Account
-- $account


-- | Type encoding for account values.
--
-- This definition provides both the 'AccountKind' and an arbitrary object
-- identifying the account. This arbitrary nature provides flexibility to
-- use-site to use its own account identity and accompanying information when
-- required.
--
-- >>> let acc = Account AccountKindAsset (1 ::Int)
-- >>> Data.Aeson.encode acc
-- "{\"kind\":\"ASSET\",\"object\":1}"
-- >>> Data.Aeson.decode @(Account Int) (Data.Aeson.encode acc)
-- Just (Account {accountKind = AccountKindAsset, accountObject = 1})
-- >>> Data.Aeson.decode (Data.Aeson.encode acc) == Just acc
-- True
data Account o = Account
  { Account o -> AccountKind
accountKind   :: !AccountKind
  , Account o -> o
accountObject :: !o
  }
  deriving (Account o -> Account o -> Bool
(Account o -> Account o -> Bool)
-> (Account o -> Account o -> Bool) -> Eq (Account o)
forall o. Eq o => Account o -> Account o -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Account o -> Account o -> Bool
$c/= :: forall o. Eq o => Account o -> Account o -> Bool
== :: Account o -> Account o -> Bool
$c== :: forall o. Eq o => Account o -> Account o -> Bool
Eq, (forall x. Account o -> Rep (Account o) x)
-> (forall x. Rep (Account o) x -> Account o)
-> Generic (Account o)
forall x. Rep (Account o) x -> Account o
forall x. Account o -> Rep (Account o) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall o x. Rep (Account o) x -> Account o
forall o x. Account o -> Rep (Account o) x
$cto :: forall o x. Rep (Account o) x -> Account o
$cfrom :: forall o x. Account o -> Rep (Account o) x
Generic, Eq (Account o)
Eq (Account o)
-> (Account o -> Account o -> Ordering)
-> (Account o -> Account o -> Bool)
-> (Account o -> Account o -> Bool)
-> (Account o -> Account o -> Bool)
-> (Account o -> Account o -> Bool)
-> (Account o -> Account o -> Account o)
-> (Account o -> Account o -> Account o)
-> Ord (Account o)
Account o -> Account o -> Bool
Account o -> Account o -> Ordering
Account o -> Account o -> Account o
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. Ord o => Eq (Account o)
forall o. Ord o => Account o -> Account o -> Bool
forall o. Ord o => Account o -> Account o -> Ordering
forall o. Ord o => Account o -> Account o -> Account o
min :: Account o -> Account o -> Account o
$cmin :: forall o. Ord o => Account o -> Account o -> Account o
max :: Account o -> Account o -> Account o
$cmax :: forall o. Ord o => Account o -> Account o -> Account o
>= :: Account o -> Account o -> Bool
$c>= :: forall o. Ord o => Account o -> Account o -> Bool
> :: Account o -> Account o -> Bool
$c> :: forall o. Ord o => Account o -> Account o -> Bool
<= :: Account o -> Account o -> Bool
$c<= :: forall o. Ord o => Account o -> Account o -> Bool
< :: Account o -> Account o -> Bool
$c< :: forall o. Ord o => Account o -> Account o -> Bool
compare :: Account o -> Account o -> Ordering
$ccompare :: forall o. Ord o => Account o -> Account o -> Ordering
$cp1Ord :: forall o. Ord o => Eq (Account o)
Ord, Int -> Account o -> ShowS
[Account o] -> ShowS
Account o -> String
(Int -> Account o -> ShowS)
-> (Account o -> String)
-> ([Account o] -> ShowS)
-> Show (Account o)
forall o. Show o => Int -> Account o -> ShowS
forall o. Show o => [Account o] -> ShowS
forall o. Show o => Account o -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Account o] -> ShowS
$cshowList :: forall o. Show o => [Account o] -> ShowS
show :: Account o -> String
$cshow :: forall o. Show o => Account o -> String
showsPrec :: Int -> Account o -> ShowS
$cshowsPrec :: forall o. Show o => Int -> Account o -> ShowS
Show)


instance Hashable o => Hashable (Account o)


instance Aeson.FromJSON o => Aeson.FromJSON (Account o) where
  parseJSON :: Value -> Parser (Account o)
parseJSON = Options -> Value -> Parser (Account o)
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
Aeson.genericParseJSON (Options -> Value -> Parser (Account o))
-> Options -> Value -> Parser (Account o)
forall a b. (a -> b) -> a -> b
$ String -> Options
commonAesonOptions String
"account"


instance Aeson.ToJSON o => Aeson.ToJSON (Account o) where
  toJSON :: Account o -> Value
toJSON = Options -> Account o -> Value
forall a.
(Generic a, GToJSON' Value Zero (Rep a)) =>
Options -> a -> Value
Aeson.genericToJSON (Options -> Account o -> Value) -> Options -> Account o -> Value
forall a b. (a -> b) -> a -> b
$ String -> Options
commonAesonOptions String
"account"