aboutsummaryrefslogtreecommitdiff
path: root/client/src/View/Payment/Table.hs
diff options
context:
space:
mode:
authorJoris2017-11-08 23:47:26 +0100
committerJoris2017-11-08 23:47:26 +0100
commit27e11b20b06f2f2dbfb56c0998a63169b4b8abc4 (patch)
tree845f54d7fe876c9a3078036975ba85ec21d224a1 /client/src/View/Payment/Table.hs
parenta3601b5e6f5a3e41fa31752a2c704ccd3632790e (diff)
downloadbudget-27e11b20b06f2f2dbfb56c0998a63169b4b8abc4.tar.gz
budget-27e11b20b06f2f2dbfb56c0998a63169b4b8abc4.tar.bz2
budget-27e11b20b06f2f2dbfb56c0998a63169b4b8abc4.zip
Use a better project structure
Diffstat (limited to 'client/src/View/Payment/Table.hs')
-rw-r--r--client/src/View/Payment/Table.hs90
1 files changed, 90 insertions, 0 deletions
diff --git a/client/src/View/Payment/Table.hs b/client/src/View/Payment/Table.hs
new file mode 100644
index 0000000..f3eb9a7
--- /dev/null
+++ b/client/src/View/Payment/Table.hs
@@ -0,0 +1,90 @@
+{-# LANGUAGE ExistentialQuantification #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecursiveDo #-}
+
+module View.Payment.Table
+ ( widget
+ , TableIn(..)
+ , TableOut(..)
+ ) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.List as L
+import qualified Data.Map as M
+import Prelude hiding (init)
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Common.Message as Message
+import qualified Common.Message.Key as Key
+import Common.Model (Payment(..), PaymentCategory(..), Category(..), User(..), Init(..))
+import qualified Common.Model as CM
+import qualified Common.Util.Text as T
+import qualified Common.View.Format as Format
+
+import qualified Icon
+
+data TableIn = TableIn
+ { _tableIn_init :: Init
+ }
+
+data TableOut = TableOut
+ {
+ }
+
+widget :: forall t m. MonadWidget t m => TableIn -> m TableOut
+widget tableIn = do
+ R.divClass "table" $
+ R.divClass "lines" $ do
+ R.divClass "header" $ do
+ R.divClass "cell name" $ R.text $ Message.get Key.Payment_Name
+ R.divClass "cell cost" $ R.text $ Message.get Key.Payment_Cost
+ R.divClass "cell user" $ R.text $ Message.get Key.Payment_User
+ R.divClass "cell category" $ R.text $ Message.get Key.Payment_Category
+ R.divClass "cell date" $ R.text $ Message.get Key.Payment_Date
+ R.divClass "cell" $ R.blank
+ R.divClass "cell" $ R.blank
+ R.divClass "cell" $ R.blank
+ let init = _tableIn_init tableIn
+ payments = _init_payments init
+ mapM_
+ (paymentRow init)
+ (take 8 . reverse . L.sortOn _payment_date $ payments)
+ return $ TableOut {}
+
+paymentRow :: forall t m. MonadWidget t m => Init -> Payment -> m ()
+paymentRow init payment =
+ R.divClass "row" $ do
+ R.divClass "cell name" . R.text $ _payment_name payment
+ R.divClass "cell cost" . R.text . Format.price (_init_currency init) $ _payment_cost payment
+ R.divClass "cell user" $
+ case CM.findUser (_payment_user payment) (_init_users init) of
+ Just user -> R.text (_user_name user)
+ _ -> R.blank
+ R.divClass "cell category" $
+ case findCategory (_init_categories init) (_init_paymentCategories init) (_payment_name payment) of
+ Just category ->
+ R.elAttr "span" (M.fromList [("class", "tag"), ("style", T.concat [ "background-color: ", _category_color category ])]) $
+ R.text $ _category_name category
+ _ ->
+ R.blank
+ R.divClass "cell date" $ do
+ R.elClass "span" "shortDate" . R.text $ Format.shortDay (_payment_date payment)
+ R.elClass "span" "longDate" . R.text $ Format.longDay (_payment_date payment)
+ R.divClass "cell button" . R.el "button" $ Icon.clone
+ R.divClass "cell button" $
+ if _payment_user payment == (_init_currentUser init)
+ then R.el "button" $ Icon.edit
+ else R.blank
+ R.divClass "cell button" $
+ if _payment_user payment == (_init_currentUser init)
+ then R.el "button" $ Icon.delete
+ else R.blank
+
+findCategory :: [Category] -> [PaymentCategory] -> Text -> Maybe Category
+findCategory categories paymentCategories paymentName = do
+ paymentCategory <- L.find
+ ((== (T.unaccent . T.toLower) paymentName) . _paymentCategory_name)
+ paymentCategories
+ L.find ((== (_paymentCategory_category paymentCategory)) . _category_id) categories