hyperbole-0.4.2: Interactive HTML apps using type-safe serverside Haskell
Copyright(c) 2024 Sean Hess
LicenseBSD3
MaintainerSean Hess <seanhess@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageGHC2021

Web.Hyperbole

Description

Create fully interactive HTML applications with type-safe serverside Haskell. Inspired by HTMX, Elm, and Phoenix LiveView

Synopsis

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

  1. 100% Haskell
  2. Type safe views, actions, routes, and forms
  3. Elegant interface with little boilerplate
  4. VirtualDOM updates over sockets, fallback to HTTP
  5. 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 can run side effects (like loading data), then respond with an HTML View. The following application has a single Page that displays a static "Hello World"

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}

module Main where

import Web.Hyperbole

main = do
  run 3000 $ do
    liveApp (basicDocument "Example") (runPage messagePage)

messagePage :: Eff es (Page '[])
messagePage = do
  pure $ do
    col (pad 10) $ do
      el bold "Hello World"

Interactive HyperViews

We can include one or more HyperViews to add type-safe interactivity to live subsections of the Page. To start, first define a data type (a ViewId) that uniquely identifies that subsection of the page:

data Message = Message
  deriving (Show, Read, ViewId)

Make our ViewId an instance of HyperView by:

  • Create an Action type with a constructor for every possible way that the user can interact with it
  • Write an update for each Action
instance HyperView Message es where
  data Action Message
    = SetMessage Text
    deriving (Show, Read, ViewAction)

  update (SetMessage t) =
    pure $ el bold (text t)

Replace the static message with our new HyperView using hyper, and add our ViewId to the Page type signature. Then add a button to trigger the Action:

messagePage :: Eff es (Page '[Message])
messagePage = do
  pure $ do
    col (pad 10 . gap 10) $ do
      hyper Message $ do
        el bold "Hello World"
        button (SetMessage "Goodbye") (border 1) "Say Goodbye"

The contents of hyper will be replaced with the result of update, leaving the rest of the page untouched.

View Functions

Rather than showing a completely different HTML View on each update, we can create a View Function for our HyperView. These are pure functions with state parameters, which return a View. The compiler will tell us if we try to trigger an Action for a HyperView that doesn't match our View context

Each HyperView should have a main view function that renders it based on its state:

messageView :: Text -> View Message ()
messageView m = do
  el bold $ text $ "Message: " <> m
  button (SetMessage "Goodbye") (border 1) "Say Goodbye"

Now we can refactor to use the same view function for both the initial hyper and the update. The only thing that will change on an update is the text of the message.

messagePage :: Eff es (Page '[Message])
messagePage = do
  pure $ do
    hyper Message $ messageView "Hello"

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

  update (SetMessage t) =
    pure $ messageView t

We can create multiple view functions with our HyperView as the context, and factor them however is most convenient.

goodbyeButton :: View Message ()
goodbyeButton = do
  button (SetMessage "Goodbye") (border 1) "Say Goodbye"

We can also create view functions that work in any context.

header :: Text -> View c ()
header txt = do
  el bold (text txt)

Factored this way, our main View for Message becomes:

messageView' :: Text -> View Message ()
messageView' m = do
  header $ "Message: " <> m
  goodbyeButton

Managing State

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

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

  update (Louder m) = do
    let new = m <> "!"
    pure $ messageView new

messageView :: Text -> View Message ()
messageView m = do
  button (Louder m) (border 1) "Louder"
  el bold $ text $ "Message: " <> m

Side Effects

For any real application with more complex state and data persistence, we need side effects.

Hyperbole relies on Effectful to compose side effects. We can use effects in a Page or an update. In this example, each client stores the latest message in their session.

From Example.Page.Simple

messagePage :: (Hyperbole :> es) => Eff es (Page '[Message])
messagePage = do
  stored <- session @Text "message"
  let msg = fromMaybe "Hello" stored
  pure $ do
    hyper Message $ messageView msg

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

  update (Louder m) = do
    let new = m <> "!"
    setSession "message" new
    pure $ messageView new

To use an Effect other than Hyperbole, add it as a constraint to the Page and any HyperView instances that need it. Then run the effect in your application

From Example.Page.Counter

{-# LANGUAGE UndecidableInstances #-}

instance (Reader (TVar Int) :> es, Concurrent :> es) => HyperView Counter es where
  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

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.

From Example.Effects.Todos

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

When you create your Application, run any Effects you need. Here we are using a runner that implements the effect with sessions from Hyperbole, but you could write a different runner that connects to a database instead.

From example/Main.hs:

app :: Application
app = do
  liveApp
    toDocument
    (runApp . routeRequest $ router)
 where
  runApp :: (Hyperbole :> es, IOE :> es) => Eff (Concurrent : Todos : es) a -> Eff es a
  runApp = runTodosSession . runConcurrent

Implementing a database runner for a custom Effect is beyond the scope of this documentation, but see the following:

Multiple HyperViews

We can add as many HyperViews to a page as we want. Let's create another HyperView for a simple counter

From Example.Intro.MultiView

data Count = Count
  deriving (Show, Read, ViewId)


instance HyperView Count es where
  data Action Count
    = Increment Int
    | Decrement Int
    deriving (Show, Read, ViewAction)

  update (Increment n) = do
    pure $ countView (n + 1)
  update (Decrement n) = do
    pure $ countView (n - 1)


countView :: Int -> View Count ()
countView n = do
  el_ $ text $ pack $ show n
  button (Increment n) (border 1) "Increment"
  button (Decrement n) (border 1) "Decrement"

We can use both Message and Count HyperViews in our page, and they will update independently:

page :: Eff es (Page '[Message, Count])
page = do
  pure $ do
    row id $ do
      hyper Message $ messageView "Hello"
      hyper Count $ countView 0

Copies

We can embed multiple copies of the same HyperView as long as the value of ViewId is unique. Let's update Message to allow for more than one value:

See Example.Page.Simple

data Message = Message1 | Message2
  deriving (Show, Read, ViewId)

Now we can embed multiple Message HyperViews into the same page. Each will update independently.

messagePage :: Eff es (Page '[Message])
messagePage = do
  pure $ do
    hyper Message1 $ messageView "Hello"
    hyper Message2 $ messageView "World!"

This is especially useful if we put identifying information in our ViewId, such as a database id. The Contacts Example uses this to allow the user to edit multiple contacts on the same page. The viewId function gives us access to that info

From Example.Contacts

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

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

  update action = do
    -- No matter which action we are performing, let's look up the user to make sure it exists
    Contact uid <- viewId
    u <- Users.find uid
    case action of
      View -> do
        pure $ contactView u
      Edit -> do
        pure $ contactEdit 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.Intro.Nested

data TodoItem = TodoItem
  deriving (Show, Read, ViewId)

instance HyperView TodoItem es where
  data Action TodoItem
    = Complete Todo
    deriving (Show, Read, ViewAction)

  update (Complete todo) = do
    let new = todo{completed = True}
    pure $ todoView new

But we also want the entire list to refresh when a user adds a new todo. We need to create a parent HyperView for the whole list.

List all allowed nested views by adding them to Require

data AllTodos = AllTodos
  deriving (Show, Read, ViewId)

instance HyperView AllTodos es where
  type Require AllTodos = '[TodoItem]

  data Action AllTodos
    = AddTodo Text [Todo]
    deriving (Show, Read, ViewAction)

  update (AddTodo txt todos) = do
    let new = Todo txt False : todos
    pure $ todosView new

Then we can embed the child HyperView into the parent with hyper

todosView :: [Todo] -> View AllTodos ()
todosView todos = do
  forM_ todos $ todo -> do
    hyper TodoItem $ todoView todo
  button (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 -> View c ()
header txt = do
  el bold (text txt)

What if we want to reuse functionality too? We can pass an Action into the view function as a parameter:

styledButton :: (ViewAction (Action id)) => Action id -> Text -> View id ()
styledButton clickAction lbl = do
  button clickAction (pad 10 . bg Primary . hover (bg PrimaryLight) . rounded 5) (text lbl)

We can create more complex view functions by passing state in as a parameter. Here's a button that toggles between a checked and unchecked state:

toggleCheckBtn :: (ViewAction (Action id)) => Action id -> Bool -> View id ()
toggleCheckBtn clickAction isSelected = do
  button clickAction (width 32 . height 32 . border 1 . rounded 100) contents
 where
  contents = if isSelected then Icon.check else " "

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.

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 = do
  run 3000 $ do
    liveApp (basicDocument "Multiple Pages") (routeRequest router)
 where
  router Message = runPage Message.page
  router Counter = runPage Counter.page

Each Page is completely independent. The web page is freshly reloaded each time you switch routes. We can add type-safe links to other pages using route

menu :: View c ()
menu = do
  route Message id "Link to /message"
  route Counter id "Link to /counter"

If you need the same header or menu on all pages, use a view function:

exampleLayout :: View c () -> View c ()
exampleLayout content = do
  layout id $ do
    el (border 1) "My Website Header"
    row id $ do
      menu
      content

examplePage :: Eff es (Page '[])
examplePage = do
  pure $ exampleLayout $ do
    el_ "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 = do
  run 3000 $ do
    liveApp (basicDocument "Example") (runPage messagePage)

run :: Port -> Application -> IO () #

Run an Application on the given port. This calls runSettings with defaultSettings.

basicDocument :: Text -> ByteString -> ByteString Source #

wrap HTML fragments in a simple document with a custom title and include required embeds

liveApp (basicDocument "App Title") (routeRequest router)

You may want to specify a custom document function instead:

myDocument :: ByteString -> ByteString
myDocument content =
  [i|<html>
    <head>
      <title>#{title}</title>
      <script type="text/javascript">#{scriptEmbed}</script>
      <style type="text/css">#{cssResetEmbed}</style>
    </head>
    <body>#{content}</body>
  </html>|]

runPage :: forall (views :: [Type]) (es :: [Effect]). (Hyperbole :> es, RunHandlers views es) => Eff es (Page views) -> Eff es Response Source #

Run a Page in Hyperbole

type Page (views :: [Type]) = View (Root views) () Source #

Type-Safe Routes

routeRequest :: forall (es :: [Effect]) route. (Hyperbole :> es, Route route) => (route -> Eff es Response) -> Eff es Response Source #

Route URL patterns to different pages

import Page.Messages qualified as Messages
import Page.Users qualified as Users

data AppRoute
  = Main
  | Messages
  | Users UserId
  deriving (Eq, Generic, Route)

router :: (Hyperbole :> es) => AppRoute -> Eff es Response
router Messages = page Messages.page
router (Users uid) = page $ Users.page uid
router Main = do
  view $ do
    el_ "click a link below to visit a page"
    route Messages id "Messages"

main = do
  run 3000 $ do
    liveApp (basicDocument "Example") (routeRequest router)

class Route a where Source #

Derive this class to use a sum type as a route. Constructors and Selectors map intuitively to url patterns

data AppRoute
 = HomePage
 | Users
 | User Int
 deriving (Generic, Route)

/         -> HomePage
/users/   -> Users
/user/100 -> User 100

Minimal complete definition

Nothing

Methods

baseRoute :: Maybe a Source #

The route to use if attempting to match on empty segments

default baseRoute :: (Generic a, GenRoute (Rep a)) => Maybe a Source #

matchRoute :: [Segment] -> Maybe a Source #

Try to match segments to a route

default matchRoute :: (Generic a, GenRoute (Rep a)) => [Segment] -> Maybe a Source #

routePath :: a -> [Segment] Source #

Map a route to segments

default routePath :: (Generic a, Eq a, GenRoute (Rep a)) => a -> [Segment] Source #

routeUrl :: Route a => a -> Url Source #

Convert a Route to a Url

>>> routeUrl (User 100)
/user/100

route :: Route a => a -> Mod c -> View c () -> View c () Source #

A hyperlink to another route

>>> route (User 100) id "View User"
<a href="/user/100">View User</a>

Hyperbole Effect

data Hyperbole (a :: Type -> Type) b Source #

In any load or handle, you can use this Effect to get extra request information or control the response manually.

For most Pages, you won't need to use this effect directly. Use custom Routes for request info, and return Views to respond

Instances

Instances details
type DispatchOf Hyperbole Source # 
Instance details

Defined in Web.Hyperbole.Effect.Hyperbole

Request

reqParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es a Source #

Require a given parameter from the Query arguments

myPage :: Page es Response
myPage = do
  load $ do
    token <- reqParam "token"
    sideEffectUsingToken token
    pure myPageView

reqParams :: forall (es :: [Effect]). Hyperbole :> es => Eff es QueryText Source #

Return the entire Query

myPage :: Page es Response
myPage = do
  load $ do
    q <- reqParams
    case lookupParam "token" q of
      Nothing -> pure $ errorView "Missing Token in Query String"
      Just t -> do
        sideEffectUsingToken token
        pure myPageView

request :: forall (es :: [Effect]). Hyperbole :> es => Eff es Request Source #

Return all information about the Request

lookupParam :: forall a (es :: [Effect]). (Hyperbole :> es, FromHttpApiData a) => Text -> Eff es (Maybe a) Source #

Maybe version of reqParam

myPage :: Page es Response
myPage = do
  load $ do
      mbToken <- lookupParam "token"
      sideEffectUsingToken $ fromMaybe "default" mbToken
      pure myPageView

hasParam :: Text -> QueryText -> Bool Source #

Whether the param is present or not

formBody :: forall (es :: [Effect]). Hyperbole :> es => Eff es Form Source #

Return the request body as a Web.FormUrlEncoded.Form

Prefer using Type-Safe Forms when possible

formData :: forall form (val :: Type -> Type) (es :: [Effect]). (Form form val, Hyperbole :> es) => Eff es (form Identity) Source #

class ToQueryData a where Source #

Reimplement ToHttpApiData based on Show

Minimal complete definition

Nothing

Methods

toQueryData :: a -> Text Source #

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

Instances

Instances details
ToQueryData Word16 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Word32 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Word64 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Word8 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Text Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData UTCTime Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Integer Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Bool Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Char Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Double Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Float Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData Int Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Methods

toQueryData :: Int -> Text Source #

ToQueryData Word Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

ToQueryData a => ToQueryData (Maybe a) Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Methods

toQueryData :: Maybe a -> Text Source #

Show a => ToQueryData [a] Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Methods

toQueryData :: [a] -> Text Source #

(ToQueryData a, ToQueryData b) => ToQueryData (Either a b) Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Methods

toQueryData :: Either a b -> Text Source #

class FromQueryData a where Source #

Reimplement FromHttpApiData based on Read

Minimal complete definition

Nothing

Instances

Instances details
FromQueryData Word16 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Word32 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Word64 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Word8 Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Text Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData UTCTime Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Integer Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Bool Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Char Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Double Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Float Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Int Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

FromQueryData Word Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Read a => FromQueryData (Maybe a) Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Read a => FromQueryData [a] Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

(FromQueryData a, FromQueryData b) => FromQueryData (Either a b) Source # 
Instance details

Defined in Web.Hyperbole.Effect.QueryData

Response

notFound :: forall (es :: [Effect]) a. Hyperbole :> es => Eff es a Source #

Respond immediately with 404 Not Found

userLoad :: (Hyperbole :> es, Users :> es) => UserId -> Eff es User
userLoad uid = do
  mu <- send (LoadUser uid)
  maybe notFound pure mu

myPage :: (Hyperbole :> es, Users :> es) => Eff es View
myPage = do
  load $ do
    u <- userLoad 100
    -- skipped if user = Nothing
    pure $ userView u

redirect :: forall (es :: [Effect]) a. Hyperbole :> es => Url -> Eff es a Source #

Redirect immediately to the Url

respondEarly :: forall (es :: [Effect]) id. (Hyperbole :> es, HyperView id es) => id -> View id () -> Eff es () Source #

Respond with the given view, and stop execution

HyperView

class (ViewId id, ViewAction (Action id)) => HyperView id (es :: [Effect]) where Source #

HyperViews are interactive subsections of a Page

Create an instance with a unique view id type and a sum type describing the actions the HyperView supports. The View Id can contain context (a database id, for example)

data Message = Message Int
  deriving (Generic, Param)

data MessageAction
  = Louder Text
  | ClearMessage
  deriving (Generic, Param)

instance HyperView Message where
  type Action Message = MessageAction

Associated Types

data Action id Source #

type Require id :: [Type] Source #

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

Methods

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

Instances

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

Defined in Web.Hyperbole.HyperView

Associated Types

data Action (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

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

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

Methods

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

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

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

Methods

viewId :: m view Source #

Instances

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

Defined in Web.Hyperbole.HyperView

Methods

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

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

Defined in Web.Hyperbole.HyperView

Methods

viewId :: View ctx ctx Source #

Events

onClick :: 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

onKeyDown :: ViewAction (Action id) => Key -> Action id -> Mod id Source #

onKeyUp :: ViewAction (Action id) => Key -> Action id -> Mod id Source #

onLoad :: ViewAction (Action id) => Action id -> DelayMs -> Mod id Source #

Send the action after N milliseconds. Can be used to implement lazy loading or polling

pollMessageView :: Text -> View Message ()
pollMessageView m = do
  onLoad LoadMessage 1000 $ do
    el bold "Current Message. Reloading in 1s"
    el_ (text m)

onRequest :: Mod id -> Mod id Source #

Apply a Mod only when a request is in flight

myView = do
  el (hide . onRequest flexCol) el_ "Loading..."
  el (onRequest hide) Loaded

data Key Source #

Instances

Instances details
Read Key Source # 
Instance details

Defined in Web.Hyperbole.View.Event

Show Key Source # 
Instance details

Defined in Web.Hyperbole.View.Event

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Interactive Elements

button :: ViewAction (Action id) => Action id -> Mod id -> View id () -> View id () Source #

<button> HTML tag which sends the action when pressed

button SomeAction (border 1) "Click Me"

search :: ViewAction (Action id) => (Text -> Action id) -> DelayMs -> Mod id -> View id () Source #

A live search field

dropdown :: ViewAction (Action id) => (opt -> Action id) -> (opt -> Bool) -> Mod id -> View (Option opt id (Action id)) () -> View id () Source #

Type-safe dropdown. Sends (opt -> Action id) when selected. The selection predicate (opt -> Bool) controls which option is selected. See Example.Contacts

data ContactsAction
  = Reload (Maybe Filter)
  | Delete Int
  deriving (Generic, Param)

allContactsView :: Maybe Filter -> View Contacts ()
allContactsView fil = do
  row (gap 10) $ do
    el (pad 10) "Filter: "
    dropdown Reload (== fil) id $ do
      option Nothing ""
      option (Just Active) "Active!"
      option (Just Inactive) "Inactive"
  ...

option :: (ViewAction (Action id), Eq opt) => opt -> View (Option opt id (Action id)) () -> View (Option opt id (Action id)) () Source #

An option for a dropdown. First argument is passed to (opt -> Action id) in the dropdown, and to the selected predicate

data Option opt (id :: k) action Source #

The view context for an option

Type-Safe Forms

Painless forms with type-checked field names, and support for validation. See Example.Forms

class Form (form :: (Type -> Type) -> Type) (val :: Type -> Type) | form -> val where Source #

Parse a FormField from the request

formAction :: (Hyperbole :> es, UserDB :> es) => FormView -> FormAction -> Eff es (View FormView ())
formAction _ SignUp = do
  a <- formField @Age
  u <- formField @User
  saveUserToDB u a
  pure $ el_ "Saved!"

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 #

genForm :: form val Source #

default genForm :: (Generic (form val), GenFields (Rep (form val))) => form val Source #

genFieldsWith :: form val -> form (FormField val) Source #

default genFieldsWith :: (Generic (form val), Generic (form (FormField val)), GConvert (Rep (form val)) (Rep (form (FormField val)))) => form val -> form (FormField val) Source #

formFields :: forall form (val :: Type -> Type). Form form val => form (FormField val) Source #

Generate FormFields for the given instance of Form, with no validation information

let f = formFields @UserForm
form @UserForm Submit id $ do
  field f.user id $ do
    label "Username"
    input Username (placeholder "Username")

formFieldsWith :: forall form (val :: Type -> Type). Form form val => form val -> form (FormField val) Source #

Generate FormFields for the givne instance of Form from validation data

let valids = UserForm { user = Valid, age = Invalid "must be 20 years old" }
let f = formFieldsWith @UserForm valids
form @UserForm Submit id $ do
  field f.user id $ do
    label "Username"
    input Username (placeholder "Username")

data FormField (v :: k -> Type) (a :: k) Source #

Instances

Instances details
GenField (FormField (Validated :: Type -> Type)) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

GenField (FormField Maybe) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Show (v a) => Show (FormField v a) Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Methods

showsPrec :: Int -> FormField v a -> ShowS #

show :: FormField v a -> String #

showList :: [FormField v a] -> ShowS #

type Field (FormField v) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (FormField v) a = FormField v a

type family Field (context :: Type -> Type) a Source #

Instances

Instances details
type Field Identity a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field Identity a = a
type Field Maybe a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field Maybe a = Maybe a
type Field (Either String) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (FieldName :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (FieldName :: Type -> Type) a = FieldName a
type Field (Validated :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (Validated :: Type -> Type) a = Validated a
type Field (FormField v) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (FormField v) a = FormField v a

data Identity a #

Identity functor and monad. (a non-strict monad)

Since: base-4.8.0.0

Instances

Instances details
MonadFix Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mfix :: (a -> Identity a) -> Identity a #

MonadZip Identity

Since: base-4.8.0.0

Instance details

Defined in Control.Monad.Zip

Methods

mzip :: Identity a -> Identity b -> Identity (a, b) #

mzipWith :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

munzip :: Identity (a, b) -> (Identity a, Identity b) #

Foldable Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldMap' :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Foldable1 Identity

Since: base-4.18.0.0

Instance details

Defined in Data.Foldable1

Methods

fold1 :: Semigroup m => Identity m -> m #

foldMap1 :: Semigroup m => (a -> m) -> Identity a -> m #

foldMap1' :: Semigroup m => (a -> m) -> Identity a -> m #

toNonEmpty :: Identity a -> NonEmpty a #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

head :: Identity a -> a #

last :: Identity a -> a #

foldrMap1 :: (a -> b) -> (a -> b -> b) -> Identity a -> b #

foldlMap1' :: (a -> b) -> (b -> a -> b) -> Identity a -> b #

foldlMap1 :: (a -> b) -> (b -> a -> b) -> Identity a -> b #

foldrMap1' :: (a -> b) -> (a -> b -> b) -> Identity a -> b #

Eq1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Identity a -> Identity b -> Bool #

Ord1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Identity a -> Identity b -> Ordering #

Read1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Identity a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Identity a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Identity a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Identity a] #

Show1 Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Identity a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Identity a] -> ShowS #

Traversable Identity

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Functor Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

Monad Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

NFData1 Identity

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Identity a -> () #

Hashable1 Identity 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Identity a -> Int #

Generic1 Identity 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep1 Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

Methods

from1 :: Identity a -> Rep1 Identity a #

to1 :: Rep1 Identity a -> Identity a #

MonadBaseControl Identity Identity 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Identity a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Identity a = a
Data a => Data (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Identity a -> c (Identity a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Identity a) #

toConstr :: Identity a -> Constr #

dataTypeOf :: Identity a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Identity a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Identity a)) #

gmapT :: (forall b. Data b => b -> b) -> Identity a -> Identity a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Identity a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Identity a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Identity a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Identity a -> m (Identity a) #

IsString a => IsString (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Identity a #

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Bits a => Bits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

FiniteBits a => FiniteBits (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Bounded a => Bounded (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Enum a => Enum (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Floating a => Floating (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

RealFloat a => RealFloat (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Ix a => Ix (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Num a => Num (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Read a => Read (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Fractional a => Fractional (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Integral a => Integral (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Real a => Real (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

toRational :: Identity a -> Rational #

RealFrac a => RealFrac (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

properFraction :: Integral b => Identity a -> (b, Identity a) #

truncate :: Integral b => Identity a -> b #

round :: Integral b => Identity a -> b #

ceiling :: Integral b => Identity a -> b #

floor :: Integral b => Identity a -> b #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

NFData a => NFData (Identity a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Identity a -> () #

Eq a => Eq (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Ord a => Ord (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Hashable a => Hashable (Identity a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Identity a -> Int #

hash :: Identity a -> Int #

FromFormKey a => FromFormKey (Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.FormUrlEncoded

ToFormKey a => ToFormKey (Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.FormUrlEncoded

Methods

toFormKey :: Identity a -> Text #

FromHttpApiData a => FromHttpApiData (Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Identity a)

Since: http-api-data-0.4.2

Instance details

Defined in Web.Internal.HttpApiData

type Rep1 Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep1 Identity = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Field Identity a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field Identity a = a
type StM Identity a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Identity a = a
type Rep (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Form View

form :: forall (form :: (Type -> Type) -> Type) (v :: Type -> Type) id. (Form form v, ViewAction (Action id)) => Action id -> Mod id -> View (FormFields id) () -> View id () Source #

Type-safe <form>. Calls (Action id) on submit

userForm :: Validation -> View FormView ()
userForm v = do
  form Signup v id $ do
    el Style.h1 "Sign Up"

    field @User id Style.invalid $ do
      label "Username"
      input Username (placeholder "username")
      el_ invalidText

    field @Age id Style.invalid $ do
      label "Age"
      input Number (placeholder "age")
      el_ invalidText

    submit (border 1) "Submit"

field :: forall id v a. FormField v a -> (v a -> Mod (FormFields id)) -> View (Input id v a) () -> View (FormFields id) () Source #

Display a FormField

data Age = Age Int deriving (Generic, FormField)

myForm = do
  form SignUp mempty id $ do
    field @Age id id $ do
     label Age
     input Number (placeholder "42")

label :: forall id (v :: Type -> Type) a. Text -> View (Input id v a) () Source #

label for a field

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 #

Button that submits the form. Use button to specify actions other than submit

data InputType Source #

Choose one for inputs to give the browser autocomplete hints

Instances

Instances details
Show InputType Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Handlers

Validation

data Validated (a :: k) Source #

Validation results for a form

data UserForm f = UserForm
  { username :: Field f
  , age :: Field f Int
  }
  deriving (Generic)


validateUsername :: Username -> Validated Username
validateUsername (Username u) =
  mconcat
    [ validate (T.elem ' ' u) "Username must not contain spaces"
    , validate (T.length u < 4) "Username must be at least 4 chars"
    , if u == "admin" || u == "guest"
        then Invalid "Username is already in use"
        else Valid
    ]

formAction :: (Hyperbole :> es, UserDB :> es) => FormView -> FormAction -> Eff es (View FormView ())
formAction _ SignUp = do
  u <- formField @Age

  case validateUser u a of
    Validation [] -> successView
    errs -> userForm v

Constructors

Invalid Text 
NotInvalid 
Valid 

Instances

Instances details
GenField (Validated :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Methods

genField :: String -> Field (Validated :: Type -> Type) a Source #

Monoid (Validated a) Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Semigroup (Validated a) Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

Methods

(<>) :: Validated a -> Validated a -> Validated a #

sconcat :: NonEmpty (Validated a) -> Validated a #

stimes :: Integral b => b -> Validated a -> Validated a #

Show (Validated a) Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

GenField (FormField (Validated :: Type -> Type)) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (Validated :: Type -> Type) a Source # 
Instance details

Defined in Web.Hyperbole.View.Forms

type Field (Validated :: Type -> Type) a = Validated a

validate :: forall {k} (a :: k). Bool -> Text -> Validated a Source #

specify a check for a Validation

fieldValid :: View (Input id v a) (v a) Source #

invalidText :: forall a id. View (Input id (Validated :: Type -> Type) a) () Source #

anyInvalid :: forall form (val :: Type -> Type). (Form form val, ValidationState val) => form val -> Bool Source #

Sessions

session :: forall a (es :: [Effect]). (FromQueryData a, Hyperbole :> es) => Text -> Eff es (Maybe a) Source #

Lookup a session variable by keyword

setSession :: forall a (es :: [Effect]). (ToQueryData a, Hyperbole :> es) => Text -> a -> Eff es () Source #

Set a session variable by keyword

clearSession :: forall (es :: [Effect]). Hyperbole :> es => Text -> Eff es () Source #

Clear a session variable

Advanced

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

Trigger actions for another view. They will update the view specified

otherView :: View OtherView ()
otherView = do
  el_ "This is not a message view"
  button OtherAction id "Do Something"

  target (Message 2) $ do
    el_ "Now we can trigger a MessageAction which will update our Message HyperView, not this one"
    button ClearMessage id "Clear Message #2"

view :: forall (es :: [Effect]). Hyperbole :> es => View () () -> Eff es Response Source #

Manually set the response to the given view. Normally you return a View from load or handle instead of using this

class ViewId a Source #

Instances

Instances details
ViewId (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toViewId :: Root views -> Text Source #

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

class ViewAction a Source #

Instances

Instances details
ViewAction () Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toAction :: () -> Text Source #

parseAction :: Text -> Maybe () Source #

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

Defined in Web.Hyperbole.HyperView

Methods

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

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

data Response Source #

Valid responses for a Hyperbole effect. Use notFound, etc instead. Reminds you to use load in your Page

myPage :: (Hyperbole :> es) => Page es Response
myPage = do
  -- compiler error: () does not equal Response
  pure ()

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

The top-level view created by load. Carries the views in its type to check that we handled all our views

Instances

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

Defined in Web.Hyperbole.HyperView

Methods

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

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

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

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

Read (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

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

readList :: ReadS [Root views] #

readPrec :: ReadPrec (Root views) #

readListPrec :: ReadPrec [Root views] #

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

Defined in Web.Hyperbole.HyperView

Methods

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

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

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

Show (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

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

show :: Root views -> String #

showList :: [Root views] -> ShowS #

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

Defined in Web.Hyperbole.HyperView

Methods

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

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

ViewId (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Methods

toViewId :: Root views -> Text Source #

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

HyperView (Root views) es Source # 
Instance details

Defined in Web.Hyperbole.HyperView

Associated Types

data Action (Root views) 
Instance details

Defined in Web.Hyperbole.HyperView

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

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

Methods

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

data Action (Root views) Source # 
Instance details

Defined in Web.Hyperbole.HyperView

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

Defined in Web.Hyperbole.HyperView

type Require (Root views) = views

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

Exports

Web.View

Hyperbole is tightly integrated with Web.View for HTML generation

text :: Text -> View c () #

Add text to a view. Not required for string literals

el_ $ do
  "Hello: "
  text user.name

data Url #

Constructors

Url 

Fields

Instances

Instances details
IsString Url 
Instance details

Defined in Web.View.Types.Url

Methods

fromString :: String -> Url #

Monoid Url 
Instance details

Defined in Web.View.Types.Url

Methods

mempty :: Url #

mappend :: Url -> Url -> Url #

mconcat :: [Url] -> Url #

Semigroup Url 
Instance details

Defined in Web.View.Types.Url

Methods

(<>) :: Url -> Url -> Url #

sconcat :: NonEmpty Url -> Url #

stimes :: Integral b => b -> Url -> Url #

Read Url 
Instance details

Defined in Web.View.Types.Url

Show Url 
Instance details

Defined in Web.View.Types.Url

Methods

showsPrec :: Int -> Url -> ShowS #

show :: Url -> String #

showList :: [Url] -> ShowS #

Eq Url 
Instance details

Defined in Web.View.Types.Url

Methods

(==) :: Url -> Url -> Bool #

(/=) :: Url -> Url -> Bool #

even :: Mod c -> Mod c #

Apply to even-numbered children

data Sides a #

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)

Constructors

All a 
TRBL a a a a 
X a 
Y a 
XY a a 
T a 
R a 
B a 
L a 

Instances

Instances details
Num a => Num (Sides a) 
Instance details

Defined in Web.View.Types

Methods

(+) :: Sides a -> Sides a -> Sides a #

(-) :: Sides a -> Sides a -> Sides a #

(*) :: Sides a -> Sides a -> Sides a #

negate :: Sides a -> Sides a #

abs :: Sides a -> Sides a #

signum :: Sides a -> Sides a #

fromInteger :: Integer -> Sides a #

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 id

If you don't want to specify any attributes, you can use id

plainView :: View c ()
plainView = el id "No styles"

truncate :: Mod c #

Cut off the contents of the element

odd :: Mod c -> Mod c #

Apply to odd-numbered children

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"

data Position #

Constructors

Absolute 
Fixed 
Sticky 
Relative 

Instances

Instances details
Show Position 
Instance details

Defined in Web.View.Style

ToClassName Position 
Instance details

Defined in Web.View.Style

ToStyleValue Position 
Instance details

Defined in Web.View.Style

link :: Url -> Mod c -> View c () -> View c () #

A hyperlink to the given url

value :: Text -> Mod c #

data Display #

Constructors

Block 

Instances

Instances details
Show Display 
Instance details

Defined in Web.View.Style

ToClassName Display 
Instance details

Defined in Web.View.Style

ToStyleValue Display 
Instance details

Defined in Web.View.Style

Style Display Display 
Instance details

Defined in Web.View.Style

Style Display None 
Instance details

Defined in Web.View.Style

offset :: Sides Length -> Mod c #

Set Top, Right, Bottom and Left. Requires position Absolute or Fixed. Also see popup

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"

data View context a #

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

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

Defined in Web.Hyperbole.HyperView

Methods

viewId :: View ctx ctx Source #

Applicative (View context) 
Instance details

Defined in Web.View.View

Methods

pure :: a -> View context a #

(<*>) :: View context (a -> b) -> View context a -> View context b #

liftA2 :: (a -> b -> c) -> View context a -> View context b -> View context c #

(*>) :: View context a -> View context b -> View context b #

(<*) :: View context a -> View context b -> View context a #

Functor (View context) 
Instance details

Defined in Web.View.View

Methods

fmap :: (a -> b) -> View context a -> View context b #

(<$) :: a -> View context b -> View context a #

Monad (View context) 
Instance details

Defined in Web.View.View

Methods

(>>=) :: View context a -> (a -> View context b) -> View context b #

(>>) :: View context a -> View context b -> View context b #

return :: a -> View context a #

IsString (View context ()) 
Instance details

Defined in Web.View.View

Methods

fromString :: String -> View context () #

style :: Text -> View c () #

layout :: Mod c -> View c () -> View c () #

We can intuitively create layouts with combinations of row, col, stack, grow, and space

Wrap main content in layout to allow the view to consume vertical screen space

holygrail :: View c ()
holygrail = layout id $ do
  row section "Top Bar"
  row grow $ do
    col section "Left Sidebar"
    col (section . grow) "Main Content"
    col section "Right Sidebar"
  row section "Bottom Bar"
  where section = border 1

name :: Text -> Mod c #

data None #

Constructors

None 

Instances

Instances details
Show None 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> None -> ShowS #

show :: None -> String #

showList :: [None] -> ShowS #

ToClassName None 
Instance details

Defined in Web.View.Types

ToStyleValue None 
Instance details

Defined in Web.View.Types

Style Display None 
Instance details

Defined in Web.View.Style

Style ListType None 
Instance details

Defined in Web.View.Style

Style Shadow None 
Instance details

Defined in Web.View.Style

position :: Position -> Mod c #

position:absolute. See stack and popout

space :: View c () #

Space that fills the available space in the parent row or col.

row id $ do
 space
 el_ "Right"

This is equivalent to an empty element with grow

space = el grow none

class ToColor a where #

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

colorValue

Methods

colorValue :: a -> HexColor #

colorName :: a -> Text #

default colorName :: Show a => a -> Text #

Instances

Instances details
ToColor HexColor 
Instance details

Defined in Web.View.Types

hover :: Mod c -> Mod c #

Apply when hovering over an element

el (bg Primary . hover (bg PrimaryLight)) "Hover"

raw :: Text -> View c () #

Embed static, unescaped HTML or SVG. Take care not to use raw with user-generated content.

spinner = raw "<svg>...</svg>"

table :: Mod c -> [dt] -> Eff '[Writer [TableColumn c dt]] () -> View c () #

Create a type safe data table by specifying columns

usersTable :: [User] -> View c ()
usersTable us = do
  table id us $ do
    tcol (th hd "Name") $ \u -> td cell $ text u.name
    tcol (th hd "Email") $ \u -> td cell $ text u.email
 where
  hd = cell . bold
  cell = pad 4 . border 1

row :: Mod c -> View c () -> View c () #

Lay out children in a row

row id $ do
   el_ "Left"
   space
   el_ "Right"

col :: Mod c -> View c () -> View c () #

Lay out children in a column.

col grow $ do
   el_ "Top"
   space
   el_ "Bottom"

cssResetLink :: Text #

Alternatively, the reset is available on a CDN

import Data.String.Interpolate (i)

toDocument :: ByteString -> ByteString
toDocument cnt =
  [i|<html>
    <head>
      <link rel="stylesheet" href="#{cssResetLink}">
    </head>
    <body>#{cnt}</body>
  </html>|]

data Align #

Instances

Instances details
Show Align 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Align -> ShowS #

show :: Align -> String #

showList :: [Align] -> ShowS #

ToClassName Align 
Instance details

Defined in Web.View.Types

ToStyleValue Align 
Instance details

Defined in Web.View.Types

newtype HexColor #

Hexidecimal Color. Can be specified with or without the leading #. Recommended to use an AppColor type instead of manually using hex colors. See ToColor

Constructors

HexColor Text 

Instances

Instances details
IsString HexColor 
Instance details

Defined in Web.View.Types

Show HexColor 
Instance details

Defined in Web.View.Types

ToClassName HexColor 
Instance details

Defined in Web.View.Types

ToColor HexColor 
Instance details

Defined in Web.View.Types

ToStyleValue HexColor 
Instance details

Defined in Web.View.Types

data Media #

Media allows for responsive designs that change based on characteristics of the window. See Layout Example

Constructors

MinWidth Int 
MaxWidth Int 

Instances

Instances details
Show Media 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Media -> ShowS #

show :: Media -> String #

showList :: [Media] -> ShowS #

Eq Media 
Instance details

Defined in Web.View.Types

Methods

(==) :: Media -> Media -> Bool #

(/=) :: Media -> Media -> Bool #

Ord Media 
Instance details

Defined in Web.View.Types

Methods

compare :: Media -> Media -> Ordering #

(<) :: Media -> Media -> Bool #

(<=) :: Media -> Media -> Bool #

(>) :: Media -> Media -> Bool #

(>=) :: Media -> Media -> Bool #

max :: Media -> Media -> Media #

min :: Media -> Media -> Media #

data Ms #

Milliseconds, used for transitions

Instances

Instances details
Num Ms 
Instance details

Defined in Web.View.Types

Methods

(+) :: Ms -> Ms -> Ms #

(-) :: Ms -> Ms -> Ms #

(*) :: Ms -> Ms -> Ms #

negate :: Ms -> Ms #

abs :: Ms -> Ms #

signum :: Ms -> Ms #

fromInteger :: Integer -> Ms #

Show Ms 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> Ms -> ShowS #

show :: Ms -> String #

showList :: [Ms] -> ShowS #

ToClassName Ms 
Instance details

Defined in Web.View.Types

Methods

toClassName :: Ms -> ClassName #

ToStyleValue Ms 
Instance details

Defined in Web.View.Types

data PxRem #

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

Instances details
Enum PxRem 
Instance details

Defined in Web.View.Types

Num PxRem 
Instance details

Defined in Web.View.Types

Integral PxRem 
Instance details

Defined in Web.View.Types

Real PxRem 
Instance details

Defined in Web.View.Types

Methods

toRational :: PxRem -> Rational #

Show PxRem 
Instance details

Defined in Web.View.Types

Methods

showsPrec :: Int -> PxRem -> ShowS #

show :: PxRem -> String #

showList :: [PxRem] -> ShowS #

Eq PxRem 
Instance details

Defined in Web.View.Types

Methods

(==) :: PxRem -> PxRem -> Bool #

(/=) :: PxRem -> PxRem -> Bool #

Ord PxRem 
Instance details

Defined in Web.View.Types

Methods

compare :: PxRem -> PxRem -> Ordering #

(<) :: PxRem -> PxRem -> Bool #

(<=) :: PxRem -> PxRem -> Bool #

(>) :: PxRem -> PxRem -> Bool #

(>=) :: PxRem -> PxRem -> Bool #

max :: PxRem -> PxRem -> PxRem #

min :: PxRem -> PxRem -> PxRem #

ToClassName PxRem 
Instance details

Defined in Web.View.Types

ToStyleValue PxRem 
Instance details

Defined in Web.View.Types

data Length #

Constructors

PxRem PxRem 
Pct Float 

Instances

Instances details
Num Length 
Instance details

Defined in Web.View.Types

Show Length 
Instance details

Defined in Web.View.Types

ToClassName Length 
Instance details

Defined in Web.View.Types

ToStyleValue Length 
Instance details

Defined in Web.View.Types

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 ListType #

Constructors

Decimal 
Disc 

Instances

Instances details
Show ListType 
Instance details

Defined in Web.View.Style

ToClassName ListType 
Instance details

Defined in Web.View.Style

ToStyleValue ListType 
Instance details

Defined in Web.View.Style

Style ListType ListType 
Instance details

Defined in Web.View.Style

Style ListType None 
Instance details

Defined in Web.View.Style

data Inner #

Constructors

Inner 

Instances

Instances details
Show Inner 
Instance details

Defined in Web.View.Style

Methods

showsPrec :: Int -> Inner -> ShowS #

show :: Inner -> String #

showList :: [Inner] -> ShowS #

ToClassName Inner 
Instance details

Defined in Web.View.Style

Style Shadow Inner 
Instance details

Defined in Web.View.Style

data Shadow #

Instances

Instances details
Style Shadow Inner 
Instance details

Defined in Web.View.Style

Style Shadow None 
Instance details

Defined in Web.View.Style

Style Shadow () 
Instance details

Defined in Web.View.Style

Methods

styleValue :: () -> StyleValue #

width :: Length -> Mod c #

Set to a specific width

height :: Length -> Mod c #

Set to a specific height

minWidth :: Length -> Mod c #

Allow width to grow to contents but not shrink any smaller than value

minHeight :: Length -> Mod c #

Allow height to grow to contents but not shrink any smaller than value

gap :: Length -> Mod c #

The space between child elements. See pad

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"

rounded :: Length -> Mod c #

Round the corners of the element

bg :: ToColor clr => clr -> Mod ctx #

Set the background color. See ToColor

color :: ToColor clr => clr -> Mod ctx #

Set the text color. See ToColor

bold :: Mod c #

italic :: Mod c #

opacity :: Float -> Mod c #

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

pointer :: Mod c #

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"

zIndex :: Int -> Mod c #

display :: (Style Display a, ToClassName a) => a -> Mod c #

Set container display

el (display None) HIDDEN

active :: Mod c -> Mod c #

Apply when the mouse is pressed down on an element

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"

url :: Text -> Url #

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 () #

Run a view with a specific context in a parent View with a different context.

parentView :: View c ()
parentView = do
  addContext 1 numberView
  addContext 2 numberView
  addContext 3 numberView

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>

data TableColumn c dt #

data TableHead a #

el :: Mod c -> View c () -> View c () #

A basic element

el (bold . pad 10) "Hello"

el_ :: View c () -> View c () #

A basic element, with no modifiers

el_ "Hello"

none :: View c () #

Do not show any content

if isVisible
 then content
 else none

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 () #

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"

ul :: Mod c -> ListItem c () -> View c () #

li :: Mod c -> View c () -> ListItem c () #

data Layer c a #

A popout does not

Instances

Instances details
Applicative (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

pure :: a -> Layer c a #

(<*>) :: Layer c (a -> b) -> Layer c a -> Layer c b #

liftA2 :: (a -> b -> c0) -> Layer c a -> Layer c b -> Layer c c0 #

(*>) :: Layer c a -> Layer c b -> Layer c b #

(<*) :: Layer c a -> Layer c b -> Layer c a #

Functor (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

fmap :: (a -> b) -> Layer c a -> Layer c b #

(<$) :: a -> Layer c b -> Layer c a #

Monad (Layer c) 
Instance details

Defined in Web.View.Layout

Methods

(>>=) :: Layer c a -> (a -> Layer c b) -> Layer c b #

(>>) :: Layer c a -> Layer c b -> Layer c b #

return :: a -> Layer c a #

root :: Mod c #

As layout but as a Mod

holygrail = col root $ do
  ...

grow :: Mod c #

Grow to fill the available space in the parent row or col

row id $ do
 el grow none
 el_ "Right"

scroll :: Mod c #

Make a fixed layout by putting scroll on a child-element

document = row root $ do
  nav (width 300) "Sidebar"
  col (grow . scroll) "Main Content"

nav :: Mod c -> View c () -> View c () #

A Nav element

stack :: Mod c -> Layer c () -> View c () #

Stack children on top of each other. Each child has the full width. See popout

stack id $ do
  row id "Background"
  row (bg Black . opacity 0.5) "Overlay"

layer :: View c () -> Layer c () #

A normal layer contributes to the size of the parent

popout :: Mod c -> View c () -> Layer c () #

This child of a stack can pop out of the parent, covering content outside of it. Only usable inside stack

stack id $ do
  layer id $ input (value "Autocomplete Box")
  layer (popout (TRBL 50 0 0 0)) $ do
    el_ "Item 1"
    el_ "Item 2"
    el_ "Item 3"
el_ "This is covered by the menu"

hide :: Mod c #

Hide an element. See display

flexRow :: Mod c #

Set container to be a row. Favor row when possible

flexCol :: Mod c #

Set container to be a column. Favor col when possible

Embeds

Embedded CSS and Javascript to include in your document function. See basicDocument

Effectful

class (e :: Effect) :> (es :: [Effect]) #

A constraint that requires that a particular effect e is a member of the type-level list es. This is used to parameterize an Eff computation over an arbitrary list of effects, so long as e is somewhere in the list.

For example, a computation that only needs access to a mutable value of type Integer would have the following type:

State Integer :> es => Eff es ()

Instances

Instances details
(TypeError (('Text "There is no handler for '" ':<>: 'ShowType e) ':<>: 'Text "' in the context") :: Constraint) => e :> ('[] :: [Effect]) 
Instance details

Defined in Effectful.Internal.Effect

Methods

reifyIndex :: Int #

e :> (e ': es) 
Instance details

Defined in Effectful.Internal.Effect

Methods

reifyIndex :: Int #

e :> es => e :> (x ': es) 
Instance details

Defined in Effectful.Internal.Effect

Methods

reifyIndex :: Int #

data Eff (es :: [Effect]) a #

The Eff monad provides the implementation of a computation that performs an arbitrary set of effects. In Eff es a, es is a type-level list that contains all the effects that the computation may perform. For example, a computation that produces an Integer by consuming a String from the global environment and acting upon a single mutable value of type Bool would have the following type:

(Reader String :> es, State Bool :> es) => Eff es Integer

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

Instances details
IOE :> es => MonadBaseControl IO (Eff es)

Instance included for compatibility with existing code.

Usage of withEffToIO is preferrable as it allows specifying the UnliftStrategy on a case-by-case basis and has better error reporting.

Note: the unlifting strategy for liftBaseWith is taken from the IOE context (see unliftStrategy).

Instance details

Defined in Effectful.Internal.Monad

Methods

liftBaseWith :: (RunInBase (Eff es) IO -> IO a) -> Eff es a #

restoreM :: StM (Eff es) a -> Eff es a #

IOE :> es => MonadBase IO (Eff es)

Instance included for compatibility with existing code.

Usage of liftIO is preferrable as it's a standard.

Instance details

Defined in Effectful.Internal.Monad

Methods

liftBase :: IO α -> Eff es α #

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

Defined in Web.Hyperbole.HyperView

Methods

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

Fail :> es => MonadFail (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

fail :: String -> Eff es a #

MonadFix (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

mfix :: (a -> Eff es a) -> Eff es a #

IOE :> es => MonadIO (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

liftIO :: IO a -> Eff es a #

NonDet :> es => Alternative (Eff es)

Since: effectful-core-2.2.0.0

Instance details

Defined in Effectful.Internal.Monad

Methods

empty :: Eff es a #

(<|>) :: Eff es a -> Eff es a -> Eff es a #

some :: Eff es a -> Eff es [a] #

many :: Eff es a -> Eff es [a] #

Applicative (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

pure :: a -> Eff es a #

(<*>) :: Eff es (a -> b) -> Eff es a -> Eff es b #

liftA2 :: (a -> b -> c) -> Eff es a -> Eff es b -> Eff es c #

(*>) :: Eff es a -> Eff es b -> Eff es b #

(<*) :: Eff es a -> Eff es b -> Eff es a #

Functor (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

fmap :: (a -> b) -> Eff es a -> Eff es b #

(<$) :: a -> Eff es b -> Eff es a #

Monad (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

(>>=) :: Eff es a -> (a -> Eff es b) -> Eff es b #

(>>) :: Eff es a -> Eff es b -> Eff es b #

return :: a -> Eff es a #

NonDet :> es => MonadPlus (Eff es)

Since: effectful-core-2.2.0.0

Instance details

Defined in Effectful.Internal.Monad

Methods

mzero :: Eff es a #

mplus :: Eff es a -> Eff es a -> Eff es a #

MonadCatch (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

catch :: (HasCallStack, Exception e) => Eff es a -> (e -> Eff es a) -> Eff es a #

MonadMask (Eff es) 
Instance details

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) 
Instance details

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 withEffToIO is preferrable as it allows specifying the UnliftStrategy on a case-by-case basis and has better error reporting.

Note: the unlifting strategy for withRunInIO is taken from the IOE context (see unliftStrategy).

Instance details

Defined in Effectful.Internal.Monad

Methods

withRunInIO :: ((forall a. Eff es a -> IO a) -> IO b) -> Eff es b #

Prim :> es => PrimMonad (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Associated Types

type PrimState (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

Methods

primitive :: (State# (PrimState (Eff es)) -> (# State# (PrimState (Eff es)), a #)) -> Eff es a #

Monoid a => Monoid (Eff es a) 
Instance details

Defined in Effectful.Internal.Monad

Methods

mempty :: Eff es a #

mappend :: Eff es a -> Eff es a -> Eff es a #

mconcat :: [Eff es a] -> Eff es a #

Semigroup a => Semigroup (Eff es a) 
Instance details

Defined in Effectful.Internal.Monad

Methods

(<>) :: Eff es a -> Eff es a -> Eff es a #

sconcat :: NonEmpty (Eff es a) -> Eff es a #

stimes :: Integral b => b -> Eff es a -> Eff es a #

type PrimState (Eff es) 
Instance details

Defined in Effectful.Internal.Monad

type StM (Eff es) a 
Instance details

Defined in Effectful.Internal.Monad

type StM (Eff es) a = a

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")

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep All = D1 ('MetaData "All" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "All" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep Any = D1 ('MetaData "Any" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Any" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAny") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version

Since: base-4.9.0.0

Instance details

Defined in Data.Version

type Rep Version = D1 ('MetaData "Version" "Data.Version" "base" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionBranch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "versionTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String])))

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic Void 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Void

Since: base-4.8.0.0

Instance details

Defined in GHC.Generics

type Rep Void = D1 ('MetaData "Void" "GHC.Base" "base" 'False) (V1 :: Type -> Type)

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic ByteOrder 
Instance details

Defined in GHC.ByteOrder

Associated Types

type Rep ByteOrder

Since: base-4.15.0.0

Instance details

Defined in GHC.ByteOrder

type Rep ByteOrder = D1 ('MetaData "ByteOrder" "GHC.ByteOrder" "base" 'False) (C1 ('MetaCons "BigEndian" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LittleEndian" 'PrefixI 'False) (U1 :: Type -> Type))
Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint

Since: base-4.15.0.0

Instance details

Defined in GHC.Generics

type Rep Fingerprint = D1 ('MetaData "Fingerprint" "GHC.Fingerprint.Type" "base" 'False) (C1 ('MetaCons "Fingerprint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))
Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep Associativity = D1 ('MetaData "Associativity" "GHC.Generics" "base" 'False) (C1 ('MetaCons "LeftAssociative" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightAssociative" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotAssociative" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "GHC.Generics" "base" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode 
Instance details

Defined in GHC.IO.Exception

type Rep ExitCode = D1 ('MetaData "ExitCode" "GHC.IO.Exception" "base" 'False) (C1 ('MetaCons "ExitSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExitFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

Methods

from :: CCFlags -> Rep CCFlags x #

to :: Rep CCFlags x -> CCFlags #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep ConcFlags = D1 ('MetaData "ConcFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "ConcFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "ctxtSwitchTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "ctxtSwitchTicks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep DebugFlags = D1 ('MetaData "DebugFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "DebugFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "scheduler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "interpreter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "weak") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "gccafs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "gc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "nonmoving_gc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "block_alloc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "sanity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: (((S1 ('MetaSel ('Just "stable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "prof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "linker") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "apply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "stm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "squeeze") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "hpc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "sparks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))
Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep DoCostCentres = D1 ('MetaData "DoCostCentres" "GHC.RTS.Flags" "base" 'False) ((C1 ('MetaCons "CostCentresNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CostCentresSummary" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CostCentresVerbose" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CostCentresAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CostCentresJSON" 'PrefixI 'False) (U1 :: Type -> Type))))
Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep DoHeapProfile = D1 ('MetaData "DoHeapProfile" "GHC.RTS.Flags" "base" 'False) (((C1 ('MetaCons "NoHeapProfiling" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeapByCCS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HeapByMod" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeapByDescr" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "HeapByType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeapByRetainer" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HeapByLDV" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HeapByClosureType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeapByInfoTable" 'PrefixI 'False) (U1 :: Type -> Type)))))
Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep DoTrace = D1 ('MetaData "DoTrace" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "TraceNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TraceEventLog" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraceStderr" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: DoTrace -> Rep DoTrace x #

to :: Rep DoTrace x -> DoTrace #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep GCFlags = D1 ('MetaData "GCFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "GCFlags" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "statsFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "giveStats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GiveGCStats) :*: S1 ('MetaSel ('Just "maxStkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) :*: ((S1 ('MetaSel ('Just "initialStkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "stkChunkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "stkChunkBufferSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "maxHeapSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))) :*: ((S1 ('MetaSel ('Just "minAllocAreaSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "largeAllocLim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "nurseryChunkSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) :*: ((S1 ('MetaSel ('Just "minOldGenSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "heapSizeSuggestion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "heapSizeSuggestionAuto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "oldGenFactor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))))) :*: (((S1 ('MetaSel ('Just "returnDecayFactor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: (S1 ('MetaSel ('Just "pcFreeHeap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "generations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) :*: ((S1 ('MetaSel ('Just "squeezeUpdFrames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "compact") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "compactThreshold") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double) :*: S1 ('MetaSel ('Just "sweep") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "ringBell") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "idleGCDelayTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "doIdleGC") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "heapBase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "allocLimitGrace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "numa") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "numaMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))))))

Methods

from :: GCFlags -> Rep GCFlags x #

to :: Rep GCFlags x -> GCFlags #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStats

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep GiveGCStats = D1 ('MetaData "GiveGCStats" "GHC.RTS.Flags" "base" 'False) ((C1 ('MetaCons "NoGCStats" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CollectGCStats" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OneLineGCStats" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SummaryGCStats" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerboseGCStats" 'PrefixI 'False) (U1 :: Type -> Type))))
Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep MiscFlags = D1 ('MetaData "MiscFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "MiscFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tickInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: (S1 ('MetaSel ('Just "installSignalHandlers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "installSEHHandlers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "generateCrashDumpFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "generateStackTrace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "machineReadable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "disableDelayedOsMemoryReturn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "internalCounters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "linkerAlwaysPic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "linkerMemBase") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: (S1 ('MetaSel ('Just "ioManager") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IoSubSystem) :*: S1 ('MetaSel ('Just "numIoWorkerThreads") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))))))
Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Methods

from :: ParFlags -> Rep ParFlags x #

to :: Rep ParFlags x -> ParFlags #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep ProfFlags = D1 ('MetaData "ProfFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "ProfFlags" 'PrefixI 'True) (((S1 ('MetaSel ('Just "doHeapProfile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DoHeapProfile) :*: (S1 ('MetaSel ('Just "heapProfileInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "heapProfileIntervalTicks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) :*: ((S1 ('MetaSel ('Just "startHeapProfileAtStartup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "showCCSOnException") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "maxRetainerSetSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "ccsLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))) :*: ((S1 ('MetaSel ('Just "modSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Just "descrSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "typeSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))) :*: ((S1 ('MetaSel ('Just "ccSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "ccsSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String))) :*: (S1 ('MetaSel ('Just "retainerSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "bioSelector") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))))
Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Methods

from :: RTSFlags -> Rep RTSFlags x #

to :: Rep RTSFlags x -> RTSFlags #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlags

Since: base-4.15.0.0

Instance details

Defined in GHC.RTS.Flags

type Rep TickyFlags = D1 ('MetaData "TickyFlags" "GHC.RTS.Flags" "base" 'False) (C1 ('MetaCons "TickyFlags" 'PrefixI 'True) (S1 ('MetaSel ('Just "showTickyStats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "tickyFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))
Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc

Since: base-4.15.0.0

Instance details

Defined in GHC.Generics

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic GCDetails 
Instance details

Defined in GHC.Stats

Associated Types

type Rep GCDetails

Since: base-4.15.0.0

Instance details

Defined in GHC.Stats

type Rep GCDetails = D1 ('MetaData "GCDetails" "GHC.Stats" "base" 'False) (C1 ('MetaCons "GCDetails" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "gcdetails_gen") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "gcdetails_threads") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "gcdetails_allocated_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "gcdetails_live_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "gcdetails_large_objects_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "gcdetails_compact_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "gcdetails_slop_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "gcdetails_mem_in_use_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "gcdetails_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "gcdetails_par_max_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "gcdetails_par_balanced_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "gcdetails_block_fragmentation_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "gcdetails_sync_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "gcdetails_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime)) :*: (S1 ('MetaSel ('Just "gcdetails_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: (S1 ('MetaSel ('Just "gcdetails_nonmoving_gc_sync_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "gcdetails_nonmoving_gc_sync_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime)))))))
Generic RTSStats 
Instance details

Defined in GHC.Stats

Associated Types

type Rep RTSStats

Since: base-4.15.0.0

Instance details

Defined in GHC.Stats

type Rep RTSStats = D1 ('MetaData "RTSStats" "GHC.Stats" "base" 'False) (C1 ('MetaCons "RTSStats" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "gcs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "major_gcs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32) :*: S1 ('MetaSel ('Just "allocated_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "max_live_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "max_large_objects_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "max_compact_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "max_slop_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))) :*: ((S1 ('MetaSel ('Just "max_mem_in_use_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "cumulative_live_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "par_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "cumulative_par_max_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "cumulative_par_balanced_copied_bytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "init_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime))))) :*: (((S1 ('MetaSel ('Just "init_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: (S1 ('MetaSel ('Just "mutator_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "mutator_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime))) :*: ((S1 ('MetaSel ('Just "gc_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "gc_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime)) :*: (S1 ('MetaSel ('Just "cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime)))) :*: ((S1 ('MetaSel ('Just "nonmoving_gc_sync_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: (S1 ('MetaSel ('Just "nonmoving_gc_sync_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "nonmoving_gc_sync_max_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime))) :*: ((S1 ('MetaSel ('Just "nonmoving_gc_cpu_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "nonmoving_gc_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime)) :*: (S1 ('MetaSel ('Just "nonmoving_gc_max_elapsed_ns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RtsTime) :*: S1 ('MetaSel ('Just "gc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GCDetails)))))))

Methods

from :: RTSStats -> Rep RTSStats x #

to :: Rep RTSStats x -> RTSStats #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory

Since: base-4.15.0.0

Instance details

Defined in GHC.Generics

type Rep GeneralCategory = D1 ('MetaData "GeneralCategory" "GHC.Unicode" "base" 'False) ((((C1 ('MetaCons "UppercaseLetter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LowercaseLetter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TitlecaseLetter" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ModifierLetter" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherLetter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NonSpacingMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SpacingCombiningMark" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "EnclosingMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecimalNumber" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LetterNumber" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherNumber" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConnectorPunctuation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DashPunctuation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OpenPunctuation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ClosePunctuation" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "InitialQuote" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FinalQuote" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherPunctuation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MathSymbol" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CurrencySymbol" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModifierSymbol" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OtherSymbol" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Space" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LineSeparator" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ParagraphSeparator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Control" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Format" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Surrogate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PrivateUse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotAssigned" 'PrefixI 'False) (U1 :: Type -> Type))))))
Generic ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Associated Types

type Rep ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

type Rep ShortByteString = D1 ('MetaData "ShortByteString" "Data.ByteString.Short.Internal" "bytestring-0.12.1.0-7b92" 'True) (C1 ('MetaCons "ShortByteString" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShortByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteArray)))
Generic Limit 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Limit 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "ffctfl-cr-2.5.1.0-1f263afc" 'False) (C1 ('MetaCons "Limited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Limit -> Rep Limit x #

to :: Rep Limit x -> Limit #

Generic Persistence 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep Persistence 
Instance details

Defined in Effectful.Internal.Unlift

type Rep Persistence = D1 ('MetaData "Persistence" "Effectful.Internal.Unlift" "ffctfl-cr-2.5.1.0-1f263afc" 'False) (C1 ('MetaCons "Ephemeral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Persistent" 'PrefixI 'False) (U1 :: Type -> Type))
Generic UnliftStrategy 
Instance details

Defined in Effectful.Internal.Unlift

Associated Types

type Rep UnliftStrategy 
Instance details

Defined in Effectful.Internal.Unlift

type Rep UnliftStrategy = D1 ('MetaData "UnliftStrategy" "Effectful.Internal.Unlift" "ffctfl-cr-2.5.1.0-1f263afc" 'False) (C1 ('MetaCons "SeqUnlift" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SeqForkUnlift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConcUnlift" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Persistence) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Limit))))
Generic OnEmptyPolicy 
Instance details

Defined in Effectful.NonDet

Associated Types

type Rep OnEmptyPolicy 
Instance details

Defined in Effectful.NonDet

type Rep OnEmptyPolicy = D1 ('MetaData "OnEmptyPolicy" "Effectful.NonDet" "ffctfl-cr-2.5.1.0-1f263afc" 'False) (C1 ('MetaCons "OnEmptyKeep" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OnEmptyRollback" 'PrefixI 'False) (U1 :: Type -> Type))
Generic OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar)))

Methods

from :: OsChar -> Rep OsChar x #

to :: Rep OsChar x -> OsChar #

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

Methods

from :: OsString -> Rep OsString x #

to :: Rep OsString x -> OsString #

Generic PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))
Generic PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))
Generic WindowsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep WindowsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))
Generic WindowsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep WindowsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

type Rep WindowsString = D1 ('MetaData "WindowsString" "System.OsString.Internal.Types.Hidden" "filepath-1.4.200.1-03b3" 'True) (C1 ('MetaCons "WindowsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))
Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-9.8.2-c69e" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LangJs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))
Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

type Rep Extension = D1 ('MetaData "Extension" "GHC.LanguageExtensions.Type" "ghc-boot-th-9.8.2-c69e" 'False) (((((((C1 ('MetaCons "Cpp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: ((((((C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: (((((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type))))))))
Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Ordering = D1 ('MetaData "Ordering" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic SrcLoc 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcLoc 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcLoc = D1 ('MetaData "SrcLoc" "Language.Haskell.Exts.SrcLoc" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "SrcLoc" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "srcLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "srcColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcSpan = D1 ('MetaData "SrcSpan" "Language.Haskell.Exts.SrcLoc" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "SrcSpan" 'PrefixI 'True) ((S1 ('MetaSel ('Just "srcSpanFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "srcSpanStartLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "srcSpanStartColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "srcSpanEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "srcSpanEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Generic SrcSpanInfo 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpanInfo 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcSpanInfo = D1 ('MetaData "SrcSpanInfo" "Language.Haskell.Exts.SrcLoc" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "SrcSpanInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcInfoSpan") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "srcInfoPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SrcSpan])))
Generic Boxed 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Boxed 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep Boxed = D1 ('MetaData "Boxed" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Boxed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unboxed" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Boxed -> Rep Boxed x #

to :: Rep Boxed x -> Boxed #

Generic Tool 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep Tool 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep Tool = D1 ('MetaData "Tool" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "GHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HUGS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NHC98" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "YHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HADDOCK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnknownTool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))

Methods

from :: Tool -> Rep Tool x #

to :: Rep Tool x -> Tool #

Generic Form 
Instance details

Defined in Web.Internal.FormUrlEncoded

Associated Types

type Rep Form 
Instance details

Defined in Web.Internal.FormUrlEncoded

type Rep Form = D1 ('MetaData "Form" "Web.Internal.FormUrlEncoded" "http-p-dt-0.6.1-9db5cac1" 'True) (C1 ('MetaCons "Form" 'PrefixI 'True) (S1 ('MetaSel ('Just "unForm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text [Text]))))

Methods

from :: Form -> Rep Form x #

to :: Rep Form x -> Form #

Generic ByteRange 
Instance details

Defined in Network.HTTP.Types.Header

Associated Types

type Rep ByteRange

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Header

Generic StdMethod 
Instance details

Defined in Network.HTTP.Types.Method

Associated Types

type Rep StdMethod

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Method

type Rep StdMethod = D1 ('MetaData "StdMethod" "Network.HTTP.Types.Method" "http-typs-0.12.4-0ae84358" 'False) (((C1 ('MetaCons "GET" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "POST" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HEAD" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PUT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DELETE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TRACE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONNECT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OPTIONS" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PATCH" 'PrefixI 'False) (U1 :: Type -> Type)))))
Generic Status 
Instance details

Defined in Network.HTTP.Types.Status

Associated Types

type Rep Status

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Status

type Rep Status = D1 ('MetaData "Status" "Network.HTTP.Types.Status" "http-typs-0.12.4-0ae84358" 'False) (C1 ('MetaCons "Status" 'PrefixI 'True) (S1 ('MetaSel ('Just "statusCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "statusMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

Generic HttpVersion 
Instance details

Defined in Network.HTTP.Types.Version

Associated Types

type Rep HttpVersion

Since: http-types-0.12.4

Instance details

Defined in Network.HTTP.Types.Version

type Rep HttpVersion = D1 ('MetaData "HttpVersion" "Network.HTTP.Types.Version" "http-typs-0.12.4-0ae84358" 'False) (C1 ('MetaCons "HttpVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "httpMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "httpMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)))
Generic ConcException 
Instance details

Defined in UnliftIO.Internals.Async

Associated Types

type Rep ConcException 
Instance details

Defined in UnliftIO.Internals.Async

type Rep ConcException = D1 ('MetaData "ConcException" "UnliftIO.Internals.Async" "nlft-0.2.25.0-699b246b" 'False) (C1 ('MetaCons "EmptyWithNoAlternative" 'PrefixI 'False) (U1 :: Type -> Type))
Generic UnixTime 
Instance details

Defined in Data.UnixTime.Types

Associated Types

type Rep UnixTime 
Instance details

Defined in Data.UnixTime.Types

type Rep UnixTime = D1 ('MetaData "UnixTime" "Data.UnixTime.Types" "nx-tm-0.4.16-f57e2391" 'False) (C1 ('MetaCons "UnixTime" 'PrefixI 'True) (S1 ('MetaSel ('Just "utSeconds") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 CTime) :*: S1 ('MetaSel ('Just "utMicroSeconds") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int32)))

Methods

from :: UnixTime -> Rep UnixTime x #

to :: Rep UnixTime x -> UnixTime #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Mode = D1 ('MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6-b285" 'False) ((C1 ('MetaCons "PageMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZigZagMode" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OneLineMode" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Style = D1 ('MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6-b285" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mode) :*: (S1 ('MetaSel ('Just "lineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ribbonsPerLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

type Rep Doc = D1 ('MetaData "Doc" "Text.PrettyPrint.HughesPJ" "pretty-1.1.3.6-b285" 'True) (C1 ('MetaCons "Doc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ()))))

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic IP 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IP 
Instance details

Defined in Data.IP.Addr

type Rep IP = D1 ('MetaData "IP" "Data.IP.Addr" "prt-1.7.15-2c08a36d" 'False) (C1 ('MetaCons "IPv4" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv4") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 IPv4)) :+: C1 ('MetaCons "IPv6" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv6") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 IPv6)))

Methods

from :: IP -> Rep IP x #

to :: Rep IP x -> IP #

Generic IPv4 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv4 
Instance details

Defined in Data.IP.Addr

type Rep IPv4 = D1 ('MetaData "IPv4" "Data.IP.Addr" "prt-1.7.15-2c08a36d" 'True) (C1 ('MetaCons "IP4" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IPv4Addr)))

Methods

from :: IPv4 -> Rep IPv4 x #

to :: Rep IPv4 x -> IPv4 #

Generic IPv6 
Instance details

Defined in Data.IP.Addr

Associated Types

type Rep IPv6 
Instance details

Defined in Data.IP.Addr

type Rep IPv6 = D1 ('MetaData "IPv6" "Data.IP.Addr" "prt-1.7.15-2c08a36d" 'True) (C1 ('MetaCons "IP6" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 IPv6Addr)))

Methods

from :: IPv6 -> Rep IPv6 x #

to :: Rep IPv6 x -> IPv6 #

Generic IPRange 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep IPRange 
Instance details

Defined in Data.IP.Range

type Rep IPRange = D1 ('MetaData "IPRange" "Data.IP.Range" "prt-1.7.15-2c08a36d" 'False) (C1 ('MetaCons "IPv4Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv4range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AddrRange IPv4))) :+: C1 ('MetaCons "IPv6Range" 'PrefixI 'True) (S1 ('MetaSel ('Just "ipv6range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (AddrRange IPv6))))

Methods

from :: IPRange -> Rep IPRange x #

to :: Rep IPRange x -> IPRange #

Generic OsChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsChar = D1 ('MetaData "OsChar" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "OsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformChar)))

Methods

from :: OsChar -> Rep OsChar x #

to :: Rep OsChar x -> OsChar #

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString 
Instance details

Defined in System.OsString.Internal.Types

type Rep OsString = D1 ('MetaData "OsString" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "OsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getOsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlatformString)))

Methods

from :: OsString -> Rep OsString x #

to :: Rep OsString x -> OsString #

Generic PosixChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixChar 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixChar = D1 ('MetaData "PosixChar" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "PosixChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8)))
Generic PosixString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixString 
Instance details

Defined in System.OsString.Internal.Types

type Rep PosixString = D1 ('MetaData "PosixString" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "PosixString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPosixString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))
Generic WindowsChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsChar 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsChar = D1 ('MetaData "WindowsChar" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "WindowsChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsChar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))
Generic WindowsString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsString 
Instance details

Defined in System.OsString.Internal.Types

type Rep WindowsString = D1 ('MetaData "WindowsString" "System.OsString.Internal.Types" "s-strng-2.0.7-eb027dcf" 'True) (C1 ('MetaCons "WindowsString" 'PrefixI 'True) (S1 ('MetaSel ('Just "getWindowsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortByteString)))
Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep AnnLookup = D1 ('MetaData "AnnLookup" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "AnnLookupModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Module)) :+: C1 ('MetaCons "AnnLookupName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))
Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep AnnTarget = D1 ('MetaData "AnnTarget" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "ModuleAnnotation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ValueAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))
Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic BndrVis 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep BndrVis 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep BndrVis = D1 ('MetaData "BndrVis" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "BndrReq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BndrInvis" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: BndrVis -> Rep BndrVis x #

to :: Rep BndrVis x -> BndrVis #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Body = D1 ('MetaData "Body" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "GuardedB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Guard, Exp)])) :+: C1 ('MetaCons "NormalB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Bytes = D1 ('MetaData "Bytes" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Bytes" 'PrefixI 'True) (S1 ('MetaSel ('Just "bytesPtr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForeignPtr Word8)) :*: (S1 ('MetaSel ('Just "bytesOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "bytesSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))))

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Callconv = D1 ('MetaData "Callconv" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "CCall" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StdCall" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Prim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScript" 'PrefixI 'False) (U1 :: Type -> Type))))

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Con = D1 ('MetaData "Con" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "NormalC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType])) :+: (C1 ('MetaCons "RecC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType])) :+: C1 ('MetaCons "InfixC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType))))) :+: (C1 ('MetaCons "ForallC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con))) :+: (C1 ('MetaCons "GadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "RecGadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Dec = D1 ('MetaData "Dec" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((((C1 ('MetaCons "FunD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause])) :+: (C1 ('MetaCons "ValD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))) :+: C1 ('MetaCons "DataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TypeDataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]))) :+: C1 ('MetaCons "TySynD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))) :+: ((C1 ('MetaCons "ClassD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunDep]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec])))) :+: (C1 ('MetaCons "InstanceD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Overlap)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))) :+: C1 ('MetaCons "SigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "KiSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "ForeignD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Foreign))) :+: (C1 ('MetaCons "InfixD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "DefaultD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type])))))) :+: (((C1 ('MetaCons "PragmaD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pragma)) :+: (C1 ('MetaCons "DataFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)))) :+: C1 ('MetaCons "DataInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TySynInstD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TySynEqn)) :+: C1 ('MetaCons "OpenTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead))))) :+: ((C1 ('MetaCons "ClosedTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TySynEqn])) :+: (C1 ('MetaCons "RoleAnnotD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role])) :+: C1 ('MetaCons "StandaloneDerivD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DerivStrategy)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "DefaultSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "PatSynD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynArgs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynDir) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: (C1 ('MetaCons "PatSynSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: C1 ('MetaCons "ImplicitParamBindD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))))

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep DerivStrategy = D1 ('MetaData "DerivStrategy" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "StockStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnyclassStrategy" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NewtypeStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ViaStrategy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))
Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: DocLoc -> Rep DocLoc x #

to :: Rep DocLoc x -> DocLoc #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Exp = D1 ('MetaData "Exp" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (((((C1 ('MetaCons "VarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "LitE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "AppE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) :+: ((C1 ('MetaCons "AppTypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "InfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))))) :+: (C1 ('MetaCons "UInfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "ParensE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))) :+: (((C1 ('MetaCons "LamE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "LamCaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match]))) :+: (C1 ('MetaCons "LamCasesE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause])) :+: C1 ('MetaCons "TupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])))) :+: ((C1 ('MetaCons "UnboxedTupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])) :+: C1 ('MetaCons "UnboxedSumE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)))) :+: (C1 ('MetaCons "CondE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "MultiIfE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Guard, Exp)])) :+: C1 ('MetaCons "LetE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))))) :+: ((((C1 ('MetaCons "CaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match])) :+: C1 ('MetaCons "DoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt]))) :+: (C1 ('MetaCons "MDoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])) :+: C1 ('MetaCons "CompE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])))) :+: ((C1 ('MetaCons "ArithSeqE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "ListE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]))) :+: (C1 ('MetaCons "SigE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "RecConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp]))))) :+: (((C1 ('MetaCons "RecUpdE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp])) :+: C1 ('MetaCons "StaticE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "UnboundVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "LabelE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: ((C1 ('MetaCons "ImplicitParamVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "GetFieldE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "ProjectionE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty String))) :+: (C1 ('MetaCons "TypedBracketE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "TypedSpliceE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))))))

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep FamilyResultSig = D1 ('MetaData "FamilyResultSig" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoSig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KindSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TyVarSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyVarBndr ())))))
Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep FixityDirection = D1 ('MetaData "FixityDirection" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "InfixL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InfixN" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep FunDep = D1 ('MetaData "FunDep" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "FunDep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Guard = D1 ('MetaData "Guard" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NormalG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "PatG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])))

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Info = D1 ('MetaData "Info" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (((C1 ('MetaCons "ClassI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])) :+: C1 ('MetaCons "ClassOpI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "TyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec)) :+: C1 ('MetaCons "FamilyI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])))) :+: ((C1 ('MetaCons "PrimTyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unlifted))) :+: C1 ('MetaCons "DataConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "PatSynI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: (C1 ('MetaCons "VarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Dec)))) :+: C1 ('MetaCons "TyVarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep InjectivityAnn = D1 ('MetaData "InjectivityAnn" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "InjectivityAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))
Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Inline = D1 ('MetaData "Inline" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoInline" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Inline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inlinable" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Lit = D1 ('MetaData "Lit" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (((C1 ('MetaCons "CharL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "StringL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "IntegerL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "RationalL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "IntPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) :+: ((C1 ('MetaCons "WordPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "FloatPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "DoublePrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)))) :+: (C1 ('MetaCons "StringPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word8])) :+: (C1 ('MetaCons "BytesPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes)) :+: C1 ('MetaCons "CharPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))))))

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep ModName = D1 ('MetaData "ModName" "Language.Haskell.TH.Syntax" "template-haskell" 'True) (C1 ('MetaCons "ModName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep ModuleInfo = D1 ('MetaData "ModuleInfo" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "ModuleInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Module])))
Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep NameSpace = D1 ('MetaData "NameSpace" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "VarName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataName" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TcClsName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FldName" 'PrefixI 'True) (S1 ('MetaSel ('Just "fldParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))
Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep OccName = D1 ('MetaData "OccName" "Language.Haskell.TH.Syntax" "template-haskell" 'True) (C1 ('MetaCons "OccName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Overlap = D1 ('MetaData "Overlap" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "Overlappable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Overlapping" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Overlaps" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Incoherent" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Pat = D1 ('MetaData "Pat" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((((C1 ('MetaCons "LitP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "VarP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "TupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: C1 ('MetaCons "UnboxedTupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])))) :+: ((C1 ('MetaCons "UnboxedSumP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity))) :+: C1 ('MetaCons "ConP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])))) :+: (C1 ('MetaCons "InfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: C1 ('MetaCons "UInfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))))) :+: (((C1 ('MetaCons "ParensP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "TildeP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "BangP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "AsP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: ((C1 ('MetaCons "WildP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldPat]))) :+: (C1 ('MetaCons "ListP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: (C1 ('MetaCons "SigP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "ViewP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))))))

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep PatSynDir = D1 ('MetaData "PatSynDir" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Unidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ImplBidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplBidir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause]))))
Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Phases = D1 ('MetaData "Phases" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "AllPhases" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FromPhase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "BeforePhase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep PkgName = D1 ('MetaData "PkgName" "Language.Haskell.TH.Syntax" "template-haskell" 'True) (C1 ('MetaCons "PkgName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Pragma = D1 ('MetaData "Pragma" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (((C1 ('MetaCons "InlineP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RuleMatch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "OpaqueP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "SpecialiseP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Inline)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "SpecialiseInstP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "RuleP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuleBndr]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases)))) :+: C1 ('MetaCons "AnnP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnTarget) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "LineP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "CompleteP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))))))

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Role = D1 ('MetaData "Role" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "NominalR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepresentationalR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PhantomR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferR" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep RuleMatch = D1 ('MetaData "RuleMatch" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "ConLike" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunLike" 'PrefixI 'False) (U1 :: Type -> Type))
Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Safety = D1 ('MetaData "Safety" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Interruptible" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Specificity = D1 ('MetaData "Specificity" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "SpecifiedSpec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferredSpec" 'PrefixI 'False) (U1 :: Type -> Type))
Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Type = D1 ('MetaData "Type" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((((C1 ('MetaCons "ForallT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "ForallVisT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr ()]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "AppT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "AppKindT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "SigT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "VarT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))) :+: ((C1 ('MetaCons "PromotedT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "InfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "UInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "PromotedInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "PromotedUInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: (C1 ('MetaCons "ParensT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "TupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))) :+: (((C1 ('MetaCons "UnboxedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "UnboxedSumT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)) :+: C1 ('MetaCons "ArrowT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MulArrowT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualityT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PromotedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "PromotedNilT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PromotedConsT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StarT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstraintT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TyLit))) :+: (C1 ('MetaCons "WildCardT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParamT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))))

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep ConstructorInfo = D1 ('MetaData "ConstructorInfo" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "ConstructorInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "constructorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Just "constructorVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndrUnit]) :*: S1 ('MetaSel ('Just "constructorContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt))) :*: (S1 ('MetaSel ('Just "constructorFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: (S1 ('MetaSel ('Just "constructorStrictness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldStrictness]) :*: S1 ('MetaSel ('Just "constructorVariant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstructorVariant)))))
Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep ConstructorVariant = D1 ('MetaData "ConstructorVariant" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "NormalConstructor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixConstructor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]))))
Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep DatatypeInfo = D1 ('MetaData "DatatypeInfo" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "DatatypeInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "datatypeContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Just "datatypeName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "datatypeVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndrUnit]))) :*: ((S1 ('MetaSel ('Just "datatypeInstTypes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: S1 ('MetaSel ('Just "datatypeVariant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatatypeVariant)) :*: (S1 ('MetaSel ('Just "datatypeReturnKind") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind) :*: S1 ('MetaSel ('Just "datatypeCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ConstructorInfo])))))
Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep DatatypeVariant = D1 ('MetaData "DatatypeVariant" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) ((C1 ('MetaCons "Datatype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Newtype" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataInstance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewtypeInstance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type))))
Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep FieldStrictness = D1 ('MetaData "FieldStrictness" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "FieldStrictness" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldUnpackedness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unpackedness) :*: S1 ('MetaSel ('Just "fieldStrictness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Strictness)))
Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep Strictness = D1 ('MetaData "Strictness" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "UnspecifiedStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Lazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep Unpackedness = D1 ('MetaData "Unpackedness" "Language.Haskell.TH.Datatype" "th-bstrctn-0.7.1.0-b813d164" 'False) (C1 ('MetaCons "UnspecifiedUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Generic FlatAttributes 
Instance details

Defined in Web.View.Types

Associated Types

type Rep FlatAttributes 
Instance details

Defined in Web.View.Types

type Rep FlatAttributes = D1 ('MetaData "FlatAttributes" "Web.View.Types" "wb-vw-0.6.2-17f67209" 'True) (C1 ('MetaCons "FlatAttributes" 'PrefixI 'True) (S1 ('MetaSel ('Just "attributes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Name AttValue))))
Generic CompressParams 
Instance details

Defined in Codec.Compression.Zlib.Internal

Associated Types

type Rep CompressParams

Since: zlib-0.7.0.0

Instance details

Defined in Codec.Compression.Zlib.Internal

type Rep CompressParams = D1 ('MetaData "CompressParams" "Codec.Compression.Zlib.Internal" "zlb-0.7.1.0-f6c290ab" 'False) (C1 ('MetaCons "CompressParams" 'PrefixI 'True) ((S1 ('MetaSel ('Just "compressLevel") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 CompressionLevel) :*: (S1 ('MetaSel ('Just "compressMethod") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Method) :*: S1 ('MetaSel ('Just "compressWindowBits") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowBits))) :*: ((S1 ('MetaSel ('Just "compressMemoryLevel") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 MemoryLevel) :*: S1 ('MetaSel ('Just "compressStrategy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CompressionStrategy)) :*: (S1 ('MetaSel ('Just "compressBufferSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "compressDictionary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString))))))
Generic DecompressError 
Instance details

Defined in Codec.Compression.Zlib.Internal

Associated Types

type Rep DecompressError

Since: zlib-0.7.0.0

Instance details

Defined in Codec.Compression.Zlib.Internal

type Rep DecompressError = D1 ('MetaData "DecompressError" "Codec.Compression.Zlib.Internal" "zlb-0.7.1.0-f6c290ab" 'False) ((C1 ('MetaCons "TruncatedInput" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DictionaryRequired" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DictionaryMismatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataFormatError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))
Generic DecompressParams 
Instance details

Defined in Codec.Compression.Zlib.Internal

Associated Types

type Rep DecompressParams

Since: zlib-0.7.0.0

Instance details

Defined in Codec.Compression.Zlib.Internal

type Rep DecompressParams = D1 ('MetaData "DecompressParams" "Codec.Compression.Zlib.Internal" "zlb-0.7.1.0-f6c290ab" 'False) (C1 ('MetaCons "DecompressParams" 'PrefixI 'True) ((S1 ('MetaSel ('Just "decompressWindowBits") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 WindowBits) :*: S1 ('MetaSel ('Just "decompressBufferSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "decompressDictionary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ByteString)) :*: S1 ('MetaSel ('Just "decompressAllMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))
Generic CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep CompressionLevel = D1 ('MetaData "CompressionLevel" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'True) (C1 ('MetaCons "CompressionLevel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Generic CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep CompressionStrategy 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep CompressionStrategy = D1 ('MetaData "CompressionStrategy" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'False) ((C1 ('MetaCons "DefaultStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Filtered" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HuffmanOnly" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RLE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fixed" 'PrefixI 'False) (U1 :: Type -> Type))))
Generic Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Format 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep Format = D1 ('MetaData "Format" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'False) ((C1 ('MetaCons "GZip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Zlib" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Raw" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GZipOrZlib" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Format -> Rep Format x #

to :: Rep Format x -> Format #

Generic MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep MemoryLevel 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep MemoryLevel = D1 ('MetaData "MemoryLevel" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'True) (C1 ('MetaCons "MemoryLevel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Generic Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep Method 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep Method = D1 ('MetaData "Method" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'False) (C1 ('MetaCons "Deflated" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Method -> Rep Method x #

to :: Rep Method x -> Method #

Generic WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

Associated Types

type Rep WindowBits 
Instance details

Defined in Codec.Compression.Zlib.Stream

type Rep WindowBits = D1 ('MetaData "WindowBits" "Codec.Compression.Zlib.Stream" "zlb-0.7.1.0-f6c290ab" 'True) (C1 ('MetaCons "WindowBits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))
Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep () = D1 ('MetaData "Unit" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "()" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep (ZipList a) = D1 ('MetaData "ZipList" "Control.Applicative" "base" 'True) (C1 ('MetaCons "ZipList" 'PrefixI 'True) (S1 ('MetaSel ('Just "getZipList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])))

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a)

Since: base-4.9.0.0

Instance details

Defined in Data.Complex

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

type Rep (Identity a) = D1 ('MetaData "Identity" "Data.Functor.Identity" "base" 'True) (C1 ('MetaCons "Identity" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentity") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (First a) = D1 ('MetaData "First" "Data.Monoid" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a)

Since: base-4.7.0.0

Instance details

Defined in Data.Monoid

type Rep (Last a) = D1 ('MetaData "Last" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

type Rep (Down a) = D1 ('MetaData "Down" "Data.Ord" "base" 'True) (C1 ('MetaCons "Down" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDown") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (First a) = D1 ('MetaData "First" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "First" 'PrefixI 'True) (S1 ('MetaSel ('Just "getFirst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Last a) = D1 ('MetaData "Last" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Last" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Max a) = D1 ('MetaData "Max" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Max" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (Min a) = D1 ('MetaData "Min" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "Min" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

type Rep (WrappedMonoid m) = D1 ('MetaData "WrappedMonoid" "Data.Semigroup" "base" 'True) (C1 ('MetaCons "WrapMonoid" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonoid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)))
Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Dual a) = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Endo a) = D1 ('MetaData "Endo" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Endo" 'PrefixI 'True) (S1 ('MetaSel ('Just "appEndo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a))))

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Product a) = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Sum a) = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (Par1 p) = D1 ('MetaData "Par1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "Par1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPar1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 p)))

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (SCC vertex) 
Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

type Rep (SCC vertex) = D1 ('MetaData "SCC" "Data.Graph" "containers-0.6.8-6b4f" 'False) (C1 ('MetaCons "AcyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 vertex)) :+: C1 ('MetaCons "CyclicSCC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [vertex])))

Methods

from :: SCC vertex -> Rep (SCC vertex) x #

to :: Rep (SCC vertex) x -> SCC vertex #

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Methods

from :: Digit a -> Rep (Digit a) x #

to :: Rep (Digit a) x -> Digit a #

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

type Rep (Elem a) = D1 ('MetaData "Elem" "Data.Sequence.Internal" "containers-0.6.8-6b4f" 'True) (C1 ('MetaCons "Elem" 'PrefixI 'True) (S1 ('MetaSel ('Just "getElem") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Elem a -> Rep (Elem a) x #

to :: Rep (Elem a) x -> Elem a #

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a)

Since: containers-0.6.1

Instance details

Defined in Data.Sequence.Internal

Methods

from :: FingerTree a -> Rep (FingerTree a) x #

to :: Rep (FingerTree a) x -> FingerTree a #

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Methods

from :: Node a -> Rep (Node a) x #

to :: Rep (Node a) x -> Node a #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

type Rep (ViewL a) = D1 ('MetaData "ViewL" "Data.Sequence.Internal" "containers-0.6.8-6b4f" 'False) (C1 ('MetaCons "EmptyL" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":<" ('InfixI 'RightAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a))))

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a)

Since: containers-0.5.8

Instance details

Defined in Data.Sequence.Internal

type Rep (ViewR a) = D1 ('MetaData "ViewR" "Data.Sequence.Internal" "containers-0.6.8-6b4f" 'False) (C1 ('MetaCons "EmptyR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons ":>" ('InfixI 'LeftAssociative 5) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a)

Since: containers-0.5.8

Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.8-6b4f" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tree a])))

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (Loc a) 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep (Loc a) 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep (Loc a) = D1 ('MetaData "Loc" "Language.Haskell.Exts.SrcLoc" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Loc" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpan) :*: S1 ('MetaSel ('Just "unLoc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Loc a -> Rep (Loc a) x #

to :: Rep (Loc a) x -> Loc a #

Generic (Activation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Activation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Activation l -> Rep (Activation l) x #

to :: Rep (Activation l) x -> Activation l #

Generic (Alt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Alt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Alt l -> Rep (Alt l) x #

to :: Rep (Alt l) x -> Alt l #

Generic (Annotation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Annotation l -> Rep (Annotation l) x #

to :: Rep (Annotation l) x -> Annotation l #

Generic (Assoc l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Assoc l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Assoc l) = D1 ('MetaData "Assoc" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "AssocNone" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: (C1 ('MetaCons "AssocLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "AssocRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))))

Methods

from :: Assoc l -> Rep (Assoc l) x #

to :: Rep (Assoc l) x -> Assoc l #

Generic (Asst l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Asst l -> Rep (Asst l) x #

to :: Rep (Asst l) x -> Asst l #

Generic (BangType l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (BangType l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (BangType l) = D1 ('MetaData "BangType" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "BangedTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: (C1 ('MetaCons "LazyTy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "NoStrictAnnot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))))

Methods

from :: BangType l -> Rep (BangType l) x #

to :: Rep (BangType l) x -> BangType l #

Generic (Binds l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Binds l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Binds l -> Rep (Binds l) x #

to :: Rep (Binds l) x -> Binds l #

Generic (BooleanFormula l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic (Bracket l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Bracket l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Bracket l -> Rep (Bracket l) x #

to :: Rep (Bracket l) x -> Bracket l #

Generic (CName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (CName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: CName l -> Rep (CName l) x #

to :: Rep (CName l) x -> CName l #

Generic (CallConv l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: CallConv l -> Rep (CallConv l) x #

to :: Rep (CallConv l) x -> CallConv l #

Generic (ClassDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ClassDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (ClassDecl l) = D1 ('MetaData "ClassDecl" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "ClsDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Decl l))) :+: C1 ('MetaCons "ClsDataFam" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ResultSig l)))))) :+: (C1 ('MetaCons "ClsTyFam" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ResultSig l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (InjectivityInfo l))))) :+: (C1 ('MetaCons "ClsTyDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TypeEqn l))) :+: C1 ('MetaCons "ClsDefSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))))))

Methods

from :: ClassDecl l -> Rep (ClassDecl l) x #

to :: Rep (ClassDecl l) x -> ClassDecl l #

Generic (ConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ConDecl l -> Rep (ConDecl l) x #

to :: Rep (ConDecl l) x -> ConDecl l #

Generic (Context l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Context l -> Rep (Context l) x #

to :: Rep (Context l) x -> Context l #

Generic (DataOrNew l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DataOrNew l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (DataOrNew l) = D1 ('MetaData "DataOrNew" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "DataType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "NewType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)))

Methods

from :: DataOrNew l -> Rep (DataOrNew l) x #

to :: Rep (DataOrNew l) x -> DataOrNew l #

Generic (Decl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Decl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Decl l) = D1 ('MetaData "Decl" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (((((C1 ('MetaCons "TypeDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "TypeFamDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ResultSig l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (InjectivityInfo l)))))) :+: (C1 ('MetaCons "ClosedTypeFamDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ResultSig l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (InjectivityInfo l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TypeEqn l])))) :+: C1 ('MetaCons "DataDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l))))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QualConDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l])))))) :+: ((C1 ('MetaCons "GDataDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l))))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Kind l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GadtDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l])))) :+: C1 ('MetaCons "DataFamDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ResultSig l)))))) :+: (C1 ('MetaCons "TypeInsDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "DataInsDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QualConDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l]))))))) :+: (((C1 ('MetaCons "GDataInsDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Kind l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GadtDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l])))) :+: C1 ('MetaCons "ClassDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DeclHead l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunDep l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [ClassDecl l])))))) :+: (C1 ('MetaCons "InstDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Overlap l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InstRule l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [InstDecl l])))) :+: C1 ('MetaCons "DerivDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (DerivStrategy l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Overlap l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InstRule l)))))) :+: ((C1 ('MetaCons "InfixDecl" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Assoc l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Op l]))) :+: C1 ('MetaCons "DefaultDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l]))) :+: (C1 ('MetaCons "SpliceDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: (C1 ('MetaCons "TSpliceDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: C1 ('MetaCons "TypeSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))))))))) :+: ((((C1 ('MetaCons "PatSynSig" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBind l])))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBind l]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))))) :+: C1 ('MetaCons "FunBind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match l]))) :+: (C1 ('MetaCons "PatBind" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Rhs l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Binds l))))) :+: C1 ('MetaCons "PatSyn" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PatternSynDirection l)))))) :+: ((C1 ('MetaCons "ForImp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CallConv l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Safety l))))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))))) :+: C1 ('MetaCons "ForExp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CallConv l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))))) :+: (C1 ('MetaCons "RulePragmaDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Rule l])) :+: (C1 ('MetaCons "DeprPragmaDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([Name l], String)])) :+: C1 ('MetaCons "WarnPragmaDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [([Name l], String)])))))) :+: (((C1 ('MetaCons "InlineSig" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Activation l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)))) :+: C1 ('MetaCons "InlineConlikeSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Activation l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))))) :+: (C1 ('MetaCons "SpecSig" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Activation l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l]))) :+: C1 ('MetaCons "SpecInlineSig" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Activation l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l])))))) :+: ((C1 ('MetaCons "InstSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (InstRule l))) :+: C1 ('MetaCons "AnnPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Annotation l)))) :+: (C1 ('MetaCons "MinimalPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (BooleanFormula l)))) :+: (C1 ('MetaCons "RoleAnnotDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role l]))) :+: C1 ('MetaCons "CompletePragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (QName l)))))))))))

Methods

from :: Decl l -> Rep (Decl l) x #

to :: Rep (Decl l) x -> Decl l #

Generic (DeclHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DeclHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: DeclHead l -> Rep (DeclHead l) x #

to :: Rep (DeclHead l) x -> DeclHead l #

Generic (DerivStrategy l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (DerivStrategy l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic (Deriving l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Deriving l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Deriving l -> Rep (Deriving l) x #

to :: Rep (Deriving l) x -> Deriving l #

Generic (EWildcard l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (EWildcard l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (EWildcard l) = D1 ('MetaData "EWildcard" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "NoWildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "EWildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Methods

from :: EWildcard l -> Rep (EWildcard l) x #

to :: Rep (EWildcard l) x -> EWildcard l #

Generic (Exp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Exp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Exp l) = D1 ('MetaData "Exp" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (((((C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: (C1 ('MetaCons "OverloadedLabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "IPVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IPName l))))) :+: ((C1 ('MetaCons "Con" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Literal l)))) :+: (C1 ('MetaCons "InfixApp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QOp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "App" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))))))) :+: ((C1 ('MetaCons "NegApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: (C1 ('MetaCons "Lambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "Let" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Binds l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: ((C1 ('MetaCons "If" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "MultiIf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GuardedRhs l]))) :+: (C1 ('MetaCons "Case" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Alt l]))) :+: C1 ('MetaCons "Do" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt l])))))) :+: (((C1 ('MetaCons "MDo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt l])) :+: (C1 ('MetaCons "Tuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Boxed) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l]))) :+: C1 ('MetaCons "UnboxedSum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: ((C1 ('MetaCons "TupleSection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Boxed) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe (Exp l)]))) :+: C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l]))) :+: (C1 ('MetaCons "ParArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l])) :+: C1 ('MetaCons "Paren" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: ((C1 ('MetaCons "LeftSection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QOp l)))) :+: (C1 ('MetaCons "RightSection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QOp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "RecConstr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldUpdate l]))))) :+: ((C1 ('MetaCons "RecUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldUpdate l]))) :+: C1 ('MetaCons "EnumFrom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: (C1 ('MetaCons "EnumFromTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "EnumFromThen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))))))))) :+: ((((C1 ('MetaCons "EnumFromThenTo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: (C1 ('MetaCons "ParArrayFromTo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "ParArrayFromThenTo" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: ((C1 ('MetaCons "ListComp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QualStmt l]))) :+: C1 ('MetaCons "ParComp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[QualStmt l]])))) :+: (C1 ('MetaCons "ParArrayComp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[QualStmt l]]))) :+: C1 ('MetaCons "ExpTypeSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))))))) :+: ((C1 ('MetaCons "VarQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: (C1 ('MetaCons "TypQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: C1 ('MetaCons "BracketExp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Bracket l))))) :+: ((C1 ('MetaCons "SpliceExp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Splice l))) :+: C1 ('MetaCons "QuasiQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: (C1 ('MetaCons "TypeApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))) :+: C1 ('MetaCons "XTag" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [XAttr l]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Exp l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l])))))))) :+: (((C1 ('MetaCons "XETag" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [XAttr l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Exp l))))) :+: (C1 ('MetaCons "XPcdata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "XExpTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))))) :+: ((C1 ('MetaCons "XChildTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l])) :+: C1 ('MetaCons "CorePragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))))) :+: (C1 ('MetaCons "SCCPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "GenPragma" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))))) :+: ((C1 ('MetaCons "Proc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: (C1 ('MetaCons "LeftArrApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "RightArrApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: ((C1 ('MetaCons "LeftArrHighApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))) :+: C1 ('MetaCons "RightArrHighApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))))) :+: (C1 ('MetaCons "ArrOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: C1 ('MetaCons "LCase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Alt l]))))))))

Methods

from :: Exp l -> Rep (Exp l) x #

to :: Rep (Exp l) x -> Exp l #

Generic (ExportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (ExportSpec l) = D1 ('MetaData "ExportSpec" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "EVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: C1 ('MetaCons "EAbs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Namespace l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))))) :+: (C1 ('MetaCons "EThingWith" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (EWildcard l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CName l]))) :+: C1 ('MetaCons "EModuleContents" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ModuleName l)))))

Methods

from :: ExportSpec l -> Rep (ExportSpec l) x #

to :: Rep (ExportSpec l) x -> ExportSpec l #

Generic (ExportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ExportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (ExportSpecList l) = D1 ('MetaData "ExportSpecList" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "ExportSpecList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExportSpec l])))
Generic (FieldDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FieldDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (FieldDecl l) = D1 ('MetaData "FieldDecl" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "FieldDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))))

Methods

from :: FieldDecl l -> Rep (FieldDecl l) x #

to :: Rep (FieldDecl l) x -> FieldDecl l #

Generic (FieldUpdate l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: FieldUpdate l -> Rep (FieldUpdate l) x #

to :: Rep (FieldUpdate l) x -> FieldUpdate l #

Generic (FunDep l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (FunDep l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: FunDep l -> Rep (FunDep l) x #

to :: Rep (FunDep l) x -> FunDep l #

Generic (GadtDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: GadtDecl l -> Rep (GadtDecl l) x #

to :: Rep (GadtDecl l) x -> GadtDecl l #

Generic (GuardedRhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (GuardedRhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (GuardedRhs l) = D1 ('MetaData "GuardedRhs" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "GuardedRhs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))

Methods

from :: GuardedRhs l -> Rep (GuardedRhs l) x #

to :: Rep (GuardedRhs l) x -> GuardedRhs l #

Generic (IPBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (IPBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: IPBind l -> Rep (IPBind l) x #

to :: Rep (IPBind l) x -> IPBind l #

Generic (IPName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: IPName l -> Rep (IPName l) x #

to :: Rep (IPName l) x -> IPName l #

Generic (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ImportDecl l -> Rep (ImportDecl l) x #

to :: Rep (ImportDecl l) x -> ImportDecl l #

Generic (ImportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ImportSpec l -> Rep (ImportSpec l) x #

to :: Rep (ImportSpec l) x -> ImportSpec l #

Generic (ImportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (ImportSpecList l) = D1 ('MetaData "ImportSpecList" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "ImportSpecList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ImportSpec l]))))
Generic (InjectivityInfo l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InjectivityInfo l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (InjectivityInfo l) = D1 ('MetaData "InjectivityInfo" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "InjectivityInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name l]))))
Generic (InstDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (InstDecl l) = D1 ('MetaData "InstDecl" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "InsDecl" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Decl l))) :+: C1 ('MetaCons "InsType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))))) :+: (C1 ('MetaCons "InsData" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [QualConDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l])))) :+: C1 ('MetaCons "InsGData" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (DataOrNew l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Kind l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GadtDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Deriving l]))))))

Methods

from :: InstDecl l -> Rep (InstDecl l) x #

to :: Rep (InstDecl l) x -> InstDecl l #

Generic (InstHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (InstHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: InstHead l -> Rep (InstHead l) x #

to :: Rep (InstHead l) x -> InstHead l #

Generic (InstRule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: InstRule l -> Rep (InstRule l) x #

to :: Rep (InstRule l) x -> InstRule l #

Generic (Literal l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Literal l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Literal l) = D1 ('MetaData "Literal" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (((C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: (C1 ('MetaCons "Int" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "Frac" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PrimInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))) :+: ((C1 ('MetaCons "PrimWord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PrimFloat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :+: (C1 ('MetaCons "PrimDouble" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PrimChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PrimString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))))))

Methods

from :: Literal l -> Rep (Literal l) x #

to :: Rep (Literal l) x -> Literal l #

Generic (Match l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Match l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Match l -> Rep (Match l) x #

to :: Rep (Match l) x -> Match l #

Generic (MaybePromotedName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (MaybePromotedName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic (Module l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Module l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Module l) = D1 ('MetaData "Module" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ModuleHead l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModulePragma l]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ImportDecl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Decl l])))) :+: (C1 ('MetaCons "XmlPage" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ModuleName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModulePragma l]))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [XAttr l])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Exp l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l])))) :+: C1 ('MetaCons "XmlHybrid" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ModuleHead l)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ModulePragma l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ImportDecl l]))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Decl l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [XAttr l]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Exp l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp l])))))))

Methods

from :: Module l -> Rep (Module l) x #

to :: Rep (Module l) x -> Module l #

Generic (ModuleHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ModuleHead l -> Rep (ModuleHead l) x #

to :: Rep (ModuleHead l) x -> ModuleHead l #

Generic (ModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (ModuleName l) = D1 ('MetaData "ModuleName" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "ModuleName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: ModuleName l -> Rep (ModuleName l) x #

to :: Rep (ModuleName l) x -> ModuleName l #

Generic (ModulePragma l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ModulePragma l -> Rep (ModulePragma l) x #

to :: Rep (ModulePragma l) x -> ModulePragma l #

Generic (Name l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Name l -> Rep (Name l) x #

to :: Rep (Name l) x -> Name l #

Generic (Namespace l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Namespace l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Namespace l) = D1 ('MetaData "Namespace" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "NoNamespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: (C1 ('MetaCons "TypeNamespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "PatternNamespace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))))

Methods

from :: Namespace l -> Rep (Namespace l) x #

to :: Rep (Namespace l) x -> Namespace l #

Generic (Op l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Op l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Op l -> Rep (Op l) x #

to :: Rep (Op l) x -> Op l #

Generic (Overlap l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Overlap l -> Rep (Overlap l) x #

to :: Rep (Overlap l) x -> Overlap l #

Generic (PXAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PXAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: PXAttr l -> Rep (PXAttr l) x #

to :: Rep (PXAttr l) x -> PXAttr l #

Generic (Pat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Pat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Pat l) = D1 ('MetaData "Pat" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((((C1 ('MetaCons "PVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l))) :+: (C1 ('MetaCons "PLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Sign l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Literal l)))) :+: C1 ('MetaCons "PNPlusK" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) :+: (C1 ('MetaCons "PInfixApp" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)))) :+: (C1 ('MetaCons "PApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat l]))) :+: C1 ('MetaCons "PTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Boxed) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat l])))))) :+: ((C1 ('MetaCons "PUnboxedSum" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)))) :+: (C1 ('MetaCons "PList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat l])) :+: C1 ('MetaCons "PParen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))))) :+: (C1 ('MetaCons "PRec" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PatField l]))) :+: (C1 ('MetaCons "PAsPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)))) :+: C1 ('MetaCons "PWildCard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)))))) :+: (((C1 ('MetaCons "PIrrPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))) :+: (C1 ('MetaCons "PatTypeSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "PViewPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)))))) :+: (C1 ('MetaCons "PRPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RPat l])) :+: (C1 ('MetaCons "PXTag" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PXAttr l]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Pat l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat l])))) :+: C1 ('MetaCons "PXETag" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (XName l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PXAttr l]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Pat l)))))))) :+: ((C1 ('MetaCons "PXPcdata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "PXPatTag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))) :+: C1 ('MetaCons "PXRPats" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RPat l])))) :+: (C1 ('MetaCons "PSplice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Splice l))) :+: (C1 ('MetaCons "PQuasiQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PBangPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))))))))

Methods

from :: Pat l -> Rep (Pat l) x #

to :: Rep (Pat l) x -> Pat l #

Generic (PatField l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: PatField l -> Rep (PatField l) x #

to :: Rep (PatField l) x -> PatField l #

Generic (PatternSynDirection l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (PatternSynDirection l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (PatternSynDirection l) = D1 ('MetaData "PatternSynDirection" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Unidirectional" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ImplicitBidirectional" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplicitBidirectional" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Decl l]))))
Generic (Promoted l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Promoted l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Promoted l) = D1 ('MetaData "Promoted" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "PromotedInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "PromotedString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: C1 ('MetaCons "PromotedCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l)))))) :+: (C1 ('MetaCons "PromotedList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l]))) :+: (C1 ('MetaCons "PromotedTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l])) :+: C1 ('MetaCons "PromotedUnit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)))))

Methods

from :: Promoted l -> Rep (Promoted l) x #

to :: Rep (Promoted l) x -> Promoted l #

Generic (QName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: QName l -> Rep (QName l) x #

to :: Rep (QName l) x -> QName l #

Generic (QOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: QOp l -> Rep (QOp l) x #

to :: Rep (QOp l) x -> QOp l #

Generic (QualConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: QualConDecl l -> Rep (QualConDecl l) x #

to :: Rep (QualConDecl l) x -> QualConDecl l #

Generic (QualStmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (QualStmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (QualStmt l) = D1 ('MetaData "QualStmt" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "QualStmt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Stmt l))) :+: (C1 ('MetaCons "ThenTrans" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: C1 ('MetaCons "ThenBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))) :+: (C1 ('MetaCons "GroupBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: (C1 ('MetaCons "GroupUsing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l))) :+: C1 ('MetaCons "GroupByUsing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Exp l)))))))

Methods

from :: QualStmt l -> Rep (QualStmt l) x #

to :: Rep (QualStmt l) x -> QualStmt l #

Generic (RPat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (RPat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (RPat l) = D1 ('MetaData "RPat" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (((C1 ('MetaCons "RPOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPatOp l)))) :+: C1 ('MetaCons "RPEither" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l))))) :+: (C1 ('MetaCons "RPSeq" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RPat l])) :+: C1 ('MetaCons "RPGuard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt l]))))) :+: ((C1 ('MetaCons "RPCAs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l)))) :+: C1 ('MetaCons "RPAs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l))))) :+: (C1 ('MetaCons "RPParen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RPat l))) :+: C1 ('MetaCons "RPPat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Pat l))))))

Methods

from :: RPat l -> Rep (RPat l) x #

to :: Rep (RPat l) x -> RPat l #

Generic (RPatOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: RPatOp l -> Rep (RPatOp l) x #

to :: Rep (RPatOp l) x -> RPatOp l #

Generic (ResultSig l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ResultSig l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: ResultSig l -> Rep (ResultSig l) x #

to :: Rep (ResultSig l) x -> ResultSig l #

Generic (Rhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Rhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Rhs l -> Rep (Rhs l) x #

to :: Rep (Rhs l) x -> Rhs l #

Generic (Role l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Role l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Role l) = D1 ('MetaData "Role" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((C1 ('MetaCons "Nominal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "Representational" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))) :+: (C1 ('MetaCons "Phantom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "RoleWildcard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))))

Methods

from :: Role l -> Rep (Role l) x #

to :: Rep (Role l) x -> Role l #

Generic (Rule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Rule l -> Rep (Rule l) x #

to :: Rep (Rule l) x -> Rule l #

Generic (RuleVar l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: RuleVar l -> Rep (RuleVar l) x #

to :: Rep (RuleVar l) x -> RuleVar l #

Generic (Safety l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Safety l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Safety l -> Rep (Safety l) x #

to :: Rep (Safety l) x -> Safety l #

Generic (Sign l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Sign l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Sign l) = D1 ('MetaData "Sign" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Signless" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "Negative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)))

Methods

from :: Sign l -> Rep (Sign l) x #

to :: Rep (Sign l) x -> Sign l #

Generic (SpecialCon l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (SpecialCon l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: SpecialCon l -> Rep (SpecialCon l) x #

to :: Rep (SpecialCon l) x -> SpecialCon l #

Generic (Splice l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Splice l -> Rep (Splice l) x #

to :: Rep (Splice l) x -> Splice l #

Generic (Stmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: Stmt l -> Rep (Stmt l) x #

to :: Rep (Stmt l) x -> Stmt l #

Generic (TyVarBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: TyVarBind l -> Rep (TyVarBind l) x #

to :: Rep (TyVarBind l) x -> TyVarBind l #

Generic (Type l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Type l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Type l) = D1 ('MetaData "Type" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) ((((C1 ('MetaCons "TyForall" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBind l]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Context l))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "TyStar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))) :+: (C1 ('MetaCons "TyFun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "TyTuple" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Boxed) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l]))))) :+: ((C1 ('MetaCons "TyUnboxedSum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type l])) :+: C1 ('MetaCons "TyList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: (C1 ('MetaCons "TyParArray" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))) :+: (C1 ('MetaCons "TyApp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "TyVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Name l))))))) :+: (((C1 ('MetaCons "TyCon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (QName l))) :+: C1 ('MetaCons "TyParen" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: (C1 ('MetaCons "TyInfix" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MaybePromotedName l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: (C1 ('MetaCons "TyKind" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Kind l)))) :+: C1 ('MetaCons "TyPromoted" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Promoted l)))))) :+: ((C1 ('MetaCons "TyEquals" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: C1 ('MetaCons "TySplice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Splice l)))) :+: (C1 ('MetaCons "TyBang" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BangType l))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Unpackedness l)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Type l)))) :+: (C1 ('MetaCons "TyWildCard" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Name l)))) :+: C1 ('MetaCons "TyQuasiQuote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))))

Methods

from :: Type l -> Rep (Type l) x #

to :: Rep (Type l) x -> Type l #

Generic (TypeEqn l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (TypeEqn l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: TypeEqn l -> Rep (TypeEqn l) x #

to :: Rep (TypeEqn l) x -> TypeEqn l #

Generic (Unpackedness l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (Unpackedness l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

type Rep (Unpackedness l) = D1 ('MetaData "Unpackedness" "Language.Haskell.Exts.Syntax" "hskll-src-xts-1.23.1-1902127c" 'False) (C1 ('MetaCons "Unpack" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: (C1 ('MetaCons "NoUnpack" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :+: C1 ('MetaCons "NoUnpackPragma" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l))))

Methods

from :: Unpackedness l -> Rep (Unpackedness l) x #

to :: Rep (Unpackedness l) x -> Unpackedness l #

Generic (WarningText l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: WarningText l -> Rep (WarningText l) x #

to :: Rep (WarningText l) x -> WarningText l #

Generic (XAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (XAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: XAttr l -> Rep (XAttr l) x #

to :: Rep (XAttr l) x -> XAttr l #

Generic (XName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

from :: XName l -> Rep (XName l) x #

to :: Rep (XName l) x -> XName l #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep (Doc a) = D1 ('MetaData "Doc" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6-b285" 'False) (((C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NilAbove" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)))) :+: (C1 ('MetaCons "TextBeside" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (AnnotDetails a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))) :+: C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))))) :+: ((C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a))) :+: C1 ('MetaCons "NoDoc" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Beside" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)))) :+: C1 ('MetaCons "Above" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc a)))))))

Methods

from :: Doc a -> Rep (Doc a) x #

to :: Rep (Doc a) x -> Doc a #

Generic (AddrRange a) 
Instance details

Defined in Data.IP.Range

Associated Types

type Rep (AddrRange a) 
Instance details

Defined in Data.IP.Range

type Rep (AddrRange a) = D1 ('MetaData "AddrRange" "Data.IP.Range" "prt-1.7.15-2c08a36d" 'False) (C1 ('MetaCons "AddrRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "addr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: (S1 ('MetaSel ('Just "mask") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "mlen") 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 Int))))

Methods

from :: AddrRange a -> Rep (AddrRange a) x #

to :: Rep (AddrRange a) x -> AddrRange a #

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

from :: TyVarBndr flag -> Rep (TyVarBndr flag) x #

to :: Rep (TyVarBndr flag) x -> TyVarBndr flag #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Solo a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Solo a)

Since: base-4.15

Instance details

Defined in GHC.Generics

type Rep (Solo a) = D1 ('MetaData "Solo" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "MkSolo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Solo a -> Rep (Solo a) x #

to :: Rep (Solo a) x -> Solo a #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep (WrappedMonad m a) = D1 ('MetaData "WrappedMonad" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapMonad" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapMonad") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m a))))

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (U1 p) = D1 ('MetaData "U1" "GHC.Generics" "base" 'False) (C1 ('MetaCons "U1" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (V1 p) = D1 ('MetaData "V1" "GHC.Generics" "base" 'False) (V1 :: Type -> Type)

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

Associated Types

type Rep (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

type Rep (MaybeT m a) = D1 ('MetaData "MaybeT" "Control.Monad.Trans.Maybe" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "MaybeT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runMaybeT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (Maybe a)))))

Methods

from :: MaybeT m a -> Rep (MaybeT m a) x #

to :: Rep (MaybeT m a) x -> MaybeT m a #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

type Rep (WrappedArrow a b c) = D1 ('MetaData "WrappedArrow" "Control.Applicative" "base" 'True) (C1 ('MetaCons "WrapArrow" 'PrefixI 'True) (S1 ('MetaSel ('Just "unwrapArrow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a b c))))

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) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

type Rep (Kleisli m a b) = D1 ('MetaData "Kleisli" "Control.Arrow" "base" 'True) (C1 ('MetaCons "Kleisli" 'PrefixI 'True) (S1 ('MetaSel ('Just "runKleisli") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> m b))))

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

type Rep (Const a b) = D1 ('MetaData "Const" "Data.Functor.Const" "base" 'True) (C1 ('MetaCons "Const" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConst") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

type Rep (Ap f a) = D1 ('MetaData "Ap" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Ap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

type Rep (Alt f a) = D1 ('MetaData "Alt" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (Rec1 f p) = D1 ('MetaData "Rec1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "Rec1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRec1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f p))))

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Char p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UChar" 'PrefixI 'True) (S1 ('MetaSel ('Just "uChar#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UChar :: Type -> Type)))

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Double p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UDouble" 'PrefixI 'True) (S1 ('MetaSel ('Just "uDouble#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UDouble :: Type -> Type)))

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) 
Instance details

Defined in GHC.Generics

type Rep (URec Float p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UFloat" 'PrefixI 'True) (S1 ('MetaSel ('Just "uFloat#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UFloat :: Type -> Type)))

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Int p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UInt" 'PrefixI 'True) (S1 ('MetaSel ('Just "uInt#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UInt :: Type -> Type)))

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UWord" 'PrefixI 'True) (S1 ('MetaSel ('Just "uWord#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UWord :: Type -> Type)))

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) 
Instance details

Defined in Data.Tagged

type Rep (Tagged s b) = D1 ('MetaData "Tagged" "Data.Tagged" "tggd-0.8.9-9dff62e1" 'True) (C1 ('MetaCons "Tagged" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTagged") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))

Methods

from :: Tagged s b -> Rep (Tagged s b) x #

to :: Rep (Tagged s b) x -> Tagged s b #

Generic (AccumT w m a) 
Instance details

Defined in Control.Monad.Trans.Accum

Associated Types

type Rep (AccumT w m a) 
Instance details

Defined in Control.Monad.Trans.Accum

type Rep (AccumT w m a) = D1 ('MetaData "AccumT" "Control.Monad.Trans.Accum" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "AccumT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> m (a, w)))))

Methods

from :: AccumT w m a -> Rep (AccumT w m a) x #

to :: Rep (AccumT w m a) x -> AccumT w m a #

Generic (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Associated Types

type Rep (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

type Rep (ExceptT e m a) = D1 ('MetaData "ExceptT" "Control.Monad.Trans.Except" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "ExceptT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (Either e a)))))

Methods

from :: ExceptT e m a -> Rep (ExceptT e m a) x #

to :: Rep (ExceptT e m a) x -> ExceptT e m a #

Generic (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Associated Types

type Rep (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

type Rep (IdentityT f a) = D1 ('MetaData "IdentityT" "Control.Monad.Trans.Identity" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "IdentityT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runIdentityT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

Methods

from :: IdentityT f a -> Rep (IdentityT f a) x #

to :: Rep (IdentityT f a) x -> IdentityT f a #

Generic (ReaderT r m a) 
Instance details

Defined in Control.Monad.Trans.Reader

Associated Types

type Rep (ReaderT r m a) 
Instance details

Defined in Control.Monad.Trans.Reader

type Rep (ReaderT r m a) = D1 ('MetaData "ReaderT" "Control.Monad.Trans.Reader" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "ReaderT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runReaderT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r -> m a))))

Methods

from :: ReaderT r m a -> Rep (ReaderT r m a) x #

to :: Rep (ReaderT r m a) x -> ReaderT r m a #

Generic (SelectT r m a) 
Instance details

Defined in Control.Monad.Trans.Select

Associated Types

type Rep (SelectT r m a) 
Instance details

Defined in Control.Monad.Trans.Select

type Rep (SelectT r m a) = D1 ('MetaData "SelectT" "Control.Monad.Trans.Select" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "SelectT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((a -> m r) -> m a))))

Methods

from :: SelectT r m a -> Rep (SelectT r m a) x #

to :: Rep (SelectT r m a) x -> SelectT r m a #

Generic (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Associated Types

type Rep (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

type Rep (StateT s m a) = D1 ('MetaData "StateT" "Control.Monad.Trans.State.Lazy" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "StateT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runStateT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (s -> m (a, s)))))

Methods

from :: StateT s m a -> Rep (StateT s m a) x #

to :: Rep (StateT s m a) x -> StateT s m a #

Generic (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Associated Types

type Rep (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Strict

type Rep (StateT s m a) = D1 ('MetaData "StateT" "Control.Monad.Trans.State.Strict" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "StateT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runStateT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (s -> m (a, s)))))

Methods

from :: StateT s m a -> Rep (StateT s m a) x #

to :: Rep (StateT s m a) x -> StateT s m a #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Associated Types

type Rep (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

type Rep (WriterT w m a) = D1 ('MetaData "WriterT" "Control.Monad.Trans.Writer.CPS" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "WriterT" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWriterT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (w -> m (a, w)))))

Methods

from :: WriterT w m a -> Rep (WriterT w m a) x #

to :: Rep (WriterT w m a) x -> WriterT w m a #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Associated Types

type Rep (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

type Rep (WriterT w m a) = D1 ('MetaData "WriterT" "Control.Monad.Trans.Writer.Lazy" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "WriterT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runWriterT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (a, w)))))

Methods

from :: WriterT w m a -> Rep (WriterT w m a) x #

to :: Rep (WriterT w m a) x -> WriterT w m a #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Associated Types

type Rep (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

type Rep (WriterT w m a) = D1 ('MetaData "WriterT" "Control.Monad.Trans.Writer.Strict" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "WriterT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runWriterT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (a, w)))))

Methods

from :: WriterT w m a -> Rep (WriterT w m a) x #

to :: Rep (WriterT w m a) x -> WriterT w m a #

Generic (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Associated Types

type Rep (Constant a b) 
Instance details

Defined in Data.Functor.Constant

type Rep (Constant a b) = D1 ('MetaData "Constant" "Data.Functor.Constant" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "Constant" 'PrefixI 'True) (S1 ('MetaSel ('Just "getConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Methods

from :: Constant a b -> Rep (Constant a b) x #

to :: Rep (Constant a b) x -> Constant a b #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

type Rep (Product f g a) = D1 ('MetaData "Product" "Data.Functor.Product" "base" 'False) (C1 ('MetaCons "Pair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (g a))))

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (K1 i c p) = D1 ('MetaData "K1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "K1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unK1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c)))

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic (ContT r m a) 
Instance details

Defined in Control.Monad.Trans.Cont

Associated Types

type Rep (ContT r m a) 
Instance details

Defined in Control.Monad.Trans.Cont

type Rep (ContT r m a) = D1 ('MetaData "ContT" "Control.Monad.Trans.Cont" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "ContT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runContT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ((a -> m r) -> m r))))

Methods

from :: ContT r m a -> Rep (ContT r m a) x #

to :: Rep (ContT r m a) x -> ContT r m a #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

type Rep (Compose f g a) = D1 ('MetaData "Compose" "Data.Functor.Compose" "base" 'True) (C1 ('MetaCons "Compose" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (g a)))))

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep ((f :.: g) p) = D1 ('MetaData ":.:" "GHC.Generics" "base" 'True) (C1 ('MetaCons "Comp1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unComp1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (g p)))))

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

type Rep (M1 i c f p) = D1 ('MetaData "M1" "GHC.Generics" "base" 'True) (C1 ('MetaCons "M1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unM1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f p))))

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Associated Types

type Rep (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

type Rep (RWST r w s m a) = D1 ('MetaData "RWST" "Control.Monad.Trans.RWS.CPS" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "RWST" 'PrefixI 'True) (S1 ('MetaSel ('Just "unRWST") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r -> s -> w -> m (a, s, w)))))

Methods

from :: RWST r w s m a -> Rep (RWST r w s m a) x #

to :: Rep (RWST r w s m a) x -> RWST r w s m a #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Associated Types

type Rep (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

type Rep (RWST r w s m a) = D1 ('MetaData "RWST" "Control.Monad.Trans.RWS.Lazy" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "RWST" 'PrefixI 'True) (S1 ('MetaSel ('Just "runRWST") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r -> s -> m (a, s, w)))))

Methods

from :: RWST r w s m a -> Rep (RWST r w s m a) x #

to :: Rep (RWST r w s m a) x -> RWST r w s m a #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Associated Types

type Rep (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

type Rep (RWST r w s m a) = D1 ('MetaData "RWST" "Control.Monad.Trans.RWS.Strict" "transformers-0.6.1.0-6c0d" 'True) (C1 ('MetaCons "RWST" 'PrefixI 'True) (S1 ('MetaSel ('Just "runRWST") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r -> s -> m (a, s, w)))))

Methods

from :: RWST r w s m a -> Rep (RWST r w s m a) x #

to :: Rep (RWST r w s m a) x -> RWST r w s m a #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

Generic (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) #

Generic (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g, h, i) -> Rep (a, b, c, d, e, f, g, h, i) x #

to :: Rep (a, b, c, d, e, f, g, h, i) x -> (a, b, c, d, e, f, g, h, i) #

Generic (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) #

Generic (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k) -> Rep (a, b, c, d, e, f, g, h, i, j, k) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) x -> (a, b, c, d, e, f, g, h, i, j, k) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) = D1 ('MetaData "Tuple13" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m))))))

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = D1 ('MetaData "Tuple14" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n))))))

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-4.16.0.0

Instance details

Defined in GHC.Generics

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = D1 ('MetaData "Tuple15" "GHC.Tuple.Prim" "ghc-prim" 'False) (C1 ('MetaCons "(,,,,,,,,,,,,,,)" 'PrefixI 'False) (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 e)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 f) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 g)))) :*: (((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 h) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 j) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 k))) :*: ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 l) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 m)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 o))))))

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #