project-m36-0.9.9: 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 Source #

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

Methods

from :: Value -> Rep Value x Source #

to :: Rep Value x -> Value Source #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type Source #

Methods

from :: All -> Rep All x Source #

to :: Rep All x -> All Source #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type Source #

Methods

from :: Any -> Rep Any x Source #

to :: Rep Any x -> Any Source #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type Source #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type Source #

Methods

from :: Void -> Rep Void x Source #

to :: Rep Void x -> Void Source #

Generic ByteOrder 
Instance details

Defined in GHC.ByteOrder

Associated Types

type Rep ByteOrder :: Type -> Type Source #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type Source #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type Source #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type Source #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlags :: Type -> Type Source #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlags :: Type -> Type Source #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags :: Type -> Type Source #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres :: Type -> Type Source #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile :: Type -> Type Source #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace :: Type -> Type Source #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlags :: Type -> Type Source #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStats :: Type -> Type Source #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags :: Type -> Type Source #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlags :: Type -> Type Source #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlags :: Type -> Type Source #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlags :: Type -> Type Source #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlags :: Type -> Type Source #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlags :: Type -> Type Source #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc :: Type -> Type Source #

Generic GCDetails 
Instance details

Defined in GHC.Stats

Associated Types

type Rep GCDetails :: Type -> Type Source #

Generic RTSStats 
Instance details

Defined in GHC.Stats

Associated Types

type Rep RTSStats :: Type -> Type Source #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory :: Type -> Type Source #

Generic ConnectionError 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep ConnectionError :: Type -> Type Source #

Generic Envelope 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep Envelope :: Type -> Type Source #

Generic MessageType 
Instance details

Defined in Network.RPC.Curryer.Server

Associated Types

type Rep MessageType :: Type -> Type Source #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type Source #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type Source #

Generic ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Associated Types

type Rep ClosureType :: Type -> Type Source #

Generic PrimType 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimType :: Type -> Type Source #

Generic TsoFlags 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep TsoFlags :: Type -> Type Source #

Generic WhatNext 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhatNext :: Type -> Type Source #

Generic WhyBlocked 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhyBlocked :: Type -> Type Source #

Generic StgInfoTable 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Associated Types

type Rep StgInfoTable :: Type -> Type Source #

Generic CostCentre 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentre :: Type -> Type Source #

Generic CostCentreStack 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentreStack :: Type -> Type Source #

Generic IndexTable 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep IndexTable :: Type -> Type Source #

Generic StgTSOProfInfo 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep StgTSOProfInfo :: Type -> Type Source #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type Source #

Generic FFIConv 
Instance details

Defined in GHCi.FFI

Associated Types

type Rep FFIConv :: Type -> Type Source #

Generic FFIType 
Instance details

Defined in GHCi.FFI

Associated Types

type Rep FFIType :: Type -> Type Source #

Generic EvalOpts 
Instance details

Defined in GHCi.Message

Associated Types

type Rep EvalOpts :: Type -> Type Source #

Generic SerializableException 
Instance details

Defined in GHCi.Message

Associated Types

type Rep SerializableException :: Type -> Type Source #

Generic THResultType 
Instance details

Defined in GHCi.Message

Associated Types

type Rep THResultType :: Type -> Type Source #

Generic ResolvedBCO 
Instance details

Defined in GHCi.ResolvedBCO

Associated Types

type Rep ResolvedBCO :: Type -> Type Source #

Generic ResolvedBCOPtr 
Instance details

Defined in GHCi.ResolvedBCO

Associated Types

type Rep ResolvedBCOPtr :: Type -> Type Source #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI :: Type -> Type Source #

Methods

from :: URI -> Rep URI x Source #

to :: Rep URI x -> URI Source #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth :: Type -> Type Source #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type Source #

Methods

from :: Mode -> Rep Mode x Source #

to :: Rep Mode x -> Mode Source #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type Source #

Methods

from :: Style -> Rep Style x Source #

to :: Rep Style x -> Style Source #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetails :: Type -> Type Source #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type Source #

Methods

from :: Doc -> Rep Doc x Source #

