From 27e11b20b06f2f2dbfb56c0998a63169b4b8abc4 Mon Sep 17 00:00:00 2001 From: Joris Date: Wed, 8 Nov 2017 23:47:26 +0100 Subject: Use a better project structure --- src/client/Component/Button.hs | 53 ------------------------------------------ src/client/Component/Input.hs | 34 --------------------------- 2 files changed, 87 deletions(-) delete mode 100644 src/client/Component/Button.hs delete mode 100644 src/client/Component/Input.hs (limited to 'src/client/Component') diff --git a/src/client/Component/Button.hs b/src/client/Component/Button.hs deleted file mode 100644 index f21798c..0000000 --- a/src/client/Component/Button.hs +++ /dev/null @@ -1,53 +0,0 @@ -{-# LANGUAGE ExistentialQuantification #-} -{-# 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 (MonadWidget, Event) -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 - } diff --git a/src/client/Component/Input.hs b/src/client/Component/Input.hs deleted file mode 100644 index 7111630..0000000 --- a/src/client/Component/Input.hs +++ /dev/null @@ -1,34 +0,0 @@ -{-# LANGUAGE ExistentialQuantification #-} -{-# LANGUAGE OverloadedStrings #-} - -module Component.Input - ( InputIn(..) - , InputOut(..) - , input - ) where - -import Data.Text (Text) -import Reflex.Dom (MonadWidget, Dynamic, Event, (&), (.~), (=:)) -import qualified Reflex.Dom as R - -data InputIn t a b = InputIn - { _inputIn_reset :: Event t a - , _inputIn_placeHolder :: Text - } - -data InputOut t = InputOut - { _inputOut_value :: Dynamic t Text - , _inputOut_enter :: Event t () - } - -input :: forall t m a b. MonadWidget t m => InputIn t a b -> m (InputOut t) -input inputIn = do - let placeHolder = R.constDyn ("placeHolder" =: _inputIn_placeHolder inputIn) - let value = fmap (const "") (_inputIn_reset inputIn) - textInput <- R.textInput $ R.def & R.attributes .~ placeHolder - & R.setValue .~ value - let enter = fmap (const ()) $ R.ffilter ((==) 13) . R._textInput_keypress $ textInput - return $ InputOut - { _inputOut_value = R._textInput_value textInput - , _inputOut_enter = enter - } -- cgit v1.2.3