generics-sop-0.3.2.0: 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 :: *) 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 :: [[*]] 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 :: [[*]] 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 :: [[*]] Source #

Generic () Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Methods

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

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

Generic DataRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic ConstrRep Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Fixity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic FormatAdjustment Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic FormatSign Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic FieldFormat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic FormatParse Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Version Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic PatternMatchFail Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic RecSelError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic RecConError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic RecUpdError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic NoMethodError Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic NonTermination Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic NestedAtomically Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Errno Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic BlockedIndefinitelyOnMVar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic BlockedIndefinitelyOnSTM Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Deadlock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic AssertionFailed Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic AsyncException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic ArrayException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic ExitCode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic BufferMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Newline Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic NewlineMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic SeekMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic MaskingState Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic IOException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic ErrorCall Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic ArithException Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic All Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code All :: [[*]] 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 :: [[*]] Source #

Methods

from :: Any -> Rep Any Source #

to :: Rep Any -> Any Source #

Generic CChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CSChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CUChar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CUShort Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CInt Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code CInt :: [[*]] 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 :: [[*]] Source #

Generic CLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CULong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CLLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CULLong Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CFloat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CDouble Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CPtrdiff Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CSize Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CWchar Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CSigAtomic Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CClock Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CTime Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CSUSeconds Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CUIntPtr Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic CUIntMax Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic IOMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Lexeme Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic Number Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic GeneralCategory Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Generic [a] Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code [a] :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (Complex a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Complex a) :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (ArgOrder a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (ArgOrder a) :: [[*]] 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) :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (First a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (First a) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (I a) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (I a) :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (a, b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Methods

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

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

Generic (Proxy t) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (Proxy t) :: [[*]] 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) :: [[*]] Source #

Methods

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

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

Generic (K a b) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

Methods

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

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

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

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d) :: [[*]] 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 (a, b, c, d, e) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code (a, b, c, d, e) :: [[*]] 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 ((f :.: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code ((f :.: g) p) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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) :: [[*]] 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 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 () Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf () :: DatatypeInfo Source #

Methods

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

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 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 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 NonTermination Source # 
Instance details

Defined in Generics.SOP.Instances

HasDatatypeInfo NestedAtomically 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 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 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 ExitCode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf ExitCode :: DatatypeInfo Source #

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 SeekMode Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf SeekMode :: DatatypeInfo Source #

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 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 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 [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 (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 (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 (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 (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 (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 (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 (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 (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 (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 ((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 :: *) (xs :: [*]) = (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: 0.3.1.0

type IsEnumType (a :: *) = (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: 0.3.1.0

type IsWrappedType (a :: *) (x :: *) = (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: 0.3.1.0

type IsNewtype (a :: *) (x :: *) = (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: 0.3.1.0