| Copyright | (c) 2024 Sean Hess |
|---|---|
| License | BSD3 |
| Maintainer | Sean Hess <seanhess@gmail.com> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | GHC2021 |
Web.Hyperbole
Description
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
- type Page (views :: [Type]) = View (Root views) ()
- runPage :: forall (es :: [Effect]) (views :: [Type]). (Hyperbole :> es, RunHandlers views es) => Eff es (Page views) -> Eff es Response
- 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
- respondEarly :: forall (es :: [Effect]) id. (Hyperbole :> es, HyperView id es) => id -> View id () -> Eff es ()
- notFound :: forall (es :: [Effect]) a. Hyperbole :> es => Eff es a
- redirect :: forall (es :: [Effect]) a. Hyperbole :> es => Url -> Eff es a
- request :: forall (es :: [Effect]). Hyperbole :> es => Eff es Request
- data Request = Request {}
- query :: forall a (es :: [Effect]). (FromQuery a, Hyperbole :> es) => Eff es a
- setQuery :: forall a (es :: [Effect]). (ToQuery a, Hyperbole :> es) => a -> Eff es ()
- param :: forall a (es :: [Effect]). (FromParam a, Hyperbole :> es) => Param -> Eff es a
- lookupParam :: forall a (es :: [Effect]). (FromParam a, Hyperbole :> es) => Param -> Eff es (Maybe a)
- setParam :: forall a (es :: [Effect]). (ToParam a, Hyperbole :> es) => Param -> a -> Eff es ()
- deleteParam :: forall (es :: [Effect]). Hyperbole :> es => Param -> Eff es ()
- queryParams :: forall (es :: [Effect]). Hyperbole :> es => Eff es QueryData
- session :: forall a (es :: [Effect]). (Session a, DefaultParam a, FromParam a, Hyperbole :> es) => Eff es a
- saveSession :: forall a (es :: [Effect]). (Session a, ToParam a, Hyperbole :> es) => a -> Eff es ()
- lookupSession :: forall a (es :: [Effect]). (Session a, FromParam a, Hyperbole :> es) => Eff es (Maybe a)
- modifySession :: forall a (es :: [Effect]). (Session a, DefaultParam a, ToParam a, FromParam a, Hyperbole :> es) => (a -> a) -> Eff es a
- modifySession_ :: forall a (es :: [Effect]). (Session a, DefaultParam a, ToParam a, FromParam a, Hyperbole :> es) => (a -> a) -> Eff es ()
- deleteSession :: forall a (es :: [Effect]). (Session a, Hyperbole :> es) => Eff es ()
- class Session a where
- sessionKey :: Param
- cookiePath :: Maybe [Segment]
- 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
- 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
- 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
- formData :: forall form (val :: Type -> Type) (es :: [Effect]). (Form form val, Hyperbole :> es) => Eff es (form Identity)
- 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
- class ToQuery a where
- class FromQuery a where
- parseQuery :: QueryData -> Either Text a
- class ToParam a where
- toParam :: a -> ParamValue
- class FromParam a where
- parseParam :: ParamValue -> Either Text a
- data QueryData
- class DefaultParam a where
- defaultParam :: a
- target :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx ()
- view :: forall (es :: [Effect]). Hyperbole :> es => View () () -> Eff es Response
- data Response
- class ViewId a
- class ViewAction a
- data Root (views :: [Type])
- 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 ()
- stack :: Mod c -> Layer c () -> View c ()
- popup :: Sides Length -> Mod c
- table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c ()
- data Attributes (c :: k)
- 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
- renderPath :: [Segment] -> 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 ()
- layer :: 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 HyperViews. 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. forms 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 Pages, which run side effects (such as loading data from a database), 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 :: IO ()
main = do
run 3000 $ do
liveApp (basicDocument "Example") (runPage page)
page :: Eff es (Page '[])
page = do
pure $ do
col (pad 10) $ do
el bold "Hello World"
HTML Views
Views are HTML fragments with embedded CSS
helloWorld ::Viewcontext () helloWorld =elbold "Hello World"
>>>Web.View.renderText $ el bold "Hello World"<style type='text/css'>.bold { font-weight:bold }</style> <div class='bold'>Hello World</div>
We can factor Views into reusable functions:
messageView :: Text ->Viewcontext () messageView msg =elbold (text msg) page' ::Effes (Page'[]) page' = do pure $ do col (pad 10) $ do messageView "Hello World"
We use plain functions to maintain a consistent look and feel rather than stylesheets:
header = bold h1 = header . fontSize 32 h2 = header . fontSize 24 page = gap 10 example = col page $ do el h1 "My Page"
See Web.View for more details
Interactive HyperViews
We can embed one or more HyperViews to add type-safe interactivity to live subsections of our 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
Actiontype with a constructor for every possible way that the user can interact with it - Write an
updatefor eachAction
instanceHyperViewMessage es where dataActionMessage = SetMessage Text deriving (Show, Read,ViewAction)update(SetMessage msg) = pure $ messageView msg
If an Action occurs, the contents of our HyperView will be replaced with update.
To embed our new HyperView, add the ViewId to the type-level list of Page, and then wrap the view in hyper.
page ::Effes (Page'[Message]) page = do pure $ do col (pad 10 . gap 10) $ doel(bold . fontSize 24) "Unchanging Header"hyperMessage $ messageView "Hello World"
Now let's add a button to trigger the Action. Note that we must update the View's context to match our ViewId. The compiler will tell us if we try to trigger actions that don't belong to our HyperView
messageView :: Text ->ViewMessage () messageView msg = doelbold $ text msgbutton(SetMessage "Goodbye") (border 1) "Say Goodbye"
If the user clicks the button, the contents of hyper will be replaced with the result of update, leaving the rest of the page untouched.
View Functions
We showed above how we can factor Views into functions. It's best-practice to have a main View for each HyperView. These take the form:
state -> View viewId ()
There's nothing special about state or View functions. They're just functions that take parameters and return a view.
We can write multiple view functions with our HyperView as the context, and factor them however is most convenient:
messageButton :: Text ->ViewMessage () messageButton msg = dobutton(SetMessage msg) (border 1) (text $ "Say " <> msg)
We can also create View functions that work in any context:
header :: Text ->Viewcontext () header txt = doelbold (text txt)
Then we can refactor our main View to use view functions to avoid repeating ourselves
messageView :: Text -> View Message ()
messageView m = do
header m
messageButton "Salutations!"
messageButton "Good Morning!"
messageButton "Goodbye"
Managing State
HyperViews 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
instanceHyperViewMessage es where dataActionMessage = Louder Text deriving (Show, Read,ViewAction)update(Louder m) = do let new = m <> "!" pure $ messageView new messageView :: Text ->ViewMessage () messageView m = dobutton(Louder m) (border 1) "Louder"elbold $ text 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. The Hyperbole effect gives us access to the request and Client state, including sessions and the query params. In this example the page keeps the message in the query params
page :: (Hyperbole:> es) =>Effes (Page'[Message]) page = do prm <-lookupParam"msg" let msg = fromMaybe "hello" prm pure $ dohyperMessage $ messageView msg instanceHyperViewMessage es where dataActionMessage = Louder Text deriving (Show, Read,ViewAction)update(Louder msg) = do let new = msg <> "!"setParam"msg" 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.
From Example.Page.Counter
{-# LANGUAGE UndecidableInstances #-}
instance (Reader (TVar Int) :> es, Concurrent :> es) => HyperView Counter es where
data Action Counter
= Increment
| Decrement
deriving (Show, Read, ViewAction)
update Increment = do
n <- modify (+ 1)
pure $ viewCount n
update Decrement = do
n <- modify (subtract 1)
pure $ viewCount n
Then run the effect in your application
app :: TVar Int -> Application app var = doliveApp(basicDocument"Example") (runReader var . runConcurrent $runPagepage)
- Read more about Effectful
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 $ do
hyper AllTodos $ todosView FilterAll todos
We run a custom effect in our Application just like any other. Here we implementing our custom effect using Hyperbole sessions, but you could write a different runner that connects to a database instead.
main :: IO () main = dorun3000 $ doliveApp(basicDocument"Example") (runTodosSession $runPagepage)
See example/Main for a full example application with multiple effects
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 HyperViews to a page as we want. Let's create another HyperView for a simple counter
data Count = Count deriving (Show, Read,ViewId) instanceHyperViewCount es where dataActionCount = 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 ->ViewCount () countView n = doel_ $ text $ pack $ show nbutton(Increment n) btn "Increment"button(Decrement n) btn "Decrement" where btn = border 1
We can use both Message and Count HyperViews in our page, and they will update independently:
page ::Effes (Page[Message, Count]) page = do pure $ do row id $ dohyperMessage $ messageView "Hello"hyperCount $ 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 HyperViews into the same page. Each will update independently.
page' ::Effes (Page'[Message]) page' = do pure $ dohyperMessage1 $ messageView "Hello"hyperMessage2 $ 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) =>HyperViewContact es where dataActionContact = Edit | Save |Viewderiving (Show, Read,ViewAction)updateaction = do -- No matter which action we are performing, let's look up the user to make sure it exists Contact uid <-viewIdu <- 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
Nesting
We can nest smaller, specific HyperViews 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.Docs.Nested
data TodoItem = TodoItem deriving (Show, Read,ViewId) instanceHyperViewTodoItem es where dataActionTodoItem = 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) instanceHyperViewAllTodos es where type Require AllTodos = '[TodoItem] dataActionAllTodos = 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] ->ViewAllTodos () todosView todos = do forM_ todos $ todo -> dohyperTodoItem $ 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 HyperViews 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 ->Viewcontext () header txt = doelbold (text txt)
What if we want to reuse functionality too? We can pass an Action into the view function as a parameter:
styledButton :: (ViewAction(Actionid)) =>Actionid -> Text ->Viewid () styledButton clickAction lbl = dobuttonclickAction btn (text lbl) where btn = pad 10 . bg Primary . hover (bg PrimaryLight) . rounded 5
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(Actionid)) => (Bool ->Actionid) -> Bool ->Viewid () toggleCheckBtn clickAction isSelected = dobutton(clickAction (not isSelected)) circle contents where contents = if isSelected then Icon.check else " " circle = width 32 . height 32 . border 1 . rounded 100
View functions can wrap other Views:
progressBar :: Float ->Viewcontext () ->Viewcontext () progressBar pct content = do row (bg Light) $ do row (bg PrimaryLight . width (Pct pct) . pad 5) content
Don't leverage HyperViews for code reuse. Think about which subsections of a page ought to update independently. Those are HyperViews. If you need reusable functionality, use view functions instead.
- See Example.View.DataTable for a more complex example
Pages
An app has multiple Pages with different Routes 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 = dorun3000 $ doliveApp(basicDocument"Multiple Pages") (routeRequestrouter) where router Message =runPageMessage.page router Counter =runPageCounter.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 ::Viewc () menu = dorouteMessage id "Link to /message"routeCounter id "Link to /counter"
If you need the same header or menu on all pages, use a view function:
exampleLayout ::Viewc () ->Viewc () exampleLayout content = dolayoutid $ doel(border 1) "My Website Header" row id $ do menu content examplePage ::Effes (Page'[]) examplePage = do pure $ exampleLayout $ doel_ "page contents"
As shown above, each Page can contain multiple interactive HyperViews 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 Pages into a Wai Application. Respond using both HTTP and WebSockets
main :: IO ()
main = do
run 3000 $ do
liveApp (basicDocument "Example") (runPage page)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") (routeRequestrouter)
You may want to specify a custom document function to import custom javascript, css, or add other information to the <head>
import Data.String.Interpolate (i)
import Web.Hyperbole (scriptEmbed, cssResetEmbed)
customDocument :: ByteString -> ByteString
customDocument content =
[i|<html>
<head>
<title>My Website</title>
<script type="text/javascript">#{scriptEmbed}</script>
<style type="text/css">#{cssResetEmbed}</style>
<script type="text/javascript" src="custom.js"></script>
</head>
<body>#{content}</body>
</html>|]type Page (views :: [Type]) = View (Root views) () Source #
Conceptually, an application is dividied up into multiple Pages. Each page module should have a function that returns a Page. The Page itself is a View with a type-level list of HyperViews used on the page.
page ::Effes (Page[Message, Count]) page = do pure $ do row id $ dohyperMessage $ messageView "Hello"hyperCount $ countView 0
runPage :: forall (es :: [Effect]) (views :: [Type]). (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 Example.Docs.Page.Messages qualified as Messages import Example.Docs.Page.Users qualified as Users type UserId = Int data AppRoute = Main | Messages | User UserId deriving (Eq, Generic) instanceRouteAppRoute where baseRoute = Just Main router :: (Hyperbole:> es) => AppRoute ->EffesResponserouter Messages =runPageMessages.page router (User cid) =runPage$ Users.page cid router Main = do view $ doel_ "click a link below to visit a page"routeMessages id "Messages"route(User 1) id "User 1"route(User 2) id "User 2"
Derive this class to use a sum type as a route. Constructors and Selectors map intuitively to url patterns
data AppRoute
= Main
| Messages
| User UserId
deriving (Eq, Generic)
instance Route AppRoute where
baseRoute = Just Main
>>>routeUrl Main/
>>>routeUrl (User 9)/user/9
Minimal complete definition
Nothing
Methods
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 #
The Hyperbole Effect allows you to access information in the Request, manually respondEarly, and manipulate the Client session and query.
Instances
| type DispatchOf Hyperbole Source # | |
Defined in Web.Hyperbole.Effect.Hyperbole | |
Response
respondEarly :: forall (es :: [Effect]) id. (Hyperbole :> es, HyperView id es) => id -> View id () -> Eff es () Source #
Respond with the given view, and stop execution
notFound :: forall (es :: [Effect]) a. Hyperbole :> es => Eff es a Source #
Respond immediately with 404 Not Found
findUser :: (Hyperbole:> es, Users :> es) => Int ->Effes User findUser uid = do mu <- send (LoadUser uid) maybe notFound pure mu userPage :: (Hyperbole:> es, Users :> es) =>Effes (Page'[]) userPage = do user <- findUser 100 -- skipped if user not found pure $ userView user
redirect :: forall (es :: [Effect]) a. Hyperbole :> es => Url -> Eff es a Source #
Redirect immediately to the Url
Request
request :: forall (es :: [Effect]). Hyperbole :> es => Eff es Request Source #
Return all information about the Request
Constructors
| Request | |
Query Params
query :: forall a (es :: [Effect]). (FromQuery a, Hyperbole :> es) => Eff es a Source #
Parse querystring from the Request into a datatype. See FromQuery
data Filters = Filters
{ active :: Bool
, term :: Text
}
deriving (Generic, FromQuery, ToQuery)
page :: (Hyperbole :> es) => Eff es (Page '[Todos])
page = do
filters <- query @Filters
todos <- loadTodos filters
pure $ do
hyper Todos $ todosView todos
setQuery :: forall a (es :: [Effect]). (ToQuery a, Hyperbole :> es) => a -> Eff es () Source #
Update the client's querystring to an encoded datatype. See ToQuery
instanceHyperViewTodos es where dataActionTodos = SetFilters Filters deriving (Show, Read,ViewAction)update(SetFilters filters) = do setQuery filters todos <- loadTodos filters pure $ todosView todos
lookupParam :: forall a (es :: [Effect]). (FromParam a, Hyperbole :> es) => Param -> Eff es (Maybe a) Source #
Parse a single parameter from the query string if available
setParam :: forall a (es :: [Effect]). (ToParam a, Hyperbole :> es) => Param -> a -> Eff es () Source #
deleteParam :: forall (es :: [Effect]). Hyperbole :> es => Param -> Eff es () Source #
Delete a single parameter from the query string
queryParams :: forall (es :: [Effect]). Hyperbole :> es => Eff es QueryData Source #
Return the query from Request as a QueryData
Sessions
session :: forall a (es :: [Effect]). (Session a, DefaultParam a, FromParam a, Hyperbole :> es) => Eff es a Source #
Persist datatypes in browser cookies. If the session doesn't exist, the DefaultParam is used
data Preferences = Preferences
{ color :: AppColor
}
deriving (Generic, Show, Read, ToParam, FromParam, Session)
instance DefaultParam Preferences where
defaultParam = Preferences White
page :: (Hyperbole :> es) => Eff es (Page '[Content])
page = do
prefs <- session @Preferences
pure $ el (bg prefs.color) "Custom Background"
saveSession :: forall a (es :: [Effect]). (Session a, ToParam a, Hyperbole :> es) => a -> Eff es () Source #
Persist datatypes in browser cookies
data Preferences = Preferences
{ color :: AppColor
}
deriving (Generic, Show, Read, ToParam, FromParam, Session)
instance DefaultParam Preferences where
defaultParam = Preferences White
instance HyperView Content es where
data Action Content
= SetColor AppColor
deriving (Show, Read, ViewAction)
update (SetColor clr) = do
let prefs = Preferences clr
saveSession prefs
pure $ el (bg prefs.color) "Custom Background"
lookupSession :: forall a (es :: [Effect]). (Session a, FromParam a, Hyperbole :> es) => Eff es (Maybe a) Source #
Return a session if it exists
modifySession :: forall a (es :: [Effect]). (Session a, DefaultParam a, ToParam a, FromParam a, Hyperbole :> es) => (a -> a) -> Eff es a Source #
modifySession_ :: forall a (es :: [Effect]). (Session a, DefaultParam a, ToParam a, FromParam a, Hyperbole :> es) => (a -> a) -> Eff es () Source #
deleteSession :: forall a (es :: [Effect]). (Session a, Hyperbole :> es) => Eff es () Source #
Remove a single Session from the browser cookies
class Session a where Source #
Configure a data type to persist in the session
data Preferences = Preferences
{ color :: AppColor
}
deriving (Generic, Show, Read, ToParam, FromParam, Session)
instance DefaultParam Preferences where
defaultParam = Preferences White
Minimal complete definition
Nothing
Methods
sessionKey :: Param Source #
Unique key for the Session. Defaults to the datatypeName
default sessionKey :: (Generic a, GDatatypeName (Rep a)) => Param Source #
cookiePath :: Maybe [Segment] Source #
By default Sessions are persisted only to the current page. Set this to `Just []` to make an application-wide Session
default cookiePath :: Maybe [Segment] Source #
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 deriving (Show, Read,ViewId) instanceHyperViewMessage es where dataActionMessage = SetMessage Text deriving (Show, Read,ViewAction)update(SetMessage msg) = pure $ messageView msg
Associated Types
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]
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
| HyperView (Root views) es Source # | |||||||||
Defined in Web.Hyperbole.HyperView Associated Types
| |||||||||
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) =>HyperViewContact es where dataActionContact = Edit | Save |Viewderiving (Show, Read,ViewAction)updateaction = do -- No matter which action we are performing, let's look up the user to make sure it exists Contact uid <-viewIdu <- 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
Instances
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.Page.Filter
familyDropdown :: Filters -> View Languages ()
familyDropdown filters =
dropdown SetFamily (== filters.family) (border 1 . pad 10) $ do
option Nothing "Any"
option (Just ObjectOriented) "Object Oriented"
option (Just Functional) "Functional"
option :: (ViewAction (Action id), Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) () Source #
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. See Example.Page.Concurrent
viewUpdating :: Int ->ViewProgress () viewUpdating prg = do let pct = fromIntegral prg / 100 Progress taskId _ <-viewIdcol (onLoad (CheckProgress prg) 0) $ do progressBar pct $ doelgrow $ text $ "Task" <> pack (show taskId)
onRequest :: Mod id -> Mod id Source #
Apply a Mod only when a request is in flight. See Example.Page.Contact
contactEditView :: User ->ViewContact () contactEditView u = doel(hide . onRequest flexCol) contactLoadingel(onRequest hide) $ contactEditViewSave u
Constructors
| ArrowDown | |
| ArrowUp | |
| ArrowLeft | |
| ArrowRight | |
| Enter | |
| Space | |
| Escape | |
| Alt | |
| CapsLock | |
| Control | |
| Fn | |
| Meta | |
| Shift | |
| OtherKey Text |
Type-Safe Forms
Painless forms with type-checked field names, and support for validation. See Example.Forms
formData :: forall form (val :: Type -> Type) (es :: [Effect]). (Form form val, Hyperbole :> es) => Eff es (form Identity) Source #
class Form (form :: (Type -> Type) -> Type) (val :: Type -> Type) | form -> val where Source #
A Form is a Higher Kinded record listing each Field. ContactForm Identity behaves like a normal record, while ContactForm Maybe would be maybe values for each field
data ContactForm f = ExampleForm
{ name :: Field f Text
, age :: Field f Int
}
deriving (Generic)
instance Form ContactForm Maybe
Minimal complete definition
Nothing
Methods
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. See Example.Page.FormSimple
data ContactForm f = ExampleForm
{ name :: Field f Text
, age :: Field f Int
}
deriving (Generic)
formView :: View FormView ()
formView = do
-- create formfields for our form
let f = formFields @ContactForm
form @ContactForm Submit (gap 10 . pad 10) $ do
el Style.h1 "Add Contact"
-- pass the form field into the 'field' function
field f.name (const id) $ do
label "Contact Name"
input Username (inp . placeholder "contact name")
field f.age (const id) $ do
label "Age"
input Number (inp . placeholder "age" . value "0")
submit Style.btn "Submit"
where
inp = Style.inputformFieldsWith :: forall form (val :: Type -> Type). Form form val => form val -> form (FormField val) Source #
Generate FormFields for the given instance of Form from validation data. See Example.Page.FormValidation
data UserForm f = UserForm
{ user :: Field f User
, age :: Field f Int
, pass1 :: Field f Text
, pass2 :: Field f Text
}
deriving (Generic)
instance Form UserForm Validated
formView :: UserForm Validated -> View FormView ()
formView v = do
let f = formFieldsWith v
form @UserForm Submit (gap 10 . pad 10) $ do
el Style.h1 "Sign Up"
field f.user valStyle $ do
label "Username"
input Username (inp . placeholder "username")
fv <- fieldValid
case fv of
Invalid t -> el_ (text t)
Valid -> el_ "Username is available"
_ -> none
field f.age valStyle $ do
label "Age"
input Number (inp . placeholder "age" . value "0")
el_ invalidText
field f.pass1 valStyle $ do
label "Password"
input NewPassword (inp . placeholder "password")
el_ invalidText
field f.pass2 (const id) $ do
label "Repeat Password"
input NewPassword (inp . placeholder "repeat password")
submit Style.btn "Submit"
where
inp = Style.input
valStyle (Invalid _) = Style.invalid
valStyle Valid = Style.success
valStyle _ = idtype family Field (context :: Type -> Type) a Source #
Field allows a Higher Kinded Form to reuse the same selectors for form parsing, generating html forms, and validation
Field Identity Text ~ Text Field Maybe Text ~ Maybe Text
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
formView ::ViewFormView () formView = do -- create formfields for our form let f = formFieldsContactForm formContactForm Submit (gap 10 . pad 10) $ doelStyle.h1 "Add Contact" -- pass the form field into thefieldfunction field f.name (const id) $ do label "Contact Name" input Username (inp . placeholder "contact name") field f.age (const id) $ do label "Age" input Number (inp . placeholder "age" . value "0") submit Style.btn "Submit" where inp = Style.input
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 inputs to give the browser autocomplete hints
Validation
data Validated (a :: k) Source #
Validation results for a Form. See validate
data UserForm f = UserForm
{ user :: Field f User
, age :: Field f Int
, pass1 :: Field f Text
, pass2 :: Field f Text
}
deriving (Generic)
instance Form UserForm Validated
validateForm :: UserForm Identity -> UserForm Validated
validateForm u =
UserForm
{ user = validateUser u.user
, age = validateAge u.age
, pass1 = validatePass u.pass1 u.pass2
, pass2 = NotInvalid
}
validateAge :: Int -> Validated Int
validateAge a =
validate (a < 20) "User must be at least 20 years old"
Constructors
| Invalid Text | |
| NotInvalid | |
| Valid |
validate :: forall {k} (a :: k). Bool -> Text -> Validated a Source #
specify a check for a Validation
validateAge :: Int -> Validated Int validateAge a = validate (a < 20) "User must be at least 20 years old"
fieldValid :: View (Input id v a) (v a) Source #
Returns the Validated for the field. See formFieldsWith
anyInvalid :: forall form (val :: Type -> Type). (Form form val, ValidationState val) => form val -> Bool Source #
Query Param Encoding
class ToQuery a where Source #
A page can store state in the browser query string. ToQuery and FromQuery control how a datatype is encoded to a full query string
data Filters = Filters
{ active :: Bool
, term :: Text
}
deriving (Generic, FromQuery, ToQuery)
>>>render $ toQuery $ Filter True "asdf""active=true&search=asdf"
If the value of a field is the same as DefaultParam, it will be omitted from the query string
>>>render $ toQuery $ Filter True """active=true"
>>>render $ toQuery $ Filter False """"
Minimal complete definition
Nothing
Methods
class FromQuery a where Source #
Decode a type from a QueryData. Missing fields are set to defaultParam
data Filters = Filters
{ active :: Bool
, term :: Text
}
deriving (Generic, FromQuery, ToQuery)
>>>parseQuery $ parse "active=true&search=asdf"Right (Filters True "asdf")
>>>parseQuery $ parse "search=asdf"Right (Filters False "asdf")
Minimal complete definition
Nothing
Methods
parseQuery :: QueryData -> Either Text a Source #
default parseQuery :: (Generic a, GFromQuery (Rep a)) => QueryData -> Either Text a Source #
class ToParam a where Source #
sessions, forms, and querys all encode data as query strings. ToParam and FromParam control how a datatype is encoded to a parameter. By default it simply url-encodes the show instance.
data Todo = Todo
{ id :: TodoId
, task :: Text
, completed :: Bool
}
deriving (Show, Read, ToParam, FromParam)
data Tags = Tags [Text]
instance ToParam Tags where
toParam (Tags ts) = ParamValue $ Text.intercalate "," ts
Minimal complete definition
Nothing
Instances
| ToParam Word16 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Word16 -> ParamValue Source # | |
| ToParam Word32 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Word32 -> ParamValue Source # | |
| ToParam Word64 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Word64 -> ParamValue Source # | |
| ToParam Word8 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Word8 -> ParamValue Source # | |
| ToParam Text Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Text -> ParamValue Source # | |
| ToParam UTCTime Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: UTCTime -> ParamValue Source # | |
| ToParam Integer Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Integer -> ParamValue Source # | |
| ToParam Bool Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Bool -> ParamValue Source # | |
| ToParam Char Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Char -> ParamValue Source # | |
| ToParam Double Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Double -> ParamValue Source # | |
| ToParam Float Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Float -> ParamValue Source # | |
| ToParam Int Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Int -> ParamValue Source # | |
| ToParam Word Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Word -> ParamValue Source # | |
| ToParam a => ToParam (Maybe a) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Maybe a -> ParamValue Source # | |
| Show a => ToParam [a] Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: [a] -> ParamValue Source # | |
| (ToParam a, ToParam b) => ToParam (Either a b) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Either a b -> ParamValue Source # | |
| (Show k, Show v) => ToParam (Map k v) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods toParam :: Map k v -> ParamValue Source # | |
class FromParam a where Source #
Decode data from a query, session, or form parameter value
data Todo = Todo
{ id :: TodoId
, task :: Text
, completed :: Bool
}
deriving (Show, Read, ToParam, FromParam)
data Tags = Tags [Text]
instance FromParam Tags where
parseParam (ParamValue t) =
pure $ Tags $ Text.splitOn "," t
Minimal complete definition
Nothing
Methods
parseParam :: ParamValue -> Either Text a Source #
default parseParam :: Read a => ParamValue -> Either Text a Source #
Instances
| FromParam Word16 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Word16 Source # | |
| FromParam Word32 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Word32 Source # | |
| FromParam Word64 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Word64 Source # | |
| FromParam Word8 Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Word8 Source # | |
| FromParam Text Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Text Source # | |
| FromParam UTCTime Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text UTCTime Source # | |
| FromParam Integer Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Integer Source # | |
| FromParam Bool Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Bool Source # | |
| FromParam Char Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Char Source # | |
| FromParam Double Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Double Source # | |
| FromParam Float Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Float Source # | |
| FromParam Int Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Int Source # | |
| FromParam Word Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text Word Source # | |
| FromParam a => FromParam (Maybe a) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text (Maybe a) Source # | |
| Read a => FromParam [a] Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text [a] Source # | |
| (FromParam a, FromParam b) => FromParam (Either a b) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text (Either a b) Source # | |
| (Read k, Read v, Ord k) => FromParam (Map k v) Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods parseParam :: ParamValue -> Either Text (Map k v) Source # | |
Key-value store for query params and sessions
class DefaultParam a where Source #
Data.Default doesn't have a Text instance. This class does
Minimal complete definition
Nothing
Instances
| DefaultParam Text Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods defaultParam :: Text Source # | |
| Default a => DefaultParam a Source # | |
Defined in Web.Hyperbole.Data.QueryData Methods defaultParam :: a Source # | |
Advanced
target :: (HyperViewHandled id ctx, ViewId id) => id -> View id () -> View ctx () Source #
Allow inputs to trigger actions for a different view
view :: forall (es :: [Effect]). Hyperbole :> es => View () () -> Eff es Response Source #
Manually set the response to the given view. Normally you would return a View from runPage instead
class ViewAction a Source #
Instances
| ViewAction () Source # | |
Defined in Web.Hyperbole.HyperView | |
| ViewAction (Action (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.
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 Associated Types
| |||||||||
| data Action (Root views) Source # | |||||||||
Defined in Web.Hyperbole.HyperView | |||||||||
| type Require (Root views) Source # | |||||||||
Defined in Web.Hyperbole.HyperView | |||||||||
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)
Instances
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 Mods with (.)
userEmail :: User -> View c ()
userEmail user = input (fontSize 16 . active) (text user.email)
where
active = isActive user then bold else idIf 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 Methods toClassName :: Position -> ClassName # | |
| ToStyleValue Position | |
Defined in Web.View.Style Methods toStyleValue :: Position -> StyleValue # | |
Constructors
| Block |
Instances
| Show Display | |
| ToClassName Display | |
Defined in Web.View.Style Methods toClassName :: Display -> ClassName # | |
| ToStyleValue Display | |
Defined in Web.View.Style Methods toStyleValue :: Display -> StyleValue # | |
| Style Display Display | |
Defined in Web.View.Style Methods styleValue :: Display -> StyleValue # | |
| Style Display None | |
Defined in Web.View.Style Methods 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) | |
| Functor (View context) | |
| Monad (View context) | |
| IsString (View context ()) | |
Defined in Web.View.View Methods 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 ::Viewc () holygrail =layoutid $ dorowsection "Top Bar"rowgrow$ docolsection "Left Sidebar"col(section .grow) "Main Content"colsection "Right Sidebar"rowsection "Bottom Bar" where section =border1
Constructors
| None |
Instances
| Show None | |
| ToClassName None | |
Defined in Web.View.Types Methods toClassName :: None -> ClassName # | |
| ToStyleValue None | |
Defined in Web.View.Types Methods toStyleValue :: None -> StyleValue # | |
| Style Display None | |
Defined in Web.View.Style Methods styleValue :: None -> StyleValue # | |
| Style ListType None | |
Defined in Web.View.Style Methods styleValue :: None -> StyleValue # | |
| Style Shadow None | |
Defined in Web.View.Style Methods 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"
Minimal complete definition
Methods
colorValue :: a -> HexColor #
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>"
stack :: Mod c -> Layer c () -> View c () #
Stack children on top of each other. Each child has the full width. See popup
stack id $ do layer id "Background" layer (bg Black . opacity 0.5) "Overlay"
popup :: Sides Length -> Mod c #
This layer is not included in the stack size, and covers content outside of it. If used outside of stack, the popup is offset from the entire page.
stack id $ do
layer id $ input (value "Autocomplete Box")
layer (popup (TRBL 50 0 0 0)) $ do
el_ "Item 1"
el_ "Item 2"
el_ "Item 3"
el_ "This is covered by the menu"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 1data Attributes (c :: k) #
The Attributes for an Element. Classes are merged and managed separately from the other attributes.
Instances
| Monoid (Attributes c) | |
Defined in Web.View.Types Methods mempty :: Attributes c # mappend :: Attributes c -> Attributes c -> Attributes c # mconcat :: [Attributes c] -> Attributes c # | |
| Semigroup (Attributes c) | |
Defined in Web.View.Types Methods (<>) :: Attributes c -> Attributes c -> Attributes c # sconcat :: NonEmpty (Attributes c) -> Attributes c # stimes :: Integral b => b -> Attributes c -> Attributes c # | |
| Show (Attributes c) | |
Defined in Web.View.Types Methods showsPrec :: Int -> Attributes c -> ShowS # show :: Attributes c -> String # showList :: [Attributes c] -> ShowS # | |
| Eq (Attributes c) | |
Defined in Web.View.Types | |
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>|]Constructors
| AlignCenter | |
| AlignLeft | |
| AlignRight | |
| AlignJustify |
Instances
| Show Align | |
| ToClassName Align | |
Defined in Web.View.Types Methods toClassName :: Align -> ClassName # | |
| ToStyleValue Align | |
Defined in Web.View.Types Methods 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 Methods fromString :: String -> HexColor # | |
| Show HexColor | |
| ToClassName HexColor | |
Defined in Web.View.Types Methods toClassName :: HexColor -> ClassName # | |
| ToColor HexColor | |
Defined in Web.View.Types | |
| ToStyleValue HexColor | |
Defined in Web.View.Types Methods 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 Methods toClassName :: Ms -> ClassName # | |
| ToStyleValue Ms | |
Defined in Web.View.Types Methods 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 Methods toRational :: PxRem -> Rational # | |
| Show PxRem | |
| Eq PxRem | |
| Ord PxRem | |
| ToClassName PxRem | |
Defined in Web.View.Types Methods toClassName :: PxRem -> ClassName # | |
| ToStyleValue PxRem | |
Defined in Web.View.Types Methods toStyleValue :: PxRem -> StyleValue # | |
Instances
| Num Length | |
| Show Length | |
| ToClassName Length | |
Defined in Web.View.Types Methods toClassName :: Length -> ClassName # | |
| ToStyleValue Length | |
Defined in Web.View.Types Methods 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 Methods showsPrec :: Int -> TransitionProperty -> ShowS # show :: TransitionProperty -> String # showList :: [TransitionProperty] -> ShowS # | |
Instances
| Show ListType | |
| ToClassName ListType | |
Defined in Web.View.Style Methods toClassName :: ListType -> ClassName # | |
| ToStyleValue ListType | |
Defined in Web.View.Style Methods toStyleValue :: ListType -> StyleValue # | |
| Style ListType ListType | |
Defined in Web.View.Style Methods styleValue :: ListType -> StyleValue # | |
| Style ListType None | |
Defined in Web.View.Style Methods styleValue :: None -> StyleValue # | |
Constructors
| Inner |
Instances
| Show Inner | |
| ToClassName Inner | |
Defined in Web.View.Style Methods toClassName :: Inner -> ClassName # | |
| Style Shadow Inner | |
Defined in Web.View.Style Methods styleValue :: Inner -> StyleValue # | |
Instances
| Style Shadow Inner | |
Defined in Web.View.Style Methods styleValue :: Inner -> StyleValue # | |
| Style Shadow None | |
Defined in Web.View.Style Methods styleValue :: None -> StyleValue # | |
| Style Shadow () | |
Defined in Web.View.Style Methods 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] #
renderPath :: [Segment] -> Text #
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"
layer :: Mod c -> View c () -> Layer c () #
A normal layer contributes to the size of the parent. See stack
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:
StateInteger:>es =>Effes ()
Instances
| (TypeError (('Text "There is no handler for '" ':<>: 'ShowType e) ':<>: 'Text "' in the context") :: Constraint) => e :> ('[] :: [Effect]) | |
Defined in Effectful.Internal.Effect Methods reifyIndex :: Int # | |
| e :> (e ': es) | |
Defined in Effectful.Internal.Effect Methods reifyIndex :: Int # | |
| e :> es => e :> (x ': es) | |
Defined in Effectful.Internal.Effect Methods 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:
(ReaderString:>es,StateBool:>es) =>EffesInteger
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 Methods 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 Methods 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≡idto.from≡id
Instances
| Generic All | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic Any | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic Version | |||||
Defined in Data.Version Associated Types
| |||||
| Generic Void | |||||
| Generic ByteOrder | |||||
Defined in GHC.ByteOrder | |||||
| Generic Fingerprint | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic Associativity | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic DecidedStrictness | |||||
Defined in GHC.Generics Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
| Generic Fixity | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic SourceStrictness | |||||
Defined in GHC.Generics Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
| Generic SourceUnpackedness | |||||
Defined in GHC.Generics Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
| Generic ExitCode | |||||
Defined in GHC.IO.Exception Associated Types
| |||||
| Generic CCFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic ConcFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic DebugFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic DoCostCentres | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic DoHeapProfile | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic DoTrace | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic GCFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic GiveGCStats | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic MiscFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic ParFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic ProfFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic RTSFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic TickyFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic TraceFlags | |||||
Defined in GHC.RTS.Flags Associated Types
| |||||
| Generic SrcLoc | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic GCDetails | |||||
Defined in GHC.Stats Associated Types
| |||||
| Generic RTSStats | |||||
Defined in GHC.Stats Associated Types
| |||||
| Generic GeneralCategory | |||||
Defined in GHC.Generics Associated Types
Methods from :: GeneralCategory -> Rep GeneralCategory x # to :: Rep GeneralCategory x -> GeneralCategory # | |||||
| Generic ShortByteString | |||||
Defined in Data.ByteString.Short.Internal Associated Types
Methods from :: ShortByteString -> Rep ShortByteString x # to :: Rep ShortByteString x -> ShortByteString # | |||||
| Generic Limit | |||||
Defined in Effectful.Internal.Unlift Associated Types
| |||||
| Generic Persistence | |||||
Defined in Effectful.Internal.Unlift Associated Types
| |||||
| Generic UnliftStrategy | |||||
Defined in Effectful.Internal.Unlift Associated Types
Methods from :: UnliftStrategy -> Rep UnliftStrategy x # to :: Rep UnliftStrategy x -> UnliftStrategy # | |||||
| Generic OnEmptyPolicy | |||||
Defined in Effectful.NonDet Associated Types
| |||||
| Generic OsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic OsString | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic PosixChar | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic PosixString | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic WindowsString | |||||
Defined in System.OsString.Internal.Types.Hidden Associated Types
| |||||
| Generic ForeignSrcLang | |||||
Defined in GHC.ForeignSrcLang.Type Associated Types
Methods from :: ForeignSrcLang -> Rep ForeignSrcLang x # to :: Rep ForeignSrcLang x -> ForeignSrcLang # | |||||
| Generic Extension | |||||
Defined in GHC.LanguageExtensions.Type Associated Types
| |||||
| Generic Ordering | |||||
Defined in GHC.Generics | |||||
| Generic SrcLoc | |||||
Defined in Language.Haskell.Exts.SrcLoc Associated Types
| |||||
| Generic SrcSpan | |||||
Defined in Language.Haskell.Exts.SrcLoc Associated Types
| |||||
| Generic SrcSpanInfo | |||||
Defined in Language.Haskell.Exts.SrcLoc Associated Types
| |||||
| Generic Boxed | |||||
Defined in Language.Haskell.Exts.Syntax | |||||
| Generic Tool | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic Form | |||||
Defined in Web.Internal.FormUrlEncoded Associated Types
| |||||
| Generic ByteRange | |||||
Defined in Network.HTTP.Types.Header Associated Types
| |||||
| Generic StdMethod | |||||
Defined in Network.HTTP.Types.Method Associated Types
| |||||
| Generic Status | |||||
Defined in Network.HTTP.Types.Status Associated Types
| |||||
| Generic HttpVersion | |||||
Defined in Network.HTTP.Types.Version Associated Types
| |||||
| Generic ConcException | |||||
Defined in UnliftIO.Internals.Async Associated Types
| |||||
| Generic UnixTime | |||||
Defined in Data.UnixTime.Types Associated Types
| |||||
| Generic Mode | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
| Generic Style | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
| Generic TextDetails | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
| Generic Doc | |||||
Defined in Text.PrettyPrint.HughesPJ Associated Types
| |||||
| Generic IP | |||||
Defined in Data.IP.Addr Associated Types
| |||||
| Generic IPv4 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
| Generic IPv6 | |||||
Defined in Data.IP.Addr Associated Types
| |||||
| Generic IPRange | |||||
Defined in Data.IP.Range Associated Types
| |||||
| Generic OsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic OsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic PosixChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic PosixString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic WindowsChar | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic WindowsString | |||||
Defined in System.OsString.Internal.Types Associated Types
| |||||
| Generic AnnLookup | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic AnnTarget | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Bang | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic BndrVis | |||||
Defined in Language.Haskell.TH.Syntax | |||||
| Generic Body | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Bytes | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Callconv | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Clause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Con | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Dec | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic DecidedStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: DecidedStrictness -> Rep DecidedStrictness x # to :: Rep DecidedStrictness x -> DecidedStrictness # | |||||
| Generic DerivClause | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic DerivStrategy | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic DocLoc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Exp | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic FamilyResultSig | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FamilyResultSig -> Rep FamilyResultSig x # to :: Rep FamilyResultSig x -> FamilyResultSig # | |||||
| Generic Fixity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic FixityDirection | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: FixityDirection -> Rep FixityDirection x # to :: Rep FixityDirection x -> FixityDirection # | |||||
| Generic Foreign | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic FunDep | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Guard | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Info | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic InjectivityAnn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: InjectivityAnn -> Rep InjectivityAnn x # to :: Rep InjectivityAnn x -> InjectivityAnn # | |||||
| Generic Inline | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Lit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Loc | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Match | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic ModName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Module | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic ModuleInfo | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Name | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic NameFlavour | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic NameSpace | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic OccName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Overlap | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Pat | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic PatSynArgs | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic PatSynDir | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Phases | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic PkgName | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Pragma | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Range | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Role | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic RuleBndr | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic RuleMatch | |||||
Defined in Language.Haskell.TH.Syntax | |||||
| Generic Safety | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic SourceStrictness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceStrictness -> Rep SourceStrictness x # to :: Rep SourceStrictness x -> SourceStrictness # | |||||
| Generic SourceUnpackedness | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: SourceUnpackedness -> Rep SourceUnpackedness x # to :: Rep SourceUnpackedness x -> SourceUnpackedness # | |||||
| Generic Specificity | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Stmt | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic TyLit | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic TySynEqn | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic Type | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic TypeFamilyHead | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
Methods from :: TypeFamilyHead -> Rep TypeFamilyHead x # to :: Rep TypeFamilyHead x -> TypeFamilyHead # | |||||
| Generic ConstructorInfo | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorInfo -> Rep ConstructorInfo x # to :: Rep ConstructorInfo x -> ConstructorInfo # | |||||
| Generic ConstructorVariant | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorVariant -> Rep ConstructorVariant x # to :: Rep ConstructorVariant x -> ConstructorVariant # | |||||
| Generic DatatypeInfo | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
| Generic DatatypeVariant | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: DatatypeVariant -> Rep DatatypeVariant x # to :: Rep DatatypeVariant x -> DatatypeVariant # | |||||
| Generic FieldStrictness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: FieldStrictness -> Rep FieldStrictness x # to :: Rep FieldStrictness x -> FieldStrictness # | |||||
| Generic Strictness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
| Generic Unpackedness | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
| Generic FlatAttributes | |||||
Defined in Web.View.Types Associated Types
Methods from :: FlatAttributes -> Rep FlatAttributes x # to :: Rep FlatAttributes x -> FlatAttributes # | |||||
| Generic CompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: CompressParams -> Rep CompressParams x # to :: Rep CompressParams x -> CompressParams # | |||||
| Generic DecompressError | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressError -> Rep DecompressError x # to :: Rep DecompressError x -> DecompressError # | |||||
| Generic DecompressParams | |||||
Defined in Codec.Compression.Zlib.Internal Associated Types
Methods from :: DecompressParams -> Rep DecompressParams x # to :: Rep DecompressParams x -> DecompressParams # | |||||
| Generic CompressionLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionLevel -> Rep CompressionLevel x # to :: Rep CompressionLevel x -> CompressionLevel # | |||||
| Generic CompressionStrategy | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
Methods from :: CompressionStrategy -> Rep CompressionStrategy x # to :: Rep CompressionStrategy x -> CompressionStrategy # | |||||
| Generic Format | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
| Generic MemoryLevel | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
| Generic Method | |||||
Defined in Codec.Compression.Zlib.Stream | |||||
| Generic WindowBits | |||||
Defined in Codec.Compression.Zlib.Stream Associated Types
| |||||
| Generic () | |||||
| Generic Bool | |||||
Defined in GHC.Generics | |||||
| Generic (ZipList a) | |||||
Defined in Control.Applicative Associated Types
| |||||
| Generic (Complex a) | |||||
Defined in Data.Complex Associated Types
| |||||
| Generic (Identity a) | |||||
Defined in Data.Functor.Identity Associated Types
| |||||
| Generic (First a) | |||||
Defined in Data.Monoid Associated Types
| |||||
| Generic (Last a) | |||||
Defined in Data.Monoid Associated Types
| |||||
| Generic (Down a) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (First a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Last a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Max a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (Min a) | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (WrappedMonoid m) | |||||
Defined in Data.Semigroup Associated Types
Methods from :: WrappedMonoid m -> Rep (WrappedMonoid m) x # to :: Rep (WrappedMonoid m) x -> WrappedMonoid m # | |||||
| Generic (Dual a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic (Endo a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic (Product a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic (Sum a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic (NonEmpty a) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (Par1 p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (SCC vertex) | |||||
Defined in Data.Graph Associated Types
| |||||
| Generic (Digit a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (Elem a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (FingerTree a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (Node a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (ViewL a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (ViewR a) | |||||
Defined in Data.Sequence.Internal Associated Types
| |||||
| Generic (Tree a) | |||||
Defined in Data.Tree Associated Types
| |||||
| Generic (Loc a) | |||||
Defined in Language.Haskell.Exts.SrcLoc Associated Types
| |||||
| Generic (Activation l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Alt l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Annotation l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Assoc l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Asst l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (BangType l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Binds l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (BooleanFormula l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: BooleanFormula l -> Rep (BooleanFormula l) x # to :: Rep (BooleanFormula l) x -> BooleanFormula l # | |||||
| Generic (Bracket l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (CName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (CallConv l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ClassDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ConDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Context l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (DataOrNew l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Decl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (DeclHead l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (DerivStrategy l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: DerivStrategy l -> Rep (DerivStrategy l) x # to :: Rep (DerivStrategy l) x -> DerivStrategy l # | |||||
| Generic (Deriving l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (EWildcard l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Exp l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ExportSpec l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ExportSpecList l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: ExportSpecList l -> Rep (ExportSpecList l) x # to :: Rep (ExportSpecList l) x -> ExportSpecList l # | |||||
| Generic (FieldDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (FieldUpdate l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: FieldUpdate l -> Rep (FieldUpdate l) x # to :: Rep (FieldUpdate l) x -> FieldUpdate l # | |||||
| Generic (FunDep l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (GadtDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (GuardedRhs l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (IPBind l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (IPName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ImportDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ImportSpec l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ImportSpecList l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: ImportSpecList l -> Rep (ImportSpecList l) x # to :: Rep (ImportSpecList l) x -> ImportSpecList l # | |||||
| Generic (InjectivityInfo l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: InjectivityInfo l -> Rep (InjectivityInfo l) x # to :: Rep (InjectivityInfo l) x -> InjectivityInfo l # | |||||
| Generic (InstDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (InstHead l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (InstRule l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Literal l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Match l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (MaybePromotedName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: MaybePromotedName l -> Rep (MaybePromotedName l) x # to :: Rep (MaybePromotedName l) x -> MaybePromotedName l # | |||||
| Generic (Module l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ModuleHead l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ModuleName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ModulePragma l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: ModulePragma l -> Rep (ModulePragma l) x # to :: Rep (ModulePragma l) x -> ModulePragma l # | |||||
| Generic (Name l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Namespace l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Op l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Overlap l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (PXAttr l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Pat l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (PatField l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (PatternSynDirection l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: PatternSynDirection l -> Rep (PatternSynDirection l) x # to :: Rep (PatternSynDirection l) x -> PatternSynDirection l # | |||||
| Generic (Promoted l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (QName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (QOp l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (QualConDecl l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: QualConDecl l -> Rep (QualConDecl l) x # to :: Rep (QualConDecl l) x -> QualConDecl l # | |||||
| Generic (QualStmt l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (RPat l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (RPatOp l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (ResultSig l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Rhs l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Role l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Rule l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (RuleVar l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Safety l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Sign l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (SpecialCon l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Splice l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Stmt l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (TyVarBind l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Type l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (TypeEqn l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Unpackedness l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: Unpackedness l -> Rep (Unpackedness l) x # to :: Rep (Unpackedness l) x -> Unpackedness l # | |||||
| Generic (WarningText l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
Methods from :: WarningText l -> Rep (WarningText l) x # to :: Rep (WarningText l) x -> WarningText l # | |||||
| Generic (XAttr l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (XName l) | |||||
Defined in Language.Haskell.Exts.Syntax Associated Types
| |||||
| Generic (Doc a) | |||||
Defined in Text.PrettyPrint.Annotated.HughesPJ Associated Types
| |||||
| Generic (AddrRange a) | |||||
Defined in Data.IP.Range Associated Types
| |||||
| Generic (TyVarBndr flag) | |||||
Defined in Language.Haskell.TH.Syntax Associated Types
| |||||
| Generic (Maybe a) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (Solo a) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic [a] | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (WrappedMonad m a) | |||||
Defined in Control.Applicative Associated Types
Methods 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 Associated Types
| |||||
| Generic (Proxy t) | |||||
Defined in GHC.Generics | |||||
| Generic (Arg a b) | |||||
Defined in Data.Semigroup Associated Types
| |||||
| Generic (U1 p) | |||||
| Generic (V1 p) | |||||
| Generic (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe Associated Types
| |||||
| Generic (a, b) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (WrappedArrow a b c) | |||||
Defined in Control.Applicative Associated Types
Methods 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 Associated Types
| |||||
| Generic (Const a b) | |||||
Defined in Data.Functor.Const Associated Types
| |||||
| Generic (Ap f a) | |||||
Defined in Data.Monoid Associated Types
| |||||
| Generic (Alt f a) | |||||
Defined in Data.Semigroup.Internal Associated Types
| |||||
| Generic (Rec1 f p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec (Ptr ()) p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec Char p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec Double p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec Float p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec Int p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (URec Word p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (Tagged s b) | |||||
Defined in Data.Tagged Associated Types
| |||||
| Generic (AccumT w m a) | |||||
Defined in Control.Monad.Trans.Accum Associated Types
| |||||
| Generic (ExceptT e m a) | |||||
Defined in Control.Monad.Trans.Except Associated Types
| |||||
| Generic (IdentityT f a) | |||||
Defined in Control.Monad.Trans.Identity Associated Types
| |||||
| Generic (ReaderT r m a) | |||||
Defined in Control.Monad.Trans.Reader Associated Types
| |||||
| Generic (SelectT r m a) | |||||
Defined in Control.Monad.Trans.Select Associated Types
| |||||
| Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Lazy Associated Types
| |||||
| Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict Associated Types
| |||||
| Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.CPS Associated Types
| |||||
| Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Lazy Associated Types
| |||||
| Generic (WriterT w m a) | |||||
Defined in Control.Monad.Trans.Writer.Strict Associated Types
| |||||
| Generic (Constant a b) | |||||
Defined in Data.Functor.Constant Associated Types
| |||||
| Generic (a, b, c) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (Product f g a) | |||||
Defined in Data.Functor.Product Associated Types
| |||||
| Generic (Sum f g a) | |||||
Defined in Data.Functor.Sum Associated Types
| |||||
| Generic ((f :*: g) p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic ((f :+: g) p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (K1 i c p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (ContT r m a) | |||||
Defined in Control.Monad.Trans.Cont Associated Types
| |||||
| Generic (a, b, c, d) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (Compose f g a) | |||||
Defined in Data.Functor.Compose Associated Types
| |||||
| Generic ((f :.: g) p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (M1 i c f p) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.CPS Associated Types
| |||||
| Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Lazy Associated Types
| |||||
| Generic (RWST r w s m a) | |||||
Defined in Control.Monad.Trans.RWS.Strict Associated Types
| |||||
| Generic (a, b, c, d, e) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |||||
Defined in GHC.Generics Associated Types
| |||||
| Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |||||
Defined in GHC.Generics Associated Types
| |||||