generics-sop-0.4.0.1: Generic Programming using True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.Universe

Description

Codes and interpretations

Synopsis

Documentation

type Rep a = SOP I (Code a) Source #

The (generic) representation of a datatype.

A datatype is isomorphic to the sum-of-products of its code. The isomorphism is witnessed by from and to from the Generic class.

class All SListI (Code a) => Generic (a :: Type) where Source #

The class of representable datatypes.

The SOP approach to generic programming is based on viewing datatypes as a representation (Rep) built from the sum of products of its components. The components of are datatype are specified using the Code type family.

The isomorphism between the original Haskell datatype and its representation is witnessed by the methods of this class, from and to. So for instances of this class, the following laws should (in general) hold:

to . from === id :: a -> a
from . to === id :: Rep a -> Rep a

You typically don't define instances of this class by hand, but rather derive the class instance automatically.

Option 1: Derive via the built-in GHC-generics. For this, you need to use the DeriveGeneric extension to first derive an instance of the Generic class from module GHC.Generics. With this, you can then give an empty instance for Generic, and the default definitions will just work. The pattern looks as follows:

import qualified GHC.Generics as GHC
import Generics.SOP

...

data T = ... deriving (GHC.Generic, ...)

instance Generic T -- empty
instance HasDatatypeInfo T -- empty, if you want/need metadata

Option 2: Derive via Template Haskell. For this, you need to enable the TemplateHaskell extension. You can then use deriveGeneric from module Generics.SOP.TH to have the instance generated for you. The pattern looks as follows:

import Generics.SOP
import Generics.SOP.TH

...

data T = ...

deriveGeneric ''T -- derives HasDatatypeInfo as well

Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.

Non-standard instances: It is possible to give Generic instances manually that deviate from the standard scheme, as long as at least

to . from === id :: a -> a

still holds.

Associated Types

type Code a :: [[Type]] Source #

The code of a datatype.

This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).

Example: The datatype

data Tree = Leaf Int | Node Tree Tree

is supposed to have the following code:

type instance Code (Tree a) =
  '[ '[ Int ]
   , '[ Tree, Tree ]
   ]

Methods

from :: a -> Rep a Source #

Converts from a value to its structural representation.

from :: (GFrom a, Generic a, Rep a ~ SOP I (GCode a)) => a -> Rep a Source #

Converts from a value to its structural representation.

to :: Rep a -> a Source #

Converts from a structural representation back to the original value.

to :: (GTo a, Generic a, Rep a ~ SOP I (GCode a)) => Rep a -> a Source #

Converts from a structural representation back to the original value.

Instances
Generic Bool Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Bool :: [[Type]] Source #

Methods

from :: Bool -> Rep Bool Source #

to :: Rep Bool -> Bool Source #

Generic Ordering Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Ordering :: [[Type]] Source #

Generic RuntimeRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RuntimeRep :: [[Type]] Source #

Generic VecCount Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code VecCount :: [[Type]] Source #

Generic VecElem Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code VecElem :: [[Type]] Source #

Generic R Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code R :: [[Type]] Source #

Methods

from :: R -> Rep R Source #

to :: Rep R -> R Source #

Generic D Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code D :: [[Type]] Source #

Methods

from :: D -> Rep D Source #

to :: Rep D -> D Source #

Generic C Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code C :: [[Type]] Source #

Methods

from :: C -> Rep C Source #

to :: Rep C -> C Source #

Generic S Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code S :: [[Type]] Source #

Methods

from :: S -> Rep S Source #

to :: Rep S -> S Source #

Generic CallStack Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CallStack :: [[Type]] Source #

Generic () Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code () :: [[Type]] Source #

Methods

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

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

Generic FFFormat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FFFormat :: [[Type]] Source #

Methods

from :: FFFormat -> Rep FFFormat Source #

to :: Rep FFFormat -> FFFormat Source #

Generic E0 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E0 :: [[Type]] Source #

Methods

from :: E0 -> Rep E0 Source #

to :: Rep E0 -> E0 Source #

Generic E1 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E1 :: [[Type]] Source #

Methods

from :: E1 -> Rep E1 Source #

to :: Rep E1 -> E1 Source #

Generic E2 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E2 :: [[Type]] Source #

Methods

from :: E2 -> Rep E2 Source #

