aboutsummaryrefslogtreecommitdiff
path: root/client/src/View/Income/Income.hs
diff options
context:
space:
mode:
authorJoris2019-11-02 20:52:27 +0100
committerJoris2019-11-02 20:52:27 +0100
commit227dcd4435b775d7dbc5ae5d3d81b589897253cc (patch)
tree6c7e71b83942a35c2b11d6874c4601c403a910c0 /client/src/View/Income/Income.hs
parentb97ad942495352c3fc1e0c820cfba82a9693ac7a (diff)
downloadbudget-227dcd4435b775d7dbc5ae5d3d81b589897253cc.tar.gz
budget-227dcd4435b775d7dbc5ae5d3d81b589897253cc.tar.bz2
budget-227dcd4435b775d7dbc5ae5d3d81b589897253cc.zip
Implement incomes server side paging
Diffstat (limited to 'client/src/View/Income/Income.hs')
-rw-r--r--client/src/View/Income/Income.hs65
1 files changed, 31 insertions, 34 deletions
diff --git a/client/src/View/Income/Income.hs b/client/src/View/Income/Income.hs
index c48f325..fedf3d8 100644
--- a/client/src/View/Income/Income.hs
+++ b/client/src/View/Income/Income.hs
@@ -1,10 +1,14 @@
+{-# LANGUAGE ExplicitForAll #-}
+
module View.Income.Income
( init
, view
, In(..)
) where
+import qualified Data.Text as T
import Data.Aeson (FromJSON)
+import qualified Data.Maybe as Maybe
import Prelude hiding (init)
import Reflex.Dom (Dynamic, Event, MonadWidget)
import qualified Reflex.Dom as R
@@ -41,45 +45,38 @@ init = do
view :: forall t m. MonadWidget t m => In t -> m ()
view input = do
- -- rec
- -- incomes <- Reducer.reducer
- -- { Reducer._in_newPage = ReflexUtil.flatten (Table._out_newPage <$> table)
- -- , Reducer._in_currentPage = ReflexUtil.flatten (Table._out_currentPage <$> table)
- -- , Reducer._in_addIncome = ReflexUtil.flatten (Table._out_add <$> table)
- -- , Reducer._in_editIncome = ReflexUtil.flatten (Table._out_edit <$> table)
- -- , Reducer._in_deleteIncome = ReflexUtil.flatten (Table._out_delete <$> table)
- -- }
-
rec
incomes <- Reducer.reducer $ Reducer.In
- { Reducer._in_newPage = Pages._out_newPage pages
- , Reducer._in_currentPage = Pages._out_currentPage pages
- , Reducer._in_addIncome = Table._out_add table
- , Reducer._in_editIncome = Table._out_edit table
- , Reducer._in_deleteIncome = Table._out_delete table
+ { Reducer._in_newPage = newPage
+ , Reducer._in_currentPage = currentPage
+ , Reducer._in_addIncome = addIncome
+ , Reducer._in_editIncome = editIncome
+ , Reducer._in_deleteIncome = deleteIncome
}
- table <- Table.view $ Table.In
- { Table._in_currentUser = _in_currentUser input
- , Table._in_currency = _in_currency input
- , Table._in_incomes = R.ffor incomes $ \case
- Loaded (IncomesAndCount xs _) -> xs
- _ -> []
- }
+ let eventFromResult :: forall a. ((Table.Out t, Pages.Out t) -> Event t a) -> m (Event t a)
+ eventFromResult op = ReflexUtil.flatten . fmap (Maybe.fromMaybe R.never . fmap op) $ result
- pages <- Pages.view $ Pages.In
- { Pages._in_total = R.ffor incomes $ \case
- Loaded (IncomesAndCount _ n) -> n
- _ -> 0
- , Pages._in_perPage = Reducer.perPage
- }
+ newPage <- eventFromResult $ Pages._out_newPage . snd
+ currentPage <- R.holdDyn 1 newPage
+ addIncome <- eventFromResult $ Table._out_add . fst
+ editIncome <- eventFromResult $ Table._out_edit . fst
+ deleteIncome <- eventFromResult $ Table._out_delete . fst
+
+ result <- R.dyn . R.ffor ((,) <$> incomes <*> currentPage) $ \(is, p) ->
+ flip Loadable.view is $ \(IncomesAndCount incomes count) -> do
+ table <- Table.view $ Table.In
+ { Table._in_currentUser = _in_currentUser input
+ , Table._in_currency = _in_currency input
+ , Table._in_incomes = incomes
+ }
+
+ pages <- Pages.view $ Pages.In
+ { Pages._in_total = R.constDyn count
+ , Pages._in_perPage = Reducer.perPage
+ , Pages._in_page = p
+ }
- -- -- table :: Event t (Maybe (Table.Out t))
- -- table <- R.dyn . R.ffor incomes . Loadable.view $ \incomes ->
- -- Table.view $ Table.In
- -- { Table._in_currentUser = _in_currentUser input
- -- , Table._in_currency = _in_currency input
- -- , Table._in_incomes = incomes
- -- }
+ return (table, pages)
return ()