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

Web.Hyperbole.HyperView

Synopsis

Documentation

class (ViewId id, ViewAction (Action id)) => HyperView id (es :: [Effect]) where 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
  deriving (Show, Read, ViewId)

instance HyperView Message es where
  data Action Message
    = SetMessage Text
    deriving (Show, Read, ViewAction)

  update (SetMessage msg) =
    pure $ messageView msg

Associated Types

data Action id Source #

Outline all actions that are permitted in this HyperView

data Action Message = SetMessage Text | ClearMessage
  deriving (Show, Read, ViewAction)

type Require id :: [Type] Source #

Include any child hyperviews here. The compiler will make sure that the page knows how to handle them

type Require = '[ChildView]

type Require id = '[] :: [Type]

Methods

update :: Action id -> Eff (Reader id ': es) (View id ()) Source #

Specify how the view should be updated for each Action

update (SetMessage msg) = pure $ messageView msg
update ClearMessage = pure $ messageView ""

Instances

Instances details
HyperView (Root views) es Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Associated Types

data Action (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

data Action (Root views) = RootNone
type Require (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

Methods

update :: Action (Root views) -> Eff (Reader (Root views) ': es) (View (Root views) ()) Source #

data Root (views :: [Type]) Source #

The top-level view returned by a Page. It carries a type-level list of every HyperView used in our Page so the compiler can check our work and wire everything together.

Constructors

Root 

Instances

Instances details
Read (Action (Root views)) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

readsPrec :: Int -> ReadS (Action (Root views)) #

readList :: ReadS [Action (Root views)] #

readPrec :: ReadPrec (Action (Root views)) #

readListPrec :: ReadPrec [Action (Root views)] #

Read (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

readsPrec :: Int -> ReadS (Root views) #

readList :: ReadS [Root views] #

readPrec :: ReadPrec (Root views) #

readListPrec :: ReadPrec [Root views] #

Show (Action (Root views)) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

showsPrec :: Int -> Action (Root views) -> ShowS #

show :: Action (Root views) -> String #

showList :: [Action (Root views)] -> ShowS #

Show (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

showsPrec :: Int -> Root views -> ShowS #

show :: Root views -> String #

showList :: [Root views] -> ShowS #

ViewAction (Action (Root views)) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toAction :: Action (Root views) -> Text Source #

parseAction :: Text -> Maybe (Action (Root views)) Source #

ViewId (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toViewId :: Root views -> Text Source #

parseViewId :: Text -> Maybe (Root views) Source #

HyperView (Root views) es Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Associated Types

data Action (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

data Action (Root views) = RootNone
type Require (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

Methods

update :: Action (Root views) -> Eff (Reader (Root views) ': es) (View (Root views) ()) Source #

data Action (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

data Action (Root views) = RootNone
type Require (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

type family ValidDescendents x :: [Type] where ... Source #

Equations

ValidDescendents x = x ': NextDescendents ('[] :: [Type]) '[x] 

type family NextDescendents (ex :: [Type]) (xs :: [Type]) :: [Type] where ... Source #

Equations

NextDescendents _1 ('[] :: [Type]) = '[] :: [Type] 
NextDescendents ex (x ': xs) = (RemoveAll (x ': ex) (Require x) <++> NextDescendents ((x ': ex) <++> Require x) (RemoveAll (x ': ex) (Require x))) <++> NextDescendents (x ': ex) (RemoveAll (x ': ex) xs) 

type NotHandled id (ctx :: t) (views :: [Type]) = TypeError ((((((((('Text "HyperView " ':<>: 'ShowType id) ':<>: 'Text " not found in (Require ") ':<>: 'ShowType ctx) ':<>: 'Text ")") ':$$: ('Text " " ':<>: 'ShowType views)) ':$$: 'Text "Try adding it to the HyperView instance:") ':$$: (('Text " instance HyperView " ':<>: 'ShowType ctx) ':<>: 'Text " where")) ':$$: (((('Text " type Action " ':<>: 'ShowType ctx) ':<>: 'Text " = ") ':<>: 'ShowType (Action id)) ':<>: 'Text "")) ':$$: (((('Text " type Require " ':<>: 'ShowType ctx) ':<>: 'Text " = [") ':<>: 'ShowType id) ':<>: 'Text ", ...]")) :: k Source #

type NotDesc (id :: t) (ctx :: t1) (x :: t2) (cs :: t3) = TypeError (((((('Text "" ':<>: 'ShowType x) ':<>: 'Text ", a child of HyperView ") ':<>: 'ShowType id) ':<>: 'Text ", not handled by context ") ':<>: 'ShowType ctx) ':$$: ('Text " Require = " ':<>: 'ShowType cs)) :: k Source #

type NotInPage (x :: a) (total :: [a]) = TypeError ((((('Text "" ':<>: 'ShowType x) ':<>: 'Text " not included in: ") ':$$: ('Text " Page es " ':<>: 'ShowType total)) ':$$: 'Text "try expanding the page views to:") ':$$: ('Text " Page es " ':<>: 'ShowType (x ': total))) :: k Source #

type HyperViewHandled id ctx = (ElemOr id (Require ctx) (NotHandled id ctx (Require ctx) :: Constraint), CheckDescendents id ctx) Source #

type family CheckDescendents id ctx where ... Source #

Equations

CheckDescendents id (Root total) = AllInPage (ValidDescendents id) total 
CheckDescendents id ctx = () 

type family AllInPage (ids :: [a]) (total :: [a]) where ... Source #

Equations

AllInPage ('[] :: [a]) (_1 :: [a]) = () 
AllInPage (x ': xs :: [a]) (total :: [a]) = (ElemOr x total (NotInPage x total :: Constraint), AllInPage xs total) 

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

Embed a HyperView into another View

page :: Eff es (Page '[Message])
page = do
  pure $ do
    col (pad 10 . gap 10) $ do
      el (bold . fontSize 24) "Unchanging Header"
      hyper Message $ messageView "Hello World"

hyperUnsafe :: ViewId id => id -> View id () -> View ctx () Source #

class ViewAction a where Source #

Minimal complete definition

Nothing

Methods

toAction :: a -> Text Source #

default toAction :: Show a => a -> Text Source #

parseAction :: Text -> Maybe a Source #

default parseAction :: Read a => Text -> Maybe a Source #

Instances

Instances details
ViewAction () Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toAction :: () -> Text Source #

parseAction :: Text -> Maybe () Source #

ViewAction (Action (Root views)) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toAction :: Action (Root views) -> Text Source #

parseAction :: Text -> Maybe (Action (Root views)) Source #

class ViewId a where Source #

Minimal complete definition

Nothing

Methods

toViewId :: a -> Text Source #

default toViewId :: Show a => a -> Text Source #

parseViewId :: Text -> Maybe a Source #

default parseViewId :: Read a => Text -> Maybe a Source #

Instances

Instances details
ViewId (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toViewId :: Root views -> Text Source #

parseViewId :: Text -> Maybe (Root views) Source #

class HasViewId (m :: k -> Type) (view :: k) where Source #

Access the viewId in a View or update

data Contact = Contact UserId
  deriving (Show, Read, ViewId)

instance (Users :> es, Debug :> es) => HyperView Contact es where
  data Action Contact
    = Edit
    | Save
    | View
    deriving (Show, Read, ViewAction)

  update action = do
    -- No matter which action we are performing, let's look up the user to make sure it exists
    Contact uid <- viewId
    u <- Users.find uid
    case action of
      View -> do
        pure $ contactView u
      Edit -> do
        pure $ contactEditView u
      Save -> do
        delay 1000
        unew <- parseUser uid
        Users.save unew
        pure $ contactView unew

Methods

viewId :: m view Source #

Instances

Instances details
HasViewId (Eff (Reader view ': es) :: Type -> Type) (view :: Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

viewId :: Eff (Reader view ': es) view Source #

HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

viewId :: View ctx ctx Source #