to :: Rep Doc x -> Doc Source #

Generic AtomFunctionError Source # 
Instance details

Defined in ProjectM36.AtomFunctionError

Associated Types

type Rep AtomFunctionError :: Type -> Type Source #

Generic Atom Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Atom :: Type -> Type Source #

Methods

from :: Atom -> Rep Atom x Source #

to :: Rep Atom x -> Atom Source #

Generic AtomType Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep AtomType :: Type -> Type Source #

Generic Attribute Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Attribute :: Type -> Type Source #

Generic Attributes Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Attributes :: Type -> Type Source #

Generic DataConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DataConstructorDef :: Type -> Type Source #

Generic DataConstructorDefArg Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DataConstructorDefArg :: Type -> Type Source #

Generic DatabaseContext Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep DatabaseContext :: Type -> Type Source #

Generic GraphRefTransactionMarker Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep GraphRefTransactionMarker :: Type -> Type Source #

Generic InclusionDependency Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep InclusionDependency :: Type -> Type Source #

Generic MergeStrategy Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep MergeStrategy :: Type -> Type Source #

Generic Notification Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Notification :: Type -> Type Source #

Generic Relation Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Relation :: Type -> Type Source #

Generic RelationCardinality Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationCardinality :: Type -> Type Source #

Generic RelationTuple Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTuple :: Type -> Type Source #

Generic RelationTupleSet Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep RelationTupleSet :: Type -> Type Source #

Generic Schema Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Schema :: Type -> Type Source #

Generic SchemaIsomorph Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep SchemaIsomorph :: Type -> Type Source #

Generic Schemas Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Schemas :: Type -> Type Source #

Generic Transaction Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep Transaction :: Type -> Type Source #

Generic TransactionGraph Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TransactionGraph :: Type -> Type Source #

Generic TransactionInfo Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TransactionInfo :: Type -> Type Source #

Generic TypeConstructorDef Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

type Rep TypeConstructorDef :: Type -> Type Source #

Generic ConnectionError Source # 
Instance details

Defined in ProjectM36.Client

Associated Types

type Rep ConnectionError :: Type -> Type Source #

Generic EvaluatedNotification Source # 
Instance details

Defined in ProjectM36.Client

Associated Types

type Rep EvaluatedNotification :: Type -> Type Source #

Generic AttributeOrder Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep AttributeOrder :: Type -> Type Source #

Generic AttributeOrderExpr Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep AttributeOrderExpr :: Type -> Type Source #

Generic DataFrame Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrame :: Type -> Type Source #

Generic DataFrameExpr Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrameExpr :: Type -> Type Source #

Generic DataFrameTuple Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep DataFrameTuple :: Type -> Type Source #

Generic Order Source # 
Instance details

Defined in ProjectM36.DataFrame

Associated Types

type Rep Order :: Type -> Type Source #

Methods

from :: Order -> Rep Order x Source #

to :: Rep Order x -> Order Source #

Generic DatabaseContextFunctionError Source # 
Instance details

Defined in ProjectM36.DatabaseContextFunctionError

Associated Types

type Rep DatabaseContextFunctionError :: Type -> Type Source #

Generic ImportError' Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep ImportError' :: Type -> Type Source #

Generic MergeError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep MergeError :: Type -> Type Source #

Generic PersistenceError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep PersistenceError :: Type -> Type Source #

Generic RelationalError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep RelationalError :: Type -> Type Source #

Generic SchemaError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep SchemaError :: Type -> Type Source #

Generic ScriptCompilationError Source # 
Instance details

Defined in ProjectM36.Error

Associated Types

type Rep ScriptCompilationError :: Type -> Type Source #

Generic SchemaExpr Source # 
Instance details

Defined in ProjectM36.IsomorphicSchema

Associated Types

type Rep SchemaExpr :: Type -> Type Source #

Generic MerkleHash Source # 
Instance details

Defined in ProjectM36.MerkleHash

Associated Types

type Rep MerkleHash :: Type -> Type Source #

Generic CloseSession Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CloseSession :: Type -> Type Source #

Generic CreateSessionAtCommit Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CreateSessionAtCommit :: Type -> Type Source #

