Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- class (ViewId id, ViewAction (Action id)) => HyperView id (es :: [Effect]) where
- data Root (views :: [Type]) = Root
- type family ValidDescendents x :: [Type] where ...
- type family NextDescendents (ex :: [Type]) (xs :: [Type]) :: [Type] where ...
- 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
- 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
- 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
- type HyperViewHandled id ctx = (ElemOr id (Require ctx) (NotHandled id ctx (Require ctx) :: Constraint), CheckDescendents id ctx)
- type family CheckDescendents id ctx where ...
- type family AllInPage (ids :: [a]) (total :: [a]) where ...
- hyper :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx ()
- hyperUnsafe :: ViewId id => id -> View id () -> View ctx ()
- class ViewAction a where
- toAction :: a -> Text
- parseAction :: Text -> Maybe a
- class ViewId a where
- toViewId :: a -> Text
- parseViewId :: Text -> Maybe a
- class HasViewId (m :: k -> Type) (view :: k) where
- viewId :: m view
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
) instanceHyperView
Message es where dataAction
Message = SetMessage Text deriving (Show, Read,ViewAction
)update
(SetMessage msg) = pure $ messageView msg
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]
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
HyperView (Root views) es Source # | |||||||||
Defined in Web.Hyperbole.HyperView
|
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.
Instances
Read (Action (Root views)) Source # | |||||||||
Read (Root views) Source # | |||||||||
Show (Action (Root views)) Source # | |||||||||
Show (Root views) Source # | |||||||||
ViewAction (Action (Root views)) Source # | |||||||||
ViewId (Root views) Source # | |||||||||
HyperView (Root views) es Source # | |||||||||
Defined in Web.Hyperbole.HyperView
| |||||||||
data Action (Root views) Source # | |||||||||
Defined in Web.Hyperbole.HyperView | |||||||||
type Require (Root views) Source # | |||||||||
Defined in Web.Hyperbole.HyperView |
type family ValidDescendents x :: [Type] where ... Source #
ValidDescendents x = x ': NextDescendents ('[] :: [Type]) '[x] |
type family NextDescendents (ex :: [Type]) (xs :: [Type]) :: [Type] where ... Source #
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 #
CheckDescendents id (Root total) = AllInPage (ValidDescendents id) total | |
CheckDescendents id ctx = () |
class ViewAction a where Source #
Nothing
Instances
ViewAction () Source # | |
Defined in Web.Hyperbole.HyperView | |
ViewAction (Action (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 dataAction
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 ofView
-> do pure $ contactView u Edit -> do pure $ contactEditView u Save -> do delay 1000 unew <- parseUser uid Users.save unew pure $ contactView unew