Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Web.Hyperbole.View.Types
Synopsis
- newtype View c a = View {}
- runView :: forall c a. c -> View c a -> Html a
- type family ViewContext (v :: Type) where ...
- context :: forall c. View c c
- addContext :: ctx -> View ctx () -> View c ()
- modifyContext :: forall ctx0 ctx1. (ctx0 -> ctx1) -> View ctx1 () -> View ctx0 ()
- tag :: Text -> View c () -> View c ()
- tag' :: Bool -> Text -> View c () -> View c ()
- text :: Text -> View c ()
- none :: View c ()
- raw :: Text -> View c ()
Documentation
Instances
HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # | |
Defined in Web.Hyperbole.HyperView.ViewId | |
Applicative (View ctx) Source # | |
Functor (View c) Source # | |
Monad (View ctx) Source # | |
IsString (View c ()) Source # | |
Defined in Web.Hyperbole.View.Types Methods fromString :: String -> View c () # | |
Attributable (View c a) Source # | |
Defined in Web.Hyperbole.View.Types | |
Styleable (View c a) Source # | |
Styleable (TableColumns c dt () -> View c ()) Source # | |
Defined in Web.Hyperbole.View.Tag Methods (~) :: (TableColumns c dt () -> View c ()) -> (CSS (TableColumns c dt () -> View c ()) -> CSS (TableColumns c dt () -> View c ())) -> TableColumns c dt () -> View c () # modCSS :: ([Rule] -> [Rule]) -> (TableColumns c dt () -> View c ()) -> TableColumns c dt () -> View c () # |
type family ViewContext (v :: Type) where ... Source #
Equations
ViewContext (View c x) = c | |
ViewContext (View c x -> View c x) = c |
addContext :: ctx -> View ctx () -> View c () Source #
modifyContext :: forall ctx0 ctx1. (ctx0 -> ctx1) -> View ctx1 () -> View ctx0 () Source #