Generic CreateSessionAtHead Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep CreateSessionAtHead :: Type -> Type Source #

Generic ExecuteAutoMergeToHead Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteAutoMergeToHead :: Type -> Type Source #

Generic ExecuteDataFrameExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDataFrameExpr :: Type -> Type Source #

Generic ExecuteDatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDatabaseContextExpr :: Type -> Type Source #

Generic ExecuteDatabaseContextIOExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteDatabaseContextIOExpr :: Type -> Type Source #

Generic ExecuteGraphExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteGraphExpr :: Type -> Type Source #

Generic ExecuteHeadName Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteHeadName :: Type -> Type Source #

Generic ExecuteRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteRelationalExpr :: Type -> Type Source #

Generic ExecuteSchemaExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteSchemaExpr :: Type -> Type Source #

Generic ExecuteSetCurrentSchema Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteSetCurrentSchema :: Type -> Type Source #

Generic ExecuteTransGraphRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Generic ExecuteTypeForRelationalExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteTypeForRelationalExpr :: Type -> Type Source #

Generic ExecuteValidateMerkleHashes Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep ExecuteValidateMerkleHashes :: Type -> Type Source #

Generic GetDDLHash Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep GetDDLHash :: Type -> Type Source #

Generic Login Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep Login :: Type -> Type Source #

Methods

from :: Login -> Rep Login x Source #

to :: Rep Login x -> Login Source #

Generic Logout Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep Logout :: Type -> Type Source #

Generic RetrieveAtomFunctionSummary Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveAtomFunctionSummary :: Type -> Type Source #

Generic RetrieveAtomTypesAsRelation Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveAtomTypesAsRelation :: Type -> Type Source #

Generic RetrieveCurrentSchemaName Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveCurrentSchemaName :: Type -> Type Source #

Generic RetrieveDDLAsRelation Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveDDLAsRelation :: Type -> Type Source #

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

Generic RetrieveInclusionDependencies Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveInclusionDependencies :: Type -> Type Source #

Generic RetrievePlanForDatabaseContextExpr Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Generic RetrieveRegisteredQueries Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveRegisteredQueries :: Type -> Type Source #

Generic RetrieveRelationVariableSummary Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Generic RetrieveSessionIsDirty Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveSessionIsDirty :: Type -> Type Source #

Generic RetrieveTransactionGraph Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveTransactionGraph :: Type -> Type Source #

Generic RetrieveTypeConstructorMapping Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep RetrieveTypeConstructorMapping :: Type -> Type Source #

Generic TestTimeout Source # 
Instance details

Defined in ProjectM36.Server.RemoteCallTypes

Associated Types

type Rep TestTimeout :: Type -> Type Source #

Generic MerkleValidationError Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep MerkleValidationError :: Type -> Type Source #

Generic TransactionGraphOperator Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionGraphOperator :: Type -> Type Source #

Generic TransactionIdHeadBacktrack Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionIdHeadBacktrack :: Type -> Type Source #

Generic TransactionIdLookup Source # 
Instance details

Defined in ProjectM36.TransactionGraph

Associated Types

type Rep TransactionIdLookup :: Type -> Type Source #

Generic Clock 
Instance details

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

Associated Types

type Rep Clock :: Type -> Type Source #

Methods

from :: Clock -> Rep Clock x Source #

to :: Rep Clock x -> Clock Source #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type Source #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type Source #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type Source #

Methods

from :: Bang -> Rep Bang x Source #

to :: Rep Bang x -> Bang Source #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type Source #

Methods

from :: Body -> Rep Body x Source #

to :: Rep Body x -> Body Source #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type Source #

Methods

from :: Bytes -> Rep Bytes x Source #

to :: Rep Bytes x -> Bytes Source #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type Source #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type Source #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type Source #

Methods

from :: Con -> Rep Con x Source #

to :: Rep Con x -> Con Source #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type Source #

Methods

from :: Dec -> Rep Dec x Source #

to :: Rep Dec x -> Dec Source #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type Source #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type Source #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type Source #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLoc :: Type -> Type Source #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type Source #

Methods

from :: Exp -> Rep Exp x Source #

