project-m36-0.9.7: Relational Algebra Engine
Safe HaskellSafe-Inferred
LanguageHaskell2010

ProjectM36.Tupleable.Deriving

Description

Newtypes for deriving Tupleable instances with customization using DerivingVia.

Inspired by Dhall.Deriving which in turn was inspired by Matt Parson's blog post Mirror Mirror: Reflection and Encoding Via.

required extensions:

  • DerivingVia
  • DeriveGenerics
  • TypeOperators (for (<<<) and (>>>))
  • DataKinds (for types that take a string argument)
Synopsis

DerivingVia Newtype

newtype Codec tag a Source #

A newtype wrapper to allow for easier deriving of Tupleable instances with customization.

The tag type variable can be used to specify options for converting the datatype to and from a RelationTuple. For example,

data Example = Example
    { exampleFoo :: Int
    , exampleBar :: Int
    }
    deriving stock (Generic)
    deriving (Tupleable)
        via Codec (Field (DropPrefix "example" >>> CamelCase)) Example

will derive an instance of Tupleable where field names are translated into attribute names by dropping the prefix "example" and then converting the result to camelCase. So "exampleFoo" becomes "foo" and "exampleBar" becomes "bar".

Requires the DerivingGeneric and DerivingVia extensions to be enabled.

Constructors

Codec 

Fields

Instances

Instances details
(ModifyOptions tag, Generic a, TupleableG (Rep a)) => Tupleable (Codec tag a) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Type-level Options

class ModifyOptions a where Source #

Types that can be used as tags for Codec.

Instances

Instances details
ModifyOptions () Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

ModifyText a => ModifyOptions (Field a) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