to :: Rep E2 -> E2 Source #

Generic E3 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E3 :: [[Type]] Source #

Methods

from :: E3 -> Rep E3 Source #

to :: Rep E3 -> E3 Source #

Generic E6 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E6 :: [[Type]] Source #

Methods

from :: E6 -> Rep E6 Source #

to :: Rep E6 -> E6 Source #

Generic E9 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E9 :: [[Type]] Source #

Methods

from :: E9 -> Rep E9 Source #

to :: Rep E9 -> E9 Source #

Generic E12 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code E12 :: [[Type]] Source #

Methods

from :: E12 -> Rep E12 Source #

to :: Rep E12 -> E12 Source #

Generic Void Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Void :: [[Type]] Source #

Methods

from :: Void -> Rep Void Source #

to :: Rep Void -> Void Source #

Generic StaticPtrInfo Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code StaticPtrInfo :: [[Type]] Source #

Generic SpecConstrAnnotation Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SpecConstrAnnotation :: [[Type]] Source #

Generic DataRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DataRep :: [[Type]] Source #

Generic ConstrRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ConstrRep :: [[Type]] Source #

Generic Fixity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Fixity :: [[Type]] Source #

Generic SrcLoc Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SrcLoc :: [[Type]] Source #

Generic Location Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Location :: [[Type]] Source #

Generic GiveGCStats Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code GiveGCStats :: [[Type]] Source #

Generic GCFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code GCFlags :: [[Type]] Source #

Generic ConcFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ConcFlags :: [[Type]] Source #

Generic MiscFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code MiscFlags :: [[Type]] Source #

Generic DebugFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DebugFlags :: [[Type]] Source #

Generic DoCostCentres Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DoCostCentres :: [[Type]] Source #

Generic CCFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CCFlags :: [[Type]] Source #

Generic DoHeapProfile Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DoHeapProfile :: [[Type]] Source #

Generic ProfFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ProfFlags :: [[Type]] Source #

Generic DoTrace Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DoTrace :: [[Type]] Source #

Generic TraceFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code TraceFlags :: [[Type]] Source #

Generic TickyFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code TickyFlags :: [[Type]] Source #

Generic ParFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ParFlags :: [[Type]] Source #

Generic RTSFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RTSFlags :: [[Type]] Source #

Generic RTSStats Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RTSStats :: [[Type]] Source #

Generic GCDetails Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code GCDetails :: [[Type]] Source #

Generic ByteOrder Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ByteOrder :: [[Type]] Source #

Generic FormatAdjustment Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FormatAdjustment :: [[Type]] Source #

Generic FormatSign Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FormatSign :: [[Type]] Source #

Generic FieldFormat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FieldFormat :: [[Type]] Source #

Generic FormatParse Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FormatParse :: [[Type]] Source #

Generic Version Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Version :: [[Type]] Source #

Generic HandlePosn Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code HandlePosn :: [[Type]] Source #

Generic LockMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code LockMode :: [[Type]] Source #

Generic PatternMatchFail Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code PatternMatchFail :: [[Type]] Source #

Generic RecSelError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RecSelError :: [[Type]] Source #

Generic RecConError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RecConError :: [[Type]] Source #

Generic RecUpdError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code RecUpdError :: [[Type]] Source #

Generic NoMethodError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code NoMethodError :: [[Type]] Source #

Generic TypeError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code TypeError :: [[Type]] Source #

Generic NonTermination Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code NonTermination :: [[Type]] Source #

Generic NestedAtomically Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code NestedAtomically :: [[Type]] Source #

Generic BlockReason Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code BlockReason :: [[Type]] Source #

Generic ThreadStatus Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ThreadStatus :: [[Type]] Source #

Generic Errno Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Errno :: [[Type]] Source #

Generic CodingFailureMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CodingFailureMode :: [[Type]] Source #

Generic BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code BlockedIndefinitelyOnMVar :: [[Type]] Source #

Generic BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code BlockedIndefinitelyOnSTM :: [[Type]] Source #

Generic Deadlock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Deadlock :: [[Type]] Source #

Generic AllocationLimitExceeded Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code AllocationLimitExceeded :: [[Type]] Source #

Generic AssertionFailed Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code AssertionFailed :: [[Type]] Source #

Generic AsyncException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code AsyncException :: [[Type]] Source #

