aboutsummaryrefslogtreecommitdiff
path: root/client/src/Component/Button.hs
blob: 9499045806848e5506f5110c0d6136bcefb964ca (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
{-# LANGUAGE OverloadedStrings #-}

module Component.Button
  ( ButtonIn(..)
  , buttonInDefault
  , ButtonOut(..)
  , button
  ) where

import qualified Data.Map    as M
import           Data.Monoid ((<>))
import           Data.Text   (Text)
import qualified Data.Text   as T
import           Reflex.Dom  (Event, MonadWidget)
import qualified Reflex.Dom  as R

import qualified Icon

data ButtonIn t m = ButtonIn
  { _buttonIn_class   :: Text
  , _buttonIn_content :: m ()
  , _buttonIn_waiting :: Event t Bool
  }

buttonInDefault :: forall t m. MonadWidget t m => ButtonIn t m
buttonInDefault = ButtonIn
  { _buttonIn_class = ""
  , _buttonIn_content = R.blank
  , _buttonIn_waiting = R.never
  }

data ButtonOut t = ButtonOut
  { _buttonOut_clic :: Event t ()
  }

button :: forall t m. MonadWidget t m => ButtonIn t m -> m (ButtonOut t)
button buttonIn = do
  attr <- R.holdDyn
    (M.fromList [("type", "button"), ("class", _buttonIn_class buttonIn)])
    (fmap
      (\w -> M.fromList $
        [ ("type", "button") ]
        <> if w
             then [("class", T.concat [ _buttonIn_class buttonIn, " waiting" ])]
             else [("class", _buttonIn_class buttonIn)])
      (_buttonIn_waiting buttonIn))
  (e, _) <- R.elDynAttr' "button" attr $ do
    Icon.loading
    R.divClass "content" $ _buttonIn_content buttonIn
  return $ ButtonOut
    { _buttonOut_clic = R.domEvent R.Click e
    }