1 module Literate.Accounting.Flow where
3 import Control.DeepSeq (NFData)
6 import Data.Functor (Functor)
7 import Data.Maybe (Maybe (..))
8 import Data.Ord (Ord (..))
9 import GHC.Generics (Generic)
10 import Text.Show (Show (..))
12 import Literate.Accounting.Math
13 import Literate.Accounting.Rebindable
17 {- | A 'Flow keeps track separatly of what goes 'In'
18 and what goes 'Out' of an account.
24 deriving (Eq, Show, Generic, NFData, Functor)
26 instance FromInteger qty => FromInteger (Flow qty) where
28 | i <= 0 = Out (fromInteger i)
29 | otherwise = In (fromInteger i)
31 flowIn :: Flow a -> Maybe a
37 flowOut :: Flow a -> Maybe a
43 flow :: Flowable a => a -> Flow a
45 case (outOf f, inOf f) of
46 (Just o, Nothing) -> Out o
47 (Nothing, Just i) -> In i
48 (Just o, Just i) -> Bidir o i
49 (Nothing, Nothing) -> Bidir f f
50 unFlow :: Addable a => Flow a -> a
56 instance Zeroable a => Zeroable (Flow a) where
58 instance (Nullable a, Addable a) => Nullable (Flow a) where
62 Bidir o i -> null (o + i)
63 instance Addable a => Addable (Flow a) where
64 In i + Out o = Bidir o i
65 In ix + In py = In (ix + py)
66 In i + Bidir ny py = Bidir ny (i + py)
67 Out ox + Out ny = Out (ox + ny)
68 Out o + In i = Bidir o i
69 Out ox + Bidir ny i = Bidir (ox + ny) i
70 Bidir ox ix + Out o = Bidir (ox + o) ix
71 Bidir ox ix + In py = Bidir ox (ix + py)
72 Bidir ox ix + Bidir ny py = Bidir (ox + ny) (ix + py)
73 instance Negable a => Negable (Flow a) where
75 In i -> Out (negate i)
76 Out o -> In (negate o)
77 Bidir o i -> Bidir (negate i) (negate o)
78 instance Flowable (Flow a) where
82 Bidir n _ -> Just (Out n)
86 Bidir _ p -> Just (In p)
91 class Flowable a where
96 instance Flowable Decimal where
103 _ | q <= 0 -> Nothing
105 instance Flowable a => Flowable (Map k a) where
107 case Map.mapMaybe inOf q of
108 m | Map.null m -> Nothing
111 case Map.mapMaybe outOf q of
112 m | Map.null m -> Nothing
114 instance Flowable a => Flowable (k, a) where
115 inOf (u, q) = (u,) <$> inOf q
116 outOf (u, q) = (u,) <$> outOf q