Copyright | (c) 2024 Sean Hess |
---|---|
License | BSD3 |
Maintainer | Sean Hess <seanhess@gmail.com> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | GHC2021 |
Create fully interactive HTML applications with type-safe serverside Haskell. Inspired by HTMX, Elm, and Phoenix LiveView
Synopsis
- liveApp :: (ByteString -> ByteString) -> Eff '[Hyperbole, Server, Concurrent, IOE] Response -> Application
- run :: Port -> Application -> IO ()
- basicDocument :: Text -> ByteString -> ByteString
- runPage :: forall (views :: [Type]) (es :: [Effect]). (Hyperbole :> es, RunHandlers views es) => Eff es (Page views) -> Eff es Response
- type Page (views :: [Type]) = View (Root views) ()
- routeRequest :: forall (es :: [Effect]) route. (Hyperbole :> es, Route route) => (route -> Eff es Response) -> Eff es Response
- class Route a where
- routeUrl :: Route a => a -> Url
- route :: Route a => a -> Mod c -> View c () -> View c ()
- data Hyperbole (a :: Type -> Type) b
- reqParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es a
- reqParams :: forall (es :: [Effect]). Hyperbole :> es => Eff es QueryText
- request :: forall (es :: [Effect]). Hyperbole :> es => Eff es Request
- lookupParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es (Maybe a)
- hasParam :: Text -> QueryText -> Bool
- formBody :: forall (es :: [Effect]). Hyperbole :> es => Eff es Form
- formData :: forall form (val :: Type -> Type) (es :: [Effect]). (Form form val, Hyperbole :> es) => Eff es (form Identity)
- class ToQueryData a where
- toQueryData :: a -> Text
- class FromQueryData a where
- parseQueryData :: Text -> Either Text a
- notFound :: forall (es :: [Effect]) a. Hyperbole :> es => Eff es a
- redirect :: forall (es :: [Effect]) a. Hyperbole :> es => Url -> Eff es a
- respondEarly :: forall (es :: [Effect]) id. (Hyperbole :> es, HyperView id es) => id -> View id () -> Eff es ()
- class (ViewId id, ViewAction (Action id)) => HyperView id (es :: [Effect]) where
- hyper :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx ()
- class HasViewId (m :: k -> Type) (view :: k) where
- viewId :: m view
- onClick :: ViewAction (Action id) => Action id -> Mod id
- onDblClick :: ViewAction (Action id) => Action id -> Mod id
- onInput :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id
- onKeyDown :: ViewAction (Action id) => Key -> Action id -> Mod id
- onKeyUp :: ViewAction (Action id) => Key -> Action id -> Mod id
- onLoad :: ViewAction (Action id) => Action id -> DelayMs -> Mod id
- onRequest :: Mod id -> Mod id
- data Key
- type DelayMs = Int
- button :: ViewAction (Action id) => Action id -> Mod id -> View id () -> View id ()
- search :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id -> View id ()
- dropdown :: ViewAction (Action id) => (opt -> Action id) -> (opt -> Bool) -> Mod id -> View (Option opt id (Action id)) () -> View id ()
- option :: (ViewAction (Action id), Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) ()
- data Option opt (id :: k) action
- class Form (form :: (Type -> Type) -> Type) (val :: Type -> Type) | form -> val where
- formParse :: Form -> Either Text (form Identity)
- collectValids :: form val -> [val ()]
- genForm :: form val
- genFieldsWith :: form val -> form (FormField val)
- formFields :: forall form (val :: Type -> Type). Form form val => form (FormField val)
- formFieldsWith :: forall form (val :: Type -> Type). Form form val => form val -> form (FormField val)
- data FormField (v :: k -> Type) (a :: k)
- type family Field (context :: Type -> Type) a
- data Identity a
- form :: forall (form :: (Type -> Type) -> Type) (v :: Type -> Type) id. (Form form v, ViewAction (Action id)) => Action id -> Mod id -> View (FormFields id) () -> View id ()
- field :: forall id v a. FormField v a -> (v a -> Mod (FormFields id)) -> View (Input id v a) () -> View (FormFields id) ()
- label :: forall id (v :: Type -> Type) a. Text -> View (Input id v a) ()
- input :: forall id (v :: Type -> Type) a. InputType -> Mod (Input id v a) -> View (Input id v a) ()
- textarea :: forall id (v :: Type -> Type) a. Mod (Input id v a) -> Maybe Text -> View (Input id v a) ()
- submit :: Mod (FormFields id) -> View (FormFields id) () -> View (FormFields id) ()
- placeholder :: Text -> Mod id
- data InputType
- data Validated (a :: k)
- = Invalid Text
- | NotInvalid
- | Valid
- validate :: forall {k} (a :: k). Bool -> Text -> Validated a
- fieldValid :: View (Input id v a) (v a)
- invalidText :: forall a id. View (Input id (Validated :: Type -> Type) a) ()
- anyInvalid :: forall form (val :: Type -> Type). (Form form val, ValidationState val) => form val -> Bool
- session :: forall a (es :: [Effect]). (FromQueryData a, Hyperbole :> es) => Text -> Eff es (Maybe a)
- setSession :: forall a (es :: [Effect]). (ToQueryData a, Hyperbole :> es) => Text -> a -> Eff es ()
- clearSession :: forall (es :: [Effect]). Hyperbole :> es => Text -> Eff es ()
- target :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx ()
- view :: forall (es :: [Effect]). Hyperbole :> es => View () () -> Eff es Response
- class ViewId a
- class ViewAction a
- data Response
- data Root (views :: [Type])
- type HyperViewHandled id ctx = (ElemOr id (Require ctx) (NotHandled id ctx (Require ctx) :: Constraint), CheckDescendents id ctx)
- text :: Text -> View c ()
- data Url = Url {}
- even :: Mod c -> Mod c
- data Sides a
- type Mod context = Attributes context -> Attributes context
- truncate :: Mod c
- odd :: Mod c -> Mod c
- list :: (ToClassName a, Style ListType a) => a -> Mod c
- data Position
- link :: Url -> Mod c -> View c () -> View c ()
- value :: Text -> Mod c
- data Display = Block
- offset :: Sides Length -> Mod c
- pad :: Sides Length -> Mod c
- data View context a
- style :: Text -> View c ()
- layout :: Mod c -> View c () -> View c ()
- name :: Text -> Mod c
- data None = None
- position :: Position -> Mod c
- space :: View c ()
- class ToColor a where
- colorValue :: a -> HexColor
- colorName :: a -> Text
- hover :: Mod c -> Mod c
- raw :: Text -> View c ()
- table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c ()
- row :: Mod c -> View c () -> View c ()
- col :: Mod c -> View c () -> View c ()
- cssResetLink :: Text
- data Align
- newtype HexColor = HexColor Text
- data Media
- data Ms
- data PxRem
- data Length
- media :: Media -> Mod c -> Mod c
- data TransitionProperty
- data ListType
- data Inner = Inner
- data Shadow
- width :: Length -> Mod c
- height :: Length -> Mod c
- minWidth :: Length -> Mod c
- minHeight :: Length -> Mod c
- gap :: Length -> Mod c
- fontSize :: Length -> Mod c
- shadow :: (Style Shadow a, ToClassName a) => a -> Mod c
- rounded :: Length -> Mod c
- bg :: ToColor clr => clr -> Mod ctx
- color :: ToColor clr => clr -> Mod ctx
- bold :: Mod c
- italic :: Mod c
- underline :: Mod c
- opacity :: Float -> Mod c
- border :: Sides PxRem -> Mod c
- borderColor :: ToColor clr => clr -> Mod ctx
- pointer :: Mod c
- transition :: Ms -> TransitionProperty -> Mod c
- textAlign :: Align -> Mod c
- zIndex :: Int -> Mod c
- display :: (Style Display a, ToClassName a) => a -> Mod c
- active :: Mod c -> Mod c
- parent :: Text -> Mod c -> Mod c
- pathUrl :: [Segment] -> Url
- cleanSegment :: Segment -> Segment
- pathSegments :: Text -> [Segment]
- url :: Text -> Url
- renderUrl :: Url -> Text
- context :: View context context
- addContext :: context -> View context () -> View c ()
- tag :: Text -> Mod c -> View c () -> View c ()
- att :: Name -> AttValue -> Mod c
- renderText :: View () () -> Text
- renderLazyText :: View () () -> Text
- renderLazyByteString :: View () () -> ByteString
- data TableColumn c dt
- data TableHead a
- el :: Mod c -> View c () -> View c ()
- el_ :: View c () -> View c ()
- none :: View c ()
- pre :: Mod c -> Text -> View c ()
- code :: Mod c -> Text -> View c ()
- script :: Text -> View c ()
- stylesheet :: Text -> View c ()
- tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] ()
- th :: Mod c -> View c () -> View (TableHead c) ()
- td :: Mod () -> View () () -> View dt ()
- ol :: Mod c -> ListItem c () -> View c ()
- ul :: Mod c -> ListItem c () -> View c ()
- li :: Mod c -> View c () -> ListItem c ()
- data Layer c a
- root :: Mod c
- grow :: Mod c
- scroll :: Mod c
- nav :: Mod c -> View c () -> View c ()
- stack :: Mod c -> Layer c () -> View c ()
- layer :: View c () -> Layer c ()
- popout :: Mod c -> View c () -> Layer c ()
- hide :: Mod c
- flexRow :: Mod c
- flexCol :: Mod c
- module Web.Hyperbole.View.Embed
- class (e :: Effect) :> (es :: [Effect])
- data Eff (es :: [Effect]) a
- type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived
- class Generic a
Introduction
Single Page Applications (SPAs) require the programmer to write two programs: a Javascript client and a Server, which both must conform to a common API
Hyperbole allows us to instead write a single Haskell program which runs exclusively on the server. All user interactions are sent to the server for processing, and a sub-section of the page is updated with the resulting HTML.
There are frameworks that support this in different ways, including HTMX, Phoenix LiveView, and others. Hyperbole has the following advantages
- 100% Haskell
- Type safe views, actions, routes, and forms
- Elegant interface with little boilerplate
- VirtualDOM updates over sockets, fallback to HTTP
- Easy to use
Like HTMX, Hyperbole extends the capability of UI elements, but it uses Haskell's type-system to prevent common errors and provide default functionality. Specifically, a page has multiple update targets called HyperView
s. These are automatically targeted by any UI element that triggers an action inside them. The compiler makes sure that actions and targets match
Like Phoenix LiveView, it upgrades the page to a fast WebSocket connection and uses VirtualDOM for live updates
Like Elm, it uses an update function to process actions, but greatly simplifies the Elm Architecture by remaining stateless. Effects are handled by Effectful. form
s are easy to use with minimal boilerplate
Hyperbole depends heavily on the following frameworks
Getting started
Hyperbole applications run via Warp and WAI
They are divided into top-level Page
s, which can run side effects (like loading data), then respond with an HTML View
. The following application has a single Page
that displays a static "Hello World"
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} module Main where import Web.Hyperbole main = dorun
3000 $ doliveApp
(basicDocument
"Example") (runPage
messagePage) messagePage ::Eff
es (Page
'[]) messagePage = do pure $ do col (pad 10) $ doel
bold "Hello World"
Interactive HyperViews
We can include one or more HyperView
s to add type-safe interactivity to live subsections of the Page
. To start, first define a data type (a ViewId
) that uniquely identifies that subsection of the page:
data Message = Message
deriving (Show, Read, ViewId
)
Make our ViewId
an instance of HyperView
by:
- Create an
Action
type with a constructor for every possible way that the user can interact with it - Write an
update
for eachAction
instanceHyperView
Message es where dataAction
Message = SetMessage Text deriving (Show, Read,ViewAction
)update
(SetMessage t) = pure $el
bold (text t)
Replace the static message with our new HyperView
using hyper
, and add our ViewId
to the Page
type signature. Then add a button
to trigger the Action
:
messagePage ::Eff
es (Page
'[Message]) messagePage = do pure $ do col (pad 10 . gap 10) $ dohyper
Message $ doel
bold "Hello World"button
(SetMessage "Goodbye") (border 1) "Say Goodbye"
The contents of hyper
will be replaced with the result of update
, leaving the rest of the page untouched.
View Functions
Rather than showing a completely different HTML View
on each update, we can create a View Function for our HyperView
. These are pure functions with state parameters, which return a View
. The compiler will tell us if we try to trigger an Action
for a HyperView
that doesn't match our View
context
Each HyperView
should have a main view function that renders it based on its state:
messageView :: Text ->View
Message () messageView m = doel
bold $ text $ "Message: " <> mbutton
(SetMessage "Goodbye") (border 1) "Say Goodbye"
Now we can refactor to use the same view function for both the initial hyper
and the update
. The only thing that will change on an update is the text of the message.
messagePage ::Eff
es (Page
'[Message]) messagePage = do pure $ dohyper
Message $ messageView "Hello" instanceHyperView
Message es where dataAction
Message = SetMessage Text deriving (Show, Read,ViewAction
)update
(SetMessage t) = pure $ messageView t
We can create multiple view functions with our HyperView
as the context
, and factor them however is most convenient.
goodbyeButton ::View
Message () goodbyeButton = dobutton
(SetMessage "Goodbye") (border 1) "Say Goodbye"
We can also create view functions that work in any context.
header :: Text ->View
c () header txt = doel
bold (text txt)
Factored this way, our main View
for Message
becomes:
messageView' :: Text -> View
Message ()
messageView' m = do
header $ "Message: " <> m
goodbyeButton
Managing State
HyperView
s are stateless. They update
based entirely on the Action
. However, we can track simple state by passing it back and forth between the Action
and the View
From Example.Page.Simple
instanceHyperView
Message es where dataAction
Message = Louder Text deriving (Show, Read,ViewAction
)update
(Louder m) = do let new = m <> "!" pure $ messageView new messageView :: Text ->View
Message () messageView m = dobutton
(Louder m) (border 1) "Louder"el
bold $ text $ "Message: " <> m
Side Effects
For any real application with more complex state and data persistence, we need side effects.
Hyperbole relies on Effectful to compose side effects. We can use effects in a Page
or an update
. In this example, each client stores the latest message in their session.
From Example.Page.Simple
messagePage :: (Hyperbole
:> es) =>Eff
es (Page
'[Message]) messagePage = do stored <- session @Text "message" let msg = fromMaybe "Hello" stored pure $ dohyper
Message $ messageView msg instanceHyperView
Message es where dataAction
Message = Louder Text deriving (Show, Read,ViewAction
)update
(Louder m) = do let new = m <> "!" setSession "message" new pure $ messageView new
To use an Effect
other than Hyperbole
, add it as a constraint to the Page
and any HyperView
instances that need it. Then run the effect in your application
From Example.Page.Counter
{-# LANGUAGE UndecidableInstances #-} instance (Reader (TVar Int) :> es, Concurrent :> es) =>HyperView
Counter es where dataAction
Counter = Increment | Decrement deriving (Show, Read,ViewAction
)update
Increment = do n <- modify (+ 1) pure $ viewCount nupdate
Decrement = do n <- modify (subtract 1) pure $ viewCount n
Databases and Custom Effects
A database is no different from any other Effect
. We recommend you create a custom effect to describe high-level data operations.
data Todos :: Effect where
LoadAll :: Todos m [Todo]
Save :: Todo -> Todos m ()
Remove :: TodoId -> Todos m ()
Create :: Text -> Todos m TodoId
loadAll :: (Todos :> es) => Eff
es [Todo]
loadAll = send LoadAll
Once you've created an Effect
, you add it to any HyperView
or Page
as a constraint.
From Example.Page.Todo:
{-# LANGUAGE UndecidableInstances #-} simplePage :: (Todos :> es) =>Eff
es (Page
'[AllTodos, TodoView]) simplePage = do todos <- Todos.loadAll pure $ dohyper
AllTodos $ todosView FilterAll todos
When you create your Application
, run any Effect
s you need. Here we are using a runner that implements the effect with sessions from Hyperbole
, but you could write a different runner that connects to a database instead.
From example/Main.hs:
app :: Application app = do liveApp toDocument (runApp . routeRequest $ router) where runApp :: (Hyperbole :> es, IOE :> es) => Eff (Concurrent : Todos : es) a -> Eff es a runApp = runTodosSession . runConcurrent
Implementing a database runner for a custom Effect
is beyond the scope of this documentation, but see the following:
- Effectful.Dynamic.Dispatch - Introduction to Effects
- NSO.Data.Datasets - Production Data Effect with a database runner
- Effectful.Rel8 - Effect for the Rel8 Postgres Library
Multiple HyperViews
We can add as many HyperView
s to a page as we want. Let's create another HyperView
for a simple counter
data Count = Count deriving (Show, Read,ViewId
) instanceHyperView
Count es where dataAction
Count = Increment Int | Decrement Int deriving (Show, Read,ViewAction
)update
(Increment n) = do pure $ countView (n + 1)update
(Decrement n) = do pure $ countView (n - 1) countView :: Int ->View
Count () countView n = doel
_ $ text $ pack $ show nbutton
(Increment n) (border 1) "Increment"button
(Decrement n) (border 1) "Decrement"
We can use both Message
and Count
HyperView
s in our page, and they will update independently:
page ::Eff
es (Page
'[Message, Count]) page = do pure $ do row id $ dohyper
Message $ messageView "Hello"hyper
Count $ countView 0
Copies
We can embed multiple copies of the same HyperView
as long as the value of ViewId
is unique. Let's update Message
to allow for more than one value:
data Message = Message1 | Message2
deriving (Show, Read, ViewId
)
Now we can embed multiple Message
HyperView
s into the same page. Each will update independently.
messagePage ::Eff
es (Page
'[Message]) messagePage = do pure $ dohyper
Message1 $ messageView "Hello"hyper
Message2 $ messageView "World!"
This is especially useful if we put identifying information in our ViewId
, such as a database id. The Contacts Example uses this to allow the user to edit multiple contacts on the same page. The viewId
function gives us access to that info
From Example.Contacts
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 $ contactEdit u Save -> do delay 1000 unew <- parseUser uid Users.save unew pure $ contactView unew
Nesting
We can nest smaller, specific HyperView
s inside of a larger parent. You might need this technique to display a list of items which need to update themselves
Let's imagine we want to display a list of Todos. The user can mark individual todos complete, and have them update independently. The specific HyperView
might look like this:
From Example.Intro.Nested
data TodoItem = TodoItem deriving (Show, Read,ViewId
) instanceHyperView
TodoItem es where dataAction
TodoItem = Complete Todo deriving (Show, Read,ViewAction
)update
(Complete todo) = do let new = todo{completed = True} pure $ todoView new
But we also want the entire list to refresh when a user adds a new todo. We need to create a parent HyperView
for the whole list.
List all allowed nested views by adding them to Require
data AllTodos = AllTodos deriving (Show, Read,ViewId
) instanceHyperView
AllTodos es where type Require AllTodos = '[TodoItem] dataAction
AllTodos = AddTodo Text [Todo] deriving (Show, Read,ViewAction
)update
(AddTodo txt todos) = do let new = Todo txt False : todos pure $ todosView new
Then we can embed the child HyperView
into the parent with hyper
todosView :: [Todo] ->View
AllTodos () todosView todos = do forM_ todos $ todo -> dohyper
TodoItem $ todoView todobutton
(AddTodo "Shopping" todos) id "Add Shopping"
See this technique used in the TodoMVC Example
Functions, not Components
You may be tempted to use HyperView
s to create reusable Components. This leads to object-oriented designs that don't compose well. We are using a functional language, so our main unit of reuse should be functions!
We showed earlier that we can write a View Function with a generic context
that we can reuse in any view. A function like this might help us reuse styles:
header :: Text ->View
c () header txt = doel
bold (text txt)
What if we want to reuse functionality too? We can pass an Action
into the view function as a parameter:
styledButton :: (ViewAction
(Action
id)) =>Action
id -> Text ->View
id () styledButton clickAction lbl = dobutton
clickAction (pad 10 . bg Primary . hover (bg PrimaryLight) . rounded 5) (text lbl)
We can create more complex view functions by passing state in as a parameter. Here's a button that toggles between a checked and unchecked state:
toggleCheckBtn :: (ViewAction
(Action
id)) =>Action
id -> Bool ->View
id () toggleCheckBtn clickAction isSelected = dobutton
clickAction (width 32 . height 32 . border 1 . rounded 100) contents where contents = if isSelected then Icon.check else " "
Don't leverage HyperView
s for code reuse. Think about which subsections of a page ought to update independently. Those are HyperView
s. If you need reusable functionality, use view functions instead.
- See Example.View.DataTable for a more complex example
Pages
An app has multiple Page
s with different Route
s that each map to a unique url path:
data AppRoute
= Message -- /message
| Counter -- /counter
deriving (Generic, Eq, Route
)
When we define our app, we define a function that maps a Route
to a Page
main = dorun
3000 $ doliveApp
(basicDocument
"Multiple Pages") (routeRequest
router) where router Message =runPage
Message.page router Counter =runPage
Counter.page
Each Page
is completely independent. The web page is freshly reloaded each time you switch routes. We can add type-safe links to other pages using route
menu ::View
c () menu = doroute
Message id "Link to /message"route
Counter id "Link to /counter"
If you need the same header or menu on all pages, use a view function:
exampleLayout ::View
c () ->View
c () exampleLayout content = dolayout
id $ doel
(border 1) "My Website Header" row id $ do menu content examplePage ::Eff
es (Page
'[]) examplePage = do pure $ exampleLayout $ doel
_ "page contents"
As shown above, each Page
can contain multiple interactive HyperView
s to add interactivity
Examples
https://docs.hyperbole.live is full of live examples demonstrating different features. Each example includes a link to the source code. Some highlights:
The National Solar Observatory uses Hyperbole for the Level 2 Data creation tool for the DKIST telescope. It is completely open source. This production application contains complex interfaces, workers, databases, and more.
Application
liveApp :: (ByteString -> ByteString) -> Eff '[Hyperbole, Server, Concurrent, IOE] Response -> Application Source #
Turn one or more Page
s into a Wai Application. Respond using both HTTP and WebSockets
main = do run 3000 $ do liveApp (basicDocument "Example") (runPage messagePage)
run :: Port -> Application -> IO () #
Run an Application
on the given port.
This calls runSettings
with defaultSettings
.
basicDocument :: Text -> ByteString -> ByteString Source #
wrap HTML fragments in a simple document with a custom title and include required embeds
liveApp
(basicDocument "App Title") (routeRequest
router)
You may want to specify a custom document function instead:
myDocument :: ByteString -> ByteString myDocument content = [i|<html> <head> <title>#{title}</title> <script type="text/javascript">#{scriptEmbed}</script> <style type="text/css">#{cssResetEmbed}</style> </head> <body>#{content}</body> </html>|]
runPage :: forall (views :: [Type]) (es :: [Effect]). (Hyperbole :> es, RunHandlers views es) => Eff es (Page views) -> Eff es Response Source #
Type-Safe Routes
routeRequest :: forall (es :: [Effect]) route. (Hyperbole :> es, Route route) => (route -> Eff es Response) -> Eff es Response Source #
Route URL patterns to different pages
import Page.Messages qualified as Messages import Page.Users qualified as Users data AppRoute = Main | Messages | Users UserId deriving (Eq, Generic,Route
) router :: (Hyperbole
:> es) => AppRoute ->Eff
esResponse
router Messages =page
Messages.page router (Users uid) =page
$ Users.page uid router Main = doview
$ doel_
"click a link below to visit a page"route
Messages id "Messages" main = dorun
3000 $ doliveApp
(basicDocument
"Example") (routeRequest router)
Derive this class to use a sum type as a route. Constructors and Selectors map intuitively to url patterns
data AppRoute = HomePage | Users | User Int deriving (Generic, Route) / -> HomePage /users/ -> Users /user/100 -> User 100
Nothing
The route to use if attempting to match on empty segments
matchRoute :: [Segment] -> Maybe a Source #
Try to match segments to a route
routePath :: a -> [Segment] Source #
Map a route to segments
route :: Route a => a -> Mod c -> View c () -> View c () Source #
A hyperlink to another route
>>>
route (User 100) id "View User"
<a href="/user/100">View User</a>
Hyperbole Effect
data Hyperbole (a :: Type -> Type) b Source #
In any load
or handle
, you can use this Effect to get extra request information or control the response manually.
For most Page
s, you won't need to use this effect directly. Use custom Route
s for request info, and return View
s to respond
Instances
type DispatchOf Hyperbole Source # | |
Defined in Web.Hyperbole.Effect.Hyperbole |
Request
reqParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es a Source #
reqParams :: forall (es :: [Effect]). Hyperbole :> es => Eff es QueryText Source #
Return the entire Query
myPage ::Page
esResponse
myPage = doload
$ do q <- reqParams caselookupParam
"token" q of Nothing -> pure $ errorView "Missing Token in Query String" Just t -> do sideEffectUsingToken token pure myPageView
request :: forall (es :: [Effect]). Hyperbole :> es => Eff es Request Source #
Return all information about the Request
lookupParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es (Maybe a) Source #
formBody :: forall (es :: [Effect]). Hyperbole :> es => Eff es Form Source #
Return the request body as a Web.FormUrlEncoded.Form
Prefer using Type-Safe Form
s when possible
formData :: forall form (val :: Type -> Type) (es :: [Effect]). (Form form val, Hyperbole :> es) => Eff es (form Identity) Source #
class ToQueryData a where Source #
Reimplement ToHttpApiData
based on Show
Nothing
toQueryData :: a -> Text Source #
default toQueryData :: Show a => a -> Text Source #
Instances
class FromQueryData a where Source #
Reimplement FromHttpApiData
based on Read
Nothing
Instances
Response
notFound :: forall (es :: [Effect]) a. Hyperbole :> es => Eff es a Source #
Respond immediately with 404 Not Found
userLoad :: (Hyperbole :> es, Users :> es) => UserId -> Eff es User userLoad uid = do mu <- send (LoadUser uid) maybe notFound pure mu myPage :: (Hyperbole :> es, Users :> es) => Eff es View myPage = do load $ do u <- userLoad 100 -- skipped if user = Nothing pure $ userView u
redirect :: forall (es :: [Effect]) a. Hyperbole :> es => Url -> Eff es a Source #
Redirect immediately to the Url
respondEarly :: forall (es :: [Effect]) id. (Hyperbole :> es, HyperView id es) => id -> View id () -> Eff es () Source #
Respond with the given view, and stop execution
HyperView
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 Int deriving (Generic,Param
) data MessageAction = Louder Text | ClearMessage deriving (Generic,Param
) instance HyperView Message where type Action Message = MessageAction
Instances
HyperView (Root views) es Source # | |||||||||
Defined in Web.Hyperbole.HyperView
|
Events
onDblClick :: ViewAction (Action id) => Action id -> Mod id Source #
onInput :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id Source #
Run an action when the user types into an input
or textarea
.
WARNING: a short delay can result in poor performance. It is not recommended to set the value
of the input
input (onInput OnSearch) 250 id
onLoad :: ViewAction (Action id) => Action id -> DelayMs -> Mod 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 $ doel
bold
"Current Message. Reloading in 1s"el_
(text
m)
onRequest :: Mod id -> Mod id Source #
Apply a Mod only when a request is in flight
myView = do
el (hide . onRequest flexCol) el_
"Loading..."
el (onRequest hide) Loaded
ArrowDown | |
ArrowUp | |
ArrowLeft | |
ArrowRight | |
Enter | |
Space | |
Escape | |
Alt | |
CapsLock | |
Control | |
Fn | |
Meta | |
Shift | |
OtherKey Text |
Interactive Elements
button :: ViewAction (Action id) => Action id -> Mod id -> View id () -> View id () Source #
<button> HTML tag which sends the action when pressed
button SomeAction (border 1) "Click Me"
search :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id -> View id () Source #
A live search field
dropdown :: ViewAction (Action id) => (opt -> Action id) -> (opt -> Bool) -> Mod id -> 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 :: (ViewAction (Action id), Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) () Source #
Type-Safe Forms
Painless forms with type-checked field names, and support for validation. See Example.Forms
class Form (form :: (Type -> Type) -> Type) (val :: Type -> Type) | form -> val where Source #
Parse a FormField
from the request
formAction :: (Hyperbole
:> es,UserDB
:> es) => FormView -> FormAction ->Eff
es (View
FormView ()) formAction _ SignUp = do a <- formField @Age u <- formField @User saveUserToDB u a pure $ el_ "Saved!"
Nothing
formParse :: Form -> Either Text (form Identity) Source #
default formParse :: (Generic (form Identity), GFormParse (Rep (form Identity))) => Form -> Either Text (form Identity) Source #
collectValids :: form val -> [val ()] Source #
default collectValids :: (Generic (form val), GCollect (Rep (form val)) val) => form val -> [val ()] Source #
genFieldsWith :: form val -> form (FormField val) Source #
formFields :: forall form (val :: Type -> Type). Form form val => form (FormField val) Source #
Generate FormFields for the given instance of Form
, with no validation information
let f = formFields @UserForm form @UserForm Submit id $ do field f.user id $ do label "Username" input Username (placeholder "Username")
formFieldsWith :: forall form (val :: Type -> Type). Form form val => form val -> form (FormField val) Source #
Generate FormFields for the givne instance of Form
from validation data
let valids = UserForm { user = Valid, age = Invalid "must be 20 years old" } let f = formFieldsWith @UserForm valids form @UserForm Submit id $ do field f.user id $ do label "Username" input Username (placeholder "Username")
type family Field (context :: Type -> Type) a Source #
Instances
type Field Identity a Source # | |
Defined in Web.Hyperbole.View.Forms | |
type Field Maybe a Source # | |
Defined in Web.Hyperbole.View.Forms | |
type Field (Either String) a Source # | |
type Field (FieldName :: Type -> Type) a Source # | |
type Field (Validated :: Type -> Type) a Source # | |
type Field (FormField v) a Source # | |
Defined in Web.Hyperbole.View.Forms |
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Instances
Form View
form :: forall (form :: (Type -> Type) -> Type) (v :: Type -> Type) id. (Form form v, ViewAction (Action id)) => Action id -> Mod id -> View (FormFields id) () -> View id () Source #
Type-safe <form>. Calls (Action id) on submit
userForm ::Validation
->View
FormView () userForm v = do form Signup v id $ do el Style.h1 "Sign Up"field
@User id Style.invalid $ dolabel
"Username"input
Username (placeholder
"username") el_invalidText
field
@Age id Style.invalid $ dolabel
"Age"input
Number (placeholder
"age") el_invalidText
submit
(border 1) "Submit"
field :: forall id v a. FormField v a -> (v a -> Mod (FormFields id)) -> View (Input id v a) () -> View (FormFields id) () Source #
input :: forall id (v :: Type -> Type) a. InputType -> Mod (Input id v a) -> View (Input id v a) () Source #
input for a field
textarea :: forall id (v :: Type -> Type) a. Mod (Input id v a) -> Maybe Text -> View (Input id v a) () Source #
textarea for a field
submit :: Mod (FormFields id) -> View (FormFields id) () -> View (FormFields id) () Source #
placeholder :: Text -> Mod id Source #
Choose one for input
s to give the browser autocomplete hints
Handlers
Validation
data Validated (a :: k) Source #
Validation results for a form
data UserForm f = UserForm { username :: Field f , age :: Field f Int } deriving (Generic) validateUsername :: Username -> Validated Username validateUsername (Username u) = mconcat [ validate (T.elem ' ' u) "Username must not contain spaces" , validate (T.length u < 4) "Username must be at least 4 chars" , if u == "admin" || u == "guest" then Invalid "Username is already in use" else Valid ] formAction :: (Hyperbole
:> es,UserDB
:> es) => FormView -> FormAction ->Eff
es (View
FormView ()) formAction _ SignUp = do u <-formField
@Age case validateUser u a ofValidation
[] -> successView errs -> userForm v
validate :: forall {k} (a :: k). Bool -> Text -> Validated a Source #
specify a check for a Validation
fieldValid :: View (Input id v a) (v a) Source #
anyInvalid :: forall form (val :: Type -> Type). (Form form val, ValidationState val) => form val -> Bool Source #
Sessions
session :: forall a (es :: [Effect]). (FromQueryData a, Hyperbole :> es) => Text -> Eff es (Maybe a) Source #
Lookup a session variable by keyword
setSession :: forall a (es :: [Effect]). (ToQueryData a, Hyperbole :> es) => Text -> a -> Eff es () Source #
Set a session variable by keyword
clearSession :: forall (es :: [Effect]). Hyperbole :> es => Text -> Eff es () Source #
Clear a session variable
Advanced
target :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx () 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"
view :: forall (es :: [Effect]). Hyperbole :> es => View () () -> Eff es Response Source #
Manually set the response to the given view. Normally you return a View
from load
or handle
instead of using this
class ViewAction a Source #
Instances
ViewAction () Source # | |
Defined in Web.Hyperbole.HyperView | |
ViewAction (Action (Root views)) Source # | |
Valid responses for a Hyperbole
effect. Use notFound
, etc instead. Reminds you to use load
in your Page
myPage :: (Hyperbole :> es) => Page es Response myPage = do -- compiler error: () does not equal Response pure ()
data Root (views :: [Type]) Source #
The top-level view created by load
. Carries the views in its type to check that we handled all our views
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 HyperViewHandled id ctx = (ElemOr id (Require ctx) (NotHandled id ctx (Require ctx) :: Constraint), CheckDescendents id ctx) Source #
Exports
Web.View
Hyperbole is tightly integrated with Web.View for HTML generation
Add text to a view. Not required for string literals
el_ $ do "Hello: " text user.name
Options for styles that support specifying various sides. This has a "fake" Num instance to support literals
border 5 border (X 2) border (TRBL 0 5 0 0)
type Mod context = Attributes context -> Attributes context #
Element functions expect a modifier function as their first argument. These can add attributes and classes. Combine multiple Mod
s with (.
)
userEmail :: User -> View c () userEmail user = input (fontSize 16 . active) (text user.email) where active = isActive user then bold else id
If you don't want to specify any attributes, you can use id
plainView :: View c () plainView = el id "No styles"
list :: (ToClassName a, Style ListType a) => a -> Mod c #
Set the list style of an item
ol id $ do li (list Decimal) "First" li (list Decimal) "Second" li (list Decimal) "Third"
Instances
Show Position | |
ToClassName Position | |
Defined in Web.View.Style toClassName :: Position -> ClassName # | |
ToStyleValue Position | |
Defined in Web.View.Style toStyleValue :: Position -> StyleValue # |
Instances
Show Display | |
ToClassName Display | |
Defined in Web.View.Style toClassName :: Display -> ClassName # | |
ToStyleValue Display | |
Defined in Web.View.Style toStyleValue :: Display -> StyleValue # | |
Style Display Display | |
Defined in Web.View.Style styleValue :: Display -> StyleValue # | |
Style Display None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
pad :: Sides Length -> Mod c #
Space surrounding the children of the element
To create even spacing around and between all elements:
col (pad 10 . gap 10) $ do el_ "one" el_ "two" el_ "three"
Views are HTML fragments that carry all CSS
used by any child element.
view :: View c () view = col (pad 10 . gap 10) $ do el bold "Hello" el_ "World"
They can also have a context which can be used to create type-safe or context-aware elements. See context
or table
for an example
Instances
HasViewId (View ctx :: Type -> Type) (ctx :: Type) Source # | |
Defined in Web.Hyperbole.HyperView | |
Applicative (View context) | |
Defined in Web.View.View | |
Functor (View context) | |
Monad (View context) | |
IsString (View context ()) | |
Defined in Web.View.View fromString :: String -> View context () # |
layout :: Mod c -> View c () -> View c () #
We can intuitively create layouts with combinations of row
, col
, stack
, grow
, and space
Wrap main content in layout
to allow the view to consume vertical screen space
holygrail ::View
c () holygrail =layout
id $ dorow
section "Top Bar"row
grow
$ docol
section "Left Sidebar"col
(section .grow
) "Main Content"col
section "Right Sidebar"row
section "Bottom Bar" where section =border
1
Instances
Show None | |
ToClassName None | |
Defined in Web.View.Types toClassName :: None -> ClassName # | |
ToStyleValue None | |
Defined in Web.View.Types toStyleValue :: None -> StyleValue # | |
Style Display None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style ListType None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style Shadow None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
ToColor allows you to create a type containing your application's colors:
data AppColor = White | Primary | Dark instance ToColor AppColor where colorValue White = "#FFF" colorValue Dark = "#333" colorValue Primary = "#00F" hello :: View c () hello = el (bg Primary . color White) "Hello"
Apply when hovering over an element
el (bg Primary . hover (bg PrimaryLight)) "Hover"
Embed static, unescaped HTML or SVG. Take care not to use raw
with user-generated content.
spinner = raw "<svg>...</svg>"
table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c () #
Create a type safe data table by specifying columns
usersTable :: [User] -> View c () usersTable us = do table id us $ do tcol (th hd "Name") $ \u -> td cell $ text u.name tcol (th hd "Email") $ \u -> td cell $ text u.email where hd = cell . bold cell = pad 4 . border 1
row :: Mod c -> View c () -> View c () #
Lay out children in a row
row id $ do el_ "Left" space el_ "Right"
col :: Mod c -> View c () -> View c () #
Lay out children in a column.
col grow $ do el_ "Top" space el_ "Bottom"
cssResetLink :: Text #
Alternatively, the reset is available on a CDN
import Data.String.Interpolate (i) toDocument :: ByteString -> ByteString toDocument cnt = [i|<html> <head> <link rel="stylesheet" href="#{cssResetLink}"> </head> <body>#{cnt}</body> </html>|]
Instances
Show Align | |
ToClassName Align | |
Defined in Web.View.Types toClassName :: Align -> ClassName # | |
ToStyleValue Align | |
Defined in Web.View.Types toStyleValue :: Align -> StyleValue # |
Hexidecimal Color. Can be specified with or without the leading #
. Recommended to use an AppColor type instead of manually using hex colors. See ToColor
Instances
IsString HexColor | |
Defined in Web.View.Types fromString :: String -> HexColor # | |
Show HexColor | |
ToClassName HexColor | |
Defined in Web.View.Types toClassName :: HexColor -> ClassName # | |
ToColor HexColor | |
Defined in Web.View.Types | |
ToStyleValue HexColor | |
Defined in Web.View.Types toStyleValue :: HexColor -> StyleValue # |
Media allows for responsive designs that change based on characteristics of the window. See Layout Example
Milliseconds, used for transitions
Instances
Num Ms | |
Show Ms | |
ToClassName Ms | |
Defined in Web.View.Types toClassName :: Ms -> ClassName # | |
ToStyleValue Ms | |
Defined in Web.View.Types toStyleValue :: Ms -> StyleValue # |
Px, converted to Rem. Allows for the user to change the document font size and have the app scale accordingly. But allows the programmer to code in pixels to match a design
Instances
Enum PxRem | |
Num PxRem | |
Integral PxRem | |
Real PxRem | |
Defined in Web.View.Types toRational :: PxRem -> Rational # | |
Show PxRem | |
Eq PxRem | |
Ord PxRem | |
ToClassName PxRem | |
Defined in Web.View.Types toClassName :: PxRem -> ClassName # | |
ToStyleValue PxRem | |
Defined in Web.View.Types toStyleValue :: PxRem -> StyleValue # |
Instances
Num Length | |
Show Length | |
ToClassName Length | |
Defined in Web.View.Types toClassName :: Length -> ClassName # | |
ToStyleValue Length | |
Defined in Web.View.Types toStyleValue :: Length -> StyleValue # |
media :: Media -> Mod c -> Mod c #
Apply when the Media matches the current window. This allows for responsive designs
el (width 100 . media (MinWidth 800) (width 400)) "Big if window > 800"
data TransitionProperty #
Instances
Show TransitionProperty | |
Defined in Web.View.Style showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # |
Instances
Show ListType | |
ToClassName ListType | |
Defined in Web.View.Style toClassName :: ListType -> ClassName # | |
ToStyleValue ListType | |
Defined in Web.View.Style toStyleValue :: ListType -> StyleValue # | |
Style ListType ListType | |
Defined in Web.View.Style styleValue :: ListType -> StyleValue # | |
Style ListType None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # |
Instances
Show Inner | |
ToClassName Inner | |
Defined in Web.View.Style toClassName :: Inner -> ClassName # | |
Style Shadow Inner | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue # |
Instances
Style Shadow Inner | |
Defined in Web.View.Style styleValue :: Inner -> StyleValue # | |
Style Shadow None | |
Defined in Web.View.Style styleValue :: None -> StyleValue # | |
Style Shadow () | |
Defined in Web.View.Style styleValue :: () -> StyleValue # |
minHeight :: Length -> Mod c #
Allow height to grow to contents but not shrink any smaller than value
shadow :: (Style Shadow a, ToClassName a) => a -> Mod c #
Add a drop shadow to an element
input (shadow Inner) "Inset Shadow" button (shadow ()) "Click Me"
border :: Sides PxRem -> Mod c #
Set a border around the element
el (border 1) "all sides" el (border (X 1)) "only left and right"
borderColor :: ToColor clr => clr -> Mod ctx #
Set a border color. See ToColor
Use a button-like cursor when hovering over the element
Button-like elements:
btn = pointer . bg Primary . hover (bg PrimaryLight) options = row id $ do el btn "Login" el btn "Sign Up"
transition :: Ms -> TransitionProperty -> Mod c #
Animate changes to the given property
el (transition 100 (Height 400)) "Tall" el (transition 100 (Height 100)) "Small"
display :: (Style Display a, ToClassName a) => a -> Mod c #
Set container display
el (display None) HIDDEN
parent :: Text -> Mod c -> Mod c #
Apply when the element is somewhere inside an anscestor.
For example, the HTMX library applies an "htmx-request" class to the body when a request is pending. We can use this to create a loading indicator
el (pad 10) $ do el (parent "htmx-request" flexRow . hide) "Loading..." el (parent "htmx-request" hide . flexRow) "Normal Content"
cleanSegment :: Segment -> Segment #
pathSegments :: Text -> [Segment] #
context :: View context context #
Views have a Reader
built-in for convienient access to static data, and to add type-safety to view functions. See 'Web.View.Element.ListItem and https://hackage.haskell.org/package/hyperbole/docs/Web-Hyperbole.html
numberView :: View Int () numberView = do num <- context el_ $ do "Number: " text (pack $ show num)
addContext :: context -> View context () -> View c () #
tag :: Text -> Mod c -> View c () -> View c () #
Create a new element constructor with the given tag name
aside :: Mod c -> View c () -> View c () aside = tag "aside"
att :: Name -> AttValue -> Mod c #
Set an attribute, replacing existing value
hlink :: Text -> View c () -> View c () hlink url content = tag "a" (att "href" url) content
renderText :: View () () -> Text #
Renders a View
as HTML with embedded CSS class definitions
>>>
renderText $ el bold "Hello"
<style type='text/css'>.bold { font-weight:bold }</style> <div class='bold'>Hello</div>
renderLazyText :: View () () -> Text #
renderLazyByteString :: View () () -> ByteString #
data TableColumn c dt #
stylesheet :: Text -> View c () #
tcol :: forall dt c. View (TableHead c) () -> (dt -> View dt ()) -> Eff '[Writer [TableColumn c dt]] () #
ol :: Mod c -> ListItem c () -> View c () #
List elements do not include any inherent styling but are useful for accessibility. See list
.
ol id $ do let nums = list Decimal li nums "one" li nums "two" li nums "three"
stack :: Mod c -> Layer c () -> View c () #
Stack children on top of each other. Each child has the full width. See popout
stack id $ do row id "Background" row (bg Black . opacity 0.5) "Overlay"
Embeds
Embedded CSS and Javascript to include in your document function. See basicDocument
module Web.Hyperbole.View.Embed
Effectful
class (e :: Effect) :> (es :: [Effect]) #
A constraint that requires that a particular effect e
is a member of the
type-level list es
. This is used to parameterize an Eff
computation over an arbitrary list of effects, so long as e
is somewhere
in the list.
For example, a computation that only needs access to a mutable value of type
Integer
would have the following type:
State
Integer
:>
es =>Eff
es ()
Instances
(TypeError (('Text "There is no handler for '" ':<>: 'ShowType e) ':<>: 'Text "' in the context") :: Constraint) => e :> ('[] :: [Effect]) | |
Defined in Effectful.Internal.Effect reifyIndex :: Int # | |
e :> (e ': es) | |
Defined in Effectful.Internal.Effect reifyIndex :: Int # | |
e :> es => e :> (x ': es) | |
Defined in Effectful.Internal.Effect reifyIndex :: Int # |
The Eff
monad provides the implementation of a computation that performs
an arbitrary set of effects. In
, Eff
es aes
is a type-level list that
contains all the effects that the computation may perform. For example, a
computation that produces an Integer
by consuming a String
from the
global environment and acting upon a single mutable value of type Bool
would have the following type:
(Reader
String
:>
es,State
Bool
:>
es) =>Eff
esInteger
Abstracting over the list of effects with (:>)
:
- Allows the computation to be used in functions that may perform other effects.
- Allows the effects to be handled in any order.
Instances
IOE :> es => MonadBaseControl IO (Eff es) | Instance included for compatibility with existing code. Usage of Note: the unlifting strategy for |
IOE :> es => MonadBase IO (Eff es) | Instance included for compatibility with existing code. Usage of |
Defined in Effectful.Internal.Monad | |
HasViewId (Eff (Reader view ': es) :: Type -> Type) (view :: Type) Source # | |
Fail :> es => MonadFail (Eff es) | |
Defined in Effectful.Internal.Monad | |
MonadFix (Eff es) | |
Defined in Effectful.Internal.Monad | |
IOE :> es => MonadIO (Eff es) | |
Defined in Effectful.Internal.Monad | |
NonDet :> es => Alternative (Eff es) | Since: effectful-core-2.2.0.0 |
Applicative (Eff es) | |
Functor (Eff es) | |
Monad (Eff es) | |
NonDet :> es => MonadPlus (Eff es) | Since: effectful-core-2.2.0.0 |
MonadCatch (Eff es) | |
Defined in Effectful.Internal.Monad | |
MonadMask (Eff es) | |
Defined in Effectful.Internal.Monad mask :: HasCallStack => ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b # uninterruptibleMask :: HasCallStack => ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b # generalBracket :: HasCallStack => Eff es a -> (a -> ExitCase b -> Eff es c) -> (a -> Eff es b) -> Eff es (b, c) # | |
MonadThrow (Eff es) | |
Defined in Effectful.Internal.Monad throwM :: (HasCallStack, Exception e) => e -> Eff es a # | |
IOE :> es => MonadUnliftIO (Eff es) | Instance included for compatibility with existing code. Usage of Note: the unlifting strategy for |
Defined in Effectful.Internal.Monad | |
Prim :> es => PrimMonad (Eff es) | |
Monoid a => Monoid (Eff es a) | |
Semigroup a => Semigroup (Eff es a) | |
type PrimState (Eff es) | |
Defined in Effectful.Internal.Monad | |
type StM (Eff es) a | |
Defined in Effectful.Internal.Monad |
Other
type Application = Request -> (Response -> IO ResponseReceived) -> IO ResponseReceived #
The WAI application.
Note that, since WAI 3.0, this type is structured in continuation passing
style to allow for proper safe resource handling. This was handled in the
past via other means (e.g., ResourceT
). As a demonstration:
app :: Application app req respond = bracket_ (putStrLn "Allocating scarce resource") (putStrLn "Cleaning up") (respond $ responseLBS status200 [] "Hello World")
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
Generic All | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic Any | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic Version | |||||
Defined in Data.Version
| |||||
Generic Void | |||||
Generic ByteOrder | |||||
Defined in GHC.ByteOrder | |||||
Generic Fingerprint | |||||
Defined in GHC.Generics
from :: Fingerprint -> Rep Fingerprint x # to :: Rep Fingerprint x -> Fingerprint # | |||||
Generic Associativity | |||||
Defined in GHC.Generics
from :: Associativity -> Rep Associativity x # to :: Rep Associativity x -> Associativity # | |||||
Generic DecidedStrictness | |||||
Defined in GHC.Generics
from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic Fixity | |||||
Defined in GHC.Generics
| |||||
Generic SourceStrictness | |||||
Defined in GHC.Generics
from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in GHC.Generics
from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic ExitCode | |||||
Defined in GHC.IO.Exception
| |||||
Generic CCFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ConcFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic DebugFlags | |||||
Defined in GHC.RTS.Flags
from :: DebugFlags -> Rep DebugFlags x # to :: Rep DebugFlags x -> DebugFlags # | |||||
Generic DoCostCentres | |||||
Defined in GHC.RTS.Flags
from :: DoCostCentres -> Rep DoCostCentres x # to :: Rep DoCostCentres x -> DoCostCentres # | |||||
Generic DoHeapProfile | |||||
Defined in GHC.RTS.Flags
from :: DoHeapProfile -> Rep DoHeapProfile x # to :: Rep DoHeapProfile x -> DoHeapProfile # | |||||
Generic DoTrace | |||||
Defined in GHC.RTS.Flags
| |||||
Generic GCFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic GiveGCStats | |||||
Defined in GHC.RTS.Flags
from :: GiveGCStats -> Rep GiveGCStats x # to :: Rep GiveGCStats x -> GiveGCStats # | |||||
Generic MiscFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ParFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic ProfFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic RTSFlags | |||||
Defined in GHC.RTS.Flags
| |||||
Generic TickyFlags | |||||
Defined in GHC.RTS.Flags
from :: TickyFlags -> Rep TickyFlags x # to :: Rep TickyFlags x -> TickyFlags # | |||||
Generic TraceFlags | |||||
Defined in GHC.RTS.Flags
from :: TraceFlags -> Rep TraceFlags x # to :: Rep TraceFlags x -> TraceFlags # | |||||
Generic SrcLoc | |||||
Defined in GHC.Generics
| |||||
Generic GCDetails | |||||
Defined in GHC.Stats
| |||||
Generic RTSStats | |||||
Defined in GHC.Stats
| |||||
Generic GeneralCategory | |||||
Defined in GHC.Generics
from :: GeneralCategory -> Rep GeneralCategory x # to :: Rep GeneralCategory x -> GeneralCategory # | |||||
Generic ShortByteString | |||||
Defined in Data.ByteString.Short.Internal
from :: ShortByteString -> Rep ShortByteString x # to :: Rep ShortByteString x -> ShortByteString # | |||||
Generic Limit | |||||
Defined in Effectful.Internal.Unlift
| |||||
Generic Persistence | |||||
Defined in Effectful.Internal.Unlift
from :: Persistence -> Rep Persistence x # to :: Rep Persistence x -> Persistence # | |||||
Generic UnliftStrategy | |||||
Defined in Effectful.Internal.Unlift
from :: UnliftStrategy -> Rep UnliftStrategy x # to :: Rep UnliftStrategy x -> UnliftStrategy # | |||||
Generic OnEmptyPolicy | |||||
Defined in Effectful.NonDet
from :: OnEmptyPolicy -> Rep OnEmptyPolicy x # to :: Rep OnEmptyPolicy x -> OnEmptyPolicy # | |||||
Generic OsChar | |||||
Defined in System.OsString.Internal.Types.Hidden
| |||||
Generic OsString | |||||
Defined in System.OsString.Internal.Types.Hidden
| |||||
Generic PosixChar | |||||
Defined in System.OsString.Internal.Types.Hidden
| |||||
Generic PosixString | |||||
Defined in System.OsString.Internal.Types.Hidden
from :: PosixString -> Rep PosixString x # to :: Rep PosixString x -> PosixString # | |||||
Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden
from :: WindowsChar -> Rep WindowsChar x # to :: Rep WindowsChar x -> WindowsChar # | |||||
Generic WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden
from :: WindowsString -> Rep WindowsString x # to :: Rep WindowsString x -> WindowsString # | |||||
Generic ForeignSrcLang | |||||
Defined in GHC.ForeignSrcLang.Type
from :: ForeignSrcLang -> Rep ForeignSrcLang x # to :: Rep ForeignSrcLang x -> ForeignSrcLang # | |||||
Generic Extension | |||||
Defined in GHC.LanguageExtensions.Type
| |||||
Generic Ordering | |||||
Defined in GHC.Generics | |||||
Generic SrcLoc | |||||
Defined in Language.Haskell.Exts.SrcLoc
| |||||
Generic SrcSpan | |||||
Defined in Language.Haskell.Exts.SrcLoc
| |||||
Generic SrcSpanInfo | |||||
Defined in Language.Haskell.Exts.SrcLoc
from :: SrcSpanInfo -> Rep SrcSpanInfo x # to :: Rep SrcSpanInfo x -> SrcSpanInfo # | |||||
Generic Boxed | |||||
Defined in Language.Haskell.Exts.Syntax | |||||
Generic Tool | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic Form | |||||
Defined in Web.Internal.FormUrlEncoded
| |||||
Generic ByteRange | |||||
Defined in Network.HTTP.Types.Header
| |||||
Generic StdMethod | |||||
Defined in Network.HTTP.Types.Method
| |||||
Generic Status | |||||
Defined in Network.HTTP.Types.Status
| |||||
Generic HttpVersion | |||||
Defined in Network.HTTP.Types.Version
from :: HttpVersion -> Rep HttpVersion x # to :: Rep HttpVersion x -> HttpVersion # | |||||
Generic ConcException | |||||
Defined in UnliftIO.Internals.Async
from :: ConcException -> Rep ConcException x # to :: Rep ConcException x -> ConcException # | |||||
Generic UnixTime | |||||
Defined in Data.UnixTime.Types
| |||||
Generic Mode | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ
| |||||
Generic Style | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ
| |||||
Generic TextDetails | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ
from :: TextDetails -> Rep TextDetails x # to :: Rep TextDetails x -> TextDetails # | |||||
Generic Doc | |||||
Defined in Text.PrettyPrint.HughesPJ
| |||||
Generic IP | |||||
Defined in Data.IP.Addr
| |||||
Generic IPv4 | |||||
Defined in Data.IP.Addr
| |||||
Generic IPv6 | |||||
Defined in Data.IP.Addr
| |||||
Generic IPRange | |||||
Defined in Data.IP.Range
| |||||
Generic OsChar | |||||
Defined in System.OsString.Internal.Types
| |||||
Generic OsString | |||||
Defined in System.OsString.Internal.Types
| |||||
Generic PosixChar | |||||
Defined in System.OsString.Internal.Types
| |||||
Generic PosixString | |||||
Defined in System.OsString.Internal.Types
from :: PosixString -> Rep PosixString x # to :: Rep PosixString x -> PosixString # | |||||
Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types
from :: WindowsChar -> Rep WindowsChar x # to :: Rep WindowsChar x -> WindowsChar # | |||||
Generic WindowsString | |||||
Defined in System.OsString.Internal.Types
from :: WindowsString -> Rep WindowsString x # to :: Rep WindowsString x -> WindowsString # | |||||
Generic AnnLookup | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic AnnTarget | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Bang | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic BndrVis | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Body | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Bytes | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Callconv | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Clause | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Con | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Dec | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic DecidedStrictness | |||||
Defined in Language.Haskell.TH.Syntax
from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
Generic DerivClause | |||||
Defined in Language.Haskell.TH.Syntax
from :: DerivClause -> Rep DerivClause x # to :: Rep DerivClause x -> DerivClause # | |||||
Generic DerivStrategy | |||||
Defined in Language.Haskell.TH.Syntax
from :: DerivStrategy -> Rep DerivStrategy x # to :: Rep DerivStrategy x -> DerivStrategy # | |||||
Generic DocLoc | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Exp | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic FamilyResultSig | |||||
Defined in Language.Haskell.TH.Syntax
from :: FamilyResultSig -> Rep FamilyResultSig x # to :: Rep FamilyResultSig x -> FamilyResultSig # | |||||
Generic Fixity | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic FixityDirection | |||||
Defined in Language.Haskell.TH.Syntax
from :: FixityDirection -> Rep FixityDirection x # to :: Rep FixityDirection x -> FixityDirection # | |||||
Generic Foreign | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic FunDep | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Guard | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Info | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic InjectivityAnn | |||||
Defined in Language.Haskell.TH.Syntax
from :: InjectivityAnn -> Rep InjectivityAnn x # to :: Rep InjectivityAnn x -> InjectivityAnn # | |||||
Generic Inline | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Lit | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Loc | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Match | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic ModName | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Module | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic ModuleInfo | |||||
Defined in Language.Haskell.TH.Syntax
from :: ModuleInfo -> Rep ModuleInfo x # to :: Rep ModuleInfo x -> ModuleInfo # | |||||
Generic Name | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic NameFlavour | |||||
Defined in Language.Haskell.TH.Syntax
from :: NameFlavour -> Rep NameFlavour x # to :: Rep NameFlavour x -> NameFlavour # | |||||
Generic NameSpace | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic OccName | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Overlap | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Pat | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic PatSynArgs | |||||
Defined in Language.Haskell.TH.Syntax
from :: PatSynArgs -> Rep PatSynArgs x # to :: Rep PatSynArgs x -> PatSynArgs # | |||||
Generic PatSynDir | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Phases | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic PkgName | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Pragma | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Range | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Role | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic RuleBndr | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic RuleMatch | |||||
Defined in Language.Haskell.TH.Syntax | |||||
Generic Safety | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic SourceStrictness | |||||
Defined in Language.Haskell.TH.Syntax
from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
Generic SourceUnpackedness | |||||
Defined in Language.Haskell.TH.Syntax
from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
Generic Specificity | |||||
Defined in Language.Haskell.TH.Syntax
from :: Specificity -> Rep Specificity x # to :: Rep Specificity x -> Specificity # | |||||
Generic Stmt | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic TyLit | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic TySynEqn | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic Type | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic TypeFamilyHead | |||||
Defined in Language.Haskell.TH.Syntax
from :: TypeFamilyHead -> Rep TypeFamilyHead x # to :: Rep TypeFamilyHead x -> TypeFamilyHead # | |||||
Generic ConstructorInfo | |||||
Defined in Language.Haskell.TH.Datatype
from :: ConstructorInfo -> Rep ConstructorInfo x # to :: Rep ConstructorInfo x -> ConstructorInfo # | |||||
Generic ConstructorVariant | |||||
Defined in Language.Haskell.TH.Datatype
from :: ConstructorVariant -> Rep ConstructorVariant x # to :: Rep ConstructorVariant x -> ConstructorVariant # | |||||
Generic DatatypeInfo | |||||
Defined in Language.Haskell.TH.Datatype
from :: DatatypeInfo -> Rep DatatypeInfo x # to :: Rep DatatypeInfo x -> DatatypeInfo # | |||||
Generic DatatypeVariant | |||||
Defined in Language.Haskell.TH.Datatype
from :: DatatypeVariant -> Rep DatatypeVariant x # to :: Rep DatatypeVariant x -> DatatypeVariant # | |||||
Generic FieldStrictness | |||||
Defined in Language.Haskell.TH.Datatype
from :: FieldStrictness -> Rep FieldStrictness x # to :: Rep FieldStrictness x -> FieldStrictness # | |||||
Generic Strictness | |||||
Defined in Language.Haskell.TH.Datatype
from :: Strictness -> Rep Strictness x # to :: Rep Strictness x -> Strictness # | |||||
Generic Unpackedness | |||||
Defined in Language.Haskell.TH.Datatype
from :: Unpackedness -> Rep Unpackedness x # to :: Rep Unpackedness x -> Unpackedness # | |||||
Generic FlatAttributes | |||||
Defined in Web.View.Types
from :: FlatAttributes -> Rep FlatAttributes x # to :: Rep FlatAttributes x -> FlatAttributes # | |||||
Generic CompressParams | |||||
Defined in Codec.Compression.Zlib.Internal
from :: CompressParams -> Rep CompressParams x # to :: Rep CompressParams x -> CompressParams # | |||||
Generic DecompressError | |||||
Defined in Codec.Compression.Zlib.Internal
from :: DecompressError -> Rep DecompressError x # to :: Rep DecompressError x -> DecompressError # | |||||
Generic DecompressParams | |||||
Defined in Codec.Compression.Zlib.Internal
from :: DecompressParams -> Rep DecompressParams x # to :: Rep DecompressParams x -> DecompressParams # | |||||
Generic CompressionLevel | |||||
Defined in Codec.Compression.Zlib.Stream
from :: CompressionLevel -> Rep CompressionLevel x # to :: Rep CompressionLevel x -> CompressionLevel # | |||||
Generic CompressionStrategy | |||||
Defined in Codec.Compression.Zlib.Stream
from :: CompressionStrategy -> Rep CompressionStrategy x # to :: Rep CompressionStrategy x -> CompressionStrategy # | |||||
Generic Format | |||||
Defined in Codec.Compression.Zlib.Stream
| |||||
Generic MemoryLevel | |||||
Defined in Codec.Compression.Zlib.Stream
from :: MemoryLevel -> Rep MemoryLevel x # to :: Rep MemoryLevel x -> MemoryLevel # | |||||
Generic Method | |||||
Defined in Codec.Compression.Zlib.Stream | |||||
Generic WindowBits | |||||
Defined in Codec.Compression.Zlib.Stream
from :: WindowBits -> Rep WindowBits x # to :: Rep WindowBits x -> WindowBits # | |||||
Generic () | |||||
Generic Bool | |||||
Defined in GHC.Generics | |||||
Generic (ZipList a) | |||||
Defined in Control.Applicative
| |||||
Generic (Complex a) | |||||
Defined in Data.Complex
| |||||
Generic (Identity a) | |||||
Defined in Data.Functor.Identity
| |||||
Generic (First a) | |||||
Defined in Data.Monoid
| |||||
Generic (Last a) | |||||
Defined in Data.Monoid
| |||||
Generic (Down a) | |||||
Defined in GHC.Generics
| |||||
Generic (First a) | |||||
Defined in Data.Semigroup
| |||||
Generic (Last a) | |||||
Defined in Data.Semigroup
| |||||
Generic (Max a) | |||||
Defined in Data.Semigroup
| |||||
Generic (Min a) | |||||
Defined in Data.Semigroup
| |||||
Generic (WrappedMonoid m) | |||||
Defined in Data.Semigroup
from :: WrappedMonoid m -> Rep (WrappedMonoid m) x # to :: Rep (WrappedMonoid m) x -> WrappedMonoid m # | |||||
Generic (Dual a) | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Endo a) | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Product a) | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Sum a) | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (NonEmpty a) | |||||
Defined in GHC.Generics
| |||||
Generic (Par1 p) | |||||
Defined in GHC.Generics
| |||||
Generic (SCC vertex) | |||||
Defined in Data.Graph
| |||||
Generic (Digit a) | |||||
Defined in Data.Sequence.Internal
| |||||
Generic (Elem a) | |||||
Defined in Data.Sequence.Internal
| |||||
Generic (FingerTree a) | |||||
Defined in Data.Sequence.Internal
from :: FingerTree a -> Rep (FingerTree a) x # to :: Rep (FingerTree a) x -> FingerTree a # | |||||
Generic (Node a) | |||||
Defined in Data.Sequence.Internal
| |||||
Generic (ViewL a) | |||||
Defined in Data.Sequence.Internal
| |||||
Generic (ViewR a) | |||||
Defined in Data.Sequence.Internal
| |||||
Generic (Tree a) | |||||
Defined in Data.Tree
| |||||
Generic (Loc a) | |||||
Defined in Language.Haskell.Exts.SrcLoc
| |||||
Generic (Activation l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: Activation l -> Rep (Activation l) x # to :: Rep (Activation l) x -> Activation l # | |||||
Generic (Alt l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Annotation l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: Annotation l -> Rep (Annotation l) x # to :: Rep (Annotation l) x -> Annotation l # | |||||
Generic (Assoc l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Asst l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (BangType l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Binds l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (BooleanFormula l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: BooleanFormula l -> Rep (BooleanFormula l) x # to :: Rep (BooleanFormula l) x -> BooleanFormula l # | |||||
Generic (Bracket l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (CName l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (CallConv l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ClassDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ConDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Context l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (DataOrNew l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Decl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (DeclHead l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (DerivStrategy l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: DerivStrategy l -> Rep (DerivStrategy l) x # to :: Rep (DerivStrategy l) x -> DerivStrategy l # | |||||
Generic (Deriving l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (EWildcard l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Exp l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ExportSpec l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ExportSpec l -> Rep (ExportSpec l) x # to :: Rep (ExportSpec l) x -> ExportSpec l # | |||||
Generic (ExportSpecList l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ExportSpecList l -> Rep (ExportSpecList l) x # to :: Rep (ExportSpecList l) x -> ExportSpecList l # | |||||
Generic (FieldDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (FieldUpdate l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: FieldUpdate l -> Rep (FieldUpdate l) x # to :: Rep (FieldUpdate l) x -> FieldUpdate l # | |||||
Generic (FunDep l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (GadtDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (GuardedRhs l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: GuardedRhs l -> Rep (GuardedRhs l) x # to :: Rep (GuardedRhs l) x -> GuardedRhs l # | |||||
Generic (IPBind l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (IPName l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ImportDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ImportDecl l -> Rep (ImportDecl l) x # to :: Rep (ImportDecl l) x -> ImportDecl l # | |||||
Generic (ImportSpec l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ImportSpec l -> Rep (ImportSpec l) x # to :: Rep (ImportSpec l) x -> ImportSpec l # | |||||
Generic (ImportSpecList l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ImportSpecList l -> Rep (ImportSpecList l) x # to :: Rep (ImportSpecList l) x -> ImportSpecList l # | |||||
Generic (InjectivityInfo l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: InjectivityInfo l -> Rep (InjectivityInfo l) x # to :: Rep (InjectivityInfo l) x -> InjectivityInfo l # | |||||
Generic (InstDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (InstHead l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (InstRule l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Literal l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Match l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (MaybePromotedName l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: MaybePromotedName l -> Rep (MaybePromotedName l) x # to :: Rep (MaybePromotedName l) x -> MaybePromotedName l # | |||||
Generic (Module l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ModuleHead l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ModuleHead l -> Rep (ModuleHead l) x # to :: Rep (ModuleHead l) x -> ModuleHead l # | |||||
Generic (ModuleName l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ModuleName l -> Rep (ModuleName l) x # to :: Rep (ModuleName l) x -> ModuleName l # | |||||
Generic (ModulePragma l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: ModulePragma l -> Rep (ModulePragma l) x # to :: Rep (ModulePragma l) x -> ModulePragma l # | |||||
Generic (Name l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Namespace l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Op l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Overlap l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (PXAttr l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Pat l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (PatField l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (PatternSynDirection l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: PatternSynDirection l -> Rep (PatternSynDirection l) x # to :: Rep (PatternSynDirection l) x -> PatternSynDirection l # | |||||
Generic (Promoted l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (QName l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (QOp l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (QualConDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: QualConDecl l -> Rep (QualConDecl l) x # to :: Rep (QualConDecl l) x -> QualConDecl l # | |||||
Generic (QualStmt l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (RPat l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (RPatOp l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (ResultSig l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Rhs l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Role l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Rule l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (RuleVar l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Safety l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Sign l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (SpecialCon l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: SpecialCon l -> Rep (SpecialCon l) x # to :: Rep (SpecialCon l) x -> SpecialCon l # | |||||
Generic (Splice l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Stmt l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (TyVarBind l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Type l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (TypeEqn l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Unpackedness l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: Unpackedness l -> Rep (Unpackedness l) x # to :: Rep (Unpackedness l) x -> Unpackedness l # | |||||
Generic (WarningText l) | |||||
Defined in Language.Haskell.Exts.Syntax
from :: WarningText l -> Rep (WarningText l) x # to :: Rep (WarningText l) x -> WarningText l # | |||||
Generic (XAttr l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (XName l) | |||||
Defined in Language.Haskell.Exts.Syntax
| |||||
Generic (Doc a) | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ
| |||||
Generic (AddrRange a) | |||||
Defined in Data.IP.Range
| |||||
Generic (TyVarBndr flag) | |||||
Defined in Language.Haskell.TH.Syntax
| |||||
Generic (Maybe a) | |||||
Defined in GHC.Generics
| |||||
Generic (Solo a) | |||||
Defined in GHC.Generics
| |||||
Generic [a] | |||||
Defined in GHC.Generics
| |||||
Generic (WrappedMonad m a) | |||||
Defined in Control.Applicative
from :: WrappedMonad m a -> Rep (WrappedMonad m a) x # to :: Rep (WrappedMonad m a) x -> WrappedMonad m a # | |||||
Generic (Either a b) | |||||
Defined in GHC.Generics
| |||||
Generic (Proxy t) | |||||
Generic (Arg a b) | |||||
Defined in Data.Semigroup
| |||||
Generic (U1 p) | |||||
Generic (V1 p) | |||||
Generic (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe
| |||||
Generic (a, b) | |||||
Defined in GHC.Generics
| |||||
Generic (WrappedArrow a b c) | |||||
Defined in Control.Applicative
from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x # to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c # | |||||
Generic (Kleisli m a b) | |||||
Defined in Control.Arrow
| |||||
Generic (Const a b) | |||||
Defined in Data.Functor.Const
| |||||
Generic (Ap f a) | |||||
Defined in Data.Monoid
| |||||
Generic (Alt f a) | |||||
Defined in Data.Semigroup.Internal
| |||||
Generic (Rec1 f p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec (Ptr ()) p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec Char p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec Double p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec Float p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec Int p) | |||||
Defined in GHC.Generics
| |||||
Generic (URec Word p) | |||||
Defined in GHC.Generics
| |||||
Generic (Tagged s b) | |||||
Defined in Data.Tagged
| |||||
Generic (AccumT w m a) | |||||
Defined in Control.Monad.Trans.Accum
| |||||
Generic (ExceptT e m a) | |||||
Defined in Control.Monad.Trans.Except
| |||||
Generic (IdentityT f a) | |||||
Defined in Control.Monad.Trans.Identity
| |||||
Generic (ReaderT r m a) | |||||
Defined in Control.Monad.Trans.Reader
| |||||
Generic (SelectT r m a) | |||||
Defined in Control.Monad.Trans.Select
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Lazy
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.CPS
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Lazy
| |||||
Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Strict
| |||||
Generic (Constant a b) | |||||
Defined in Data.Functor.Constant
| |||||
Generic (a, b, c) | |||||
Defined in GHC.Generics
| |||||
Generic (Product f g a) | |||||
Defined in Data.Functor.Product
| |||||
Generic (Sum f g a) | |||||
Defined in Data.Functor.Sum
| |||||
Generic ((f :*: g) p) | |||||
Defined in GHC.Generics
| |||||
Generic ((f :+: g) p) | |||||
Defined in GHC.Generics
| |||||
Generic (K1 i c p) | |||||
Defined in GHC.Generics
| |||||
Generic (ContT r m a) | |||||
Defined in Control.Monad.Trans.Cont
| |||||
Generic (a, b, c, d) | |||||
Defined in GHC.Generics
| |||||
Generic (Compose f g a) | |||||
Defined in Data.Functor.Compose
| |||||
Generic ((f :.: g) p) | |||||
Defined in GHC.Generics
| |||||
Generic (M1 i c f p) | |||||
Defined in GHC.Generics
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.CPS
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Lazy
| |||||
Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Strict
| |||||
Generic (a, b, c, d, e) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
Defined in GHC.Generics
| |||||
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
Defined in GHC.Generics
|