Skip to content

Commit

Permalink
adding ajbarber's patch to concur and associated debounce (#129)
Browse files Browse the repository at this point in the history
  • Loading branch information
bbarker authored May 16, 2021
1 parent 0f9d83f commit 4de3076
Show file tree
Hide file tree
Showing 2 changed files with 19 additions and 16 deletions.
10 changes: 6 additions & 4 deletions packages.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -139,14 +139,16 @@ let additions =
, "arrays"
, "avar"
, "console"
, "debug"
, "foldable-traversable"
, "free"
, "js-timers"
, "nonempty"
, "profunctor-lenses"
, "tailrec"
]
"https://github.com/purescript-concur/purescript-concur-core.git"
"f175dd4a4f7b8904d2cc4abb51e3b5179140c294"
"https://github.com/ajbarber/purescript-concur-core.git"
"c66c3a9f8e7e325e86ab5faa1505aa2e51a46e4b"
, concur-react =
mkPackage
[ "aff"
Expand All @@ -162,8 +164,8 @@ let additions =
, "web-dom"
, "web-html"
]
"https://github.com/purescript-concur/purescript-concur-react.git"
"v0.4.2"
"https://github.com/ajbarber/purescript-concur-react.git"
"ed06698d06582cc0d64bd2d7c667b0a8964b447b"
, datacite =
{ dependencies =
[ "effect", "functors", "generics-rep", "naturals", "simple-json" ]
Expand Down
25 changes: 13 additions & 12 deletions src/Metajelo/FormUtil.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,8 @@ module Metajelo.FormUtil where

import Concur.Core (Widget)
import Concur.Core.ElementBuilder (Element)
import Concur.Core.FRP (Signal, debounce, display, fireOnce, justWait, loopS, loopW, oneShot, step)
import Concur.Core.FRP (Signal, display, fireOnce, justWait, loopS, loopW, oneShot, step)
import Concur.Core.Types (debounced)
import Concur.React (HTML)
import Concur.React.DOM as D
import Concur.React.Props as P
Expand All @@ -11,16 +12,16 @@ import Control.Alternative (empty)
import Control.Applicative (class Applicative)
import Control.Apply (class Apply, apply)
import Control.Extend (class Extend)
import Data.Array as A
import Data.Array (catMaybes, filter, length, replicate, (:), (..))
import Data.Array as A
import Data.Array.NonEmpty (NonEmptyArray, fromArray, toArray)
import Data.Bifunctor (lmap)
import Data.Bounded (bottom)
import Data.Eq ((==))
import Data.Date (canonicalDate)
import Data.DateTime (DateTime(..))
import Data.Either (Either(..), hush)
import Data.Enum (class BoundedEnum, class Enum, class SmallBounded, upFromIncluding, toEnum)
import Data.Eq ((==))
import Data.Foldable (class Foldable, fold)
import Data.Functor (class Functor)
import Data.Generic.Rep (class Generic)
Expand Down Expand Up @@ -72,11 +73,11 @@ import Web.DOM (Node)
import Web.DOM.Document (Document, getElementsByClassName, toNonElementParentNode)
import Web.DOM.Element as Ele
import Web.DOM.HTMLCollection as HTML
import Web.HTML.HTMLDocument as HTML
import Web.HTML.HTMLInputElement as HTML
import Web.DOM.NonElementParentNode (getElementById)
import Web.DOM.ParentNode (children)
import Web.HTML (window)
import Web.HTML.HTMLDocument as HTML
import Web.HTML.HTMLInputElement as HTML
import Web.HTML.Window (document)

type Email = EA.EmailAddress
Expand Down Expand Up @@ -146,18 +147,18 @@ labelSig widg props sigIn = D.div_ props do
sigIn

textInputWidget :: String -> Widget HTML String
textInputWidget txt =
textInputWidget txt = debounced 1000 $
D.input [P.defaultValue txt, P.unsafeTargetValue <$> P.onChange]

textInput' :: CtrlSignal HTML String
textInput' initVal = sig initVal
textInput' initVal = sigNow initVal
where
-- Alternative to 'sig' that doesn't debounce, for debugging:
-- sigNow rs = step rs $ do
-- pure $ unsafePerformEffect $ log $ "refstr in textInput sigNow': " <> (show rs)
-- rsNew <- textInputWidget rs
-- pure $ sigNow rsNew
sig txt = debounce 1000.0 txt textInputWidget
sigNow rs = step rs $ do
pure $ unsafePerformEffect $ log $ "refstr in textInput sigNow': " <> (show rs)
rsNew <- textInputWidget rs
pure $ sigNow rsNew
--sig txt = debounce 1000.0 txt textInputWidget

-- | Reasonable defaults for filtering input text
textFilter :: Signal HTML String -> Signal HTML (Maybe NonEmptyString)
Expand Down

0 comments on commit 4de3076

Please sign in to comment.