hyperbole-0.4.2: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellNone
LanguageGHC2021

Web.Hyperbole.View.Event

Synopsis

Documentation

onLoad :: ViewAction (Action id) => Action id -> DelayMs -> Mod id Source #

Send the action after N milliseconds. Can be used to implement lazy loading or polling

pollMessageView :: Text -> View Message ()
pollMessageView m = do
  onLoad LoadMessage 1000 $ do
    el bold "Current Message. Reloading in 1s"
    el_ (text m)

onClick :: ViewAction (Action id) => Action id -> Mod id Source #

onInput :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id Source #

Run an action when the user types into an input or textarea.

WARNING: a short delay can result in poor performance. It is not recommended to set the value of the input

input (onInput OnSearch) 250 id

onKeyDown :: ViewAction (Action id) => Key -> Action id -> Mod id Source #

onKeyUp :: ViewAction (Action id) => Key -> Action id -> Mod id Source #

data Key Source #

Instances

Instances details
Read Key Source # 
Instance details

Defined in Web.Hyperbole.View.Event

Show Key Source # 
Instance details

Defined in Web.Hyperbole.View.Event

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

toActionInput :: ViewAction a => (Text -> a) -> Text Source #

Serialize a constructor that expects a single Text, like `data MyAction = GoSearch Text`

onRequest :: Mod id -> Mod id Source #

Apply a Mod only when a request is in flight

myView = do
  el (hide . onRequest flexCol) el_ "Loading..."
  el (onRequest hide) Loaded

dataTarget :: ViewId a => a -> Mod x Source #

Internal

target :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx () Source #

Trigger actions for another view. They will update the view specified

otherView :: View OtherView ()
otherView = do
  el_ "This is not a message view"
  button OtherAction id "Do Something"

  target (Message 2) $ do
    el_ "Now we can trigger a MessageAction which will update our Message HyperView, not this one"
    button ClearMessage id "Clear Message #2"