aboutsummaryrefslogtreecommitdiff
path: root/client/src/View/Payment/Pages.hs
diff options
context:
space:
mode:
Diffstat (limited to 'client/src/View/Payment/Pages.hs')
-rw-r--r--client/src/View/Payment/Pages.hs57
1 files changed, 33 insertions, 24 deletions
diff --git a/client/src/View/Payment/Pages.hs b/client/src/View/Payment/Pages.hs
index f9a2b4e..cf3e115 100644
--- a/client/src/View/Payment/Pages.hs
+++ b/client/src/View/Payment/Pages.hs
@@ -1,6 +1,5 @@
-{-# LANGUAGE ExistentialQuantification #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE RecursiveDo #-}
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE RecursiveDo #-}
module View.Payment.Pages
( widget
@@ -8,35 +7,45 @@ module View.Payment.Pages
, PagesOut(..)
) where
-import qualified Data.Text as T
-import Reflex.Dom (MonadWidget)
-import qualified Reflex.Dom as R
+import qualified Data.Text as T
+import Reflex.Dom (Event, Dynamic, MonadWidget)
+import qualified Reflex.Dom as R
-import Common.Model (Payment(..))
+import Common.Model (Payment (..))
+import Component (ButtonIn (..), ButtonOut (..))
+import qualified Component as Component
import qualified Icon
data PagesIn = PagesIn
{ _pagesIn_payments :: [Payment]
}
-data PagesOut = PagesOut
- {
+data PagesOut t = PagesOut
+ { _pagesOut_currentPage :: Dynamic t Int
}
-widget :: forall t m. MonadWidget t m => PagesIn -> m PagesOut
+widget :: forall t m. MonadWidget t m => PagesIn -> m (PagesOut t)
widget _ = do
- R.divClass "pages" $ do
- page Icon.doubleLeftBar
- page Icon.doubleLeft
- page (R.text . T.pack . show $ (1 :: Integer))
- page (R.text . T.pack . show $ (2 :: Integer))
- page (R.text . T.pack . show $ (3 :: Integer))
- page (R.text . T.pack . show $ (4 :: Integer))
- page (R.text . T.pack . show $ (5 :: Integer))
- page Icon.doubleRight
- page Icon.doubleRightBar
- return $ PagesOut {}
-
-page :: forall t m. MonadWidget t m => m () -> m ()
-page content = R.elClass "button" "page" $ content
+ currentPage <- R.divClass "pages" $ do
+ a <- page 1 Icon.doubleLeftBar
+ b <- page 1 Icon.doubleLeft
+ c <- page 1 (R.text . T.pack . show $ (1 :: Integer))
+ d <- page 2 (R.text . T.pack . show $ (2 :: Integer))
+ e <- page 3 (R.text . T.pack . show $ (3 :: Integer))
+ f <- page 4 (R.text . T.pack . show $ (4 :: Integer))
+ g <- page 5 (R.text . T.pack . show $ (5 :: Integer))
+ h <- page 5 Icon.doubleRight
+ i <- page 5 Icon.doubleRightBar
+ R.holdDyn 1 $ R.leftmost [ a, b, c, d, e, f, g, h, i ]
+ return $ PagesOut
+ { _pagesOut_currentPage = currentPage
+ }
+
+page :: forall t m. MonadWidget t m => Int -> m () -> m (Event t Int)
+page n content =
+ ((fmap (const n)) . _buttonOut_clic) <$> (Component.button $ ButtonIn
+ { _buttonIn_class = "page"
+ , _buttonIn_content = content
+ , _buttonIn_waiting = R.never
+ })