Generic ArrayException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ArrayException :: [[Type]] Source #

Generic FixIOException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FixIOException :: [[Type]] Source #

Generic ExitCode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ExitCode :: [[Type]] Source #

Generic IOErrorType Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code IOErrorType :: [[Type]] Source #

Generic BufferMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code BufferMode :: [[Type]] Source #

Generic Newline Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Newline :: [[Type]] Source #

Generic NewlineMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code NewlineMode :: [[Type]] Source #

Generic IODeviceType Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code IODeviceType :: [[Type]] Source #

Generic SeekMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SeekMode :: [[Type]] Source #

Generic CodingProgress Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CodingProgress :: [[Type]] Source #

Generic BufferState Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code BufferState :: [[Type]] Source #

Generic MaskingState Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code MaskingState :: [[Type]] Source #

Generic IOException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code IOException :: [[Type]] Source #

Generic ErrorCall Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ErrorCall :: [[Type]] Source #

Generic ArithException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ArithException :: [[Type]] Source #

Generic All Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code All :: [[Type]] Source #

Methods

from :: All -> Rep All Source #

to :: Rep All -> All Source #

Generic Any Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Any :: [[Type]] Source #

Methods

from :: Any -> Rep Any Source #

to :: Rep Any -> Any Source #

Generic Fixity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Fixity :: [[Type]] Source #

Generic Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Associativity :: [[Type]] Source #

Generic SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SourceUnpackedness :: [[Type]] Source #

Generic SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SourceStrictness :: [[Type]] Source #

Generic DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code DecidedStrictness :: [[Type]] Source #

Generic CChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CChar :: [[Type]] Source #

Generic CSChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CSChar :: [[Type]] Source #

Generic CUChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUChar :: [[Type]] Source #

Generic CShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CShort :: [[Type]] Source #

Generic CUShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUShort :: [[Type]] Source #

Generic CInt Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CInt :: [[Type]] Source #

Methods

from :: CInt -> Rep CInt Source #

to :: Rep CInt -> CInt Source #

Generic CUInt Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUInt :: [[Type]] Source #

Generic CLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CLong :: [[Type]] Source #

Generic CULong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CULong :: [[Type]] Source #

Generic CLLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CLLong :: [[Type]] Source #

Generic CULLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CULLong :: [[Type]] Source #

Generic CFloat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CFloat :: [[Type]] Source #

Generic CDouble Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CDouble :: [[Type]] Source #

Generic CPtrdiff Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CPtrdiff :: [[Type]] Source #

Generic CSize Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CSize :: [[Type]] Source #

Generic CWchar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CWchar :: [[Type]] Source #

Generic CSigAtomic Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CSigAtomic :: [[Type]] Source #

Generic CClock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CClock :: [[Type]] Source #

Generic CTime Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CTime :: [[Type]] Source #

Generic CUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUSeconds :: [[Type]] Source #

Generic CSUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CSUSeconds :: [[Type]] Source #

Generic CIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CIntPtr :: [[Type]] Source #

Generic CUIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUIntPtr :: [[Type]] Source #

Generic CIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CIntMax :: [[Type]] Source #

Generic CUIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CUIntMax :: [[Type]] Source #

Generic IOMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code IOMode :: [[Type]] Source #

Generic Fingerprint Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Fingerprint :: [[Type]] Source #

Generic Lexeme Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Lexeme :: [[Type]] Source #

Generic Number Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code Number :: [[Type]] Source #

Generic GeneralCategory Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code GeneralCategory :: [[Type]] Source #

Generic SrcLoc Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code SrcLoc :: [[Type]] Source #

Generic [a] Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code [a] :: [[Type]] Source #

Methods

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

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

Generic (Maybe a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Maybe a) :: [[Type]] Source #

Methods

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

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

Generic (Par1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Par1 p) :: [[Type]] Source #

Methods

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

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

Generic (Complex a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Complex a) :: [[Type]] Source #

Methods

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

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

Generic (Fixed a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Fixed a) :: [[Type]] Source #

Methods

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

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

Generic (Min a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Min a) :: [[Type]] Source #

Methods

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

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

Generic (Max a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Max a) :: [[Type]] Source #

Methods

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

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

