Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- class (Param id, Param (Action id)) => HyperView id where
- hyper :: forall id ctx. HyperView id => id -> View id () -> View ctx ()
- button :: HyperView id => Action id -> Mod -> View id () -> View id ()
- onLoad :: HyperView id => Action id -> DelayMs -> View id () -> View id ()
- type DelayMs = Int
- onRequest :: View id () -> View id () -> View id ()
- dataTarget :: Param a => a -> Mod
- target :: HyperView id => id -> View id () -> View a ()
- dropdown :: HyperView id => (opt -> Action id) -> (opt -> Bool) -> Mod -> View (Option opt id (Action id)) () -> View id ()
- option :: (HyperView id, Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) ()
- selected :: Bool -> Mod
- data Option opt id action = Option {}
- class Param a where
- toParam :: a -> Text
- parseParam :: Text -> Maybe a
- class GParam f where
- gToParam :: f p -> Text
- gParseParam :: Text -> Maybe (f p)
- breakSegment :: Text -> (Text, Text)
- toSegment :: String -> Text
- route :: Route a => a -> Mod -> View c () -> View c ()
Documentation
class (Param id, Param (Action id)) => HyperView id Source #
HyperViews are interactive subsections of a Page
Create an instance with a unique view id type and a sum type describing the actions the HyperView supports. The View Id can contain context (a database id, for example)
data Message = Message Int deriving (Generic,Param
) data MessageAction = Louder Text | ClearMessage deriving (Generic,Param
) instance HyperView Message where type Action Message = MessageAction
Instances
(HyperView id, Param id) => HyperView (FormFields id) Source # | |
Defined in Web.Hyperbole.Forms type Action (FormFields id) Source # |
hyper :: forall id ctx. HyperView id => id -> View id () -> View ctx () Source #
Embed HyperViews into the page, or nest them into other views
myPage :: (Hyperbole
:> es) =>Page
esResponse
myPage = dohandle
messagesload
$ do pure $ doel_
"My Page"hyper
(Message 1) $ messageView "Hello World"hyper
(Message 2) $ do messageView "Another Message"hyper
OtherView otherView
Views can only trigger actions that match their HyperView
messageView :: Text -> View Message () messageView m = do el_ (text m) button (Louder m) Louder otherView :: View OtherView () otherView = do -- Type Error! button (Louder "Hi") id Louder
button :: HyperView id => Action id -> Mod -> View id () -> View id () Source #
<button> HTML tag which sends the action when pressed
button SomeAction (border 1) "Click Me"
dataTarget :: Param a => a -> Mod Source #
Internal
target :: HyperView id => id -> View id () -> View a () 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"
dropdown :: HyperView id => (opt -> Action id) -> (opt -> Bool) -> Mod -> View (Option opt id (Action id)) () -> View id () Source #
Type-safe dropdown. Sends (opt -> Action id) when selected. The selection predicate (opt -> Bool) controls which option is selected. See Example.Contacts
data ContactsAction = Reload (Maybe Filter) | Delete Int deriving (Generic, Param) allContactsView :: Maybe Filter -> View Contacts () allContactsView fil = do row (gap 10) $ do el (pad 10) "Filter: " dropdown Reload (== fil) id $ do option Nothing "" option (Just Active) "Active!" option (Just Inactive) Inactive ...
option :: (HyperView id, Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) () Source #
Types that can be serialized. HyperView
requires this for both its view id and action
data Message = Message Int deriving (Generic, Param)
Nothing
parseParam :: Text -> Maybe a Source #
Instances
Param Text Source # | |
Param Integer Source # | |
Param () Source # | |
Defined in Web.Hyperbole.HyperView | |
Param Float Source # | |
Param Int Source # | |
Param id => Param (FormFields id) Source # | |
Defined in Web.Hyperbole.Forms toParam :: FormFields id -> Text Source # parseParam :: Text -> Maybe (FormFields id) Source # | |
Param a => Param (Maybe a) Source # | |
Instances
GParam (U1 :: k -> Type) Source # | |
(GParam f, GParam g) => GParam (f :*: g :: k -> Type) Source # | |
(GParam f, GParam g) => GParam (f :+: g :: k -> Type) Source # | |
GParam (K1 R Text :: k -> Type) Source # | |
GParam (K1 R String :: k -> Type) Source # | |
Param a => GParam (K1 R a :: k -> Type) Source # | |
(Constructor c, GParam f) => GParam (M1 C c f :: k -> Type) Source # | |
(Datatype d, GParam f) => GParam (M1 D d f :: k -> Type) Source # | |
GParam f => GParam (M1 S s f :: k -> Type) Source # | |