Skip to content

Instantly share code, notes, and snippets.

@ajnsit
Created December 5, 2019 09:38
Show Gist options
  • Save ajnsit/454c9432cd0cdcb10a846f88260a7053 to your computer and use it in GitHub Desktop.
Save ajnsit/454c9432cd0cdcb10a846f88260a7053 to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Concur.Core (Widget)
import Concur.Core.FRP (Signal, debounce, display, dyn)
import Concur.React (HTML)
import Concur.React.DOM as D
import Concur.React.Props as P
import Data.Foldable (class Foldable, fold)
import Data.Maybe (Maybe(..))
import Data.String (trim)
import Data.String.NonEmpty (NonEmptyString, fromString, toString)
type CtrlSignal v a = a -> Signal v a
main :: Effect Unit
main = runWidgetInDom "root" mainWidget
mainWidget :: forall a. Widget HTML a
mainWidget = dyn $ do
s <- textInput D.div' "HELLO" Nothing
display (D.div' [D.text (show s)])
foldf :: ∀ a f m. Foldable f => Functor f => Monoid m => (a -> m) -> f a -> m
foldf f vals = fold $ f <$> vals
textInputWidget :: String -> Widget HTML String
textInputWidget txt =
D.input [P.value txt, P.unsafeTargetValue <$> P.onChange]
textInput' :: D.El' -> String -> CtrlSignal HTML String
textInput' tag label initVal = labelSig' tag label [] $ sig initVal
where
sig :: String -> Signal HTML String
sig txt = debounce 500.0 txt textInputWidget
-- | Reasonable defaults for filtering input text
textFilter :: Signal HTML String -> Signal HTML (Maybe NonEmptyString)
textFilter txtSig = do
txt <- txtSig
pure $ fromString $ trim txt
textInput :: D.El' -> String -> CtrlSignal HTML (Maybe NonEmptyString)
textInput tag label iVal = textFilter $ textInput' tag label
(foldf toString iVal)
-- | Prepend a label heading to a siginal
labelSig' :: ∀ a. D.El'
-> String
-> Array (P.ReactProps a)
-> Signal HTML a
-> Signal HTML a
labelSig' tag label props sigIn = labelSig (tag [D.text label]) props sigIn
labelSig :: ∀ a. (∀ b. Widget HTML b)
-> Array (P.ReactProps a)
-> Signal HTML a
-> Signal HTML a
labelSig widg props sigIn = D.div_ props do
display widg
sigIn
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment