aboutsummaryrefslogtreecommitdiff
path: root/client/src
diff options
context:
space:
mode:
authorJoris2020-01-30 11:35:31 +0000
committerJoris2020-01-30 11:35:31 +0000
commit960fa7cb7ae4c57d01306f78cd349f3a8337d0ab (patch)
tree5077cc720525fb025e4dba65a9a8b631862cbcc8 /client/src
parent14bdbc8c937f5d0b35c61350dba28cb41c3737cd (diff)
parent6a04e640955051616c3ad0874605830c448f2d75 (diff)
downloadbudget-960fa7cb7ae4c57d01306f78cd349f3a8337d0ab.tar.gz
budget-960fa7cb7ae4c57d01306f78cd349f3a8337d0ab.tar.bz2
budget-960fa7cb7ae4c57d01306f78cd349f3a8337d0ab.zip
Merge branch 'with-ghcjs' into 'master'
Use Haskell on the frontend See merge request guyonvarch/shared-cost!2
Diffstat (limited to 'client/src')
-rw-r--r--client/src/Component/Appearing.hs10
-rw-r--r--client/src/Component/Button.hs57
-rw-r--r--client/src/Component/ConfirmDialog.hs49
-rw-r--r--client/src/Component/Form.hs12
-rw-r--r--client/src/Component/Input.hs151
-rw-r--r--client/src/Component/Link.hs33
-rw-r--r--client/src/Component/Modal.hs117
-rw-r--r--client/src/Component/ModalForm.hs71
-rw-r--r--client/src/Component/Pages.hs86
-rw-r--r--client/src/Component/Select.hs80
-rw-r--r--client/src/Component/Table.hs105
-rw-r--r--client/src/Component/Tag.hs27
-rw-r--r--client/src/Loadable.hs109
-rw-r--r--client/src/Main.hs39
-rw-r--r--client/src/Model/Route.hs11
-rw-r--r--client/src/Util/Ajax.hs139
-rw-r--r--client/src/Util/Css.hs9
-rw-r--r--client/src/Util/Either.hs7
-rw-r--r--client/src/Util/Reflex.hs59
-rw-r--r--client/src/Util/Router.hs266
-rw-r--r--client/src/Util/Validation.hs36
-rw-r--r--client/src/Util/WaitFor.hs17
-rw-r--r--client/src/View/App.hs108
-rw-r--r--client/src/View/Category/Category.hs94
-rw-r--r--client/src/View/Category/Form.hs117
-rw-r--r--client/src/View/Category/Reducer.hs59
-rw-r--r--client/src/View/Category/Table.hs93
-rw-r--r--client/src/View/Header.hs123
-rw-r--r--client/src/View/Icon.hs71
-rw-r--r--client/src/View/Income/Form.hs119
-rw-r--r--client/src/View/Income/Header.hs77
-rw-r--r--client/src/View/Income/Income.hs75
-rw-r--r--client/src/View/Income/Reducer.hs59
-rw-r--r--client/src/View/Income/Table.hs93
-rw-r--r--client/src/View/NotFound.hs20
-rw-r--r--client/src/View/Payment/Form.hs199
-rw-r--r--client/src/View/Payment/HeaderForm.hs85
-rw-r--r--client/src/View/Payment/HeaderInfos.hs94
-rw-r--r--client/src/View/Payment/Payment.hs101
-rw-r--r--client/src/View/Payment/Reducer.hs110
-rw-r--r--client/src/View/Payment/Table.hs143
-rw-r--r--client/src/View/SignIn.hs82
-rw-r--r--client/src/View/Statistics/Chart.hs102
-rw-r--r--client/src/View/Statistics/Statistics.hs85
44 files changed, 3599 insertions, 0 deletions
diff --git a/client/src/Component/Appearing.hs b/client/src/Component/Appearing.hs
new file mode 100644
index 0000000..e0144ca
--- /dev/null
+++ b/client/src/Component/Appearing.hs
@@ -0,0 +1,10 @@
+module Component.Appearing
+ ( view
+ ) where
+
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+view :: forall t m a. MonadWidget t m => m a -> m a
+view =
+ R.divClass "g-Appearing"
diff --git a/client/src/Component/Button.hs b/client/src/Component/Button.hs
new file mode 100644
index 0000000..153a61b
--- /dev/null
+++ b/client/src/Component/Button.hs
@@ -0,0 +1,57 @@
+module Component.Button
+ ( In(..)
+ , Out(..)
+ , view
+ , defaultIn
+ ) where
+
+import qualified Data.Map as M
+import Data.Maybe (catMaybes)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified View.Icon as Icon
+
+data In t m = In
+ { _in_class :: Dynamic t Text
+ , _in_content :: m ()
+ , _in_waiting :: Event t Bool
+ , _in_tabIndex :: Maybe Int
+ , _in_submit :: Bool
+ }
+
+defaultIn :: forall t m. MonadWidget t m => m () -> In t m
+defaultIn content = In
+ { _in_class = R.constDyn ""
+ , _in_content = content
+ , _in_waiting = R.never
+ , _in_tabIndex = Nothing
+ , _in_submit = False
+ }
+
+data Out t = Out
+ { _out_clic :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t m -> m (Out t)
+view input = do
+ dynWaiting <- R.holdDyn False $ _in_waiting input
+
+ let attr = do
+ buttonClass <- _in_class input
+ waiting <- dynWaiting
+ return . M.fromList . catMaybes $
+ [ Just ("type", if _in_submit input then "submit" else "button")
+ , (\i -> ("tabindex", T.pack . show $ i)) <$> _in_tabIndex input
+ , Just ("class", T.intercalate " " [ buttonClass, if waiting then "waiting" else "" ])
+ ]
+
+ (e, _) <- R.elDynAttr' "button" attr $ do
+ Icon.loading
+ R.divClass "content" $ _in_content input
+
+ return $ Out
+ { _out_clic = R.domEvent R.Click e
+ }
diff --git a/client/src/Component/ConfirmDialog.hs b/client/src/Component/ConfirmDialog.hs
new file mode 100644
index 0000000..cf26593
--- /dev/null
+++ b/client/src/Component/ConfirmDialog.hs
@@ -0,0 +1,49 @@
+module Component.ConfirmDialog
+ ( In(..)
+ , view
+ ) where
+
+import Data.Text (Text)
+import Reflex.Dom (Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Common.Msg as Msg
+import qualified Component.Button as Button
+import qualified Component.Modal as Modal
+import qualified Util.Either as EitherUtil
+import qualified Util.WaitFor as WaitFor
+
+data In t m = In
+ { _in_header :: Text
+ , _in_confirm :: Event t () -> m (Event t ())
+ }
+
+view :: forall t m a. MonadWidget t m => (In t m) -> Modal.Content t m
+view input _ =
+ R.divClass "confirm" $ do
+ R.divClass "confirmHeader" $
+ R.text $ _in_header input
+
+ R.divClass "confirmContent" $ do
+ (confirm, cancel) <- R.divClass "buttons" $ do
+
+ cancel <- Button._out_clic <$> (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.Dialog_Undo))
+ { Button._in_class = R.constDyn "undo" })
+
+ rec
+ confirm <- Button._out_clic <$> (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.Dialog_Confirm))
+ { Button._in_class = R.constDyn "confirm"
+ , Button._in_submit = True
+ , Button._in_waiting = waiting
+ })
+
+ (result, waiting) <- WaitFor.waitFor (_in_confirm input) confirm
+
+ return (result, cancel)
+
+ return $
+ ( R.leftmost [ cancel, () <$ confirm ]
+ , confirm
+ )
diff --git a/client/src/Component/Form.hs b/client/src/Component/Form.hs
new file mode 100644
index 0000000..6878e68
--- /dev/null
+++ b/client/src/Component/Form.hs
@@ -0,0 +1,12 @@
+module Component.Form
+ ( view
+ ) where
+
+import qualified Data.Map as M
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+view :: forall t m a. MonadWidget t m => m a -> m a
+view content =
+ R.elAttr "form" (M.singleton "onsubmit" "event.preventDefault()") $
+ content
diff --git a/client/src/Component/Input.hs b/client/src/Component/Input.hs
new file mode 100644
index 0000000..bcff377
--- /dev/null
+++ b/client/src/Component/Input.hs
@@ -0,0 +1,151 @@
+module Component.Input
+ ( In(..)
+ , Out(..)
+ , view
+ , defaultIn
+ ) where
+
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time (NominalDiffTime)
+import Data.Validation (Validation (Failure, Success))
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget, Reflex,
+ (&), (.~))
+import qualified Reflex.Dom as R
+
+import qualified Common.Util.Validation as ValidationUtil
+import qualified Component.Button as Button
+import qualified View.Icon as Icon
+
+data In a = In
+ { _in_hasResetButton :: Bool
+ , _in_label :: Text
+ , _in_initialValue :: Text
+ , _in_inputType :: Text
+ , _in_validation :: Text -> Validation Text a
+ }
+
+defaultIn :: In Text
+defaultIn = In
+ { _in_hasResetButton = True
+ , _in_label = ""
+ , _in_initialValue = ""
+ , _in_inputType = "text"
+ , _in_validation = V.Success
+ }
+
+data Out t a = Out
+ { _out_raw :: Dynamic t Text
+ , _out_value :: Dynamic t (Validation Text a)
+ , _out_enter :: Event t ()
+ }
+
+view
+ :: forall t m a b. MonadWidget t m
+ => In a
+ -> Event t Text -- reset
+ -> Event t b -- validate
+ -> m (Out t a)
+view input reset validate = do
+ rec
+ let resetValue = R.leftmost
+ [ reset
+ , fmap (const "") resetClic
+ ]
+
+ inputAttr = R.ffor value (\v ->
+ if T.null v && _in_inputType input /= "date" && _in_inputType input /= "color"
+ then M.empty
+ else M.singleton "class" "filled")
+
+ value = R._textInput_value textInput
+
+ containerAttr = R.ffor inputError (\e ->
+ M.singleton "class" $ T.intercalate " "
+ [ "textInput"
+ , if Maybe.isJust e then "error" else ""
+ ])
+
+ let valueWithValidation = R.ffor value (\v -> (v, _in_validation input $ v))
+ inputError <- getInputError valueWithValidation validate
+
+ (textInput, resetClic) <- R.elDynAttr "div" containerAttr $ do
+
+ textInput <- R.el "label" $ do
+ textInput <- R.textInput $ R.def
+ & R.attributes .~ inputAttr
+ & R.setValue .~ resetValue
+ & R.textInputConfig_initialValue .~ (_in_initialValue input)
+ & R.textInputConfig_inputType .~ (_in_inputType input)
+
+ R.divClass "label" $
+ R.text (_in_label input)
+
+ return textInput
+
+ resetClic <-
+ if _in_hasResetButton input
+ then
+ Button._out_clic <$> (Button.view $
+ (Button.defaultIn Icon.cross)
+ { Button._in_class = R.constDyn "reset"
+ , Button._in_tabIndex = Just (-1)
+ })
+ else
+ return R.never
+
+ R.divClass "errorMessage" $
+ R.dynText . fmap (Maybe.fromMaybe "") $ inputError
+
+ return (textInput, resetClic)
+
+ let enter = fmap (const ()) $ R.ffilter ((==) 13) . R._textInput_keypress $ textInput
+
+ return $ Out
+ { _out_raw = value
+ , _out_value = fmap snd valueWithValidation
+ , _out_enter = enter
+ }
+
+getInputError
+ :: forall t m a b c. MonadWidget t m
+ => Dynamic t (Text, Validation Text a)
+ -> Event t c
+ -> m (Dynamic t (Maybe Text))
+getInputError validatedValue validate = do
+ let errorDynamic = fmap (\(t, v) -> (t, validationError v)) validatedValue
+ errorEvent = R.updated errorDynamic
+ delayedError <- R.debounce (1 :: NominalDiffTime) errorEvent
+ fmap (fmap fst) $ R.foldDyn
+ (\event (err, hasBeenResetted) ->
+ case event of
+ ModifiedEvent t ->
+ (Nothing, T.null t)
+
+ ValidateEvent e ->
+ (e, False)
+
+ DelayEvent e ->
+ if hasBeenResetted then
+ (Nothing, False)
+ else
+ (e, False)
+ )
+ (Nothing, False)
+ (R.leftmost
+ [ fmap (\(t, _) -> ModifiedEvent t) errorEvent
+ , fmap (\(_, e) -> DelayEvent e) delayedError
+ , R.attachWith (\(_, e) _ -> ValidateEvent e) (R.current errorDynamic) validate
+ ])
+
+validationError :: (Validation Text a) -> Maybe Text
+validationError (Failure e) = Just e
+validationError _ = Nothing
+
+data InputEvent
+ = ModifiedEvent Text
+ | DelayEvent (Maybe Text)
+ | ValidateEvent (Maybe Text)
diff --git a/client/src/Component/Link.hs b/client/src/Component/Link.hs
new file mode 100644
index 0000000..1fd620e
--- /dev/null
+++ b/client/src/Component/Link.hs
@@ -0,0 +1,33 @@
+module Component.Link
+ ( view
+ ) where
+
+import Data.Map (Map)
+import qualified Data.Map as M
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, MonadWidget)
+import qualified Reflex.Dom as R
+
+view :: forall t m a. MonadWidget t m => Text -> Dynamic t (Map Text Text) -> Text -> m ()
+view href inputAttrs content =
+ R.elDynAttr "a" attrs (R.text content)
+ where
+
+ onclickHandler =
+ T.intercalate ";"
+ [ "history.pushState(0, '', event.target.href)"
+ , "dispatchEvent(new PopStateEvent('popstate', {cancelable: true, bubbles: true, view: window}))"
+ , "return false"
+ ]
+
+ attrs =
+ R.ffor inputAttrs (\as ->
+ (M.union
+ (M.fromList
+ [ ("onclick", onclickHandler)
+ , ("href", href)
+ ]
+ )
+ as)
+ )
diff --git a/client/src/Component/Modal.hs b/client/src/Component/Modal.hs
new file mode 100644
index 0000000..46d3f64
--- /dev/null
+++ b/client/src/Component/Modal.hs
@@ -0,0 +1,117 @@
+module Component.Modal
+ ( In(..)
+ , Content
+ , view
+ ) where
+
+import Control.Monad (void)
+import qualified Data.Map as M
+import qualified Data.Map.Lazy as LM
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time.Clock (NominalDiffTime)
+import qualified GHCJS.DOM.Element as Element
+import qualified GHCJS.DOM.Node as Node
+import JSDOM.Types (JSString)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+import qualified Reflex.Dom.Class as R
+
+import qualified Util.Reflex as ReflexUtil
+
+-- Content = CurtainClickEvent -> (CancelEvent, ConfirmEvent)
+type Content t m = Event t () -> m (Event t (), Event t ())
+
+data In t m = In
+ { _in_show :: Event t ()
+ , _in_content :: Content t m
+ }
+
+view :: forall t m a. MonadWidget t m => In t m -> m (Event t ())
+view input = do
+ rec
+ let show = Show <$ (_in_show input)
+
+ startHiding =
+ R.attachWithMaybe
+ (\a _ -> if a then Just StartHiding else Nothing)
+ (R.current canBeHidden)
+ (R.leftmost [ hide, curtainClick ])
+
+ canBeHidden <-
+ R.holdDyn True $ R.leftmost
+ [ False <$ startHiding
+ , True <$ endHiding
+ ]
+
+ endHiding <-
+ R.delay (0.2 :: NominalDiffTime) (EndHiding <$ startHiding)
+
+ let action =
+ R.leftmost [ show, startHiding, endHiding ]
+
+ modalClass <-
+ R.holdDyn "" (fmap getModalClass action)
+
+ (elem, dyn) <-
+ R.buildElement "div" (getAttributes <$> modalClass) $
+ ReflexUtil.visibleIfEvent
+ (isVisible <$> action)
+ (R.blank >> return (R.never, R.never, R.never))
+ (do
+ (curtain, _) <- R.elAttr' "div" (M.singleton "class" "g-Modal__Curtain") $ R.blank
+ let curtainClick = R.domEvent R.Click curtain
+ (hide, content) <- R.divClass "g-Modal__Content" (_in_content input curtainClick)
+ return (curtainClick, hide, content))
+
+
+ performShowEffects action elem
+
+ let curtainClick = R.switchDyn $ (\(a, _, _) -> a) <$> dyn
+ let hide = R.switchDyn $ (\(_, b, _) -> b) <$> dyn
+ let content = R.switchDyn $ (\(_, _, c) -> c) <$> dyn
+
+ -- Delay the event in order to let time for the modal to disappear
+ R.delay (0.5 :: NominalDiffTime) content
+
+getAttributes :: Text -> LM.Map Text Text
+getAttributes modalClass =
+ M.singleton "class" $
+ T.intercalate " " [ "g-Modal", modalClass]
+
+performShowEffects
+ :: forall t m a. MonadWidget t m
+ => Event t Action
+ -> Element.Element
+ -> m ()
+performShowEffects showEvent elem = do
+ body <- ReflexUtil.getBody
+
+ let showEffects =
+ flip fmap showEvent (\case
+ Show -> do
+ Node.appendChild body elem
+ Element.setClassName body ("g-Body--Modal" :: JSString)
+ StartHiding ->
+ return ()
+ EndHiding -> do
+ Node.removeChild body elem
+ Element.setClassName body ("" :: JSString)
+ )
+
+ R.performEvent_ $ void `fmap` showEffects
+
+data Action
+ = Show
+ | StartHiding
+ | EndHiding
+
+getModalClass :: Action -> Text
+getModalClass Show = "g-Modal--Show"
+getModalClass StartHiding = "g-Modal--Hiding"
+getModalClass _ = ""
+
+isVisible :: Action -> Bool
+isVisible Show = True
+isVisible StartHiding = True
+isVisible EndHiding = False
diff --git a/client/src/Component/ModalForm.hs b/client/src/Component/ModalForm.hs
new file mode 100644
index 0000000..c56ff88
--- /dev/null
+++ b/client/src/Component/ModalForm.hs
@@ -0,0 +1,71 @@
+module Component.ModalForm
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import Data.Aeson (ToJSON)
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time.Calendar (Day)
+import Data.Validation (Validation)
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Common.Msg as Msg
+import qualified Component.Button as Button
+import qualified Component.Form as Form
+import qualified Util.Either as EitherUtil
+import qualified Util.Validation as ValidationUtil
+import qualified Util.WaitFor as WaitFor
+
+data In m t a e = In
+ { _in_headerLabel :: Text
+ , _in_form :: m (Dynamic t (Validation e a))
+ , _in_ajax :: Event t a -> m (Event t (Either Text ()))
+ }
+
+data Out t = Out
+ { _out_hide :: Event t ()
+ , _out_cancel :: Event t ()
+ , _out_confirm :: Event t ()
+ , _out_validate :: Event t ()
+ }
+
+view :: forall t m a e. (MonadWidget t m, ToJSON a) => In m t a e -> m (Out t)
+view input =
+ R.divClass "form" $ do
+ R.divClass "formHeader" $
+ R.text (_in_headerLabel input)
+
+ Form.view $
+ R.divClass "formContent" $ do
+ rec
+ form <- _in_form input
+
+ (validate, cancel, confirm) <- R.divClass "buttons" $ do
+ rec
+ cancel <- Button._out_clic <$> (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.Dialog_Undo))
+ { Button._in_class = R.constDyn "undo" })
+
+ confirm <- Button._out_clic <$> (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.Dialog_Confirm))
+ { Button._in_class = R.constDyn "confirm"
+ , Button._in_waiting = waiting
+ , Button._in_submit = True
+ })
+
+ (validate, waiting) <- WaitFor.waitFor
+ (_in_ajax input)
+ (ValidationUtil.fireValidation form confirm)
+
+ return (R.fmapMaybe EitherUtil.eitherToMaybe validate, cancel, confirm)
+
+ return Out
+ { _out_hide = R.leftmost [ cancel, () <$ validate ]
+ , _out_cancel = cancel
+ , _out_confirm = confirm
+ , _out_validate = validate
+ }
diff --git a/client/src/Component/Pages.hs b/client/src/Component/Pages.hs
new file mode 100644
index 0000000..d54cd3d
--- /dev/null
+++ b/client/src/Component/Pages.hs
@@ -0,0 +1,86 @@
+module Component.Pages
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Component.Button as Button
+
+import qualified Util.Reflex as ReflexUtil
+import qualified View.Icon as Icon
+
+data In t = In
+ { _in_total :: Dynamic t Int
+ , _in_perPage :: Int
+ , _in_page :: Int
+ }
+
+data Out t = Out
+ { _out_newPage :: Event t Int
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input = do
+ newPage <- ReflexUtil.divVisibleIf ((> 0) <$> (_in_total input)) $ pageButtons input
+
+ return $ Out
+ { _out_newPage = newPage
+ }
+
+pageButtons
+ :: forall t m. MonadWidget t m
+ => In t
+ -> m (Event t Int)
+pageButtons input = do
+ R.divClass "pages" $ do
+ rec
+ let newPage = R.leftmost
+ [ firstPageClic
+ , previousPageClic
+ , pageClic
+ , nextPageClic
+ , lastPageClic
+ ]
+
+ currentPage <- R.holdDyn (_in_page input) newPage
+
+ firstPageClic <- pageButton noCurrentPage (R.constDyn 1) Icon.doubleLeftBar
+
+ previousPageClic <- pageButton noCurrentPage (fmap (\x -> max (x - 1) 1) currentPage) Icon.doubleLeft
+
+ pageClic <- pageEvent <$> (R.simpleList (range <$> currentPage <*> maxPage) $ \p ->
+ pageButton (Just <$> currentPage) p (R.dynText $ fmap (T.pack . show) p))
+
+ nextPageClic <- pageButton noCurrentPage ((\c m -> min (c + 1) m) <$> currentPage <*> maxPage) Icon.doubleRight
+
+ lastPageClic <- pageButton noCurrentPage maxPage Icon.doubleRightBar
+
+ return newPage
+
+ where maxPage = R.ffor (_in_total input) (\t -> ceiling $ toRational t / toRational (_in_perPage input))
+ pageEvent = R.switch . R.current . fmap R.leftmost
+ noCurrentPage = R.constDyn Nothing
+
+range :: Int -> Int -> [Int]
+range currentPage maxPage = [start..end]
+ where sidePages = 2
+ start = max 1 (min (currentPage - sidePages) (maxPage - sidePages * 2))
+ end = min maxPage (start + sidePages * 2)
+
+pageButton :: forall t m. MonadWidget t m => Dynamic t (Maybe Int) -> Dynamic t Int -> m () -> m (Event t Int)
+pageButton currentPage page content = do
+ clic <- Button._out_clic <$> (Button.view $ Button.In
+ { Button._in_class = do
+ cp <- currentPage
+ p <- page
+ if cp == Just p then "page current" else "page"
+ , Button._in_content = content
+ , Button._in_waiting = R.never
+ , Button._in_tabIndex = Nothing
+ , Button._in_submit = False
+ })
+ return . fmap fst $ R.attach (R.current page) clic
diff --git a/client/src/Component/Select.hs b/client/src/Component/Select.hs
new file mode 100644
index 0000000..70f5f58
--- /dev/null
+++ b/client/src/Component/Select.hs
@@ -0,0 +1,80 @@
+module Component.Select
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import Data.Map (Map)
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Validation (Validation)
+import Reflex.Dom (Dynamic, Event, MonadWidget, Reflex)
+import qualified Reflex.Dom as R
+
+import qualified Util.Validation as ValidationUtil
+
+data (Reflex t) => In t a b c = In
+ { _in_label :: Text
+ , _in_initialValue :: a
+ , _in_value :: Event t a
+ , _in_values :: Dynamic t (Map a Text)
+ , _in_reset :: Event t b
+ , _in_isValid :: a -> Validation Text a
+ , _in_validate :: Event t c
+ }
+
+data Out t a = Out
+ { _out_raw :: Dynamic t a
+ , _out_value :: Dynamic t (Validation Text a)
+ }
+
+view :: forall t m a b c. (Ord a, MonadWidget t m) => In t a b c -> m (Out t a)
+view input = do
+ rec
+ let containerAttr = R.ffor showedError (\e ->
+ M.singleton "class" $ T.intercalate " "
+ [ "input selectInput"
+ , if Maybe.isJust e then "error" else ""
+ ])
+
+ validatedValue =
+ fmap (_in_isValid input) value
+
+ maybeError =
+ fmap ValidationUtil.maybeError validatedValue
+
+ showedError <- R.holdDyn Nothing $ R.leftmost
+ [ Nothing <$ _in_reset input
+ , R.updated maybeError
+ , R.attachWith const (R.current maybeError) (_in_validate input)
+ ]
+
+ value <- R.elDynAttr "div" containerAttr $ do
+ let initialValue = _in_initialValue input
+
+ let setValue = R.leftmost
+ [ initialValue <$ (_in_reset input)
+ , _in_value input
+ ]
+
+ value <- R.el "label" $ do
+ R.divClass "label" $
+ R.text (_in_label input)
+
+ R._dropdown_value <$>
+ R.dropdown
+ initialValue
+ (_in_values input)
+ (R.def { R._dropdownConfig_setValue = setValue })
+
+ R.divClass "errorMessage" . R.dynText $
+ R.ffor showedError (Maybe.fromMaybe "")
+
+ return value
+
+ return Out
+ { _out_raw = value
+ , _out_value = validatedValue
+ }
diff --git a/client/src/Component/Table.hs b/client/src/Component/Table.hs
new file mode 100644
index 0000000..1482f91
--- /dev/null
+++ b/client/src/Component/Table.hs
@@ -0,0 +1,105 @@
+module Component.Table
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.Map as M
+import Data.Text (Text)
+import Reflex.Dom (Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Component.Button as Button
+import qualified Component.Modal as Modal
+import qualified Util.Reflex as ReflexUtil
+import qualified View.Icon as Icon
+
+data In m t h r = In
+ { _in_headerLabel :: h -> Text
+ , _in_rows :: [r]
+ , _in_cell :: h -> r -> m ()
+ , _in_cloneModal :: r -> Modal.Content t m
+ , _in_editModal :: r -> Modal.Content t m
+ , _in_deleteModal :: r -> Modal.Content t m
+ , _in_canEdit :: r -> Bool
+ , _in_canDelete :: r -> Bool
+ }
+
+data Out t = Out
+ { _out_add :: Event t ()
+ , _out_edit :: Event t ()
+ , _out_delete :: Event t ()
+ }
+
+view :: forall t m h r. (MonadWidget t m, Bounded h, Enum h) => In m t h r -> m (Out t)
+view input =
+ R.divClass "table" $ do
+ rec
+ result <- R.divClass "lines" $ do
+
+ R.divClass "header" $ do
+ flip mapM_ [minBound..] $ \header ->
+ R.divClass "cell" . R.text $
+ _in_headerLabel input header
+
+ R.divClass "cell" $ R.blank
+ R.divClass "cell" $ R.blank
+ R.divClass "cell" $ R.blank
+
+ flip mapM (_in_rows input) $ \row ->
+ R.divClass "row" $ do
+ flip mapM_ [minBound..] $ \header ->
+ R.divClass "cell" $
+ _in_cell input header row
+
+ cloneButton <-
+ R.divClass "cell button" $
+ Button._out_clic <$> (Button.view $
+ Button.defaultIn Icon.clone)
+
+ clone <-
+ Modal.view $ Modal.In
+ { Modal._in_show = cloneButton
+ , Modal._in_content = _in_cloneModal input row
+ }
+
+ let visibleIf cond =
+ R.elAttr
+ "div"
+ (if cond then M.empty else M.singleton "style" "display:none")
+
+ editButton <-
+ R.divClass "cell button" $
+ visibleIf (_in_canEdit input row) $
+ Button._out_clic <$> (Button.view $
+ Button.defaultIn Icon.edit)
+
+ edit <-
+ Modal.view $ Modal.In
+ { Modal._in_show = editButton
+ , Modal._in_content = _in_editModal input row
+ }
+
+ deleteButton <-
+ R.divClass "cell button" $
+ visibleIf (_in_canDelete input row) $
+ Button._out_clic <$> (Button.view $
+ Button.defaultIn Icon.delete)
+
+ delete <-
+ Modal.view $ Modal.In
+ { Modal._in_show = deleteButton
+ , Modal._in_content = _in_deleteModal input row
+ }
+
+ return (clone, edit, delete)
+
+ let add = R.leftmost . map (\(a, _, _) -> a) $ result
+ edit = R.leftmost . map (\(_, a, _) -> a) $ result
+ delete = R.leftmost . map (\(_, _, a) -> a) $ result
+
+ return $ Out
+ { _out_add = add
+ , _out_edit = edit
+ , _out_delete = delete
+ }
diff --git a/client/src/Component/Tag.hs b/client/src/Component/Tag.hs
new file mode 100644
index 0000000..f75b8d3
--- /dev/null
+++ b/client/src/Component/Tag.hs
@@ -0,0 +1,27 @@
+module Component.Tag
+ ( In(..)
+ , view
+ ) where
+
+import qualified Data.Map as M
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+data In = In
+ { _in_text :: Text
+ , _in_color :: Text
+ }
+
+view :: forall t m a. MonadWidget t m => In -> m ()
+view input =
+ R.elAttr "span" attrs $
+ R.text $ _in_text input
+
+ where
+ attrs =
+ M.fromList
+ [ ("class", "tag")
+ , ("style", T.concat [ "background-color: ", _in_color input ])
+ ]
diff --git a/client/src/Loadable.hs b/client/src/Loadable.hs
new file mode 100644
index 0000000..4806b08
--- /dev/null
+++ b/client/src/Loadable.hs
@@ -0,0 +1,109 @@
+module Loadable
+ ( Loadable (..)
+ , fromEither
+ , fromEvent
+ , viewHideValueWhileLoading
+ , viewShowValueWhileLoading
+ ) where
+
+import qualified Data.Map as M
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+import Data.Functor (Functor)
+import Data.Text (Text)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+data Loadable t
+ = Loading
+ | Error Text
+ | Loaded t
+ deriving (Eq, Show)
+
+instance Functor Loadable where
+ fmap f Loading = Loading
+ fmap f (Error e) = Error e
+ fmap f (Loaded x) = Loaded (f x)
+
+instance Applicative Loadable where
+ pure x = Loaded x
+
+ Loading <*> _ = Loading
+ (Error e) <*> _ = Error e
+ (Loaded f) <*> Loading = Loading
+ (Loaded f) <*> (Error e) = Error e
+ (Loaded f) <*> (Loaded x) = Loaded (f x)
+
+instance Monad Loadable where
+ Loading >>= f = Loading
+ (Error e) >>= f = Error e
+ (Loaded x) >>= f = f x
+
+fromEither :: forall a b. Either Text b -> Loadable b
+fromEither (Left err) = Error err
+fromEither (Right value) = Loaded value
+
+fromEvent :: forall t m a. MonadWidget t m => Event t (Either Text a) -> m (Dynamic t (Loadable a))
+fromEvent =
+ R.foldDyn
+ (\res _ -> case res of
+ Left err -> Error err
+ Right t -> Loaded t
+ )
+ Loading
+
+viewHideValueWhileLoading :: forall t m a b. MonadWidget t m => (a -> m b) -> Loadable a -> m (Maybe b)
+viewHideValueWhileLoading f loadable =
+ case loadable of
+ Loading ->
+ (R.divClass "pageSpinner" $ R.divClass "spinner" $ R.blank) >> return Nothing
+
+ Error err ->
+ R.text err >> return Nothing
+
+ Loaded x ->
+ Just <$> f x
+
+viewShowValueWhileLoading
+ :: forall t m a b. (MonadWidget t m, Eq a)
+ => Dynamic t (Loadable a)
+ -> (a -> m b)
+ -> m (Event t (Maybe b))
+viewShowValueWhileLoading loadable f = do
+
+ value <-
+ (R.foldDyn
+ (\l v1 ->
+ case l of
+ Loaded v2 -> Just v2
+ _ -> v1)
+ Nothing
+ (R.updated loadable)) >>= R.holdUniqDyn
+
+ withLoader (fmap ((==) Loading) loadable) $
+ R.dyn . R.ffor value $ \case
+ Nothing -> return Nothing
+ Just x -> Just <$> f x
+
+withLoader
+ :: forall t m a. MonadWidget t m
+ => Dynamic t Bool
+ -> m a
+ -> m a
+withLoader isLoading block =
+ R.divClass "g-Loadable" $ do
+ res <- R.elDynAttr "div" (blockAttrs <$> isLoading) $
+ block
+ R.elDynAttr "div" (spinnerAttrs <$> isLoading) $
+ R.divClass "spinner" R.blank
+ return res
+
+ where
+ spinnerAttrs l = M.singleton "class" $
+ "g-Loadable__Spinner"
+ <> (if l then " g-Loadable__Spinner--Loading" else "")
+
+ blockAttrs l = M.singleton "class" $
+ "g-Loadable__Content"
+ <> (if l then " g-Loadable__Content--Loading" else "")
diff --git a/client/src/Main.hs b/client/src/Main.hs
new file mode 100644
index 0000000..c71b0f0
--- /dev/null
+++ b/client/src/Main.hs
@@ -0,0 +1,39 @@
+module Main
+ ( main
+ ) where
+
+import qualified Data.Aeson as Aeson
+import qualified Data.ByteString.Lazy as LB
+import qualified Data.JSString.Text as Dom
+import qualified Data.Text.Encoding as T
+import qualified JSDOM as Dom
+import qualified JSDOM.Generated.HTMLElement as Dom
+import qualified JSDOM.Generated.NonElementParentNode as Dom
+import JSDOM.Types (HTMLElement (..), JSM,
+ JSString)
+import qualified JSDOM.Types as Dom
+import Prelude hiding (error, init)
+
+import Common.Model (Init)
+import qualified Common.Msg as Msg
+
+import qualified View.App as App
+
+main :: JSM ()
+main = do
+ initResult <- readInit
+ App.widget initResult
+
+readInit :: JSM (Maybe Init)
+readInit = do
+ document <- Dom.currentDocumentUnchecked
+ initNode <- Dom.getElementById document ("init" :: JSString)
+
+ case initNode of
+ Just node -> do
+ text <- Dom.textFromJSString <$> Dom.getInnerText (Dom.uncheckedCastTo HTMLElement node)
+ return $ case Aeson.decode (LB.fromStrict . T.encodeUtf8 $ text) of
+ Just init -> init
+ Nothing -> Nothing
+ _ ->
+ return Nothing
diff --git a/client/src/Model/Route.hs b/client/src/Model/Route.hs
new file mode 100644
index 0000000..f92e9be
--- /dev/null
+++ b/client/src/Model/Route.hs
@@ -0,0 +1,11 @@
+module Model.Route
+ ( Route(..)
+ ) where
+
+data Route
+ = RootRoute
+ | IncomeRoute
+ | CategoryRoute
+ | StatisticsRoute
+ | NotFoundRoute
+ deriving (Eq, Show)
diff --git a/client/src/Util/Ajax.hs b/client/src/Util/Ajax.hs
new file mode 100644
index 0000000..dcfd402
--- /dev/null
+++ b/client/src/Util/Ajax.hs
@@ -0,0 +1,139 @@
+module Util.Ajax
+ ( getNow
+ , get
+ , post
+ , postAndParseResult
+ , put
+ , putAndParseResult
+ , delete
+ ) where
+
+import Control.Arrow (left)
+import Data.Aeson (FromJSON, ToJSON)
+import qualified Data.Aeson as Aeson
+import Data.ByteString (ByteString)
+import qualified Data.ByteString.Lazy as LBS
+import Data.Default (def)
+import qualified Data.Map.Lazy as LM
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Text.Encoding as T
+import Data.Time.Clock (NominalDiffTime)
+import Reflex.Dom (Dynamic, Event, IsXhrPayload,
+ MonadWidget, XhrRequest,
+ XhrRequestConfig (..), XhrResponse,
+ XhrResponseHeaders (..))
+import qualified Reflex.Dom as R
+
+import Loadable (Loadable)
+import qualified Loadable
+
+getNow :: forall t m a. (MonadWidget t m, FromJSON a) => Text -> m (Dynamic t (Loadable a))
+getNow url = do
+ postBuild <- R.getPostBuild
+ get (url <$ postBuild)
+ >>= R.debounce (0 :: NominalDiffTime) -- Fired 2 times otherwise
+ >>= Loadable.fromEvent
+
+get
+ :: forall t m a. (MonadWidget t m, FromJSON a)
+ => Event t Text
+ -> m (Event t (Either Text a))
+get url =
+ fmap getJsonResult <$>
+ R.performRequestAsync (R.ffor url $ \u -> jsonRequest "GET" u (Aeson.String ""))
+
+post
+ :: forall t m a. (MonadWidget t m, ToJSON a)
+ => Text
+ -> Event t a
+ -> m (Event t (Either Text ()))
+post url input =
+ fmap checkResult <$>
+ R.performRequestAsync (jsonRequest "POST" url <$> input)
+
+postAndParseResult
+ :: forall t m a b. (MonadWidget t m, ToJSON a, FromJSON b)
+ => Text
+ -> Event t a
+ -> m (Event t (Either Text b))
+postAndParseResult url input =
+ fmap getJsonResult <$>
+ R.performRequestAsync (jsonRequest "POST" url <$> input)
+
+put
+ :: forall t m a. (MonadWidget t m, ToJSON a)
+ => Text
+ -> Event t a
+ -> m (Event t (Either Text ()))
+put url input =
+ fmap checkResult <$>
+ R.performRequestAsync (jsonRequest "PUT" url <$> input)
+
+putAndParseResult
+ :: forall t m a b. (MonadWidget t m, ToJSON a, FromJSON b)
+ => Text
+ -> Event t a
+ -> m (Event t (Either Text b))
+putAndParseResult url input =
+ fmap getJsonResult <$>
+ R.performRequestAsync (jsonRequest "PUT" url <$> input)
+
+delete
+ :: forall t m a. (MonadWidget t m)
+ => Dynamic t Text
+ -> Event t ()
+ -> m (Event t (Either Text Text))
+delete url fire = do
+ fmap getResult <$>
+ (R.performRequestAsync $
+ R.attachWith (\u _ -> request "DELETE" u ()) (R.current url) fire)
+
+checkResult :: XhrResponse -> Either Text ()
+checkResult response =
+ () <$ getResult response
+
+getJsonResult :: forall a. (FromJSON a) => XhrResponse -> Either Text a
+getJsonResult response =
+ case getResult response of
+ Left l -> Left l
+ Right r -> left T.pack . Aeson.eitherDecodeStrict $ (T.encodeUtf8 r)
+
+getResult :: XhrResponse -> Either Text Text
+getResult response =
+ case R._xhrResponse_responseText response of
+ Just responseText ->
+ if R._xhrResponse_status response == 200
+ then Right responseText
+ else Left responseText
+ _ -> Left "NoKey"
+
+request :: forall a. (IsXhrPayload a) => Text -> Text -> a -> XhrRequest a
+request method url payload =
+ let
+ config = XhrRequestConfig
+ { _xhrRequestConfig_headers = def
+ , _xhrRequestConfig_user = def
+ , _xhrRequestConfig_password = def
+ , _xhrRequestConfig_responseType = def
+ , _xhrRequestConfig_responseHeaders = def
+ , _xhrRequestConfig_withCredentials = False
+ , _xhrRequestConfig_sendData = payload
+ }
+ in
+ R.xhrRequest method url config
+
+jsonRequest :: forall a. (ToJSON a) => Text -> Text -> a -> XhrRequest ByteString
+jsonRequest method url payload =
+ let
+ config = XhrRequestConfig
+ { _xhrRequestConfig_headers = def
+ , _xhrRequestConfig_user = def
+ , _xhrRequestConfig_password = def
+ , _xhrRequestConfig_responseType = def
+ , _xhrRequestConfig_responseHeaders = def
+ , _xhrRequestConfig_withCredentials = False
+ , _xhrRequestConfig_sendData = LBS.toStrict $ Aeson.encode payload
+ }
+ in
+ R.xhrRequest method url config
diff --git a/client/src/Util/Css.hs b/client/src/Util/Css.hs
new file mode 100644
index 0000000..804b10f
--- /dev/null
+++ b/client/src/Util/Css.hs
@@ -0,0 +1,9 @@
+module Util.Css
+ ( classes
+ ) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+
+classes :: [(Text, Bool)] -> Text
+classes = T.unwords . map fst . filter snd
diff --git a/client/src/Util/Either.hs b/client/src/Util/Either.hs
new file mode 100644
index 0000000..e76bc8a
--- /dev/null
+++ b/client/src/Util/Either.hs
@@ -0,0 +1,7 @@
+module Util.Either
+ ( eitherToMaybe
+ ) where
+
+eitherToMaybe :: forall a b. Either a b -> Maybe b
+eitherToMaybe (Right b) = Just b
+eitherToMaybe _ = Nothing
diff --git a/client/src/Util/Reflex.hs b/client/src/Util/Reflex.hs
new file mode 100644
index 0000000..aa5cebb
--- /dev/null
+++ b/client/src/Util/Reflex.hs
@@ -0,0 +1,59 @@
+module Util.Reflex
+ ( visibleIfDyn
+ , visibleIfEvent
+ , divVisibleIf
+ , divClassVisibleIf
+ , flatten
+ , flattenTuple
+ , getBody
+ ) where
+
+import qualified Data.Map as M
+import Data.Text (Text)
+import qualified GHCJS.DOM as Dom
+import qualified GHCJS.DOM.Document as Document
+import qualified GHCJS.DOM.HTMLCollection as HTMLCollection
+import GHCJS.DOM.Types (Element)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+visibleIfDyn :: forall t m a. MonadWidget t m => Dynamic t Bool -> m a -> m a -> m (Event t a)
+visibleIfDyn cond empty content =
+ R.dyn $ R.ffor cond $ \case
+ True -> content
+ False -> empty
+
+visibleIfEvent :: forall t m a. MonadWidget t m => Event t Bool -> m a -> m a -> m (Dynamic t a)
+visibleIfEvent cond empty content =
+ R.widgetHold empty $
+ R.ffor cond $ \case
+ True -> content
+ False -> empty
+
+divVisibleIf :: forall t m a. MonadWidget t m => Dynamic t Bool -> m a -> m a
+divVisibleIf cond content = divClassVisibleIf cond "" content
+
+divClassVisibleIf :: forall t m a. MonadWidget t m => Dynamic t Bool -> Text -> m a -> m a
+divClassVisibleIf cond className content =
+ R.elDynAttr
+ "div"
+ (fmap (\c -> (M.singleton "class" className) `M.union` if c then M.empty else M.singleton "style" "display:none") cond)
+ content
+
+flatten :: forall t m a. MonadWidget t m => Event t (Event t a) -> m (Event t a)
+flatten e = do
+ dyn <- R.holdDyn R.never e
+ return $ R.switchDyn dyn
+
+flattenTuple
+ :: forall t m a b. MonadWidget t m
+ => Event t (Event t a, Event t b)
+ -> m (Event t a, Event t b)
+flattenTuple e = (,) <$> (flatten $ fmap fst e) <*> (flatten $ fmap snd e)
+
+getBody :: forall t m. MonadWidget t m => m Element
+getBody = do
+ document <- Dom.currentDocumentUnchecked
+ nodelist <- Document.getElementsByTagName document ("body" :: String)
+ Just body <- nodelist `HTMLCollection.item` 0
+ return body
diff --git a/client/src/Util/Router.hs b/client/src/Util/Router.hs
new file mode 100644
index 0000000..e9d0a1a
--- /dev/null
+++ b/client/src/Util/Router.hs
@@ -0,0 +1,266 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE JavaScriptFFI #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE RecursiveDo #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TypeFamilies #-}
+
+module Util.Router (
+ -- == High-level routers
+ route
+ , route'
+ , partialPathRoute
+
+ -- = Low-level URL bar access
+ , getLoc
+ , getURI
+ , getUrlText
+ , uriOrigin
+ , URI
+
+ -- = History movement
+ , goForward
+ , goBack
+ ) where
+
+------------------------------------------------------------------------------
+import Control.Lens ((&), (.~), (^.))
+import Control.Monad.Fix (MonadFix)
+import qualified Data.ByteString.Char8 as BS
+import Data.Monoid ((<>))
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Text.Encoding as T
+import GHCJS.DOM (currentDocumentUnchecked,
+ currentWindowUnchecked)
+import GHCJS.DOM.Document (createEvent)
+import GHCJS.DOM.Event (initEvent)
+import GHCJS.DOM.EventM (on)
+import GHCJS.DOM.EventTarget (dispatchEvent_)
+import GHCJS.DOM.History (History, back, forward,
+ pushState)
+import GHCJS.DOM.Location (getHref)
+import GHCJS.DOM.PopStateEvent
+import GHCJS.DOM.Types (Location (..),
+ PopStateEvent (..))
+import GHCJS.DOM.Types (MonadJSM, uncheckedCastTo)
+import qualified GHCJS.DOM.Types as DOM
+import GHCJS.DOM.Window (getHistory, getLocation)
+import GHCJS.DOM.WindowEventHandlers (popState)
+import GHCJS.Foreign (isFunction)
+import GHCJS.Marshal.Pure (pFromJSVal)
+import Language.Javascript.JSaddle (JSM, Object (..), ghcjsPure,
+ liftJSM)
+import qualified Language.Javascript.JSaddle as JS
+import Reflex.Dom.Core hiding (EventName, Window)
+import qualified URI.ByteString as U
+------------------------------------------------------------------------------
+
+
+-------------------------------------------------------------------------------
+-- | Manipulate and track the URL 'GHCJS.DOM.Types.Location' for dynamic
+-- routing of a widget
+-- These sources of URL-bar change will be reflected in the output URI
+-- - Input events to 'route'
+-- - Browser Forward/Back button clicks
+-- - forward/back javascript calls (or 'goForward'/'goBack') Haskell calls
+-- - Any URL changes followed by a popState event
+-- But external calls to pushState that don't manually fire a popState
+-- won't be detected
+route
+ :: forall t m.
+ ( MonadHold t m
+ , PostBuild t m
+ , TriggerEvent t m
+ , PerformEvent t m
+ , HasJSContext m
+ , HasJSContext (Performable m)
+ , MonadJSM m
+ , MonadJSM (Performable m))
+ => Event t T.Text
+ -> m (Dynamic t (U.URIRef U.Absolute))
+route pushTo = do
+ loc0 <- getURI
+
+ _ <- performEvent $ ffor pushTo $ \t -> do
+ let newState = Just t
+ withHistory $ \h -> pushState h (0 :: Double) ("" :: T.Text) (newState :: Maybe T.Text)
+ liftJSM dispatchEvent'
+
+ locUpdates <- getPopState
+ holdDyn loc0 locUpdates
+
+route'
+ :: forall t m a b.
+ ( MonadHold t m
+ , PostBuild t m
+ , TriggerEvent t m
+ , PerformEvent t m
+ , HasJSContext m
+ , HasJSContext (Performable m)
+ , MonadJSM m
+ , MonadJSM (Performable m)
+ , MonadFix m)
+ => (URI -> a -> URI)
+ -> (URI -> b)
+ -> Event t a
+ -> m (Dynamic t b)
+route' encode decode routeUpdate = do
+ rec rUri <- route (T.decodeUtf8 . U.serializeURIRef' <$> urlUpdates)
+ let urlUpdates = attachWith encode (current rUri) routeUpdate
+ return $ decode <$> rUri
+
+
+-------------------------------------------------------------------------------
+-- | Route a single page app according to the part of the path after
+-- pathBase
+partialPathRoute
+ :: forall t m.
+ ( MonadHold t m
+ , PostBuild t m
+ , DomBuilder t m
+ , TriggerEvent t m
+ , PerformEvent t m
+ , HasJSContext m
+ , HasJSContext (Performable m)
+ , MonadJSM m
+ , MonadJSM (Performable m)
+ , MonadFix m)
+ => T.Text -- ^ The path segments not related to SPA routing
+ -- (leading '/' will be added automaticaly)
+ -> Event t T.Text -- ^ Updates to the path segments used for routing
+ -- These values will be appended to the base path
+ -> m (Dynamic t [T.Text]) -- ^ Path segments used for routing
+partialPathRoute pathBase pathUpdates = do
+ route' (flip updateUrl) parseParts pathUpdates
+ where
+
+ rootPathBase :: T.Text
+ rootPathBase =
+ if T.null pathBase then
+ ""
+ else
+ "/" <> cleanT pathBase
+
+ toPath :: T.Text -> BS.ByteString
+ toPath dynpath = T.encodeUtf8 $ rootPathBase <> "/" <> cleanT dynpath
+
+ updateUrl :: T.Text -> URI -> URI
+ updateUrl updateParts u = u & U.pathL .~ toPath updateParts
+
+ parseParts :: URI -> [T.Text]
+ parseParts u =
+ maybe (error $ pfxErr u pathBase)
+ (T.splitOn "/" . T.decodeUtf8 . cleanB) .
+ BS.stripPrefix (T.encodeUtf8 $ cleanT pathBase) $
+ cleanB (u ^. U.pathL)
+
+ cleanT = T.dropWhile (=='/')
+ cleanB = BS.dropWhile (== '/')
+
+
+-------------------------------------------------------------------------------
+uriOrigin :: U.URIRef U.Absolute -> T.Text
+uriOrigin r = T.decodeUtf8 $ U.serializeURIRef' r'
+ where
+ r' = r { U.uriPath = mempty
+ , U.uriQuery = mempty
+ , U.uriFragment = mempty
+ }
+
+
+-------------------------------------------------------------------------------
+getPopState
+ :: forall t m.
+ ( MonadHold t m
+ , TriggerEvent t m
+ , MonadJSM m) => m (Event t URI)
+getPopState = do
+ window <- currentWindowUnchecked
+ wrapDomEventMaybe window (`on` popState) $ do
+ loc <- getLocation window
+ locStr <- getHref loc
+ return . hush $ U.parseURI U.laxURIParserOptions (T.encodeUtf8 locStr)
+
+
+-------------------------------------------------------------------------------
+goForward :: (HasJSContext m, MonadJSM m) => m ()
+goForward = withHistory forward
+
+
+-------------------------------------------------------------------------------
+goBack :: (HasJSContext m, MonadJSM m) => m ()
+goBack = withHistory back
+
+
+-------------------------------------------------------------------------------
+withHistory :: (HasJSContext m, MonadJSM m) => (History -> m a) -> m a
+withHistory act = do
+ w <- currentWindowUnchecked
+ h <- getHistory w
+ act h
+
+
+-------------------------------------------------------------------------------
+-- | (Unsafely) get the 'GHCJS.DOM.Location.Location' of a window
+getLoc :: (HasJSContext m, MonadJSM m) => m Location
+getLoc = do
+ win <- currentWindowUnchecked
+ loc <- getLocation win
+ return loc
+
+
+-------------------------------------------------------------------------------
+-- | (Unsafely) get the URL text of a window
+getUrlText :: (HasJSContext m, MonadJSM m) => m T.Text
+getUrlText = getLoc >>= getHref
+
+
+-------------------------------------------------------------------------------
+type URI = U.URIRef U.Absolute
+
+
+-------------------------------------------------------------------------------
+getURI :: (HasJSContext m, MonadJSM m) => m URI
+getURI = do
+ l <- getUrlText
+ return $ either (error "No parse of window location") id .
+ U.parseURI U.laxURIParserOptions $ T.encodeUtf8 l
+
+
+dispatchEvent' :: JSM ()
+dispatchEvent' = do
+ window <- currentWindowUnchecked
+ obj@(Object o) <- JS.create
+ JS.objSetPropertyByName obj ("cancelable" :: Text) True
+ JS.objSetPropertyByName obj ("bubbles" :: Text) True
+ JS.objSetPropertyByName obj ("view" :: Text) window
+ event <- JS.jsg ("PopStateEvent" :: Text) >>= ghcjsPure . isFunction >>= \case
+ True -> newPopStateEvent ("popstate" :: Text) $ Just $ pFromJSVal o
+ False -> do
+ doc <- currentDocumentUnchecked
+ event <- createEvent doc ("PopStateEvent" :: Text)
+ initEvent event ("popstate" :: Text) True True
+ JS.objSetPropertyByName obj ("view" :: Text) window
+ return $ uncheckedCastTo PopStateEvent event
+
+ dispatchEvent_ window event
+
+
+-------------------------------------------------------------------------------
+hush :: Either e a -> Maybe a
+hush (Right a) = Just a
+hush _ = Nothing
+
+
+-------------------------------------------------------------------------------
+pfxErr :: URI -> T.Text -> String
+pfxErr pn pathBase =
+ T.unpack $ "Encountered path (" <> T.decodeUtf8 (U.serializeURIRef' pn)
+ <> ") without expected prefix (" <> pathBase <> ")"
diff --git a/client/src/Util/Validation.hs b/client/src/Util/Validation.hs
new file mode 100644
index 0000000..50f2468
--- /dev/null
+++ b/client/src/Util/Validation.hs
@@ -0,0 +1,36 @@
+module Util.Validation
+ ( nelError
+ , toMaybe
+ , maybeError
+ , fireValidation
+ ) where
+
+import Control.Monad (join)
+import Data.List.NonEmpty (NonEmpty)
+import qualified Data.List.NonEmpty as NEL
+import Data.Text (Text)
+import Data.Validation (Validation (Failure, Success))
+import qualified Data.Validation as Validation
+import Reflex.Dom (Dynamic, Event, Reflex)
+import qualified Reflex.Dom as R
+
+nelError :: Validation a b -> Validation (NonEmpty a) b
+nelError = Validation.validation (Failure . NEL.fromList . (:[])) Success
+
+toMaybe :: Validation a b -> Maybe b
+toMaybe (Success s) = Just s
+toMaybe (Failure _) = Nothing
+
+maybeError :: Validation a b -> Maybe a
+maybeError (Success _) = Nothing
+maybeError (Failure e) = Just e
+
+fireValidation
+ :: forall t a b c. Reflex t
+ => Dynamic t (Validation a b)
+ -> Event t c
+ -> Event t b
+fireValidation value validate =
+ R.fmapMaybe
+ (Validation.validation (const Nothing) Just)
+ (R.tag (R.current value) validate)
diff --git a/client/src/Util/WaitFor.hs b/client/src/Util/WaitFor.hs
new file mode 100644
index 0000000..fe7b733
--- /dev/null
+++ b/client/src/Util/WaitFor.hs
@@ -0,0 +1,17 @@
+module Util.WaitFor
+ ( waitFor
+ ) where
+
+import Data.Time (NominalDiffTime)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+waitFor
+ :: forall t m a b. MonadWidget t m
+ => (Event t a -> m (Event t b))
+ -> Event t a
+ -> m (Event t b, Event t Bool)
+waitFor op input = do
+ result <- op input >>= R.debounce (0.5 :: NominalDiffTime)
+ let waiting = R.leftmost [ True <$ input , False <$ result ]
+ return (result, waiting)
diff --git a/client/src/View/App.hs b/client/src/View/App.hs
new file mode 100644
index 0000000..71f0234
--- /dev/null
+++ b/client/src/View/App.hs
@@ -0,0 +1,108 @@
+module View.App
+ ( widget
+ ) where
+
+import qualified Data.Text as T
+import Prelude hiding (error, init)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Currency, Init (..), UserId)
+import qualified Common.Msg as Msg
+
+import Model.Route (Route (..))
+import qualified Util.Reflex as ReflexUtil
+import qualified Util.Router as Router
+import qualified View.Category.Category as Category
+import qualified View.Header as Header
+import qualified View.Income.Income as Income
+import qualified View.NotFound as NotFound
+import qualified View.Payment.Payment as Payment
+import qualified View.SignIn as SignIn
+import qualified View.Statistics.Statistics as Statistics
+
+widget :: Maybe Init -> IO ()
+widget init =
+ R.mainWidget $ R.divClass "app" $ do
+
+ route <- getRoute
+
+ rec
+ header <- Header.view $ Header.In
+ { Header._in_init = initState
+ , Header._in_route = route
+ }
+
+ initState <-
+ R.foldDyn
+ const
+ init
+ (R.leftmost $
+ [ initEvent
+ , Nothing <$ (Header._out_signOut header)
+ ])
+
+ initEvent <-
+ (R.dyn . R.ffor initState $ \case
+ Nothing -> do
+ signIn <- SignIn.view
+ return (Just <$> SignIn._out_success signIn)
+
+ Just i -> do
+ signedWidget i route
+ return R.never) >>= ReflexUtil.flatten
+
+ return ()
+
+signedWidget :: forall t m. MonadWidget t m => Init -> Dynamic t Route -> m ()
+signedWidget init route = do
+ R.dyn . R.ffor route $ \case
+ RootRoute ->
+ Payment.view $ Payment.In
+ { Payment._in_currentUser = _init_currentUser init
+ , Payment._in_currency = _init_currency init
+ , Payment._in_users = _init_users init
+ }
+
+ IncomeRoute ->
+ Income.view $ Income.In
+ { Income._in_currentUser = _init_currentUser init
+ , Income._in_currency = _init_currency init
+ , Income._in_users = _init_users init
+ }
+
+ CategoryRoute ->
+ Category.view $ Category.In
+ { Category._in_currentUser = _init_currentUser init
+ , Category._in_currency = _init_currency init
+ , Category._in_users = _init_users init
+ }
+
+ StatisticsRoute ->
+ Statistics.view $ Statistics.In
+ { Statistics._in_currency = _init_currency init
+ }
+
+ NotFoundRoute ->
+ NotFound.view
+
+ return ()
+
+getRoute :: forall t m. MonadWidget t m => m (Dynamic t Route)
+getRoute = do
+ r <- Router.partialPathRoute "" . R.switchPromptlyDyn =<< R.holdDyn R.never R.never
+ return . R.ffor r $ \case
+ [""] ->
+ RootRoute
+
+ ["income"] ->
+ IncomeRoute
+
+ ["category"] ->
+ CategoryRoute
+
+ ["statistics"] ->
+ StatisticsRoute
+
+ _ ->
+ NotFoundRoute
diff --git a/client/src/View/Category/Category.hs b/client/src/View/Category/Category.hs
new file mode 100644
index 0000000..5b41bb6
--- /dev/null
+++ b/client/src/View/Category/Category.hs
@@ -0,0 +1,94 @@
+{-# LANGUAGE ExplicitForAll #-}
+
+module View.Category.Category
+ ( 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 (Category, CategoryPage (..), Currency,
+ User, UserId)
+import qualified Common.Msg as Msg
+
+import qualified Component.Button as Button
+import qualified Component.Modal as Modal
+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 Util.Reflex as ReflexUtil
+import qualified View.Category.Form as Form
+import qualified View.Category.Reducer as Reducer
+import qualified View.Category.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
+ categoryPage <- Reducer.reducer $ Reducer.In
+ { Reducer._in_page = page
+ , Reducer._in_addCategory = R.leftmost [ headerAddCategory, tableAddCategory ]
+ , Reducer._in_editCategory = editCategory
+ , Reducer._in_deleteCategory = deleteCategory
+ }
+
+ let eventFromResult :: forall a. ((Event t (), Table.Out t, Pages.Out t) -> Event t a) -> m (Event t a)
+ eventFromResult op = ReflexUtil.flatten $ (Maybe.fromMaybe R.never . fmap op) <$> result
+
+ page <- eventFromResult $ Pages._out_newPage . (\(_, _, c) -> c)
+ headerAddCategory <- eventFromResult $ (\(a, _, _) -> a)
+ tableAddCategory <- eventFromResult $ Table._out_add . (\(_, b, _) -> b)
+ editCategory <- eventFromResult $ Table._out_edit . (\(_, b, _) -> b)
+ deleteCategory <- eventFromResult $ Table._out_delete . (\(_, b, _) -> b)
+
+ result <- Loadable.viewShowValueWhileLoading categoryPage $
+ \(CategoryPage page categories usedCategories count) -> do
+ header <- headerView
+
+ table <- Table.view $ Table.In
+ { Table._in_currentUser = _in_currentUser input
+ , Table._in_currency = _in_currency input
+ , Table._in_categories = categories
+ , Table._in_usedCategories = usedCategories
+ , 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 = page
+ }
+
+ return (header, table, pages)
+
+ return ()
+
+headerView :: forall t m. MonadWidget t m => m (Event t ())
+headerView =
+ R.divClass "withMargin" $
+ R.divClass "titleButton" $ do
+ R.el "h1" $
+ R.text $
+ Msg.get Msg.Category_Title
+
+ addCategory <- Button._out_clic <$>
+ (Button.view . Button.defaultIn . R.text $
+ Msg.get Msg.Category_Add)
+
+ addCategory <- Modal.view $ Modal.In
+ { Modal._in_show = addCategory
+ , Modal._in_content = Form.view $ Form.In { Form._in_operation = Form.New }
+ }
+
+ return addCategory
diff --git a/client/src/View/Category/Form.hs b/client/src/View/Category/Form.hs
new file mode 100644
index 0000000..d91fc2e
--- /dev/null
+++ b/client/src/View/Category/Form.hs
@@ -0,0 +1,117 @@
+module View.Category.Form
+ ( view
+ , In(..)
+ , Operation(..)
+ ) where
+
+import Control.Monad.IO.Class (liftIO)
+import Data.Aeson (Value)
+import qualified Data.Aeson as Aeson
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Time.Calendar as Calendar
+import qualified Data.Time.Clock as Time
+import Data.Validation (Validation)
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Category (..),
+ CreateCategoryForm (..),
+ EditCategoryForm (..))
+import qualified Common.Msg as Msg
+import qualified Common.Util.Time as TimeUtil
+import qualified Common.Validation.Category as CategoryValidation
+import qualified Component.Input as Input
+import qualified Component.Modal as Modal
+import qualified Component.ModalForm as ModalForm
+import qualified Util.Ajax as Ajax
+
+data In = In
+ { _in_operation :: Operation
+ }
+
+data Operation
+ = New
+ | Clone Category
+ | Edit Category
+
+view :: forall t m a. MonadWidget t m => In -> Modal.Content t m
+view input cancel = do
+
+ rec
+ let reset = R.leftmost
+ [ "" <$ ModalForm._out_cancel modalForm
+ , "" <$ ModalForm._out_validate modalForm
+ , "" <$ cancel
+ ]
+
+ modalForm <- ModalForm.view $ ModalForm.In
+ { ModalForm._in_headerLabel = headerLabel
+ , ModalForm._in_ajax = ajax "/api/category"
+ , ModalForm._in_form = form reset (ModalForm._out_confirm modalForm)
+ }
+
+ return (ModalForm._out_hide modalForm, ModalForm._out_validate modalForm)
+
+ where
+
+ form
+ :: Event t String
+ -> Event t ()
+ -> m (Dynamic t (Validation Text Value))
+ form reset confirm = do
+ name <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Category_Name
+ , Input._in_initialValue = name
+ , Input._in_validation = CategoryValidation.name
+ })
+ (name <$ reset)
+ confirm)
+
+ color <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Category_Color
+ , Input._in_initialValue = color
+ , Input._in_inputType = "color"
+ , Input._in_hasResetButton = False
+ , Input._in_validation = CategoryValidation.color
+ })
+ (color <$ reset)
+ confirm)
+
+ return $ do
+ n <- name
+ c <- color
+ return . V.Success $ mkPayload n c
+
+ op = _in_operation input
+
+ name =
+ case op of
+ New -> ""
+ Clone c -> _category_name c
+ Edit c -> _category_name c
+
+ color =
+ case op of
+ New -> ""
+ Clone c -> _category_color c
+ Edit c -> _category_color c
+
+ ajax =
+ case op of
+ Edit _ -> Ajax.put
+ _ -> Ajax.post
+
+ headerLabel =
+ case op of
+ Edit _ -> Msg.get Msg.Category_Edit
+ _ -> Msg.get Msg.Category_Add
+
+ mkPayload =
+ case op of
+ Edit i -> \a b -> Aeson.toJSON $ EditCategoryForm (_category_id i) a b
+ _ -> \a b -> Aeson.toJSON $ CreateCategoryForm a b
diff --git a/client/src/View/Category/Reducer.hs b/client/src/View/Category/Reducer.hs
new file mode 100644
index 0000000..5ad0ddb
--- /dev/null
+++ b/client/src/View/Category/Reducer.hs
@@ -0,0 +1,59 @@
+module View.Category.Reducer
+ ( perPage
+ , reducer
+ , In(..)
+ ) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (CategoryPage)
+
+import Loadable (Loadable (..))
+import qualified Loadable as Loadable
+import qualified Util.Ajax as AjaxUtil
+import qualified Util.Either as EitherUtil
+
+perPage :: Int
+perPage = 7
+
+data In t a b c = In
+ { _in_page :: Event t Int
+ , _in_addCategory :: Event t a
+ , _in_editCategory :: Event t b
+ , _in_deleteCategory :: Event t c
+ }
+
+reducer :: forall t m a b c. MonadWidget t m => In t a b c -> m (Dynamic t (Loadable CategoryPage))
+reducer input = do
+
+ postBuild <- R.getPostBuild
+
+ currentPage <- R.holdDyn 1 (_in_page input)
+
+ let loadPage =
+ R.leftmost
+ [ 1 <$ postBuild
+ , _in_page input
+ , 1 <$ _in_addCategory input
+ , R.tag (R.current currentPage) (_in_editCategory input)
+ , R.tag (R.current currentPage) (_in_deleteCategory input)
+ ]
+
+ getResult <- AjaxUtil.get $ fmap pageUrl loadPage
+
+ R.holdDyn
+ Loading
+ (R.leftmost
+ [ Loading <$ loadPage
+ , Loadable.fromEither <$> getResult
+ ])
+
+ where
+ pageUrl p =
+ "api/categories?page="
+ <> (T.pack . show $ p)
+ <> "&perPage="
+ <> (T.pack . show $ perPage)
diff --git a/client/src/View/Category/Table.hs b/client/src/View/Category/Table.hs
new file mode 100644
index 0000000..90d013d
--- /dev/null
+++ b/client/src/View/Category/Table.hs
@@ -0,0 +1,93 @@
+module View.Category.Table
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Category (..), CategoryId, Currency,
+ User (..), UserId)
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+import qualified Component.ConfirmDialog as ConfirmDialog
+import qualified Component.Table as Table
+import qualified Component.Tag as Tag
+import qualified Util.Ajax as Ajax
+import qualified Util.Either as EitherUtil
+import qualified View.Category.Form as Form
+
+data In t = In
+ { _in_currentUser :: UserId
+ , _in_currency :: Currency
+ , _in_categories :: [Category]
+ , _in_usedCategories :: [CategoryId]
+ , _in_users :: [User]
+ }
+
+data Out t = Out
+ { _out_add :: Event t ()
+ , _out_edit :: Event t ()
+ , _out_delete :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input = do
+
+ table <- Table.view $ Table.In
+ { Table._in_headerLabel = headerLabel
+ , Table._in_rows = _in_categories input
+ , Table._in_cell = cell (_in_users input) (_in_currency input)
+ , Table._in_cloneModal = \category ->
+ Form.view $ Form.In
+ { Form._in_operation = Form.Clone category
+ }
+ , Table._in_editModal = \category ->
+ Form.view $ Form.In
+ { Form._in_operation = Form.Edit category
+ }
+ , Table._in_deleteModal = \category ->
+ ConfirmDialog.view $ ConfirmDialog.In
+ { ConfirmDialog._in_header = Msg.get Msg.Category_DeleteConfirm
+ , ConfirmDialog._in_confirm = \e -> do
+ res <- Ajax.delete
+ (R.constDyn $ T.concat ["/api/category/", T.pack . show $ _category_id category])
+ e
+ return $ () <$ R.fmapMaybe EitherUtil.eitherToMaybe res
+ }
+ , Table._in_canEdit = const True
+ , Table._in_canDelete = not . flip elem (_in_usedCategories input) . _category_id
+ }
+
+ return $ Out
+ { _out_add = Table._out_add table
+ , _out_edit = Table._out_edit table
+ , _out_delete = Table._out_delete table
+ }
+
+data Header
+ = NameHeader
+ | ColorHeader
+ deriving (Eq, Show, Bounded, Enum)
+
+headerLabel :: Header -> Text
+headerLabel NameHeader = Msg.get Msg.Category_Name
+headerLabel ColorHeader = Msg.get Msg.Category_Color
+
+cell :: forall t m. MonadWidget t m => [User] -> Currency -> Header -> Category -> m ()
+cell users currency header category =
+ case header of
+ NameHeader ->
+ R.text $ _category_name category
+
+ ColorHeader ->
+ Tag.view $ Tag.In
+ { Tag._in_text = _category_name category
+ , Tag._in_color = _category_color category
+ }
diff --git a/client/src/View/Header.hs b/client/src/View/Header.hs
new file mode 100644
index 0000000..ff9f40a
--- /dev/null
+++ b/client/src/View/Header.hs
@@ -0,0 +1,123 @@
+module View.Header
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import Data.Map (Map)
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time (NominalDiffTime)
+import Prelude hiding (error, init)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Init (..), User (..))
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Component.Button as Button
+import qualified Component.Link as Link
+import Model.Route (Route (..))
+import qualified Util.Css as CssUtil
+import qualified Util.Reflex as ReflexUtil
+import qualified View.Icon as Icon
+
+data In t = In
+ { _in_init :: Dynamic t (Maybe Init)
+ , _in_route :: Dynamic t Route
+ }
+
+data Out t = Out
+ { _out_signOut :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => (In t) -> m (Out t)
+view input =
+ R.el "header" $ do
+
+ R.divClass "title" $
+ R.text $ Msg.get Msg.App_Title
+
+ let showLinks = Maybe.isJust <$> _in_init input
+
+ signOut <- R.el "div" $ do
+ ReflexUtil.visibleIfDyn showLinks R.blank (links $ _in_route input)
+ (R.dyn $ nameSignOut <$> _in_init input) >>= ReflexUtil.flatten
+
+ return $ Out
+ { _out_signOut = signOut
+ }
+
+links :: forall t m. MonadWidget t m => Dynamic t Route -> m ()
+links route = do
+ Link.view
+ "/"
+ (R.ffor route (attrs RootRoute))
+ (Msg.get Msg.Payment_Title)
+
+ Link.view
+ "/income"
+ (R.ffor route (attrs IncomeRoute))
+ (Msg.get Msg.Income_Title)
+
+ Link.view
+ "/category"
+ (R.ffor route (attrs CategoryRoute))
+ (Msg.get Msg.Category_Title)
+
+ Link.view
+ "/statistics"
+ (R.ffor route (attrs StatisticsRoute))
+ (Msg.get Msg.Statistics_Title)
+
+ where
+ attrs linkRoute currentRoute =
+ M.singleton "class" $
+ CssUtil.classes
+ [ ("item", True)
+ , ("current", linkRoute == currentRoute)
+ ]
+
+nameSignOut :: forall t m. MonadWidget t m => Maybe Init -> m (Event t ())
+nameSignOut init =
+ case init of
+ Just init -> do
+ rec
+ attr <- R.holdDyn
+ (M.singleton "class" "nameSignOut")
+ (fmap (const $ M.fromList [("style", "visibility: hidden"), ("class", "nameSignOut")]) signOut)
+
+ signOut <- R.elDynAttr "nameSignOut" attr $ do
+ case CM.findUser (_init_currentUser init) (_init_users init) of
+ Just user -> R.divClass "name" $ R.text (_user_name user)
+ Nothing -> R.blank
+ signOutButton
+
+ return signOut
+ _ ->
+ return R.never
+
+signOutButton :: forall t m. MonadWidget t m => m (Event t ())
+signOutButton = do
+ rec
+ signOut <- Button.view $
+ (Button.defaultIn Icon.signOut)
+ { Button._in_class = R.constDyn "signOut item"
+ , Button._in_waiting = waiting
+ }
+ let signOutClic = Button._out_clic signOut
+ waiting = R.leftmost
+ [ fmap (const True) signOutClic
+ , fmap (const False) signOutSuccess
+ ]
+ signOutSuccess <- askSignOut signOutClic >>= R.debounce (0.5 :: NominalDiffTime)
+
+ return . fmap (const ()) . R.ffilter (== True) $ signOutSuccess
+
+ where askSignOut :: forall t m. MonadWidget t m => Event t () -> m (Event t Bool)
+ askSignOut signOut =
+ fmap getResult <$> R.performRequestAsync xhrRequest
+ where xhrRequest = fmap (const $ R.postJson "/api/signOut" ()) signOut
+ getResult = (== 200) . R._xhrResponse_status
diff --git a/client/src/View/Icon.hs b/client/src/View/Icon.hs
new file mode 100644
index 0000000..cc2ef3f
--- /dev/null
+++ b/client/src/View/Icon.hs
@@ -0,0 +1,71 @@
+module View.Icon
+ ( clone
+ , cross
+ , delete
+ , edit
+ , loading
+ , doubleLeft
+ , doubleLeftBar
+ , doubleRight
+ , doubleRightBar
+ , signOut
+ ) where
+
+import Data.Map (Map)
+import qualified Data.Map as M
+import Data.Text (Text)
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+
+clone :: forall t m. MonadWidget t m => m ()
+clone =
+ svgAttr "svg" (M.fromList [ ("width", "24"), ("height", "24"), ("viewBox", "0 0 24 24") ]) $
+ svgAttr "path" (M.fromList [("d", "M15.143 13.244l.837-2.244 2.698 5.641-5.678 2.502.805-2.23s-8.055-3.538-7.708-10.913c2.715 5.938 9.046 7.244 9.046 7.244zm8.857-7.244v18h-18v-6h-6v-18h18v6h6zm-2 2h-12.112c-.562-.578-1.08-1.243-1.521-2h7.633v-4h-14v14h4v-3.124c.6.961 1.287 1.823 2 2.576v6.548h14v-14z")]) $ R.blank
+
+cross :: forall t m. MonadWidget t m => m ()
+cross =
+ svgAttr "svg" (M.fromList [ ("width", "15"), ("height", "15"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M1490 1322q0 40-28 68l-136 136q-28 28-68 28t-68-28l-294-294-294 294q-28 28-68 28t-68-28l-136-136q-28-28-28-68t28-68l294-294-294-294q-28-28-28-68t28-68l136-136q28-28 68-28t68 28l294 294 294-294q28-28 68-28t68 28l136 136q28 28 28 68t-28 68l-294 294 294 294q28 28 28 68z")]) $ R.blank
+
+delete :: forall t m. MonadWidget t m => m ()
+delete =
+ svgAttr "svg" (M.fromList [ ("width", "18"), ("height", "18"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M704 1376v-704q0-14-9-23t-23-9h-64q-14 0-23 9t-9 23v704q0 14 9 23t23 9h64q14 0 23-9t9-23zm256 0v-704q0-14-9-23t-23-9h-64q-14 0-23 9t-9 23v704q0 14 9 23t23 9h64q14 0 23-9t9-23zm256 0v-704q0-14-9-23t-23-9h-64q-14 0-23 9t-9 23v704q0 14 9 23t23 9h64q14 0 23-9t9-23zm-544-992h448l-48-117q-7-9-17-11h-317q-10 2-17 11zm928 32v64q0 14-9 23t-23 9h-96v948q0 83-47 143.5t-113 60.5h-832q-66 0-113-58.5t-47-141.5v-952h-96q-14 0-23-9t-9-23v-64q0-14 9-23t23-9h309l70-167q15-37 54-63t79-26h320q40 0 79 26t54 63l70 167h309q14 0 23 9t9 23z")]) $ R.blank
+
+doubleLeft :: forall t m. MonadWidget t m => m ()
+doubleLeft =
+ svgAttr "svg" (M.fromList [ ("width", "13"), ("height", "13"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M1683 141q19-19 32-13t13 32v1472q0 26-13 32t-32-13l-710-710q-8-9-13-19v710q0 26-13 32t-32-13l-710-710q-19-19-19-45t19-45l710-710q19-19 32-13t13 32v710q5-11 13-19z")]) $ R.blank
+
+doubleLeftBar :: forall t m. MonadWidget t m => m ()
+doubleLeftBar =
+ svgAttr "svg" (M.fromList [ ("width", "13"), ("height", "13"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M1747 141q19-19 32-13t13 32v1472q0 26-13 32t-32-13l-710-710q-9-9-13-19v710q0 26-13 32t-32-13l-710-710q-9-9-13-19v678q0 26-19 45t-45 19h-128q-26 0-45-19t-19-45v-1408q0-26 19-45t45-19h128q26 0 45 19t19 45v678q4-11 13-19l710-710q19-19 32-13t13 32v710q4-11 13-19z")]) $ R.blank
+
+doubleRight :: forall t m. MonadWidget t m => m ()
+doubleRight =
+ svgAttr "svg" (M.fromList [ ("width", "13"), ("height", "13"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M109 1651q-19 19-32 13t-13-32v-1472q0-26 13-32t32 13l710 710q8 8 13 19v-710q0-26 13-32t32 13l710 710q19 19 19 45t-19 45l-710 710q-19 19-32 13t-13-32v-710q-5 10-13 19z")]) $ R.blank
+
+doubleRightBar :: forall t m. MonadWidget t m => m ()
+doubleRightBar =
+ svgAttr "svg" (M.fromList [ ("width", "13"), ("height", "13"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M45 1651q-19 19-32 13t-13-32v-1472q0-26 13-32t32 13l710 710q8 8 13 19v-710q0-26 13-32t32 13l710 710q8 8 13 19v-678q0-26 19-45t45-19h128q26 0 45 19t19 45v1408q0 26-19 45t-45 19h-128q-26 0-45-19t-19-45v-678q-5 10-13 19l-710 710q-19 19-32 13t-13-32v-710q-5 10-13 19z")]) $ R.blank
+
+edit :: forall t m. MonadWidget t m => m ()
+edit =
+ svgAttr "svg" (M.fromList [ ("width", "18"), ("height", "18"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M491 1536l91-91-235-235-91 91v107h128v128h107zm523-928q0-22-22-22-10 0-17 7l-542 542q-7 7-7 17 0 22 22 22 10 0 17-7l542-542q7-7 7-17zm-54-192l416 416-832 832h-416v-416zm683 96q0 53-37 90l-166 166-416-416 166-165q36-38 90-38 53 0 91 38l235 234q37 39 37 91z")]) $ R.blank
+
+loading :: forall t m. MonadWidget t m => m ()
+loading =
+ svgAttr "svg" (M.fromList [ ("width", "24"), ("height", "24"), ("viewBox", "0 0 24 24"), ("class", "loader"), ("fill", "currentColor") ]) $
+ svgAttr "path" (M.fromList [("d", "M13.75 22c0 .966-.783 1.75-1.75 1.75s-1.75-.784-1.75-1.75.783-1.75 1.75-1.75 1.75.784 1.75 1.75zm-1.75-22c-1.104 0-2 .896-2 2s.896 2 2 2 2-.896 2-2-.896-2-2-2zm10 10.75c.689 0 1.249.561 1.249 1.25 0 .69-.56 1.25-1.249 1.25-.69 0-1.249-.559-1.249-1.25 0-.689.559-1.25 1.249-1.25zm-22 1.25c0 1.105.896 2 2 2s2-.895 2-2c0-1.104-.896-2-2-2s-2 .896-2 2zm19-8c.551 0 1 .449 1 1 0 .553-.449 1.002-1 1-.551 0-1-.447-1-.998 0-.553.449-1.002 1-1.002zm0 13.5c.828 0 1.5.672 1.5 1.5s-.672 1.501-1.502 1.5c-.826 0-1.498-.671-1.498-1.499 0-.829.672-1.501 1.5-1.501zm-14-14.5c1.104 0 2 .896 2 2s-.896 2-2.001 2c-1.103 0-1.999-.895-1.999-2s.896-2 2-2zm0 14c1.104 0 2 .896 2 2s-.896 2-2.001 2c-1.103 0-1.999-.895-1.999-2s.896-2 2-2z")]) $ R.blank
+
+signOut :: forall t m. MonadWidget t m => m ()
+signOut =
+ svgAttr "svg" (M.fromList [ ("width", "30"), ("height", "30"), ("viewBox", "0 0 1792 1792") ]) $
+ svgAttr "path" (M.fromList [("d", "M1664 896q0 156-61 298t-164 245-245 164-298 61-298-61-245-164-164-245-61-298q0-182 80.5-343t226.5-270q43-32 95.5-25t83.5 50q32 42 24.5 94.5t-49.5 84.5q-98 74-151.5 181t-53.5 228q0 104 40.5 198.5t109.5 163.5 163.5 109.5 198.5 40.5 198.5-40.5 163.5-109.5 109.5-163.5 40.5-198.5q0-121-53.5-228t-151.5-181q-42-32-49.5-84.5t24.5-94.5q31-43 84-50t95 25q146 109 226.5 270t80.5 343zm-640-768v640q0 52-38 90t-90 38-90-38-38-90v-640q0-52 38-90t90-38 90 38 38 90z")]) $ R.blank
+
+svgAttr :: forall t m a. MonadWidget t m => Text -> Map Text Text -> m a -> m a
+svgAttr elementTag attrs child = R.elWith elementTag (R.ElConfig (Just "http://www.w3.org/2000/svg") attrs) child
diff --git a/client/src/View/Income/Form.hs b/client/src/View/Income/Form.hs
new file mode 100644
index 0000000..59f6a0d
--- /dev/null
+++ b/client/src/View/Income/Form.hs
@@ -0,0 +1,119 @@
+module View.Income.Form
+ ( view
+ , In(..)
+ , Operation(..)
+ ) where
+
+import Control.Monad.IO.Class (liftIO)
+import Data.Aeson (Value)
+import qualified Data.Aeson as Aeson
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Time.Calendar as Calendar
+import qualified Data.Time.Clock as Time
+import Data.Validation (Validation)
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (CreateIncomeForm (..),
+ EditIncomeForm (..), Income (..))
+import qualified Common.Msg as Msg
+import qualified Common.Util.Time as TimeUtil
+import qualified Common.Validation.Income as IncomeValidation
+import qualified Component.Input as Input
+import qualified Component.Modal as Modal
+import qualified Component.ModalForm as ModalForm
+import qualified Util.Ajax as Ajax
+
+data In = In
+ { _in_operation :: Operation
+ }
+
+data Operation
+ = New
+ | Clone Income
+ | Edit Income
+
+view :: forall t m a. MonadWidget t m => In -> Modal.Content t m
+view input cancel = do
+
+ rec
+ let reset = R.leftmost
+ [ "" <$ ModalForm._out_cancel modalForm
+ , "" <$ ModalForm._out_validate modalForm
+ , "" <$ cancel
+ ]
+
+ modalForm <- ModalForm.view $ ModalForm.In
+ { ModalForm._in_headerLabel = headerLabel
+ , ModalForm._in_ajax = ajax "/api/income"
+ , ModalForm._in_form = form reset (ModalForm._out_confirm modalForm)
+ }
+
+ return (ModalForm._out_hide modalForm, ModalForm._out_validate modalForm)
+
+ where
+
+ form
+ :: Event t String
+ -> Event t ()
+ -> m (Dynamic t (Validation Text Value))
+ form reset confirm = do
+ amount <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Income_Amount
+ , Input._in_initialValue = amount
+ , Input._in_validation = IncomeValidation.amount
+ })
+ (amount <$ reset)
+ confirm)
+
+ currentDay <- liftIO $ Time.getCurrentTime >>= TimeUtil.timeToDay
+
+ let initialDate = T.pack . Calendar.showGregorian $ date currentDay
+
+ date <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Income_Date
+ , Input._in_initialValue = initialDate
+ , Input._in_inputType = "date"
+ , Input._in_hasResetButton = False
+ , Input._in_validation = IncomeValidation.date
+ })
+ (initialDate <$ reset)
+ confirm)
+
+ return $ do
+ a <- amount
+ d <- date
+ return . V.Success $ mkPayload a d
+
+ op = _in_operation input
+
+ amount =
+ case op of
+ New -> ""
+ Clone i -> T.pack . show . _income_amount $ i
+ Edit i -> T.pack . show . _income_amount $ i
+
+ date currentDay =
+ case op of
+ Edit i -> _income_date i
+ _ -> currentDay
+
+ ajax =
+ case op of
+ Edit _ -> Ajax.put
+ _ -> Ajax.post
+
+ headerLabel =
+ case op of
+ Edit _ -> Msg.get Msg.Income_Edit
+ _ -> Msg.get Msg.Income_AddLong
+
+ mkPayload =
+ case op of
+ Edit i -> \a b -> Aeson.toJSON $ EditIncomeForm (_income_id i) a b
+ _ -> \a b -> Aeson.toJSON $ CreateIncomeForm a b
diff --git a/client/src/View/Income/Header.hs b/client/src/View/Income/Header.hs
new file mode 100644
index 0000000..a26e16a
--- /dev/null
+++ b/client/src/View/Income/Header.hs
@@ -0,0 +1,77 @@
+module View.Income.Header
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import Control.Monad.IO.Class (liftIO)
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import qualified Data.Text as T
+import qualified Data.Time.Clock as Clock
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Currency, Income (..),
+ IncomeHeader (..), User (..))
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+import qualified Component.Button as Button
+import qualified Component.Modal as Modal
+import qualified View.Income.Form as Form
+
+data In t = In
+ { _in_users :: [User]
+ , _in_header :: IncomeHeader
+ , _in_currency :: Currency
+ }
+
+data Out t = Out
+ { _out_add :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input =
+ R.divClass "withMargin" $ do
+
+ currentTime <- liftIO Clock.getCurrentTime
+
+ case _incomeHeader_since $ _in_header input of
+ Nothing ->
+ R.blank
+
+ Just since ->
+ R.el "div" $ do
+
+ R.el "h1" $ do
+ R.text $ Msg.get (Msg.Income_CumulativeSince (Format.longDay since))
+
+ R.el "ul" $
+ flip mapM_ (M.toList . _incomeHeader_byUser $ _in_header input) $ \(userId, amount) ->
+ R.el "li" $
+ R.text $
+ T.intercalate " "
+ [ Maybe.fromMaybe "" . fmap _user_name $ CM.findUser userId (_in_users input)
+ , "−"
+ , Format.price (_in_currency input) amount
+ ]
+
+ R.divClass "titleButton" $ do
+ R.el "h1" $
+ R.text $
+ Msg.get Msg.Income_MonthlyNet
+
+ addIncome <- Button._out_clic <$>
+ (Button.view . Button.defaultIn . R.text $
+ Msg.get Msg.Income_AddLong)
+
+ addIncome <- Modal.view $ Modal.In
+ { Modal._in_show = addIncome
+ , Modal._in_content = Form.view $ Form.In { Form._in_operation = Form.New }
+ }
+
+ return $ Out
+ { _out_add = addIncome
+ }
diff --git a/client/src/View/Income/Income.hs b/client/src/View/Income/Income.hs
new file mode 100644
index 0000000..7be8091
--- /dev/null
+++ b/client/src/View/Income/Income.hs
@@ -0,0 +1,75 @@
+{-# 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 (..), IncomePage (..),
+ 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 Util.Reflex as ReflexUtil
+import qualified View.Income.Header as Header
+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
+ incomePage <- Reducer.reducer $ Reducer.In
+ { Reducer._in_page = page
+ , Reducer._in_addIncome = R.leftmost [headerAddIncome, tableAddIncome]
+ , Reducer._in_editIncome = editIncome
+ , Reducer._in_deleteIncome = deleteIncome
+ }
+
+ let eventFromResult :: forall a. ((Header.Out t, 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
+
+ page <- eventFromResult $ Pages._out_newPage . (\(_, _, c) -> c)
+ headerAddIncome <- eventFromResult $ Header._out_add . (\(a, _, _) -> a)
+ tableAddIncome <- eventFromResult $ Table._out_add . (\(_, b, _) -> b)
+ editIncome <- eventFromResult $ Table._out_edit . (\(_, b, _) -> b)
+ deleteIncome <- eventFromResult $ Table._out_delete . (\(_, b, _) -> b)
+
+ result <- Loadable.viewShowValueWhileLoading incomePage $
+ \(IncomePage page header incomes count) -> do
+ header <- Header.view $ Header.In
+ { Header._in_users = _in_users input
+ , Header._in_header = header
+ , Header._in_currency = _in_currency input
+ }
+
+ 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 = page
+ }
+
+ return (header, table, pages)
+
+ return ()
diff --git a/client/src/View/Income/Reducer.hs b/client/src/View/Income/Reducer.hs
new file mode 100644
index 0000000..ea9f664
--- /dev/null
+++ b/client/src/View/Income/Reducer.hs
@@ -0,0 +1,59 @@
+module View.Income.Reducer
+ ( perPage
+ , reducer
+ , In(..)
+ ) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (IncomePage)
+
+import Loadable (Loadable (..))
+import qualified Loadable as Loadable
+import qualified Util.Ajax as AjaxUtil
+import qualified Util.Either as EitherUtil
+
+perPage :: Int
+perPage = 7
+
+data In t a b c = In
+ { _in_page :: Event t Int
+ , _in_addIncome :: Event t a
+ , _in_editIncome :: Event t b
+ , _in_deleteIncome :: Event t c
+ }
+
+reducer :: forall t m a b c. MonadWidget t m => In t a b c -> m (Dynamic t (Loadable IncomePage))
+reducer input = do
+
+ postBuild <- R.getPostBuild
+
+ currentPage <- R.holdDyn 1 (_in_page input)
+
+ let loadPage =
+ R.leftmost
+ [ 1 <$ postBuild
+ , _in_page input
+ , 1 <$ _in_addIncome input
+ , R.tag (R.current currentPage) (_in_editIncome input)
+ , R.tag (R.current currentPage) (_in_deleteIncome input)
+ ]
+
+ getResult <- AjaxUtil.get $ fmap pageUrl loadPage
+
+ R.holdDyn
+ Loading
+ (R.leftmost
+ [ Loading <$ loadPage
+ , Loadable.fromEither <$> getResult
+ ])
+
+ where
+ pageUrl p =
+ "api/incomes?page="
+ <> (T.pack . show $ p)
+ <> "&perPage="
+ <> (T.pack . show $ perPage)
diff --git a/client/src/View/Income/Table.hs b/client/src/View/Income/Table.hs
new file mode 100644
index 0000000..7b7940d
--- /dev/null
+++ b/client/src/View/Income/Table.hs
@@ -0,0 +1,93 @@
+module View.Income.Table
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Currency, Income (..), User (..),
+ UserId)
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+import qualified Component.ConfirmDialog as ConfirmDialog
+import qualified Component.Table as Table
+import qualified Util.Ajax as Ajax
+import qualified Util.Either as EitherUtil
+import qualified View.Income.Form as Form
+
+data In t = In
+ { _in_currentUser :: UserId
+ , _in_currency :: Currency
+ , _in_incomes :: [Income]
+ , _in_users :: [User]
+ }
+
+data Out t = Out
+ { _out_add :: Event t ()
+ , _out_edit :: Event t ()
+ , _out_delete :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input = do
+
+ table <- Table.view $ Table.In
+ { Table._in_headerLabel = headerLabel
+ , Table._in_rows = _in_incomes input
+ , Table._in_cell = cell (_in_users input) (_in_currency input)
+ , Table._in_cloneModal = \income ->
+ Form.view $ Form.In
+ { Form._in_operation = Form.Clone income
+ }
+ , Table._in_editModal = \income ->
+ Form.view $ Form.In
+ { Form._in_operation = Form.Edit income
+ }
+ , Table._in_deleteModal = \income ->
+ ConfirmDialog.view $ ConfirmDialog.In
+ { ConfirmDialog._in_header = Msg.get Msg.Income_DeleteConfirm
+ , ConfirmDialog._in_confirm = \e -> do
+ res <- Ajax.delete
+ (R.constDyn $ T.concat ["/api/income/", T.pack . show $ _income_id income])
+ e
+ return $ () <$ R.fmapMaybe EitherUtil.eitherToMaybe res
+ }
+ , Table._in_canEdit = (== (_in_currentUser input)) . _income_userId
+ , Table._in_canDelete = (== (_in_currentUser input)) . _income_userId
+ }
+
+ return $ Out
+ { _out_add = Table._out_add table
+ , _out_edit = Table._out_edit table
+ , _out_delete = Table._out_delete table
+ }
+
+data Header
+ = UserHeader
+ | AmountHeader
+ | DateHeader
+ deriving (Eq, Show, Bounded, Enum)
+
+headerLabel :: Header -> Text
+headerLabel UserHeader = Msg.get Msg.Income_Name
+headerLabel DateHeader = Msg.get Msg.Income_Date
+headerLabel AmountHeader = Msg.get Msg.Income_Amount
+
+cell :: forall t m. MonadWidget t m => [User] -> Currency -> Header -> Income -> m ()
+cell users currency header income =
+ case header of
+ UserHeader ->
+ R.text . Maybe.fromMaybe "" . fmap _user_name $ CM.findUser (_income_userId income) users
+
+ DateHeader ->
+ R.text . Format.longDay . _income_date $ income
+
+ AmountHeader ->
+ R.text . Format.price currency . _income_amount $ income
diff --git a/client/src/View/NotFound.hs b/client/src/View/NotFound.hs
new file mode 100644
index 0000000..1597849
--- /dev/null
+++ b/client/src/View/NotFound.hs
@@ -0,0 +1,20 @@
+module View.NotFound
+ ( view
+ ) where
+
+import qualified Data.Map as M
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import qualified Common.Msg as Msg
+import qualified Component.Link as Link
+
+view :: forall t m. MonadWidget t m => m ()
+view =
+ R.divClass "notfound" $ do
+ R.text (Msg.get Msg.NotFound_Message)
+
+ Link.view
+ "/"
+ (R.constDyn $ M.singleton "class" "link")
+ (Msg.get Msg.NotFound_LinkMessage)
diff --git a/client/src/View/Payment/Form.hs b/client/src/View/Payment/Form.hs
new file mode 100644
index 0000000..6c31fad
--- /dev/null
+++ b/client/src/View/Payment/Form.hs
@@ -0,0 +1,199 @@
+module View.Payment.Form
+ ( view
+ , In(..)
+ , Operation(..)
+ ) where
+
+import Control.Monad (join)
+import Control.Monad.IO.Class (liftIO)
+import Data.Aeson (Value)
+import qualified Data.Aeson as Aeson
+import qualified Data.List as L
+import Data.List.NonEmpty (NonEmpty)
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time (NominalDiffTime)
+import Data.Time.Calendar (Day)
+import qualified Data.Time.Calendar as Calendar
+import qualified Data.Time.Clock as Clock
+import Data.Validation (Validation)
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+import qualified Text.Read as T
+
+import Common.Model (Category (..), CategoryId,
+ CreatePaymentForm (..),
+ EditPaymentForm (..),
+ Frequency (..), Payment (..))
+import qualified Common.Msg as Msg
+import qualified Common.Util.Time as TimeUtil
+import qualified Common.Validation.Payment as PaymentValidation
+
+import qualified Component.Input as Input
+import qualified Component.Modal as Modal
+import qualified Component.ModalForm as ModalForm
+import qualified Component.Select as Select
+import qualified Util.Ajax as Ajax
+import qualified Util.Either as EitherUtil
+import qualified Util.Validation as ValidationUtil
+
+data In t = In
+ { _in_categories :: [Category]
+ , _in_operation :: Operation t
+ , _in_frequency :: Frequency
+ }
+
+data Operation t
+ = New
+ | Clone Payment
+ | Edit Payment
+
+view :: forall t m a. MonadWidget t m => In t -> Modal.Content t m
+view input cancel = do
+ rec
+ let reset = R.leftmost
+ [ "" <$ ModalForm._out_cancel modalForm
+ , "" <$ ModalForm._out_validate modalForm
+ , "" <$ cancel
+ ]
+
+ modalForm <- ModalForm.view $ ModalForm.In
+ { ModalForm._in_headerLabel = headerLabel
+ , ModalForm._in_ajax = ajax "/api/payment"
+ , ModalForm._in_form = form reset (ModalForm._out_confirm modalForm)
+ }
+
+ return (ModalForm._out_hide modalForm, ModalForm._out_validate modalForm)
+
+ where
+
+ form
+ :: Event t String
+ -> Event t ()
+ -> m (Dynamic t (Validation (NonEmpty Text) Value))
+ form reset confirm = do
+ name <- Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Payment_Name
+ , Input._in_initialValue = name
+ , Input._in_validation = PaymentValidation.name
+ })
+ (name <$ reset)
+ confirm
+
+ cost <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Payment_Cost
+ , Input._in_initialValue = cost
+ , Input._in_validation = PaymentValidation.cost
+ })
+ (cost <$ reset)
+ confirm)
+
+ currentDate <- date
+
+ date <-
+ case frequency of
+ Punctual -> do
+ Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.Payment_Date
+ , Input._in_initialValue = currentDate
+ , Input._in_inputType = "date"
+ , Input._in_hasResetButton = False
+ , Input._in_validation = PaymentValidation.date
+ })
+ (currentDate <$ reset)
+ confirm)
+ Monthly ->
+ return . R.constDyn $ currentDate
+
+ setCategory <-
+ R.debounce (1 :: NominalDiffTime) (R.updated $ Input._out_raw name)
+ >>= (return . R.ffilter (\name -> T.length name >= 3))
+ >>= (Ajax.get . (fmap ("/api/payment/category?name=" <>)))
+ >>= (return . R.mapMaybe (join . EitherUtil.eitherToMaybe))
+
+ category <- Select._out_value <$> (Select.view $ Select.In
+ { Select._in_label = Msg.get Msg.Payment_Category
+ , Select._in_initialValue = category
+ , Select._in_value = setCategory
+ , Select._in_values = R.constDyn categories
+ , Select._in_reset = category <$ reset
+ , Select._in_isValid = PaymentValidation.category (map _category_id $ _in_categories input)
+ , Select._in_validate = confirm
+ })
+
+ return $ do
+ n <- Input._out_value name
+ c <- cost
+ d <- date
+ cat <- category
+ return (mkPayload
+ <$> ValidationUtil.nelError n
+ <*> V.Success c
+ <*> V.Success d
+ <*> ValidationUtil.nelError cat
+ <*> V.Success frequency)
+
+ frequencies =
+ M.fromList
+ [ (Punctual, Msg.get Msg.Payment_PunctualMale)
+ , (Monthly, Msg.get Msg.Payment_MonthlyMale)
+ ]
+
+ categories = M.fromList . flip map (_in_categories input) $ \c ->
+ (_category_id c, _category_name c)
+
+ category =
+ case op of
+ New -> -1
+ Clone p -> _payment_category p
+ Edit p -> _payment_category p
+
+ op = _in_operation input
+
+ name =
+ case op of
+ New -> ""
+ Clone p -> _payment_name p
+ Edit p -> _payment_name p
+
+ cost =
+ case op of
+ New -> ""
+ Clone p -> T.pack . show . _payment_cost $ p
+ Edit p -> T.pack . show . _payment_cost $ p
+
+ date = do
+ currentDay <- liftIO $ Clock.getCurrentTime >>= TimeUtil.timeToDay
+ return . T.pack . Calendar.showGregorian $
+ case op of
+ New -> currentDay
+ Clone p -> currentDay
+ Edit p -> _payment_date p
+
+ frequency =
+ case op of
+ New -> _in_frequency input
+ Clone p -> _payment_frequency p
+ Edit p -> _payment_frequency p
+
+ headerLabel =
+ case op of
+ New -> Msg.get Msg.Payment_Add
+ Clone _ -> Msg.get Msg.Payment_CloneLong
+ Edit _ -> Msg.get Msg.Payment_EditLong
+
+ ajax =
+ case op of
+ Edit _ -> Ajax.put
+ _ -> Ajax.post
+
+ mkPayload =
+ case op of
+ Edit p -> \a b c d e -> Aeson.toJSON $ EditPaymentForm (_payment_id p) a b c d e
+ _ -> \a b c d e -> Aeson.toJSON $ CreatePaymentForm a b c d e
diff --git a/client/src/View/Payment/HeaderForm.hs b/client/src/View/Payment/HeaderForm.hs
new file mode 100644
index 0000000..1915841
--- /dev/null
+++ b/client/src/View/Payment/HeaderForm.hs
@@ -0,0 +1,85 @@
+module View.Payment.HeaderForm
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.Map as M
+import Data.Text (Text)
+import qualified Data.Validation as V
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Category, Currency, Frequency (..),
+ Income (..), Payment (..), User (..))
+import qualified Common.Msg as Msg
+
+import qualified Component.Button as Button
+import qualified Component.Input as Input
+import qualified Component.Modal as Modal
+import qualified Component.Select as Select
+import qualified Util.Reflex as ReflexUtil
+import qualified View.Payment.Form as Form
+
+data In t = In
+ { _in_reset :: Event t ()
+ , _in_categories :: [Category]
+ }
+
+data Out t = Out
+ { _out_search :: Event t Text
+ , _out_frequency :: Event t Frequency
+ , _out_addPayment :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input =
+ R.divClass "g-PaymentHeaderForm" $ do
+
+ (searchName, frequency) <- R.el "div" $ do
+
+ searchName <- Input._out_raw <$> (Input.view
+ ( Input.defaultIn { Input._in_label = Msg.get Msg.Search_Name })
+ ("" <$ _in_reset input)
+ R.never)
+
+ let frequencies = M.fromList
+ [ (Punctual, Msg.get Msg.Payment_PunctualMale)
+ , (Monthly, Msg.get Msg.Payment_MonthlyMale)
+ ]
+
+ frequency <- Select._out_raw <$> (Select.view $ Select.In
+ { Select._in_label = ""
+ , Select._in_initialValue = Punctual
+ , Select._in_value = R.never
+ , Select._in_values = R.constDyn frequencies
+ , Select._in_reset = R.never
+ , Select._in_isValid = V.Success
+ , Select._in_validate = R.never
+ })
+
+ return (searchName, frequency)
+
+ addPaymentButton <- Button._out_clic <$>
+ (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.Payment_Add))
+ { Button._in_class = R.constDyn "addPayment"
+ })
+
+ addPayment <-
+ (R.dyn . R.ffor frequency $ \frequency ->
+ Modal.view $ Modal.In
+ { Modal._in_show = addPaymentButton
+ , Modal._in_content =
+ Form.view $ Form.In
+ { Form._in_categories = _in_categories input
+ , Form._in_operation = Form.New
+ , Form._in_frequency = frequency
+ }
+ }) >>= ReflexUtil.flatten
+
+ return $ Out
+ { _out_search = R.updated searchName
+ , _out_frequency = R.updated frequency
+ , _out_addPayment = addPayment
+ }
diff --git a/client/src/View/Payment/HeaderInfos.hs b/client/src/View/Payment/HeaderInfos.hs
new file mode 100644
index 0000000..f84ee1f
--- /dev/null
+++ b/client/src/View/Payment/HeaderInfos.hs
@@ -0,0 +1,94 @@
+module View.Payment.HeaderInfos
+ ( view
+ , In(..)
+ ) where
+
+import Control.Monad.IO.Class (liftIO)
+import qualified Data.List as L hiding (groupBy)
+import Data.Map (Map)
+import qualified Data.Map as M
+import Data.Maybe (fromMaybe)
+import Data.Text (Text)
+import qualified Data.Text as T
+import qualified Data.Time as Time
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Currency, ExceedingPayer (..),
+ Payment (..), PaymentHeader (..),
+ User (..), UserId)
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+data In t = In
+ { _in_users :: [User]
+ , _in_currency :: Currency
+ , _in_header :: PaymentHeader
+ , _in_paymentCount :: Int
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m ()
+view input =
+ R.divClass "g-PaymentHeaderInfos" $ do
+ exceedingPayers
+ (_in_users input)
+ (_in_currency input)
+ (_paymentHeader_exceedingPayers header)
+
+ infos
+ (_in_users input)
+ (_in_currency input)
+ (_paymentHeader_repartition header)
+ (_in_paymentCount input)
+
+ where
+ header = _in_header input
+
+exceedingPayers
+ :: forall t m. MonadWidget t m
+ => [User]
+ -> Currency
+ -> [ExceedingPayer]
+ -> m ()
+exceedingPayers users currency payers =
+ R.divClass "g-PaymentHeaderInfos__ExceedingPayers" $
+ flip mapM_ payers $ \payer ->
+ R.elClass "span" "exceedingPayer" $ do
+ R.elClass "span" "userName" $
+ R.text $
+ fromMaybe "" . fmap _user_name $ CM.findUser (_exceedingPayer_userId payer) users
+ R.elClass "span" "amount" $ do
+ R.text "+ "
+ R.text . Format.price currency $ _exceedingPayer_amount payer
+
+infos
+ :: forall t m. MonadWidget t m
+ => [User]
+ -> Currency
+ -> Map UserId Int
+ -> Int
+ -> m ()
+infos users currency repartition paymentCount =
+ R.divClass "g-PaymentHeaderInfos__Repartition" $ do
+
+ R.elClass "span" "total" $ do
+ R.text $
+ Msg.get $ Msg.Payment_Worth
+ (T.intercalate " "
+ [ (Format.number paymentCount)
+ , if paymentCount > 1
+ then Msg.get Msg.Payment_Many
+ else Msg.get Msg.Payment_One
+ ])
+ (Format.price currency (M.foldl (+) 0 repartition))
+
+ R.elClass "span" "partition" . R.text $
+ let totalByUser =
+ L.sortBy (\(_, t1) (_, t2) -> compare t2 t1)
+ . M.toList
+ $ repartition
+ in T.intercalate ", " . flip map totalByUser $ \(userId, userTotal) ->
+ Msg.get $ Msg.Payment_By
+ (fromMaybe "" . fmap _user_name $ CM.findUser userId users)
+ (Format.price currency userTotal)
diff --git a/client/src/View/Payment/Payment.hs b/client/src/View/Payment/Payment.hs
new file mode 100644
index 0000000..26444d7
--- /dev/null
+++ b/client/src/View/Payment/Payment.hs
@@ -0,0 +1,101 @@
+module View.Payment.Payment
+ ( view
+ , In(..)
+ ) where
+
+import Control.Monad.IO.Class (liftIO)
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time.Clock (NominalDiffTime)
+import Prelude hiding (init)
+import Reflex.Dom (Dynamic, Event, MonadWidget, Reflex)
+import qualified Reflex.Dom as R
+
+import Common.Model (Currency, Frequency, Income (..),
+ Payment (..), PaymentId,
+ PaymentPage (..), User, UserId)
+import qualified Common.Util.Text as T
+
+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.Payment.HeaderForm as HeaderForm
+import qualified View.Payment.HeaderInfos as HeaderInfos
+import qualified View.Payment.Reducer as Reducer
+import qualified View.Payment.Table as Table
+
+data In t = In
+ { _in_currentUser :: UserId
+ , _in_users :: [User]
+ , _in_currency :: Currency
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m ()
+view input = do
+
+ categories <- AjaxUtil.getNow "api/allCategories"
+
+ R.dyn . R.ffor categories . Loadable.viewHideValueWhileLoading $ \categories -> do
+
+ rec
+ paymentPage <- Reducer.reducer $ Reducer.In
+ { Reducer._in_page = page
+ , Reducer._in_search = HeaderForm._out_search form
+ , Reducer._in_frequency = HeaderForm._out_frequency form
+ , Reducer._in_addPayment = addPayment
+ , Reducer._in_editPayment = editPayment
+ , Reducer._in_deletePayment = deletePayment
+ }
+
+ 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
+
+ let addPayment =
+ R.leftmost
+ [ tableAddPayment
+ , HeaderForm._out_addPayment form
+ ]
+
+ page <- eventFromResult $ Pages._out_newPage . snd
+ tableAddPayment <- eventFromResult $ Table._out_add . fst
+ editPayment <- eventFromResult $ Table._out_edit . fst
+ deletePayment <- eventFromResult $ Table._out_delete . fst
+
+ form <- HeaderForm.view $ HeaderForm.In
+ { HeaderForm._in_reset = () <$ addPayment
+ , HeaderForm._in_categories = categories
+ }
+
+ result <- Loadable.viewShowValueWhileLoading paymentPage $
+ \(PaymentPage page frequency header payments count) -> do
+
+ HeaderInfos.view $ HeaderInfos.In
+ { HeaderInfos._in_users = _in_users input
+ , HeaderInfos._in_currency = _in_currency input
+ , HeaderInfos._in_header = header
+ , HeaderInfos._in_paymentCount = count
+ }
+
+ table <- Table.view $ Table.In
+ { Table._in_users = _in_users input
+ , Table._in_currentUser = _in_currentUser input
+ , Table._in_categories = categories
+ , Table._in_currency = _in_currency input
+ , Table._in_payments = payments
+ , Table._in_frequency = frequency
+ }
+
+ pages <- Pages.view $ Pages.In
+ { Pages._in_total = R.constDyn count
+ , Pages._in_perPage = Reducer.perPage
+ , Pages._in_page = page
+ }
+
+ return (table, pages)
+
+ return ()
+
+ return ()
diff --git a/client/src/View/Payment/Reducer.hs b/client/src/View/Payment/Reducer.hs
new file mode 100644
index 0000000..3fe59b2
--- /dev/null
+++ b/client/src/View/Payment/Reducer.hs
@@ -0,0 +1,110 @@
+module View.Payment.Reducer
+ ( perPage
+ , reducer
+ , In(..)
+ , Params(..)
+ ) where
+
+import Data.Text (Text)
+import qualified Data.Text as T
+import Data.Time (NominalDiffTime)
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Frequency (..), PaymentPage)
+
+import Loadable (Loadable (..))
+import qualified Loadable as Loadable
+import qualified Util.Ajax as AjaxUtil
+import qualified Util.Either as EitherUtil
+
+perPage :: Int
+perPage = 7
+
+data In t a b c = In
+ { _in_page :: Event t Int
+ , _in_search :: Event t Text
+ , _in_frequency :: Event t Frequency
+ , _in_addPayment :: Event t a
+ , _in_editPayment :: Event t b
+ , _in_deletePayment :: Event t c
+ }
+
+data Params = Params
+ { _params_page :: Int
+ , _params_search :: Text
+ , _params_frequency :: Frequency
+ } deriving (Show)
+
+initParams = Params 1 "" Punctual
+
+data Msg
+ = Page Int
+ | Search Text
+ | Frequency Common.Model.Frequency
+ | ResetSearch
+ deriving Show
+
+reducer :: forall t m a b c. MonadWidget t m => In t a b c -> m (Dynamic t (Loadable PaymentPage))
+reducer input = do
+
+ postBuild <- R.getPostBuild
+
+ debouncedSearch <- R.debounce (1 :: NominalDiffTime) (_in_search input)
+
+ params <- R.foldDynMaybe
+ (\msg params -> case msg of
+ Page page ->
+ Just $ params { _params_page = page }
+
+ Search "" ->
+ if _params_search params == "" then
+ Nothing
+
+ else
+ Just $ initParams { _params_frequency = _params_frequency params }
+
+ Search search ->
+ Just $ params { _params_search = search, _params_page = _params_page initParams }
+
+ Frequency frequency ->
+ Just $ params { _params_frequency = frequency, _params_page = _params_page initParams }
+
+ ResetSearch ->
+ Just $ initParams { _params_frequency = _params_frequency params }
+ )
+ initParams
+ (R.leftmost
+ [ Page <$> _in_page input
+ , Search <$> debouncedSearch
+ , Frequency <$> _in_frequency input
+ , ResetSearch <$ _in_addPayment input
+ ])
+
+ let paramsEvent =
+ R.leftmost
+ [ initParams <$ postBuild
+ , R.updated params
+ , R.tag (R.current params) (_in_editPayment input)
+ , R.tag (R.current params) (_in_deletePayment input)
+ ]
+
+ getResult <- AjaxUtil.get (pageUrl <$> paramsEvent)
+
+ R.holdDyn
+ Loading
+ (R.leftmost
+ [ Loading <$ paramsEvent
+ , Loadable.fromEither <$> getResult
+ ])
+
+ where
+ pageUrl (Params page search frequency) =
+ "api/payments?page="
+ <> (T.pack . show $ page)
+ <> "&perPage="
+ <> (T.pack . show $ perPage)
+ <> "&search="
+ <> search
+ <> "&frequency="
+ <> (T.pack $ show frequency)
diff --git a/client/src/View/Payment/Table.hs b/client/src/View/Payment/Table.hs
new file mode 100644
index 0000000..bfa0fb9
--- /dev/null
+++ b/client/src/View/Payment/Table.hs
@@ -0,0 +1,143 @@
+module View.Payment.Table
+ ( view
+ , In(..)
+ , Out(..)
+ ) where
+
+import qualified Data.List as L
+import qualified Data.Map as M
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Text as T
+import Reflex.Dom (Dynamic, Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Category (..), Currency,
+ Frequency (..), Payment (..),
+ User (..), UserId)
+import qualified Common.Model as CM
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+import qualified Component.ConfirmDialog as ConfirmDialog
+import qualified Component.Table as Table
+import qualified Component.Tag as Tag
+import qualified Util.Ajax as Ajax
+import qualified Util.Either as EitherUtil
+import qualified View.Payment.Form as Form
+
+data In t = In
+ { _in_users :: [User]
+ , _in_currentUser :: UserId
+ , _in_categories :: [Category]
+ , _in_currency :: Currency
+ , _in_payments :: [Payment]
+ , _in_frequency :: Frequency
+ }
+
+data Out t = Out
+ { _out_add :: Event t ()
+ , _out_edit :: Event t ()
+ , _out_delete :: Event t ()
+ }
+
+view :: forall t m. MonadWidget t m => In t -> m (Out t)
+view input = do
+
+ table <- Table.view $ Table.In
+ { Table._in_headerLabel = headerLabel (_in_frequency input)
+ , Table._in_rows = _in_payments input
+ , Table._in_cell =
+ cell
+ (_in_users input)
+ (_in_categories input)
+ (_in_frequency input)
+ (_in_currency input)
+ , Table._in_cloneModal = \payment ->
+ Form.view $ Form.In
+ { Form._in_categories = _in_categories input
+ , Form._in_operation = Form.Clone payment
+ , Form._in_frequency = _in_frequency input
+ }
+ , Table._in_editModal = \payment ->
+ Form.view $ Form.In
+ { Form._in_categories = _in_categories input
+ , Form._in_operation = Form.Edit payment
+ , Form._in_frequency = _in_frequency input
+ }
+ , Table._in_deleteModal = \payment ->
+ ConfirmDialog.view $ ConfirmDialog.In
+ { ConfirmDialog._in_header = Msg.get Msg.Payment_DeleteConfirm
+ , ConfirmDialog._in_confirm = \e -> do
+ res <- Ajax.delete
+ (R.constDyn $ T.concat ["/api/payment/", T.pack . show $ _payment_id payment])
+ e
+ return $ () <$ R.fmapMaybe EitherUtil.eitherToMaybe res
+ }
+ , Table._in_canEdit = (== (_in_currentUser input)) . _payment_user
+ , Table._in_canDelete = (== (_in_currentUser input)) . _payment_user
+ }
+
+ return $ Out
+ { _out_add = Table._out_add table
+ , _out_edit = Table._out_edit table
+ , _out_delete = Table._out_delete table
+ }
+
+data Header
+ = NameHeader
+ | CostHeader
+ | UserHeader
+ | CategoryHeader
+ | DateHeader
+ deriving (Eq, Show, Bounded, Enum)
+
+headerLabel :: Frequency -> Header -> Text
+headerLabel _ NameHeader = Msg.get Msg.Payment_Name
+headerLabel _ CostHeader = Msg.get Msg.Payment_Cost
+headerLabel _ UserHeader = Msg.get Msg.Payment_User
+headerLabel _ CategoryHeader = Msg.get Msg.Payment_Category
+headerLabel Punctual DateHeader = Msg.get Msg.Payment_Date
+headerLabel Monthly DateHeader = ""
+
+cell
+ :: forall t m. MonadWidget t m
+ => [User]
+ -> [Category]
+ -> Frequency
+ -> Currency
+ -> Header
+ -> Payment
+ -> m ()
+cell users categories frequency currency header payment =
+ case header of
+ NameHeader ->
+ R.text $ _payment_name payment
+
+ CostHeader ->
+ R.text . Format.price currency . _payment_cost $ payment
+
+ UserHeader ->
+ R.text . Maybe.fromMaybe "" . fmap _user_name $ CM.findUser (_payment_user payment) users
+
+ CategoryHeader ->
+ let
+ category =
+ L.find ((== (_payment_category payment)) . _category_id) categories
+ in
+ Maybe.fromMaybe R.blank . flip fmap category $ \c ->
+ Tag.view $ Tag.In
+ { Tag._in_text = _category_name c
+ , Tag._in_color = _category_color c
+ }
+
+ DateHeader ->
+ if frequency == Punctual then
+ do
+ R.elClass "span" "shortDate" $
+ R.text . Format.shortDay . _payment_date $ payment
+
+ R.elClass "span" "longDate" $
+ R.text . Format.longDay . _payment_date $ payment
+ else
+ R.blank
diff --git a/client/src/View/SignIn.hs b/client/src/View/SignIn.hs
new file mode 100644
index 0000000..e68755f
--- /dev/null
+++ b/client/src/View/SignIn.hs
@@ -0,0 +1,82 @@
+module View.SignIn
+ ( view
+ , Out(..)
+ ) where
+
+import qualified Data.Either as Either
+import qualified Data.Maybe as Maybe
+import Data.Text (Text)
+import qualified Data.Validation as V
+import Reflex.Dom (Event, MonadWidget)
+import qualified Reflex.Dom as R
+
+import Common.Model (Init, SignInForm (SignInForm))
+import qualified Common.Msg as Msg
+import qualified Common.Validation.SignIn as SignInValidation
+
+import qualified Component.Button as Button
+import qualified Component.Form as Form
+import qualified Component.Input as Input
+import qualified Util.Ajax as Ajax
+import qualified Util.Validation as ValidationUtil
+import qualified Util.WaitFor as WaitFor
+
+data Out t = Out
+ { _out_success :: Event t Init
+ }
+
+view :: forall t m. MonadWidget t m => m (Out t)
+view = do
+ signInResult <- R.divClass "signIn" $
+ Form.view $ do
+ rec
+ let resetForm = ("" <$ R.ffilter Either.isRight signInResult)
+
+ email <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.SignIn_EmailLabel
+ , Input._in_validation = SignInValidation.email
+ })
+ resetForm
+ validate)
+
+ password <- Input._out_raw <$> (Input.view
+ (Input.defaultIn
+ { Input._in_label = Msg.get Msg.SignIn_PasswordLabel
+ , Input._in_validation = SignInValidation.password
+ , Input._in_inputType = "password"
+ })
+ resetForm
+ validate)
+
+ validate <- Button._out_clic <$> (Button.view $
+ (Button.defaultIn (R.text $ Msg.get Msg.SignIn_Button))
+ { Button._in_class = R.constDyn "validate"
+ , Button._in_waiting = waiting
+ , Button._in_submit = True
+ })
+
+ let form = do
+ e <- email
+ p <- password
+ return . V.Success $ SignInForm e p
+
+ (signInResult, waiting) <- WaitFor.waitFor
+ (Ajax.postAndParseResult "/api/signIn")
+ (ValidationUtil.fireValidation form validate)
+
+ showSignInResult signInResult
+
+ return signInResult
+
+ return $ Out
+ { _out_success = R.filterRight signInResult
+ }
+
+showSignInResult :: forall t m. MonadWidget t m => Event t (Either Text Init) -> m ()
+showSignInResult signInResult = do
+ _ <- R.widgetHold R.blank $ showResult <$> signInResult
+ R.blank
+
+ where showResult (Left error) = R.divClass "error" . R.text $ error
+ showResult (Right _) = R.blank
diff --git a/client/src/View/Statistics/Chart.hs b/client/src/View/Statistics/Chart.hs
new file mode 100644
index 0000000..63df2a1
--- /dev/null
+++ b/client/src/View/Statistics/Chart.hs
@@ -0,0 +1,102 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE JavaScriptFFI #-}
+
+module View.Statistics.Chart
+ ( view
+ , In(..)
+ , Dataset(..)
+ ) where
+
+import qualified Control.Concurrent as Concurrent
+import Control.Monad (void)
+import Control.Monad.IO.Class (liftIO)
+import Data.Aeson ((.=))
+import qualified Data.Aeson as AE
+import qualified Data.Map as M
+import Data.Text (Text)
+import Language.Javascript.JSaddle (JSString, JSVal)
+import qualified Language.Javascript.JSaddle.Value as JSValue
+import Reflex.Dom (MonadWidget)
+import qualified Reflex.Dom as R
+-- import GHCJS.Foreign.Callback
+
+
+#ifdef __GHCJS__
+foreign import javascript unsafe "new Chart(document.getElementById($1), $2);" drawChart :: JSString -> JSVal -> IO ()
+#else
+drawChart = error "drawChart: only available from JavaScript"
+#endif
+
+data In = In
+ { _in_title :: Text
+ , _in_labels :: [Text]
+ , _in_datasets :: [Dataset]
+ }
+
+data Dataset = Dataset
+ { _dataset_label :: Text
+ , _dataset_data :: [Int]
+ , _dataset_color :: Text
+ }
+
+view :: forall t m. MonadWidget t m => In -> m ()
+view input = do
+ R.divClass "g-Chart" $
+ R.elAttr "canvas" (M.singleton "id" "chart") $
+ R.blank
+
+ liftIO $ Concurrent.forkIO $ do
+ Concurrent.threadDelay 500000
+ config <- JSValue.valMakeJSON (configToJson input)
+ drawChart "chart" config
+
+ return ()
+
+configToJson (In title labels datasets) =
+ AE.object
+ [ "type" .= AE.String "line"
+ , "data" .=
+ AE.object
+ [ "labels" .= labels
+ , "datasets" .= map datasetToJson datasets
+ ]
+ , "options" .=
+ AE.object
+ [ "responsive" .= True
+ , "title" .=
+ AE.object
+ [ "display" .= True
+ , "text" .= title
+ ]
+ , "tooltips" .=
+ AE.object
+ [ "mode" .= AE.String "nearest"
+ , "intersect" .= False
+ ]
+ , "hover" .=
+ AE.object
+ [ "mode" .= AE.String "nearest"
+ , "intersect" .= True
+ ]
+ , "scales" .=
+ AE.object
+ [ "yAxes" .=
+ [ [ AE.object
+ [ "ticks" .=
+ AE.object
+ [ "beginAtZero" .= True ]
+ ]
+ ]
+ ]
+ ]
+ ]
+ ]
+
+datasetToJson (Dataset label data_ color) =
+ AE.object
+ [ "label" .= label
+ , "data" .= data_
+ , "fill" .= False
+ , "backgroundColor" .= color
+ , "borderColor" .= color
+ ]
diff --git a/client/src/View/Statistics/Statistics.hs b/client/src/View/Statistics/Statistics.hs
new file mode 100644
index 0000000..d931b2b
--- /dev/null
+++ b/client/src/View/Statistics/Statistics.hs
@@ -0,0 +1,85 @@
+module View.Statistics.Statistics
+ ( view
+ , In(..)
+ ) where
+
+import Control.Monad (void)
+import Data.Map (Map)
+import qualified Data.Map as M
+import qualified Data.Text as T
+import Data.Time.Calendar (Day)
+import qualified Data.Time.Calendar as Calendar
+import Loadable (Loadable)
+import qualified Loadable
+import Reflex.Dom (Dynamic, MonadWidget)
+import qualified Reflex.Dom as R
+import qualified Util.Ajax as AjaxUtil
+import qualified View.Statistics.Chart as Chart
+
+import Common.Model (Category (..), Currency, Income,
+ MonthStats (..), Stats, User (..))
+import qualified Common.Msg as Msg
+import qualified Common.View.Format as Format
+
+data In = In
+ { _in_currency :: Currency
+ }
+
+view :: forall t m. MonadWidget t m => In -> m ()
+view input = do
+
+ users <- AjaxUtil.getNow "api/users"
+ categories <- AjaxUtil.getNow "api/allCategories"
+ statistics <- AjaxUtil.getNow "api/statistics"
+
+ let loadable = (\u c s -> (,,) <$> u <*> c <*> s) <$> users <*> categories <*> statistics
+
+ R.divClass "withMargin" $
+ R.divClass "titleButton" $
+ R.el "h1" $
+ R.text $ Msg.get Msg.Statistics_Title
+
+ void . R.dyn . R.ffor loadable . Loadable.viewHideValueWhileLoading $
+ stats (_in_currency input)
+
+stats :: forall t m. MonadWidget t m => Currency -> ([User], [Category], Stats) -> m ()
+stats currency (users, categories, stats) =
+ Chart.view $ Chart.In
+ { Chart._in_title = Msg.get (Msg.Statistics_ByMonthsAndMean averagePayment averageIncome)
+ , Chart._in_labels = map (Format.monthAndYear . _monthStats_start) stats
+ , Chart._in_datasets = totalIncomeDataset : totalPaymentDataset : (map categoryDataset categories)
+ }
+
+ where
+ averageIncome =
+ Format.price currency $ sum totalIncomes `div` length stats
+
+ totalIncomeDataset =
+ Chart.Dataset
+ { Chart._dataset_label = Msg.get Msg.Statistics_TotalIncomes
+ , Chart._dataset_data = totalIncomes
+ , Chart._dataset_color = "#222222"
+ }
+
+ totalIncomes =
+ map (sum . map snd . M.toList . _monthStats_incomeByUser) stats
+
+ averagePayment =
+ Format.price currency $ sum totalPayments `div` length stats
+
+ totalPaymentDataset =
+ Chart.Dataset
+ { Chart._dataset_label = Msg.get Msg.Statistics_TotalPayments
+ , Chart._dataset_data = totalPayments
+ , Chart._dataset_color = "#555555"
+ }
+
+ totalPayments =
+ map (sum . map snd . M.toList . _monthStats_paymentsByCategory) stats
+
+ categoryDataset category =
+ Chart.Dataset
+ { Chart._dataset_label = _category_name category
+ , Chart._dataset_data = map (M.findWithDefault 0 (_category_id category) . _monthStats_paymentsByCategory) stats
+ , Chart._dataset_color = _category_color category
+ }