Generic (First a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (First a) :: [[Type]] Source #

Methods

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

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

Generic (Last a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Last a) :: [[Type]] Source #

Methods

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

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

Generic (WrappedMonoid m) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (WrappedMonoid m) :: [[Type]] Source #

Generic (Option a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Option a) :: [[Type]] Source #

Methods

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

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

Generic (ArgOrder a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (ArgOrder a) :: [[Type]] Source #

Methods

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

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

Generic (OptDescr a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (OptDescr a) :: [[Type]] Source #

Methods

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

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

Generic (ArgDescr a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (ArgDescr a) :: [[Type]] Source #

Methods

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

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

Generic (Identity a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Identity a) :: [[Type]] Source #

Methods

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

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

Generic (Buffer e) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Buffer e) :: [[Type]] Source #

Methods

from :: Buffer e -> Rep (Buffer e) Source #

to :: Rep (Buffer e) -> Buffer e Source #

Generic (First a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (First a) :: [[Type]] Source #

Methods

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

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

Generic (Last a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Last a) :: [[Type]] Source #

Methods

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

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

Generic (Dual a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Dual a) :: [[Type]] Source #

Methods

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

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

Generic (Endo a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Endo a) :: [[Type]] Source #

Methods

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

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

Generic (Sum a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Sum a) :: [[Type]] Source #

Methods

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

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

Generic (Product a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Product a) :: [[Type]] Source #

Methods

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

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

Generic (Down a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Down a) :: [[Type]] Source #

Methods

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

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

Generic (NonEmpty a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (NonEmpty a) :: [[Type]] Source #

Methods

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

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

Generic (I a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (I a) :: [[Type]] Source #

Methods

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

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

Generic (Either a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Either a b) :: [[Type]] Source #

Methods

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

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

Generic (V1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (V1 p) :: [[Type]] Source #

Methods

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

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

Generic (U1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (U1 p) :: [[Type]] Source #

Methods

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

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

Generic (a, b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b) :: [[Type]] Source #

Methods

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

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

Generic (Arg a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Arg a b) :: [[Type]] Source #

Methods

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

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

Generic (Proxy t) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Proxy t) :: [[Type]] Source #

Methods

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

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

Generic (a, b, c) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c) :: [[Type]] Source #

Methods

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

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

Generic (BufferCodec from to state) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (BufferCodec from to state) :: [[Type]] Source #

Methods

from :: BufferCodec from to state -> Rep (BufferCodec from to state) Source #

to :: Rep (BufferCodec from to state) -> BufferCodec from to state Source #

Generic (Const a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Const a b) :: [[Type]] Source #

Methods

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

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

Generic (Alt f a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Alt f a) :: [[Type]] Source #

Methods

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

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

Generic (K a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (K a b) :: [[Type]] Source #

Methods

from :: K a b -> Rep (K a b) Source #

to :: Rep (K a b) -> K a b Source #

Generic (K1 i c p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (K1 i c p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code ((f :+: g) p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code ((f :*: g) p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d) :: [[Type]] Source #

Methods

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

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

Generic (Product f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Product f g a) :: [[Type]] Source #

Methods

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

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

Generic (Sum f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Sum f g a) :: [[Type]] Source #

Methods

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

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

Generic ((f -.-> g) a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ((f -.-> g) a) :: [[Type]] Source #

Methods

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

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

Generic (M1 i c f p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (M1 i c f p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code ((f :.: g) p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e) :: [[Type]] Source #

Methods

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

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

Generic (Compose f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Compose f g a) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code ((f :.: g) p) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i) :: [[Type]] Source #

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j) :: [[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) Source #

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

Generic (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k) :: [[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) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k) -> (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) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l) :: [[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) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) -> (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) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m) :: [[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) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (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) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: [[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) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (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) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: [[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) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) :: [[Type]] Source #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source #

class Generic a => HasDatatypeInfo a where Source #

A class of datatypes that have associated metadata.

It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.

You typically don't define instances of this class by hand, but rather derive the class instance automatically. See the documentation of Generic for the options.

Associated Types

type DatatypeInfoOf a :: DatatypeInfo Source #

Type-level datatype info

Methods

datatypeInfo :: proxy a -> DatatypeInfo (Code a) Source #

Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.

datatypeInfo :: (GDatatypeInfo a, GCode a ~ Code a) => proxy a -> DatatypeInfo (Code a) Source #

Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.

Instances
HasDatatypeInfo Bool Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Bool :: DatatypeInfo Source #

HasDatatypeInfo Ordering Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Ordering :: DatatypeInfo Source #

HasDatatypeInfo RuntimeRep Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo VecCount Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf VecCount :: DatatypeInfo Source #

HasDatatypeInfo VecElem Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf VecElem :: DatatypeInfo Source #

HasDatatypeInfo R Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf R :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy R -> DatatypeInfo (Code R) Source #

HasDatatypeInfo D Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf D :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy D -> DatatypeInfo (Code D) Source #

HasDatatypeInfo C Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf C :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy C -> DatatypeInfo (Code C) Source #

HasDatatypeInfo S Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf S :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy S -> DatatypeInfo (Code S) Source #

HasDatatypeInfo CallStack Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CallStack :: DatatypeInfo Source #

HasDatatypeInfo () Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf () :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy () -> DatatypeInfo (Code ()) Source #

HasDatatypeInfo FFFormat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf FFFormat :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy FFFormat -> DatatypeInfo (Code FFFormat) Source #

HasDatatypeInfo E0 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E0 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E0 -> DatatypeInfo (Code E0) Source #

HasDatatypeInfo E1 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E1 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E1 -> DatatypeInfo (Code E1) Source #

HasDatatypeInfo E2 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E2 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E2 -> DatatypeInfo (Code E2) Source #

HasDatatypeInfo E3 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E3 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E3 -> DatatypeInfo (Code E3) Source #

HasDatatypeInfo E6 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E6 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E6 -> DatatypeInfo (Code E6) Source #

HasDatatypeInfo E9 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E9 :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy E9 -> DatatypeInfo (Code E9) Source #

HasDatatypeInfo E12 Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf E12 :: DatatypeInfo Source #

HasDatatypeInfo Void Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Void :: DatatypeInfo Source #

HasDatatypeInfo StaticPtrInfo Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo SpecConstrAnnotation Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo DataRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf DataRep :: DatatypeInfo Source #

HasDatatypeInfo ConstrRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ConstrRep :: DatatypeInfo Source #

HasDatatypeInfo Fixity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Fixity :: DatatypeInfo Source #

HasDatatypeInfo SrcLoc Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf SrcLoc :: DatatypeInfo Source #

HasDatatypeInfo Location Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Location :: DatatypeInfo Source #

HasDatatypeInfo GiveGCStats Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo GCFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf GCFlags :: DatatypeInfo Source #

HasDatatypeInfo ConcFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ConcFlags :: DatatypeInfo Source #

HasDatatypeInfo MiscFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf MiscFlags :: DatatypeInfo Source #

HasDatatypeInfo DebugFlags Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo DoCostCentres Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo CCFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CCFlags :: DatatypeInfo Source #

HasDatatypeInfo DoHeapProfile Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ProfFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ProfFlags :: DatatypeInfo Source #

HasDatatypeInfo DoTrace Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf DoTrace :: DatatypeInfo Source #

HasDatatypeInfo TraceFlags Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo TickyFlags Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ParFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ParFlags :: DatatypeInfo Source #

HasDatatypeInfo RTSFlags Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf RTSFlags :: DatatypeInfo Source #

HasDatatypeInfo RTSStats Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf RTSStats :: DatatypeInfo Source #

HasDatatypeInfo GCDetails Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf GCDetails :: DatatypeInfo Source #

HasDatatypeInfo ByteOrder Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ByteOrder :: DatatypeInfo Source #

HasDatatypeInfo FormatAdjustment Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo FormatSign Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo FieldFormat Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo FormatParse Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo Version Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Version :: DatatypeInfo Source #

HasDatatypeInfo HandlePosn Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo LockMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf LockMode :: DatatypeInfo Source #

HasDatatypeInfo PatternMatchFail Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo RecSelError Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo RecConError Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo RecUpdError Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo NoMethodError Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo TypeError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf TypeError :: DatatypeInfo Source #

HasDatatypeInfo NonTermination Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo NestedAtomically Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo BlockReason Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ThreadStatus Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo Errno Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Errno :: DatatypeInfo Source #

HasDatatypeInfo CodingFailureMode Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo Deadlock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Deadlock :: DatatypeInfo Source #

HasDatatypeInfo AllocationLimitExceeded Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo AssertionFailed Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo AsyncException Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ArrayException Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo FixIOException Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ExitCode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ExitCode :: DatatypeInfo Source #

HasDatatypeInfo IOErrorType Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo BufferMode Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo Newline Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Newline :: DatatypeInfo Source #

HasDatatypeInfo NewlineMode Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo IODeviceType Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo SeekMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf SeekMode :: DatatypeInfo Source #

HasDatatypeInfo CodingProgress Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo BufferState Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo MaskingState Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo IOException Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo ErrorCall Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ErrorCall :: DatatypeInfo Source #

HasDatatypeInfo ArithException Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo All Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf All :: DatatypeInfo Source #

HasDatatypeInfo Any Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Any :: DatatypeInfo Source #

HasDatatypeInfo Fixity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Fixity :: DatatypeInfo Source #

HasDatatypeInfo Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo SourceUnpackedness Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo SourceStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo DecidedStrictness Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo CChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CChar :: DatatypeInfo Source #

HasDatatypeInfo CSChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CSChar :: DatatypeInfo Source #

HasDatatypeInfo CUChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUChar :: DatatypeInfo Source #

HasDatatypeInfo CShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CShort :: DatatypeInfo Source #

HasDatatypeInfo CUShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUShort :: DatatypeInfo Source #

HasDatatypeInfo CInt Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CInt :: DatatypeInfo Source #

HasDatatypeInfo CUInt Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUInt :: DatatypeInfo Source #

HasDatatypeInfo CLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CLong :: DatatypeInfo Source #

HasDatatypeInfo CULong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CULong :: DatatypeInfo Source #

HasDatatypeInfo CLLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CLLong :: DatatypeInfo Source #

HasDatatypeInfo CULLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CULLong :: DatatypeInfo Source #

HasDatatypeInfo CFloat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CFloat :: DatatypeInfo Source #

HasDatatypeInfo CDouble Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CDouble :: DatatypeInfo Source #

HasDatatypeInfo CPtrdiff Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CPtrdiff :: DatatypeInfo Source #

HasDatatypeInfo CSize Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CSize :: DatatypeInfo Source #

HasDatatypeInfo CWchar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CWchar :: DatatypeInfo Source #

HasDatatypeInfo CSigAtomic Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo CClock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CClock :: DatatypeInfo Source #

HasDatatypeInfo CTime Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CTime :: DatatypeInfo Source #

HasDatatypeInfo CUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUSeconds :: DatatypeInfo Source #

HasDatatypeInfo CSUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo CIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CIntPtr :: DatatypeInfo Source #

HasDatatypeInfo CUIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUIntPtr :: DatatypeInfo Source #

HasDatatypeInfo CIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CIntMax :: DatatypeInfo Source #

HasDatatypeInfo CUIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf CUIntMax :: DatatypeInfo Source #

HasDatatypeInfo IOMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf IOMode :: DatatypeInfo Source #

HasDatatypeInfo Fingerprint Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo Lexeme Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Lexeme :: DatatypeInfo Source #

HasDatatypeInfo Number Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf Number :: DatatypeInfo Source #

HasDatatypeInfo GeneralCategory Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo SrcLoc Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf SrcLoc :: DatatypeInfo Source #

HasDatatypeInfo [a] Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf [a] :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy [a] -> DatatypeInfo (Code [a]) Source #

HasDatatypeInfo (Maybe a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Maybe a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Maybe a) -> DatatypeInfo (Code (Maybe a)) Source #

HasDatatypeInfo (Par1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Par1 p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Par1 p) -> DatatypeInfo (Code (Par1 p)) Source #

HasDatatypeInfo (Complex a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Complex a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Complex a) -> DatatypeInfo (Code (Complex a)) Source #

HasDatatypeInfo (Fixed a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Fixed a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Fixed a) -> DatatypeInfo (Code (Fixed a)) Source #

HasDatatypeInfo (Min a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Min a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Min a) -> DatatypeInfo (Code (Min a)) Source #

HasDatatypeInfo (Max a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Max a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Max a) -> DatatypeInfo (Code (Max a)) Source #

HasDatatypeInfo (First a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (First a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (First a) -> DatatypeInfo (Code (First a)) Source #

HasDatatypeInfo (Last a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Last a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Last a) -> DatatypeInfo (Code (Last a)) Source #

HasDatatypeInfo (WrappedMonoid m) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (WrappedMonoid m) :: DatatypeInfo Source #

HasDatatypeInfo (Option a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Option a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Option a) -> DatatypeInfo (Code (Option a)) Source #

HasDatatypeInfo (ArgOrder a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (ArgOrder a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (ArgOrder a) -> DatatypeInfo (Code (ArgOrder a)) Source #

HasDatatypeInfo (OptDescr a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (OptDescr a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (OptDescr a) -> DatatypeInfo (Code (OptDescr a)) Source #

HasDatatypeInfo (ArgDescr a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (ArgDescr a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (ArgDescr a) -> DatatypeInfo (Code (ArgDescr a)) Source #

HasDatatypeInfo (Identity a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Identity a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Identity a) -> DatatypeInfo (Code (Identity a)) Source #

HasDatatypeInfo (Buffer e) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Buffer e) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Buffer e) -> DatatypeInfo (Code (Buffer e)) Source #

HasDatatypeInfo (First a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (First a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (First a) -> DatatypeInfo (Code (First a)) Source #

HasDatatypeInfo (Last a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Last a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Last a) -> DatatypeInfo (Code (Last a)) Source #

HasDatatypeInfo (Dual a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Dual a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Dual a) -> DatatypeInfo (Code (Dual a)) Source #

HasDatatypeInfo (Endo a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Endo a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Endo a) -> DatatypeInfo (Code (Endo a)) Source #

HasDatatypeInfo (Sum a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Sum a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Sum a) -> DatatypeInfo (Code (Sum a)) Source #

HasDatatypeInfo (Product a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Product a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Product a) -> DatatypeInfo (Code (Product a)) Source #

HasDatatypeInfo (Down a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Down a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Down a) -> DatatypeInfo (Code (Down a)) Source #

HasDatatypeInfo (NonEmpty a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (NonEmpty a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (NonEmpty a) -> DatatypeInfo (Code (NonEmpty a)) Source #

HasDatatypeInfo (I a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (I a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (I a) -> DatatypeInfo (Code (I a)) Source #

HasDatatypeInfo (Either a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Either a b) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Either a b) -> DatatypeInfo (Code (Either a b)) Source #

HasDatatypeInfo (V1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (V1 p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (V1 p) -> DatatypeInfo (Code (V1 p)) Source #

HasDatatypeInfo (U1 p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (U1 p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (U1 p) -> DatatypeInfo (Code (U1 p)) Source #

HasDatatypeInfo (a, b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b) -> DatatypeInfo (Code (a, b)) Source #

HasDatatypeInfo (Arg a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Arg a b) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Arg a b) -> DatatypeInfo (Code (Arg a b)) Source #

HasDatatypeInfo (Proxy t) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Proxy t) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Proxy t) -> DatatypeInfo (Code (Proxy t)) Source #

HasDatatypeInfo (a, b, c) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c) -> DatatypeInfo (Code (a, b, c)) Source #

HasDatatypeInfo (BufferCodec from to state) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (BufferCodec from to state) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (BufferCodec from to state) -> DatatypeInfo (Code (BufferCodec from to state)) Source #

HasDatatypeInfo (Const a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Const a b) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Const a b) -> DatatypeInfo (Code (Const a b)) Source #

HasDatatypeInfo (Alt f a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Alt f a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Alt f a) -> DatatypeInfo (Code (Alt f a)) Source #

HasDatatypeInfo (K a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (K a b) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (K a b) -> DatatypeInfo (Code (K a b)) Source #

HasDatatypeInfo (K1 i c p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (K1 i c p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (K1 i c p) -> DatatypeInfo (Code (K1 i c p)) Source #

HasDatatypeInfo ((f :+: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ((f :+: g) p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy ((f :+: g) p) -> DatatypeInfo (Code ((f :+: g) p)) Source #

HasDatatypeInfo ((f :*: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ((f :*: g) p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy ((f :*: g) p) -> DatatypeInfo (Code ((f :*: g) p)) Source #

HasDatatypeInfo (a, b, c, d) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d) -> DatatypeInfo (Code (a, b, c, d)) Source #

HasDatatypeInfo (Product f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Product f g a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Product f g a) -> DatatypeInfo (Code (Product f g a)) Source #

HasDatatypeInfo (Sum f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Sum f g a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Sum f g a) -> DatatypeInfo (Code (Sum f g a)) Source #

HasDatatypeInfo ((f -.-> g) a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ((f -.-> g) a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy ((f -.-> g) a) -> DatatypeInfo (Code ((f -.-> g) a)) Source #

HasDatatypeInfo (M1 i c f p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (M1 i c f p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (M1 i c f p) -> DatatypeInfo (Code (M1 i c f p)) Source #

HasDatatypeInfo ((f :.: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ((f :.: g) p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy ((f :.: g) p) -> DatatypeInfo (Code ((f :.: g) p)) Source #

HasDatatypeInfo (a, b, c, d, e) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e) -> DatatypeInfo (Code (a, b, c, d, e)) Source #

HasDatatypeInfo (Compose f g a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (Compose f g a) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (Compose f g a) -> DatatypeInfo (Code (Compose f g a)) Source #

HasDatatypeInfo ((f :.: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ((f :.: g) p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy ((f :.: g) p) -> DatatypeInfo (Code ((f :.: g) p)) Source #

HasDatatypeInfo (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f) -> DatatypeInfo (Code (a, b, c, d, e, f)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g) -> DatatypeInfo (Code (a, b, c, d, e, f, g)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28)) Source #

HasDatatypeInfo (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) :: DatatypeInfo Source #

Methods

datatypeInfo :: proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) -> DatatypeInfo (Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29)) Source #

type IsProductType (a :: Type) (xs :: [Type]) = (Generic a, Code a ~ '[xs]) Source #

Constraint that captures that a datatype is a product type, i.e., a type with a single constructor.

It also gives access to the code for the arguments of that constructor.

Since: generics-sop-0.3.1.0

type ProductCode (a :: Type) = Head (Code a) Source #

Direct access to the part of the code that is relevant for a product type.

Since: generics-sop-0.4.0.0

productTypeFrom :: IsProductType a xs => a -> NP I xs Source #

Convert from a product type to its product representation.

Since: generics-sop-0.4.0.0

productTypeTo :: IsProductType a xs => NP I xs -> a Source #

Convert a product representation to the original type.

Since: generics-sop-0.4.0.0

type IsEnumType (a :: Type) = (Generic a, All ((~) '[]) (Code a)) Source #

Constraint that captures that a datatype is an enumeration type, i.e., none of the constructors have any arguments.

Since: generics-sop-0.3.1.0

enumTypeFrom :: IsEnumType a => a -> NS (K ()) (Code a) Source #

Convert from an enum type to its sum representation.

Since: generics-sop-0.4.0.0

enumTypeTo :: IsEnumType a => NS (K ()) (Code a) -> a Source #

Convert a sum representation to ihe original type.

type IsWrappedType (a :: Type) (x :: Type) = (Generic a, Code a ~ '['[x]]) Source #

Constraint that captures that a datatype is a single-constructor, single-field datatype. This always holds for newtype-defined types, but it can also be true for data-defined types.

The constraint also gives access to the type that is wrapped.

Since: generics-sop-0.3.1.0

type WrappedCode (a :: Type) = Head (Head (Code a)) Source #

Direct access to the part of the code that is relevant for wrapped types and newtypes.

Since: generics-sop-0.4.0.0

wrappedTypeFrom :: IsWrappedType a x => a -> x Source #

Convert from a wrapped type to its inner type.

Since: generics-sop-0.4.0.0

wrappedTypeTo :: IsWrappedType a x => x -> a Source #

Convert a type to a wrapped type.

Since: generics-sop-0.4.0.0

type IsNewtype (a :: Type) (x :: Type) = (IsWrappedType a x, Coercible a x) Source #

Constraint that captures that a datatype is a newtype. This makes use of the fact that newtypes are always coercible to the type they wrap, whereas datatypes are not.

Since: generics-sop-0.3.1.0

newtypeFrom :: IsNewtype a x => a -> x Source #

Convert a newtype to its inner type.

This is a specialised synonym for coerce.

Since: generics-sop-0.4.0.0

newtypeTo :: IsNewtype a x => x -> a Source #

Convert a type to a newtype.

This is a specialised synonym for coerce.

Since: generics-sop-0.4.0.0