]> Git — Sourcephile - haskell/symantic-compta.git/blob - src/Symantic/Compta/Calc/Flow.hs
init
[haskell/symantic-compta.git] / src / Symantic / Compta / Calc / Flow.hs
1 module Symantic.Compta.Calc.Flow where
2
3 import Control.DeepSeq (NFData)
4 import Data.Bool
5 import Data.Eq (Eq)
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(..))
11
12 import Symantic.Compta.Lang
13
14 -- ** Type 'Flow'
15 -- | A 'Flow keeps track separatly of what goes 'In'
16 -- and what goes 'Out' of an account.
17 data Flow a
18 = In !a
19 | Out !a
20 | Bidir !a !a
21 deriving (Eq, Show, Generic, NFData, Functor)
22
23 instance FromInteger qty => FromInteger (Flow qty) where
24 fromInteger i | i <= 0 = Out (fromInteger i)
25 | otherwise = In (fromInteger i)
26
27 flowIn :: Flow a -> Maybe a
28 flowIn = \case
29 In i -> Just i
30 Out _ -> Nothing
31 Bidir _ i -> Just i
32
33 flowOut :: Flow a -> Maybe a
34 flowOut = \case
35 In _ -> Nothing
36 Out o -> Just o
37 Bidir o _ -> Just o
38
39 flow :: Flowable a => a -> Flow a
40 flow f =
41 case (outOf f, inOf f) of
42 (Just o, Nothing) -> Out o
43 (Nothing, Just i) -> In i
44 (Just o, Just i) -> Bidir o i
45 (Nothing, Nothing) -> Bidir f f
46 unFlow :: Addable a => Flow a -> a
47 unFlow = \case
48 In i -> i
49 Out o -> o
50 Bidir o i -> o + i
51
52 instance Zeroable a => Zeroable (Flow a) where
53 zero = In zero
54 instance (Nullable a, Addable a) => Nullable (Flow a) where
55 null = \case
56 Out o -> null o
57 In i -> null i
58 Bidir o i -> null (o + i)
59 instance Addable a => Addable (Flow a) where
60 In i + Out o = Bidir o i
61 In ix + In py = In (ix + py)
62 In i + Bidir ny py = Bidir ny (i + py)
63
64 Out ox + Out ny = Out (ox + ny)
65 Out o + In i = Bidir o i
66 Out ox + Bidir ny i = Bidir (ox + ny) i
67
68 Bidir ox ix + Out o = Bidir (ox + o) ix
69 Bidir ox ix + In py = Bidir ox (ix + py)
70 Bidir ox ix + Bidir ny py = Bidir (ox + ny) (ix + py)
71 instance Negable a => Negable (Flow a) where
72 negate = \case
73 In i -> Out (negate i)
74 Out o -> In (negate o)
75 Bidir o i -> Bidir (negate i) (negate o)
76 instance Flowable (Flow a) where
77 outOf f = case f of
78 In _ -> Nothing
79 Out _ -> Just f
80 Bidir n _ -> Just (Out n)
81 inOf f = case f of
82 In _ -> Just f
83 Out _ -> Nothing
84 Bidir _ p -> Just (In p)
85 --instance Eq
86
87 -- * Class 'Flowable'
88 class Flowable a where
89 outOf :: a -> Maybe a
90 inOf :: a -> Maybe a
91 {-
92 instance Flowable Decimal where
93 outOf q =
94 case q of
95 _ | q < 0 -> Just q
96 _ -> Nothing
97 inOf q =
98 case q of
99 _ | q <= 0 -> Nothing
100 _ -> Just q
101 instance Flowable a => Flowable (Map k a) where
102 inOf q =
103 case Map.mapMaybe inOf q of
104 m | Map.null m -> Nothing
105 m -> Just m
106 outOf q =
107 case Map.mapMaybe outOf q of
108 m | Map.null m -> Nothing
109 m -> Just m
110 instance Flowable a => Flowable (k, a) where
111 inOf (u, q) = (u,) <$> inOf q
112 outOf (u, q) = (u,) <$> outOf q
113 -}