aboutsummaryrefslogtreecommitdiff
path: root/lib/Malodivo/Budget.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Malodivo/Budget.hs')
-rw-r--r--lib/Malodivo/Budget.hs69
1 files changed, 29 insertions, 40 deletions
diff --git a/lib/Malodivo/Budget.hs b/lib/Malodivo/Budget.hs
index a707cec..657cf14 100644
--- a/lib/Malodivo/Budget.hs
+++ b/lib/Malodivo/Budget.hs
@@ -3,20 +3,32 @@
Budget planning in the Kingdom of Malodivo.
-}
+{-# LANGUAGE DeriveAnyClass #-}
+{-# LANGUAGE DeriveGeneric #-}
+
module Malodivo.Budget
- ( DistrictFunds
- , normalizeDown
- , manyToOne
+ ( BillBudget
, manyToMany
+ , manyToOne
+ , normalizeDown
) where
+import GHC.Generics (Generic)
+
+import Data.Aeson (ToJSON)
import qualified Data.HashMap.Strict as HM
import qualified Malodivo.Types.Bill as B
import qualified Malodivo.Types.District as D
--- | Convenient type. Describes available or allocated funds per 'District'.
-type DistrictFunds = HM.HashMap D.District Integer
+-- | This is output type. It describes contribution of each district into a bill.
+data BillBudget = BillBudget
+ { bill :: B.Bill
+ , districts :: [D.DistrictInfo]
+ } deriving (Generic, ToJSON)
+
+zipBills :: [B.Bill] -> [D.DistrictFunds] -> [BillBudget]
+zipBills = zipWith $ \b df -> BillBudget {bill = b, districts = D.df2di df}
{-|
Normalize list of integers, i. e. proportionally decrease each list element
@@ -125,52 +137,29 @@ True
-}
manyToOne ::
- DistrictFunds -- ^ Amounts of available funds per district.
+ D.DistrictFunds -- ^ Amounts of available funds per district.
-> B.Bill -- ^ A bill requiring funding.
- -> DistrictFunds -- ^ Contribution of each district.
-manyToOne funds bill = fundRaising (B.amount bill) funds
+ -> D.DistrictFunds -- ^ Contribution of each district.
+manyToOne df b = fundRaising (B.amount b) df
{-|
Districts funding multiple bills. No constraints.
-
->>> :set -XOverloadedStrings
->>> import Data.Maybe (fromJust)
->>> import qualified Data.HashMap.Strict as HM
->>> import qualified Malodivo.Types.Bill as B
->>> import qualified Malodivo.Types.District as D
->>> import qualified Malodivo.Types.Ministry as M
-
->>> let billA = B.Bill { B.amount = 30, B.name = "Bill A", B.ministry = M.Science }
->>> let billB = B.Bill { B.amount = 10, B.name = "Bill B", B.ministry = M.Welfare }
->>> let equalAmountBills = take 3 (repeat billB)
->>> let nonEqualAmountBills = [billA, billB]
-
-
-If all bills requires the same amount, funds of a single district are
-allocated evenly:
-
->>> let funds = HM.fromList [(D.Palolene, 100)]
->>> let contribution = manyToMany funds equalAmountBills
->>> all (== B.amount (head equalAmountBills)) (fromJust . HM.lookup D.Palolene <$> contribution)
-True
-
-}
manyToMany ::
- DistrictFunds -- ^ Amounts of available funds per district.
+ D.DistrictFunds -- ^ Amounts of available funds per district.
-> [B.Bill] -- ^ Bills requiring funding.
- -> [DistrictFunds] -- ^ Contribution of each district to each bill.
-manyToMany funds bills =
- flip fundRaising funds <$> normalizeDown fundsTotal billAmounts
+ -> [BillBudget] -- ^ Contribution of each district to each bill.
+manyToMany df bills = zipBills bills allocated
where
billAmounts = B.amount <$> bills
- fundsTotal = sum $ HM.elems funds
+ fundsTotal = sum $ HM.elems df
+ allocated = flip fundRaising df <$> normalizeDown fundsTotal billAmounts
-- | Helper function to maintain DRY and backward compatibility.
fundRaising ::
Integer -- ^ Amount to be raised.
- -> DistrictFunds -- ^ Amounts of available funds per district.
- -> DistrictFunds -- ^ Contribution of each district.
-fundRaising needed df = HM.fromList $ zip districts funds'
+ -> D.DistrictFunds -- ^ Amounts of available funds per district.
+ -> D.DistrictFunds -- ^ Contribution of each district.
+fundRaising needed df = HM.fromList $ zip ds (normalizeDown needed fs)
where
- (districts, funds) = unzip $ HM.toList df
- funds' = normalizeDown needed funds
+ (ds, fs) = unzip $ HM.toList df