aboutsummaryrefslogtreecommitdiff
path: root/client/src/View/Income/Income.hs
blob: d31775a9279734f031b05ffd156fd41ca77c7d13 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
{-# LANGUAGE ExplicitForAll #-}

module View.Income.Income
  ( view
  , In(..)
  ) where

import           Data.Aeson          (FromJSON)
import qualified Data.Maybe          as Maybe
import qualified Data.Text           as T
import           Reflex.Dom          (Dynamic, Event, MonadWidget)
import qualified Reflex.Dom          as R

import           Common.Model        (Currency, Income (..),
                                      IncomesAndCount (..), User, UserId)

import qualified Component.Pages     as Pages
import           Loadable            (Loadable (..))
import qualified Loadable
import qualified Util.Ajax           as AjaxUtil
import qualified Util.Reflex         as ReflexUtil
-- import qualified View.Income.Header as Header
import           View.Income.Init    (Init (..))
import qualified View.Income.Reducer as Reducer
import qualified View.Income.Table   as Table

data In t = In
  { _in_users       :: [User]
  , _in_currentUser :: UserId
  , _in_currency    :: Currency
  }

view :: forall t m. MonadWidget t m => In t -> m ()
view input = do
  rec
    incomes <- Reducer.reducer $ Reducer.In
      { Reducer._in_newPage      = newPage
      , Reducer._in_currentPage  = currentPage
      , Reducer._in_addIncome    = addIncome
      , Reducer._in_editIncome   = editIncome
      , Reducer._in_deleteIncome = deleteIncome
      }

    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

    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
          , Table._in_users = _in_users input
          }

        pages <- Pages.view $ Pages.In
          { Pages._in_total = R.constDyn count
          , Pages._in_perPage = Reducer.perPage
          , Pages._in_page = p
          }

        return (table, pages)

  return ()