to :: Rep Exp x -> Exp Source #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type Source #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type Source #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: Type -> Type Source #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type Source #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type Source #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type Source #

Methods

from :: Guard -> Rep Guard x Source #

to :: Rep Guard x -> Guard Source #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type Source #

Methods

from :: Info -> Rep Info x Source #

to :: Rep Info x -> Info Source #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type Source #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type Source #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type Source #

Methods

from :: Lit -> Rep Lit x Source #

to :: Rep Lit x -> Lit Source #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type Source #

Methods

from :: Loc -> Rep Loc x Source #

to :: Rep Loc x -> Loc Source #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type Source #

Methods

from :: Match -> Rep Match x Source #

to :: Rep Match x -> Match Source #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type Source #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type Source #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type Source #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type Source #

Methods

from :: Name -> Rep Name x Source #

to :: Rep Name x -> Name Source #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type Source #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type Source #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type Source #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type Source #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type Source #

Methods

from :: Pat -> Rep Pat x Source #

to :: Rep Pat x -> Pat Source #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type Source #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type Source #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type Source #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type Source #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type Source #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type Source #

Methods

from :: Range -> Rep Range x Source #

to :: Rep Range x -> Range Source #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type Source #

Methods

from :: Role -> Rep Role x Source #

to :: Rep Role x -> Role Source #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type Source #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type Source #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type Source #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type Source #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type Source #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type Source #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type Source #

Methods

from :: Stmt -> Rep Stmt x Source #

to :: Rep Stmt x -> Stmt Source #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type Source #

Methods

from :: TyLit -> Rep TyLit x Source #

to :: Rep TyLit x -> TyLit Source #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type Source #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type Source #

Methods

from :: Type -> Rep Type x Source #

to :: Rep Type x -> Type Source #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type Source #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type Source #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type Source #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type Source #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type Source #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type Source #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type Source #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type Source #

Generic Tag 
Instance details

Defined in Codec.Winery.Base

Associated Types

type Rep Tag :: Type -> Type Source #

Methods

from :: Tag -> Rep Tag x Source #

to :: Rep Tag x -> Tag Source #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type Source #

Methods

from :: Bool -> Rep Bool x Source #

to :: Rep Bool x -> Bool Source #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

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

Methods

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

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

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

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

Methods

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

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

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

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

Methods

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

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

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

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

Methods

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

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

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: Type -> Type Source #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (SCC vertex) 
Instance details

Defined in Data.Graph

Associated Types

type Rep (SCC vertex) :: Type -> Type Source #

Methods

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

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

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

Methods

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

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

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

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

Methods

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

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