(ModifyOptions a, ModifyOptions b) => ModifyOptions (a <<< b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

(ModifyOptions a, ModifyOptions b) => ModifyOptions (a >>> b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

data Field a Source #

Change how record field names are translated into attribute names. For example,

Field SnakeCase

will translate the field name fooBar into the attribute name foo_bar.

Instances

Instances details
ModifyText a => ModifyOptions (Field a) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Type-level Text -> Text Functions

class ModifyText a where Source #

Types that can be used in options that modify Text such as in Field.

Methods

modifyText :: proxy a -> Text -> Text Source #

Instances

Instances details
ModifyText CamelCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy CamelCase -> Text -> Text Source #

ModifyText LowerCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy LowerCase -> Text -> Text Source #

ModifyText PascalCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy PascalCase -> Text -> Text Source #

ModifyText SnakeCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy SnakeCase -> Text -> Text Source #

ModifyText SpinalCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy SpinalCase -> Text -> Text Source #

ModifyText TitleCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy TitleCase -> Text -> Text Source #

ModifyText TrainCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy TrainCase -> Text -> Text Source #

ModifyText UpperCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy UpperCase -> Text -> Text Source #

ModifyText () Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy () -> Text -> Text Source #

KnownSymbol prefix => ModifyText (AddPrefix prefix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (AddPrefix prefix) -> Text -> Text Source #

KnownSymbol suffix => ModifyText (AddSuffix suffix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (AddSuffix suffix) -> Text -> Text Source #

KnownSymbol prefix => ModifyText (DropPrefix prefix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (DropPrefix prefix) -> Text -> Text Source #

KnownSymbol suffix => ModifyText (DropSuffix suffix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (DropSuffix suffix) -> Text -> Text Source #

(ModifyText a, ModifyText b) => ModifyText (a <<< b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (a <<< b) -> Text -> Text Source #

(ModifyText a, ModifyText b) => ModifyText (a >>> b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (a >>> b) -> Text -> Text Source #

data AddPrefix (prefix :: Symbol) Source #

Add a prefix. AddPrefix "foo" will transform "bar" into "foobar".

Instances

Instances details
KnownSymbol prefix => ModifyText (AddPrefix prefix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (AddPrefix prefix) -> Text -> Text Source #

data DropPrefix (prefix :: Symbol) Source #

Drop a prefix. DropPrefix "bar" will transform "foobar" into "foo".

Instances

Instances details
KnownSymbol prefix => ModifyText (DropPrefix prefix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (DropPrefix prefix) -> Text -> Text Source #

data AddSuffix (suffix :: Symbol) Source #

Add a suffix. AddSuffix "bar" will transform "foo" into "foobar".

Instances

Instances details
KnownSymbol suffix => ModifyText (AddSuffix suffix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (AddSuffix suffix) -> Text -> Text Source #

data DropSuffix (suffix :: Symbol) Source #

Drop a suffix. DropSuffix "bar" will transform "foobar" into "foo".

Instances

Instances details
KnownSymbol suffix => ModifyText (DropSuffix suffix) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (DropSuffix suffix) -> Text -> Text Source #

data UpperCase Source #

Convert to UPPERCASE. Will transform "foobar" into "FOOBAR".

Instances

Instances details
ModifyText UpperCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy UpperCase -> Text -> Text Source #

data LowerCase Source #

Convert to lowercase. Will transform "FOOBAR" into "foobar".

Instances

Instances details
ModifyText LowerCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy LowerCase -> Text -> Text Source #

data TitleCase Source #

Convert to Title Case. Will transform "fooBar" into "Foo Bar".

Instances

Instances details
ModifyText TitleCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy TitleCase -> Text -> Text Source #

data CamelCase Source #

Convert to camelCase. Will transform "foo_bar" into "fooBar".

Instances

Instances details
ModifyText CamelCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy CamelCase -> Text -> Text Source #

data PascalCase Source #

Convert to PascalCase. Will transform "foo_bar" into "FooBar".

Instances

Instances details
ModifyText PascalCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy PascalCase -> Text -> Text Source #

data SnakeCase Source #

Convert to snake_case. Will transform "fooBar" into "foo_bar".

Instances

Instances details
ModifyText SnakeCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy SnakeCase -> Text -> Text Source #

data SpinalCase Source #

Convert to spinal-case. will transform "fooBar" into "foo-bar".

Instances

Instances details
ModifyText SpinalCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy SpinalCase -> Text -> Text Source #

data TrainCase Source #

Convert to Train-Case. Will transform "fooBar" into "Foo-Bar".

Instances

Instances details
ModifyText TrainCase Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy TrainCase -> Text -> Text Source #

Composition

type AsIs = () Source #

Identity option.

data a <<< b Source #

Right to left composition.

Requires the TypeOperators extension to be enabled.

Instances

Instances details
(ModifyOptions a, ModifyOptions b) => ModifyOptions (a <<< b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

(ModifyText a, ModifyText b) => ModifyText (a <<< b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (a <<< b) -> Text -> Text Source #

data a >>> b Source #

Left to right composition.

Requires the TypeOperators extension to be enabled.

Instances

Instances details
(ModifyOptions a, ModifyOptions b) => ModifyOptions (a >>> b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

(ModifyText a, ModifyText b) => ModifyText (a >>> b) Source # 
Instance details

Defined in ProjectM36.Tupleable.Deriving

Methods

modifyText :: proxy (a >>> b) -> Text -> Text Source #

Re-Exports

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

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

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 :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: 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 :: Type -> Type #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags :: Type -> Type #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres :: Type -> Type #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile :: Type -> Type #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace :: 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 :: Type -> Type #

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 :: Type -> Type #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags :: Type -> Type #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlags :: Type -> Type #

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 :: Type -> Type #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlags :: Type -> Type #

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 :: Type -> Type #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlags :: Type -> Type #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc :: Type -> Type #

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic GCDetails 
Instance details

Defined in GHC.Stats

Associated Types

type Rep GCDetails :: Type -> Type #

Generic RTSStats 
Instance details

Defined in GHC.Stats

Associated Types

type Rep RTSStats :: Type -> Type #

Methods

from :: RTSStats -> Rep RTSStats x #

to :: Rep RTSStats x -> RTSStats #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory :: Type -> Type #

Generic ConnectionError 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep ConnectionError :: Type -> Type #

Generic Envelope 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep Envelope :: Type -> Type #

Methods

from :: Envelope -> Rep Envelope x #

to :: Rep Envelope x -> Envelope #

Generic MessageType 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep MessageType :: Type -> Type #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Generic ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Associated Types

type Rep ClosureType :: Type -> Type #

Generic PrimType 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimType :: Type -> Type #

Methods

from :: PrimType -> Rep PrimType x #

to :: Rep PrimType x -> PrimType #

Generic TsoFlags 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep TsoFlags :: Type -> Type #

Methods

from :: TsoFlags -> Rep TsoFlags x #

to :: Rep TsoFlags x -> TsoFlags #

Generic WhatNext 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhatNext :: Type -> Type #

Methods

from :: WhatNext -> Rep WhatNext x #

to :: Rep WhatNext x -> WhatNext #

Generic WhyBlocked 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhyBlocked :: Type -> Type #

Generic StgInfoTable 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Associated Types

type Rep StgInfoTable :: Type -> Type #

Generic CostCentre 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentre :: Type -> Type #

Generic CostCentreStack 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentreStack :: Type -> Type #

Generic IndexTable 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep IndexTable :: Type -> Type #

Generic StgTSOProfInfo 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep StgTSOProfInfo :: Type -> Type #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic FFIConv 
Instance details

Defined in GHCi.FFI

Associated Types

type Rep FFIConv :: Type -> Type #

Methods

from :: FFIConv -> Rep FFIConv x #

to :: Rep FFIConv x -> FFIConv #

Generic FFIType 
Instance details

Defined in GHCi.FFI

Associated Types

type Rep FFIType :: Type -> Type #

Methods

from :: FFIType -> Rep FFIType x #

to :: Rep FFIType x -> FFIType #

Generic EvalOpts 
Instance details

Defined in GHCi.Message

Associated Types

type Rep EvalOpts :: Type -> Type #

Methods

from :: EvalOpts -> Rep EvalOpts x #

to :: Rep EvalOpts x -> EvalOpts #

Generic SerializableException 
Instance details

Defined in GHCi.Message

Associated Types

type Rep SerializableException :: Type -> Type #

Generic THResultType 
Instance details

Defined in GHCi.Message

Associated Types

type Rep THResultType :: Type -> Type #

Generic ResolvedBCO 
Instance details

Defined in GHCi.ResolvedBCO

Associated Types

type Rep ResolvedBCO :: Type -> Type #

Generic ResolvedBCOPtr 
Instance details

Defined in GHCi.ResolvedBCO

Associated Types

type Rep ResolvedBCOPtr :: Type -> Type #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: 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 :: Type -> Type #

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 :: Type -> Type #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Generic AtomFunctionError Source # 
Instance details

Defined in ProjectM36.AtomFunctionError

Associated Types

type Rep AtomFunctionError :: Type -> Type #

Generic Atom Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Atom :: Type -> Type #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

Generic AtomType Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep AtomType :: Type -> Type #

Methods

from :: AtomType -> Rep AtomType x #

to :: Rep AtomType x -> AtomType #

Generic Attribute Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Attribute :: Type -> Type #

Generic Attributes Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Attributes :: Type -> Type #

Generic DataConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DataConstructorDef :: Type -> Type #

Generic DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DataConstructorDefArg :: Type -> Type #

Generic DatabaseContext Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DatabaseContext :: Type -> Type #

Generic GraphRefTransactionMarker Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep GraphRefTransactionMarker :: Type -> Type #

Generic InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep InclusionDependency :: Type -> Type #

Generic MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep MergeStrategy :: Type -> Type #

Generic Notification Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Notification :: Type -> Type #

Generic Relation Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Relation :: Type -> Type #

Methods

from :: Relation -> Rep Relation x #

to :: Rep Relation x -> Relation #

Generic RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationCardinality :: Type -> Type #

Generic RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTuple :: Type -> Type #

Generic RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTupleSet :: Type -> Type #

Generic Schema Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Schema :: Type -> Type #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Generic SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep SchemaIsomorph :: Type -> Type #

Generic Schemas Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Schemas :: Type -> Type #

Methods

from :: Schemas -> Rep Schemas x #

to :: Rep Schemas x -> Schemas #

Generic Transaction Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Transaction :: Type -> Type #

Generic TransactionGraph Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TransactionGraph :: Type -> Type #

Generic TransactionInfo Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TransactionInfo :: Type -> Type #

Generic TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TypeConstructorDef :: Type -> Type #

Generic ConnectionError Source # 
Instance details

Defined in ProjectM36.Client

Associated Types

type Rep ConnectionError :: Type -> Type #

Generic EvaluatedNotification Source # 
Instance details

Defined in ProjectM36.Client

Associated Types

type Rep EvaluatedNotification :: Type -> Type #

Generic AttributeOrder Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep AttributeOrder :: Type -> Type #

Generic AttributeOrderExpr Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep AttributeOrderExpr :: Type -> Type #

Generic DataFrame Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrame :: Type -> Type #

Generic DataFrameExpr Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrameExpr :: Type -> Type #

Generic DataFrameTuple Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrameTuple :: Type -> Type #

Generic Order Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep Order :: Type -> Type #

Methods

from :: Order -> Rep Order x #

to :: Rep Order x -> Order #

Generic DatabaseContextFunctionError Source # 
Instance details

Defined in ProjectM36.DatabaseContextFunctionError

Associated Types

type Rep DatabaseContextFunctionError :: Type -> Type #

Generic ImportError' Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep ImportError' :: Type -> Type #

Generic MergeError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep MergeError :: Type -> Type #

Generic PersistenceError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep PersistenceError :: Type -> Type #

Generic RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep RelationalError :: Type -> Type #

Generic SchemaError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep SchemaError :: Type -> Type #

Generic ScriptCompilationError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep ScriptCompilationError :: Type -> Type #

Generic SchemaExpr Source # 
Instance details

Defined in ProjectM36.IsomorphicSchema

Associated Types

type Rep SchemaExpr :: Type -> Type #

Generic MerkleHash Source # 
Instance details

Defined in ProjectM36.MerkleHash

Associated Types

type Rep MerkleHash :: Type -> Type #

Generic CloseSession Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CloseSession :: Type -> Type #

Generic CreateSessionAtCommit Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CreateSessionAtCommit :: Type -> Type #

Generic CreateSessionAtHead Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CreateSessionAtHead :: Type -> Type #

Generic ExecuteAutoMergeToHead Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteAutoMergeToHead :: Type -> Type #

Generic ExecuteDataFrameExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDataFrameExpr :: Type -> Type #

Generic ExecuteDatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDatabaseContextExpr :: Type -> Type #

Generic ExecuteDatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDatabaseContextIOExpr :: Type -> Type #

Generic ExecuteGraphExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteGraphExpr :: Type -> Type #

Generic ExecuteHeadName Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteHeadName :: Type -> Type #

Generic ExecuteRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteRelationalExpr :: Type -> Type #

Generic ExecuteSchemaExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteSchemaExpr :: Type -> Type #

Generic ExecuteSetCurrentSchema Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteSetCurrentSchema :: Type -> Type #

Generic ExecuteTransGraphRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteTransGraphRelationalExpr :: Type -> Type #

Generic ExecuteTypeForRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteTypeForRelationalExpr :: Type -> Type #

Generic ExecuteValidateMerkleHashes Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteValidateMerkleHashes :: Type -> Type #

Generic GetDDLHash Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep GetDDLHash :: Type -> Type #

Generic Login Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep Login :: Type -> Type #

Methods

from :: Login -> Rep Login x #

to :: Rep Login x -> Login #

Generic Logout Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep Logout :: Type -> Type #

Methods

from :: Logout -> Rep Logout x #

to :: Rep Logout x -> Logout #

Generic RetrieveAtomFunctionSummary Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveAtomFunctionSummary :: Type -> Type #

Generic RetrieveAtomTypesAsRelation Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveAtomTypesAsRelation :: Type -> Type #

Generic RetrieveCurrentSchemaName Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveCurrentSchemaName :: Type -> Type #

Generic RetrieveDDLAsRelation Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveDDLAsRelation :: Type -> Type #

Generic RetrieveDatabaseContextFunctionSummary Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Generic RetrieveHeadTransactionId Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveHeadTransactionId :: Type -> Type #

Generic RetrieveInclusionDependencies Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveInclusionDependencies :: Type -> Type #

Generic RetrievePlanForDatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrievePlanForDatabaseContextExpr :: Type -> Type #

Generic RetrieveRegisteredQueries Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveRegisteredQueries :: Type -> Type #

Generic RetrieveRelationVariableSummary Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveRelationVariableSummary :: Type -> Type #

Generic RetrieveSessionIsDirty Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveSessionIsDirty :: Type -> Type #

Generic RetrieveTransactionGraph Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveTransactionGraph :: Type -> Type #

Generic RetrieveTypeConstructorMapping Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveTypeConstructorMapping :: Type -> Type #

Generic TestTimeout Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep TestTimeout :: Type -> Type #

Generic MerkleValidationError Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep MerkleValidationError :: Type -> Type #

Generic TransactionGraphOperator Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionGraphOperator :: Type -> Type #

Generic TransactionIdHeadBacktrack Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionIdHeadBacktrack :: Type -> Type #

Generic TransactionIdLookup Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionIdLookup :: Type -> Type #

Generic Clock 
Instance details

Defined in Streamly.Internal.Data.Time.Clock.Type

Associated Types

type Rep Clock :: Type -> Type #

Methods

from :: Clock -> Rep Clock x #

to :: Rep Clock x -> Clock #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type #

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 :: Type -> Type #

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 :: 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 :: Type -> Type #

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 :: Type -> 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 :: Type -> Type #

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 :: Type -> Type #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLoc :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

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 :: Type -> Type #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> 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 :: Type -> Type #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: 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 :: Type -> Type #

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 :: Type -> Type #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type #

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 :: 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 :: Type -> Type #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type #

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 :: Type -> Type #

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 :: Type -> Type #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type #

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 :: 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 :: Type -> Type #

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 :: Type -> Type #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: 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 :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type #

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 :: Type -> Type #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type #

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 :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type #

Generic Tag 
Instance details

Defined in Codec.Winery.Base

Associated Types

type Rep Tag :: Type -> Type #

Methods

from :: Tag -> Rep Tag x #

to :: Rep Tag x -> Tag #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

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

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

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

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

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

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

Methods

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

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

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

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) :: Type -> Type #

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

Associated Types

type Rep (Digit a) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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

Associated Types

type Rep (Node a) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

Methods

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

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

Generic (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

type Rep (Fix f) :: Type -> Type #

Methods

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

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

Generic (SizedSeq a) 
Instance details

Defined in GHC.Data.SizedSeq

Associated Types

type Rep (SizedSeq a) :: Type -> Type #

Methods

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

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

Generic (GenClosure b) 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep (GenClosure b) :: Type -> Type #

Methods

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

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

Generic (EvalExpr a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalExpr a) :: Type -> Type #

Methods

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

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

Generic (EvalResult a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalResult a) :: Type -> Type #

Methods

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

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

Generic (QResult a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (QResult a) :: Type -> Type #

Methods

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

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

Generic (THResult a) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (THResult a) :: Type -> Type #

Methods

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

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

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) :: Type -> Type #

Methods

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

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

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type #

Methods

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

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

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (SimpleDocStream ann) :: Type -> Type #

Methods

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

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

Generic (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (AtomExprBase a) :: Type -> Type #

Methods

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

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

Generic (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (AttributeExprBase a) :: Type -> Type #

Generic (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (AttributeNamesBase a) :: Type -> Type #

Generic (DatabaseContextExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (DatabaseContextExprBase a) :: Type -> Type #

Generic (DatabaseContextIOExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (DatabaseContextIOExprBase a) :: Type -> Type #

Generic (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (ExtendTupleExprBase a) :: Type -> Type #

Generic (Function a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (Function a) :: Type -> Type #

Methods

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

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

Generic (FunctionBody a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (FunctionBody a) :: Type -> Type #

Methods

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

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

Generic (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (RelationalExprBase a) :: Type -> Type #

Generic (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (RestrictionPredicateExprBase a) :: Type -> Type #

Generic (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (TupleExprBase a) :: Type -> Type #

Generic (TupleExprsBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (TupleExprsBase a) :: Type -> Type #

Generic (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (TypeConstructorBase a) :: Type -> Type #

Generic (WithNameExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep (WithNameExprBase a) :: Type -> Type #

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

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

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

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep (TyVarBndr flag) :: Type -> Type #

Methods

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

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

Generic (SingleField a) 
Instance details

Defined in Codec.Winery

Associated Types

type Rep (SingleField a) :: Type -> Type #

Methods

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

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

Generic (SchemaP a) 
Instance details

Defined in Codec.Winery.Base

Associated Types

type Rep (SchemaP a) :: Type -> Type #

Methods

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

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

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

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

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

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

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

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

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a) :: Type -> Type #

Methods

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

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

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Container b a) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (Container b a) :: Type -> Type #

Methods

from :: Container b a -> Rep (Container b a) x #

to :: Rep (Container b a) x -> Container b a #

Generic (ErrorContainer b e) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (ErrorContainer b e) :: Type -> Type #

Methods

from :: ErrorContainer b e -> Rep (ErrorContainer b e) x #

to :: Rep (ErrorContainer b e) x -> ErrorContainer b e #

Generic (Unit f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Unit f) :: Type -> Type #

Methods

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

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

Generic (Void f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Void f) :: Type -> Type #

Methods

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

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

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: Type -> Type #

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) :: Type -> Type #

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) :: 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) :: Type -> Type #

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) :: 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) :: Type -> Type #

Methods

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

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

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) :: Type -> Type #

Methods

from :: Cofree f a -> Rep (Cofree f a) x #

to :: Rep (Cofree f a) x -> Cofree f a #

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) :: Type -> Type #

Methods

from :: Free f a -> Rep (Free f a) x #

to :: Rep (Free f a) x -> Free f a #

Generic (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Associated Types

type Rep (EvalStatus_ a b) :: Type -> Type #

Methods

from :: EvalStatus_ a b -> Rep (EvalStatus_ a b) x #

to :: Rep (EvalStatus_ a b) x -> EvalStatus_ a b #

Generic (ListT m a) 
Instance details

Defined in ListT

Associated Types

type Rep (ListT m a) :: Type -> Type #

Methods

from :: ListT m a -> Rep (ListT m a) x #

to :: Rep (ListT m a) x -> ListT m a #

Generic (ListF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (ListF a b) :: Type -> Type #

Methods

from :: ListF a b -> Rep (ListF a b) x #

to :: Rep (ListF a b) x -> ListF a b #

Generic (NonEmptyF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (NonEmptyF a b) :: Type -> Type #

Methods

from :: NonEmptyF a b -> Rep (NonEmptyF a b) x #

to :: Rep (NonEmptyF a b) x -> NonEmptyF a b #

Generic (TreeF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (TreeF a b) :: Type -> Type #

Methods

from :: TreeF a b -> Rep (TreeF a b) x #

to :: Rep (TreeF a b) x -> TreeF a b #

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

type Rep (These a b) :: Type -> Type #

Methods

from :: These a b -> Rep (These a b) x #

to :: Rep (These a b) x -> These a b #

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep (Pair a b) :: Type -> Type #

Methods

from :: Pair a b -> Rep (Pair a b) x #

to :: Rep (Pair a b) x -> Pair a b #

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

type Rep (These a b) :: Type -> Type #

Methods

from :: These a b -> Rep (These a b) x #

to :: Rep (These a b) x -> These a b #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: 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) :: 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) :: 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) :: 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) :: 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) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) :: Type -> Type #

Methods

from :: Join p a -> Rep (Join p a) x #

to :: Rep (Join p a) x -> Join p a #

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep (CofreeF f a b) :: Type -> Type #

Methods

from :: CofreeF f a b -> Rep (CofreeF f a b) x #

to :: Rep (CofreeF f a b) x -> CofreeF f a b #

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

type Rep (FreeF f a b) :: Type -> Type #

Methods

from :: FreeF f a b -> Rep (FreeF f a b) x #

to :: Rep (FreeF f a b) x -> FreeF f a b #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) :: Type -> Type #

Methods

from :: Tagged s b -> Rep (Tagged s b) x #

to :: Rep (Tagged s b) x -> Tagged s b #

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

type Rep (These1 f g a) :: Type -> Type #

Methods

from :: These1 f g a -> Rep (These1 f g a) x #

to :: Rep (These1 f g a) x -> These1 f g a #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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 (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) :: Type -> Type #

Methods

from :: Clown f a b -> Rep (Clown f a b) x #

to :: Rep (Clown f a b) x -> Clown f a b #

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) :: Type -> Type #

Methods

from :: Flip p a b -> Rep (Flip p a b) x #

to :: Rep (Flip p a b) x -> Flip p a b #

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) :: Type -> Type #

Methods

from :: Joker g a b -> Rep (Joker g a b) x #

to :: Rep (Joker g a b) x -> Joker g a b #

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) :: Type -> Type #

Methods

from :: WrappedBifunctor p a b -> Rep (WrappedBifunctor p a b) x #

to :: Rep (WrappedBifunctor p a b) x -> WrappedBifunctor p a b #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

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 (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) :: Type -> Type #

Methods

from :: Product f g a b -> Rep (Product f g a b) x #

to :: Rep (Product f g a b) x -> Product f g a b #

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) :: Type -> Type #

Methods

from :: Sum p q a b -> Rep (Sum p q a b) x #

to :: Rep (Sum p q a b) x -> Sum p q a b #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

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 (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) :: Type -> Type #

Methods

from :: Tannen f p a b -> Rep (Tannen f p a b) x #

to :: Rep (Tannen f p a b) x -> Tannen f p a b #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

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

Associated Types

type Rep (a, b, c, d, e, f, g, h) :: Type -> Type #

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 (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) :: Type -> Type #

Methods

from :: Biff p f g a b -> Rep (Biff p f g a b) x #

to :: Rep (Biff p f g a b) x -> Biff p f g a b #

Generic (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i) :: Type -> Type #

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

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type #

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

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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