hyperbole-0.3.6: Interactive HTML apps using type-safe serverside Haskell
Safe HaskellSafe-Inferred
LanguageGHC2021

Web.Hyperbole.HyperView

Synopsis

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

Associated Types

type Action id :: Type Source #

Instances

Instances details
(HyperView id, Param id) => HyperView (FormFields id) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Associated Types

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 es Response
myPage = do
  handle messages
  load $ do
    pure $ do
      el_ "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"

onLoad :: HyperView id => Action id -> DelayMs -> View id () -> View 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)

onRequest :: View id () -> View id () -> View id () Source #

Give visual feedback when an action is in-flight.

myView = do
  onRequest loadingIndicator $ do
    el_ "Loaded"
  where
    loadingIndicator = el_ "Loading..."

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 #

An option for a dropdown. First argument is passed to (opt -> Action id) in the dropdown, and to the selected predicate

selected :: Bool -> Mod Source #

sets selected = true if the dropdown predicate returns True

data Option opt id action Source #

The view context for an option

Constructors

Option 

Fields

class Param a where Source #

Types that can be serialized. HyperView requires this for both its view id and action

data Message = Message Int
  deriving (Generic, Param)

Minimal complete definition

Nothing

Methods

toParam :: a -> Text Source #

default toParam :: (Generic a, GParam (Rep a)) => a -> Text Source #

parseParam :: Text -> Maybe a Source #

default parseParam :: (Generic a, GParam (Rep a)) => Text -> Maybe a Source #

Instances

Instances details
Param Text Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Param Integer Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Param () Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toParam :: () -> Text Source #

parseParam :: Text -> Maybe () Source #

Param Float Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Param Int Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Param id => Param (FormFields id) Source # 
Instance details

Defined in Web.Hyperbole.Forms

Param a => Param (Maybe a) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

class GParam f where Source #

Methods

gToParam :: f p -> Text Source #

gParseParam :: Text -> Maybe (f p) Source #

Instances

Instances details
GParam (U1 :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). U1 p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (U1 p) Source #

(GParam f, GParam g) => GParam (f :*: g :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). (f :*: g) p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe ((f :*: g) p) Source #

(GParam f, GParam g) => GParam (f :+: g :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). (f :+: g) p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe ((f :+: g) p) Source #

GParam (K1 R Text :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). K1 R Text p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (K1 R Text p) Source #

GParam (K1 R String :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). K1 R String p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (K1 R String p) Source #

Param a => GParam (K1 R a :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). K1 R a p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (K1 R a p) Source #

(Constructor c, GParam f) => GParam (M1 C c f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). M1 C c f p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (M1 C c f p) Source #

(Datatype d, GParam f) => GParam (M1 D d f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). M1 D d f p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (M1 D d f p) Source #

GParam f => GParam (M1 S s f :: k -> Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

gToParam :: forall (p :: k0). M1 S s f p -> Text Source #

gParseParam :: forall (p :: k0). Text -> Maybe (M1 S s f p) Source #

route :: Route a => a -> Mod -> View c () -> View c () Source #

A hyperlink to another route

>>> route (User 100) id "View User"
<a href="/user/100">View User</a>