Generic (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

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

Methods

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

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

Generic (SizedSeq a) 
Instance details

Defined in GHC.Data.SizedSeq

Associated Types

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

Methods

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

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

Generic (GenClosure b) 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

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

Methods

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

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

Generic (EvalExpr a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Generic (EvalResult a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Generic (QResult a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Generic (THResult a) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

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

Methods

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

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

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

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

Methods

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

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

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

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

Generic (AtomExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (AttributeExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (AttributeNamesBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (DatabaseContextExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (DatabaseContextIOExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (ExtendTupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (Function a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Methods

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

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

Generic (FunctionBody a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (RelationalExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (RestrictionPredicateExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (TupleExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (TupleExprsBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (TypeConstructorBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (WithNameExprBase a) Source # 
Instance details

Defined in ProjectM36.Base

Associated Types

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

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

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

Methods

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

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

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

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

Methods

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

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

Generic (SingleField a) 
Instance details

Defined in Codec.Winery

Associated Types

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

Generic (SchemaP a) 
Instance details

Defined in Codec.Winery.Base

Associated Types

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

Methods

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

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

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Container b a) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

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

Methods

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

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

Generic (ErrorContainer b e) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

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

Generic (Unit f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

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

Methods

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

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

Generic (Void f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

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

Methods

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

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

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x Source #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a Source #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type Source #

Methods

from :: Proxy t -> Rep (Proxy t) x Source #

to :: Rep (Proxy t) x -> Proxy t Source #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: Type -> Type Source #

Methods

from :: Arg a b -> Rep (Arg a b) x Source #

to :: Rep (Arg a b) x -> Arg a b Source #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type Source #

Methods

from :: U1 p -> Rep (U1 p) x Source #

to :: Rep (U1 p) x -> U1 p Source #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type Source #

Methods

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

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

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

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

Methods

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

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

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

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

Methods

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

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

Generic (EvalStatus_ a b) 
Instance details

Defined in GHCi.Message

Associated Types

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

Methods

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

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

Generic (ListT m a) 
Instance details

Defined in ListT

Associated Types

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

Methods

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

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

Generic (ListF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

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

Methods

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

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

Generic (NonEmptyF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

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

Methods

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

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

Generic (TreeF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

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

Methods

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

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

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

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

Methods

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

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

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

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

Methods

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

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

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

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

Methods

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

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

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

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

Methods

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

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

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

from :: (a, b) -> Rep (a, b) x Source #

to :: Rep (a, b) x -> (a, b) Source #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x Source #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c Source #

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type Source #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x Source #

to :: Rep (Kleisli m a b) x -> Kleisli m a b Source #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: Type -> Type Source #

Methods

from :: Const a b -> Rep (Const a b) x Source #

to :: Rep (Const a b) x -> Const a b Source #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type Source #

Methods

from :: Ap f a -> Rep (Ap f a) x Source #

to :: Rep (Ap f a) x -> Ap f a Source #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type Source #

Methods

from :: Alt f a -> Rep (Alt f a) x Source #

to :: Rep (Alt f a) x -> Alt f a Source #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type Source #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x Source #

to :: Rep (Rec1 f p) x -> Rec1 f p Source #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type Source #

Methods

from :: URec Char p -> Rep (URec Char p) x Source #

to :: Rep (URec Char p) x -> URec Char p Source #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type Source #

Methods

from :: URec Double p -> Rep (URec Double p) x Source #

to :: Rep (URec Double p) x -> URec Double p Source #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type Source #

Methods

from :: URec Float p -> Rep (URec Float p) x Source #

to :: Rep (URec Float p) x -> URec Float p Source #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type Source #

Methods

from :: URec Int p -> Rep (URec Int p) x Source #

to :: Rep (URec Int p) x -> URec Int p Source #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type Source #

Methods

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

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

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

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

Methods

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

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

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

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

Methods

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

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

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

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

Methods

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

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

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

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

Methods

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

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

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

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

Methods

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

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

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

from :: (a, b, c) -> Rep (a, b, c) x Source #

to :: Rep (a, b, c) x -> (a, b, c) Source #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

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

Methods

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

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

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

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

Methods

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

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

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type Source #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x Source #

to :: Rep ((f :*: g) p) x -> (f :*: g) p Source #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type Source #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x Source #

to :: Rep ((f :+: g) p) x -> (f :+: g) p Source #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type Source #

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x Source #

to :: Rep (a, b, c, d) x -> (a, b, c, d) Source #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

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

Methods

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

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

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type Source #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x Source #

to :: Rep ((f :.: g) p) x -> (f :.: g) p Source #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type Source #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x Source #

to :: Rep (M1 i c f p) x -> M1 i c f p Source #

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

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

Methods

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

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

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

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

Methods

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

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

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

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

Methods

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

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

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x Source #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) Source #

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

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

Methods

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

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

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

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

Methods

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

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

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

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x Source #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) Source #

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

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

Methods

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

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

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

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x Source #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) Source #

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

Methods

from :: (a, b, c, d, e, f, g, h) -> Rep (a, b, c, d, e, f, g, h) x Source #

to :: Rep (a, b, c, d, e, f, g, h) x -> (a, b, c, d, e, f, g, h) Source #

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

Methods

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

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

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

Methods

from :: (a, b, c, d, e, f, g, h, i) -> Rep (a, b, c, d, e, f, g, h, i) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i) x -> (a, b, c, d, e, f, g, h, i) Source #

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

Methods

from :: (a, b, c, d, e, f, g, h, i, j) -> Rep (a, b, c, d, e, f, g, h, i, j) x Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j) x -> (a, b, c, d, e, f, g, h, i, j) Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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