generics-sop-0.5.0.0: Generic Programming using True Sums of Products
Safe HaskellNone
LanguageHaskell2010

Generics.SOP

Description

Main module of generics-sop

In most cases, you will probably want to import just this module, and possibly Generics.SOP.TH if you want to use Template Haskell to generate Generic instances for you.

Generic programming with sums of products

You need this library if you want to define your own generic functions in the sum-of-products SOP style. Generic programming in the SOP style follows the following idea:

  1. A large class of datatypes can be viewed in a uniform, structured way: the choice between constructors is represented using an n-ary sum (called NS), and the arguments of each constructor are represented using an n-ary product (called NP).
  2. The library captures the notion of a datatype being representable in the following way. There is a class Generic, which for a given datatype A, associates the isomorphic SOP representation with the original type under the name Rep A. The class also provides functions from and to that convert between A and Rep A and witness the isomorphism.
  3. Since all Rep types are sums of products, you can define functions over them by performing induction on the structure, or by using predefined combinators that the library provides. Such functions then work for all Rep types.
  4. By combining the conversion functions from and to with the function that works on Rep types, we obtain a function that works on all types that are in the Generic class.
  5. Most types can very easily be made an instance of Generic. For example, if the datatype can be represented using GHC's built-in approach to generic programming and has an instance for the Generic class from module GHC.Generics, then an instance of the SOP Generic can automatically be derived. There is also Template Haskell code in Generics.SOP.TH that allows to auto-generate an instance of Generic for most types.

Example

Instantiating a datatype for use with SOP generics

Let's assume we have the datatypes:

data A   = C Bool | D A Int | E (B ())
data B a = F | G a Char Bool

To create Generic instances for A and B via GHC.Generics, we say

{-# LANGUAGE DeriveGeneric #-}

import qualified GHC.Generics as GHC
import Generics.SOP

data A   = C Bool | D A Int | E (B ())
  deriving (Show, GHC.Generic)
data B a = F | G a Char Bool
  deriving (Show, GHC.Generic)

instance Generic A     -- empty
instance Generic (B a) -- empty

Now we can convert between A and Rep A (and between B and Rep B). For example,

>>> from (D (C True) 3) :: Rep A
SOP (S (Z (I (C True) :* I 3 :* Nil)))
>>> to it :: A
D (C True) 3

Note that the transformation is shallow: In D (C True) 3, the inner value C True of type A is not affected by the transformation.

For more details about Rep A, have a look at the Generics.SOP.Universe module.

Defining a generic function

As an example of a generic function, let us define a generic version of rnf from the deepseq package.

The type of rnf is

NFData a => a -> ()

and the idea is that for a term x of type a in the NFData class, rnf x forces complete evaluation of x (i.e., evaluation to normal form), and returns ().

We call the generic version of this function grnf. A direct definition in SOP style, making use of structural recursion on the sums and products, looks as follows:

grnf :: (Generic a, All2 NFData (Code a)) => a -> ()
grnf x = grnfS (from x)

grnfS :: (All2 NFData xss) => SOP I xss -> ()
grnfS (SOP (Z xs))  = grnfP xs
grnfS (SOP (S xss)) = grnfS (SOP xss)

grnfP :: (All NFData xs) => NP I xs -> ()
grnfP Nil         = ()
grnfP (I x :* xs) = x `deepseq` (grnfP xs)

The grnf function performs the conversion between a and Rep a by applying from and then applies grnfS. The type of grnf indicates that a must be in the Generic class so that we can apply from, and that all the components of a (i.e., all the types that occur as constructor arguments) must be in the NFData class (All2).

The function grnfS traverses the outer sum structure of the sum of products (note that Rep a = SOP I (Code a)). It encodes which constructor was used to construct the original argument of type a. Once we've found the constructor in question (Z), we traverse the arguments of that constructor using grnfP.

The function grnfP traverses the product structure of the constructor arguments. Each argument is evaluated using the deepseq function from the NFData class. This requires that all components of the product must be in the NFData class (All) and triggers the corresponding constraints on the other functions. Once the end of the product is reached (Nil), we return ().

Defining a generic function using combinators

In many cases, generic functions can be written in a much more concise way by avoiding the explicit structural recursion and resorting to the powerful combinators provided by this library instead.

For example, the grnf function can also be defined as a one-liner as follows:

grnf :: (Generic a, All2 NFData (Code a)) => a -> ()
grnf = rnf . hcollapse . hcmap (Proxy :: Proxy NFData) (mapIK rnf) . from

mapIK and friends (mapII, mapKI, etc.) are small helpers for working with I and K functors, for example mapIK is defined as mapIK f = \ (I x) -> K (f x)

The following interaction should provide an idea of the individual transformation steps:

>>> let x = G 2.5 'A' False :: B Double
>>> from x
SOP (S (Z (I 2.5 :* I 'A' :* I False :* Nil)))
>>> hcmap (Proxy :: Proxy NFData) (mapIK rnf) it
SOP (S (Z (K () :* K () :* K () :* Nil)))
>>> hcollapse it
[(),(),()]
>>> rnf it
()

The from call converts into the structural representation. Via hcmap, we apply rnf to all the components. The result is a sum of products of the same shape, but the components are no longer heterogeneous (I), but homogeneous (K ()). A homogeneous structure can be collapsed (hcollapse) into a normal Haskell list. Finally, rnf actually forces evaluation of this list (and thereby actually drives the evaluation of all the previous steps) and produces the final result.

Using a generic function

We can directly invoke grnf on any type that is an instance of class Generic.

>>> grnf (G 2.5 'A' False)
()
>>> grnf (G 2.5 undefined False)
*** Exception: Prelude.undefined
...

Note that the type of grnf requires that all components of the type are in the NFData class. For a recursive datatype such as B, this means that we have to make A (and in this case, also B) an instance of NFData in order to be able to use the grnf function. But we can use grnf to supply the instance definitions:

instance NFData A where rnf = grnf
instance NFData a => NFData (B a) where rnf = grnf

More examples

The best way to learn about how to define generic functions in the SOP style is to look at a few simple examples. Examples are provided by the following packages:

The generic functions in these packages use a wide variety of the combinators that are offered by the library.

Paper

A detailed description of the ideas behind this library is provided by the paper:

Synopsis

Codes and interpretations

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 a 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.

Minimal complete definition

Nothing

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 ]
   ]

type Code a = GCode a Source #

Methods

from :: a -> Rep a Source #

Converts from a value to its structural representation.

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

to :: Rep a -> a Source #

Converts from a structural representation back to the original value.

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

Instances

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

Defined in Generics.SOP.Instances

Associated Types

type Code StaticPtrInfo :: [[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 FFFormat Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

type Code FFFormat :: [[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 #

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.

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

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

Convert from a product type to its product representation.

Since: 0.4.0.0

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

Convert a product representation to the original type.

Since: 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: 0.3.1.0

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

Convert from an enum type to its sum representation.

Since: 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: 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: 0.4.0.0

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

Convert from a wrapped type to its inner type.

Since: 0.4.0.0

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

Convert a type to a wrapped type.

Since: 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: 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: 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: 0.4.0.0

n-ary datatypes

data NP (a :: k -> Type) (b :: [k]) where #

Constructors

Nil :: forall k (a :: k -> Type). NP a ('[] :: [k]) 
(:*) :: forall k (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NP a xs -> NP a (x ': xs) 

Instances

Instances details
HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

HAp (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HPure (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HSequence (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

HTraverse_ (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

All (Compose Eq f) xs => Eq (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose Semigroup f) xs => Semigroup (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

(<>) :: NP f xs -> NP f xs -> NP f xs #

sconcat :: NonEmpty (NP f xs) -> NP f xs #

stimes :: Integral b => b -> NP f xs -> NP f xs #

(All (Compose Monoid f) xs, All (Compose Semigroup f) xs) => Monoid (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

mempty :: NP f xs #

mappend :: NP f xs -> NP f xs -> NP f xs #

mconcat :: [NP f xs] -> NP f xs #

All (Compose NFData f) xs => NFData (NP f xs) 
Instance details

Defined in Data.SOP.NP

Methods

rnf :: NP f xs -> () #

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) = AllZip c
type Same (NP :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NP

type Same (NP :: (k1 -> Type) -> [k1] -> Type) = NP :: (k2 -> Type) -> [k2] -> Type
type Prod (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type UnProd (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = NS :: (k -> Type) -> [k] -> Type
type SListIN (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type SListIN (NP :: (k -> Type) -> [k] -> Type) = SListI :: [k] -> Constraint
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c

data NS (a :: k -> Type) (b :: [k]) where #

Constructors

Z :: forall k (a :: k -> Type) (x :: k) (xs :: [k]). a x -> NS a (x ': xs) 
S :: forall k (a :: k -> Type) (xs :: [k]) (x :: k). NS a xs -> NS a (x ': xs) 

Instances

Instances details
HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod NS) (LiftedCoercible f g) xs ys, HTrans NS NS) => NS f xs -> NS g ys #

HAp (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HApInjs (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type). SListIN NS xs => Prod NS f xs -> [NS f xs] #

HCollapse (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HExpand (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

HIndex (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type) (xs :: l). NS f xs -> Int #

HSequence (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

HTraverse_ (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () #

All (Compose Eq f) xs => Eq (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

(==) :: NS f xs -> NS f xs -> Bool #

(/=) :: NS f xs -> NS f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

compare :: NS f xs -> NS f xs -> Ordering #

(<) :: NS f xs -> NS f xs -> Bool #

(<=) :: NS f xs -> NS f xs -> Bool #

(>) :: NS f xs -> NS f xs -> Bool #

(>=) :: NS f xs -> NS f xs -> Bool #

max :: NS f xs -> NS f xs -> NS f xs #

min :: NS f xs -> NS f xs -> NS f xs #

All (Compose Show f) xs => Show (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> NS f xs -> ShowS #

show :: NS f xs -> String #

showList :: [NS f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NS f xs) 
Instance details

Defined in Data.SOP.NS

Methods

rnf :: NS f xs -> () #

type Same (NS :: (k1 -> Type) -> [k1] -> Type) 
Instance details

Defined in Data.SOP.NS

type Same (NS :: (k1 -> Type) -> [k1] -> Type) = NS :: (k2 -> Type) -> [k2] -> Type
type Prod (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (NS :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type SListIN (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type SListIN (NS :: (k -> Type) -> [k] -> Type) = SListI :: [k] -> Constraint
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a = a
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c

newtype SOP (f :: k -> Type) (xss :: [[k]]) #

Constructors

SOP (NS (NP f) xss) 

Instances

Instances details
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod SOP) (LiftedCoercible f g) xs ys, HTrans SOP SOP) => SOP f xs -> SOP g ys #

HAp (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs #

HApInjs (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type). SListIN SOP xs => Prod SOP f xs -> [SOP f xs] #

HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN SOP xs => SOP (K a) xs -> CollapseTo SOP a #

HExpand (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod SOP) xs => (forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod SOP) c xs => proxy c -> (forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs #

HIndex (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type) (xs :: l). SOP f xs -> Int #

HSequence (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) #

HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () #

Eq (NS (NP f) xss) => Eq (SOP f xss) 
Instance details

Defined in Data.SOP.NS

Methods

(==) :: SOP f xss -> SOP f xss -> Bool #

(/=) :: SOP f xss -> SOP f xss -> Bool #

Ord (NS (NP f) xss) => Ord (SOP f xss) 
Instance details

Defined in Data.SOP.NS

Methods

compare :: SOP f xss -> SOP f xss -> Ordering #

(<) :: SOP f xss -> SOP f xss -> Bool #

(<=) :: SOP f xss -> SOP f xss -> Bool #

(>) :: SOP f xss -> SOP f xss -> Bool #

(>=) :: SOP f xss -> SOP f xss -> Bool #

max :: SOP f xss -> SOP f xss -> SOP f xss #

min :: SOP f xss -> SOP f xss -> SOP f xss #

Show (NS (NP f) xss) => Show (SOP f xss) 
Instance details

Defined in Data.SOP.NS

Methods

showsPrec :: Int -> SOP f xss -> ShowS #

show :: SOP f xss -> String #

showList :: [SOP f xss] -> ShowS #

NFData (NS (NP f) xss) => NFData (SOP f xss) 
Instance details

Defined in Data.SOP.NS

Methods

rnf :: SOP f xss -> () #

type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) 
Instance details

Defined in Data.SOP.NS

type Same (SOP :: (k1 -> Type) -> [[k1]] -> Type) = SOP :: (k2 -> Type) -> [[k2]] -> Type
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (SOP :: (k -> Type) -> [[k]] -> Type) = POP :: (k -> Type) -> [[k]] -> Type
type SListIN (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

type SListIN (SOP :: (k -> Type) -> [[k]] -> Type) = SListI2 :: [[k]] -> Constraint
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a = [a]
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) = All2 c

unSOP :: forall k (f :: k -> Type) (xss :: [[k]]). SOP f xss -> NS (NP f) xss #

newtype POP (f :: k -> Type) (xss :: [[k]]) #

Constructors

POP (NP (NP f) xss) 

Instances

Instances details
HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod POP) (LiftedCoercible f g) xs ys, HTrans POP POP) => POP f xs -> POP g ys #

HAp (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod POP (f -.-> g) xs -> POP f xs -> POP g xs #

HCollapse (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN POP xs => POP (K a) xs -> CollapseTo POP a #

HPure (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN POP xs => (forall (a :: k0). f a) -> POP f xs #

hcpure :: forall c (xs :: l) proxy f. AllN POP c xs => proxy c -> (forall (a :: k0). c a => f a) -> POP f xs #

HSequence (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) #

HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () #

Eq (NP (NP f) xss) => Eq (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

(==) :: POP f xss -> POP f xss -> Bool #

(/=) :: POP f xss -> POP f xss -> Bool #

Ord (NP (NP f) xss) => Ord (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

compare :: POP f xss -> POP f xss -> Ordering #

(<) :: POP f xss -> POP f xss -> Bool #

(<=) :: POP f xss -> POP f xss -> Bool #

(>) :: POP f xss -> POP f xss -> Bool #

(>=) :: POP f xss -> POP f xss -> Bool #

max :: POP f xss -> POP f xss -> POP f xss #

min :: POP f xss -> POP f xss -> POP f xss #

Show (NP (NP f) xss) => Show (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

showsPrec :: Int -> POP f xss -> ShowS #

show :: POP f xss -> String #

showList :: [POP f xss] -> ShowS #

Semigroup (NP (NP f) xss) => Semigroup (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

(<>) :: POP f xss -> POP f xss -> POP f xss #

sconcat :: NonEmpty (POP f xss) -> POP f xss #

stimes :: Integral b => b -> POP f xss -> POP f xss #

Monoid (NP (NP f) xss) => Monoid (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

mempty :: POP f xss #

mappend :: POP f xss -> POP f xss -> POP f xss #

mconcat :: [POP f xss] -> POP f xss #

NFData (NP (NP f) xss) => NFData (POP f xss) 
Instance details

Defined in Data.SOP.NP

Methods

rnf :: POP f xss -> () #

type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) = AllZip2 c
type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) 
Instance details

Defined in Data.SOP.NP

type Same (POP :: (k1 -> Type) -> [[k1]] -> Type) = POP :: (k2 -> Type) -> [[k2]] -> Type
type Prod (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (POP :: (k -> Type) -> [[k]] -> Type) = POP :: (k -> Type) -> [[k]] -> Type
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (POP :: (k -> Type) -> [[k]] -> Type) = SOP :: (k -> Type) -> [[k]] -> Type
type SListIN (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

type SListIN (POP :: (k -> Type) -> [[k]] -> Type) = SListI2 :: [[k]] -> Constraint
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a = [[a]]
type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) = All2 c

unPOP :: forall k (f :: k -> Type) (xss :: [[k]]). POP f xss -> NP (NP f) xss #

Metadata

data DatatypeInfo :: [[Type]] -> Type where Source #

Metadata for a datatype.

A value of type DatatypeInfo c contains the information about a datatype that is not contained in Code c. This information consists primarily of the names of the datatype, its constructors, and possibly its record selectors.

The constructor indicates whether the datatype has been declared using newtype or not.

moduleName :: DatatypeInfo xss -> ModuleName Source #

The module name where a datatype is defined.

Since: 0.2.3.0

datatypeName :: DatatypeInfo xss -> DatatypeName Source #

The name of a datatype (or newtype).

Since: 0.2.3.0

constructorInfo :: DatatypeInfo xss -> NP ConstructorInfo xss Source #

The constructor info for a datatype (or newtype).

Since: 0.2.3.0

data ConstructorInfo :: [Type] -> Type where Source #

Metadata for a single constructor.

This is indexed by the product structure of the constructor components.

constructorName :: ConstructorInfo xs -> ConstructorName Source #

The name of a constructor.

Since: 0.2.3.0

data FieldInfo :: Type -> Type where Source #

For records, this functor maps the component to its selector name.

Constructors

FieldInfo :: FieldName -> FieldInfo a 

Instances

Instances details
Functor FieldInfo Source # 
Instance details

Defined in Generics.SOP.Metadata

Methods

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

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

Eq (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

Methods

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

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

Ord (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

Show (FieldInfo a) Source # 
Instance details

Defined in Generics.SOP.Metadata

fieldName :: FieldInfo a -> FieldName Source #

The name of a field.

Since: 0.2.3.0

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.

Minimal complete definition

Nothing

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.

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

Instances

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

Defined in Generics.SOP.Instances

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

Defined in Generics.SOP.Instances

Associated Types

type DatatypeInfoOf FFFormat :: 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 DatatypeName = String Source #

The name of a datatype.

type ModuleName = String Source #

The name of a module.

type ConstructorName = String Source #

The name of a data constructor.

type FieldName = String Source #

The name of a field / record selector.

data Associativity #

Datatype to represent the associativity of a constructor

Instances

Instances details
Bounded Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Data Associativity

Since: base-4.9.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Associativity -> Constr #

dataTypeOf :: Associativity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Read Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ix Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

SingKind Associativity

Since: base-4.0.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Associativity

Methods

fromSing :: forall (a :: Associativity). Sing a -> DemoteRep Associativity

HasDatatypeInfo Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

Generic Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

Associated Types

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

SingI 'LeftAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'LeftAssociative

SingI 'RightAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'RightAssociative

SingI 'NotAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'NotAssociative

type Rep Associativity 
Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

type DemoteRep Associativity 
Instance details

Defined in GHC.Generics

type DemoteRep Associativity = Associativity
type DatatypeInfoOf Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf Associativity = 'ADT "GHC.Generics" "Associativity" '['Constructor "LeftAssociative", 'Constructor "RightAssociative", 'Constructor "NotAssociative"] '['[] :: [StrictnessInfo], '[] :: [StrictnessInfo], '[] :: [StrictnessInfo]]
type Code Associativity Source # 
Instance details

Defined in Generics.SOP.Instances

type Code Associativity = '['[] :: [Type], '[] :: [Type], '[] :: [Type]]

type Fixity = Int Source #

The fixity of an infix constructor.

Combinators

Constructing products

class HPure (h :: (k -> Type) -> l -> Type) where #

Methods

hpure :: forall (xs :: l) f. SListIN h xs => (forall (a :: k). f a) -> h f xs #

hcpure :: forall c (xs :: l) proxy f. AllN h c xs => proxy c -> (forall (a :: k). c a => f a) -> h f xs #

Instances

Instances details
HPure (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN POP xs => (forall (a :: k0). f a) -> POP f xs #

hcpure :: forall c (xs :: l) proxy f. AllN POP c xs => proxy c -> (forall (a :: k0). c a => f a) -> POP f xs #

HPure (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hpure :: forall (xs :: l) f. SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: forall c (xs :: l) proxy f. AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

Destructing products

hd :: forall k f (x :: k) (xs :: [k]). NP f (x ': xs) -> f x #

tl :: forall k (f :: k -> Type) (x :: k) (xs :: [k]). NP f (x ': xs) -> NP f xs #

type Projection (f :: k -> Type) (xs :: [k]) = (K (NP f xs) :: k -> Type) -.-> f #

projections :: forall k (xs :: [k]) (f :: k -> Type). SListI xs => NP (Projection f xs) xs #

shiftProjection :: forall a1 (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Projection f xs a2 -> Projection f (x ': xs) a2 #

Application

newtype ((f :: k -> Type) -.-> (g :: k -> Type)) (a :: k) #

Constructors

Fn 

Fields

  • apFn :: f a -> g a
     

Instances

Instances details
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 #

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 #

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

Defined in Generics.SOP.Instances

type DatatypeInfoOf ((f -.-> g) a) = 'Newtype "Data.SOP.Classes" "-.->" ('Record "Fn" '['FieldInfo "apFn"])
type Code ((f -.-> g) a) Source # 
Instance details

Defined in Generics.SOP.Instances

type Code ((f -.-> g) a) = '['[f a -> g a]]

fn :: forall k f (a :: k) f'. (f a -> f' a) -> (f -.-> f') a #

fn_2 :: forall k f (a :: k) f' f''. (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a #

fn_3 :: forall k f (a :: k) f' f'' f'''. (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a #

fn_4 :: forall k f (a :: k) f' f'' f''' f''''. (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a #

type family Prod (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type #

Instances

Instances details
type Prod (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (NS :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type Prod (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

type Prod (SOP :: (k -> Type) -> [[k]] -> Type) = POP :: (k -> Type) -> [[k]] -> Type
type Prod (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (NP :: (k -> Type) -> [k] -> Type) = NP :: (k -> Type) -> [k] -> Type
type Prod (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

type Prod (POP :: (k -> Type) -> [[k]] -> Type) = POP :: (k -> Type) -> [[k]] -> Type

class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> Type) -> l -> Type) where #

Methods

hap :: forall (f :: k -> Type) (g :: k -> Type) (xs :: l). Prod h (f -.-> g) xs -> h f xs -> h g xs #

Instances

Instances details
HAp (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs #

HAp (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HAp (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod POP (f -.-> g) xs -> POP f xs -> POP g xs #

HAp (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hap :: forall (f :: k0 -> Type) (g :: k0 -> Type) (xs :: l). Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

Lifting / mapping

hliftA :: forall k l h (xs :: l) f f'. (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #

hliftA2 :: forall k l h (xs :: l) f f' f''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #

hliftA3 :: forall k l h (xs :: l) f f' f'' f'''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #

hcliftA :: forall k l h c (xs :: l) proxy f f'. (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #

hcliftA2 :: forall k l h c (xs :: l) proxy f f' f''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #

hcliftA3 :: forall k l h c (xs :: l) proxy f f' f'' f'''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #

hmap :: forall k l h (xs :: l) f f'. (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #

hzipWith :: forall k l h (xs :: l) f f' f''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #

hzipWith3 :: forall k l h (xs :: l) f f' f'' f'''. (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #

hcmap :: forall k l h c (xs :: l) proxy f f'. (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #

hczipWith :: forall k l h c (xs :: l) proxy f f' f''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #

hczipWith3 :: forall k l h c (xs :: l) proxy f f' f'' f'''. (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #

Constructing sums

type Injection (f :: k -> Type) (xs :: [k]) = f -.-> (K (NS f xs) :: k -> Type) #

injections :: forall k (xs :: [k]) (f :: k -> Type). SListI xs => NP (Injection f xs) xs #

shift :: forall a1 (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Injection f xs a2 -> Injection f (x ': xs) a2 #

shiftInjection :: forall a1 (f :: a1 -> Type) (xs :: [a1]) (a2 :: a1) (x :: a1). Injection f xs a2 -> Injection f (x ': xs) a2 #

type family UnProd (h :: (k -> Type) -> l -> Type) :: (k -> Type) -> l -> Type #

Instances

Instances details
type UnProd (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (NP :: (k -> Type) -> [k] -> Type) = NS :: (k -> Type) -> [k] -> Type
type UnProd (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

type UnProd (POP :: (k -> Type) -> [[k]] -> Type) = SOP :: (k -> Type) -> [[k]] -> Type

class UnProd (Prod h) ~ h => HApInjs (h :: (k -> Type) -> l -> Type) where #

Methods

hapInjs :: forall (xs :: l) (f :: k -> Type). SListIN h xs => Prod h f xs -> [h f xs] #

Instances

Instances details
HApInjs (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type). SListIN SOP xs => Prod SOP f xs -> [SOP f xs] #

HApInjs (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hapInjs :: forall (xs :: l) (f :: k0 -> Type). SListIN NS xs => Prod NS f xs -> [NS f xs] #

apInjs_NP :: forall k (xs :: [k]) (f :: k -> Type). SListI xs => NP f xs -> [NS f xs] #

apInjs_POP :: forall k (xss :: [[k]]) (f :: k -> Type). SListI xss => POP f xss -> [SOP f xss] #

Destructing sums

unZ :: forall k f (x :: k). NS f '[x] -> f x #

class HIndex (h :: (k -> Type) -> l -> Type) where #

Methods

hindex :: forall (f :: k -> Type) (xs :: l). h f xs -> Int #

Instances

Instances details
HIndex (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type) (xs :: l). SOP f xs -> Int #

HIndex (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hindex :: forall (f :: k0 -> Type) (xs :: l). NS f xs -> Int #

type Ejection (f :: k -> Type) (xs :: [k]) = (K (NS f xs) :: k -> Type) -.-> (Maybe :.: f) #

ejections :: forall k (xs :: [k]) (f :: k -> Type). SListI xs => NP (Ejection f xs) xs #

shiftEjection :: forall a1 (f :: a1 -> Type) (x :: a1) (xs :: [a1]) (a2 :: a1). Ejection f xs a2 -> Ejection f (x ': xs) a2 #

Dealing with All c

hcliftA' :: forall k (c :: k -> Constraint) (xss :: [[k]]) h proxy f f'. (All2 c xss, Prod h ~ (NP :: ([k] -> Type) -> [[k]] -> Type), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs) -> h f xss -> h f' xss #

hcliftA2' :: forall k (c :: k -> Constraint) (xss :: [[k]]) h proxy f f' f''. (All2 c xss, Prod h ~ (NP :: ([k] -> Type) -> [[k]] -> Type), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss #

hcliftA3' :: forall k (c :: k -> Constraint) (xss :: [[k]]) h proxy f f' f'' f'''. (All2 c xss, Prod h ~ (NP :: ([k] -> Type) -> [[k]] -> Type), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss #

Comparison

compare_NS :: forall k r f g (xs :: [k]). r -> (forall (x :: k). f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r #

ccompare_NS :: forall k c proxy r f g (xs :: [k]). All c xs => proxy c -> r -> (forall (x :: k). c x => f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r #

compare_SOP :: forall k r (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). r -> (forall (xs :: [k]). NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r #

ccompare_SOP :: forall k (c :: k -> Constraint) proxy r (f :: k -> Type) (g :: k -> Type) (xss :: [[k]]). All2 c xss => proxy c -> r -> (forall (xs :: [k]). All c xs => NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r #

Collapsing

type family CollapseTo (h :: (k -> Type) -> l -> Type) x #

Instances

Instances details
type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (NS :: (k -> Type) -> [k] -> Type) a = a
type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a 
Instance details

Defined in Data.SOP.NS

type CollapseTo (SOP :: (k -> Type) -> [[k]] -> Type) a = [a]
type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (NP :: (k -> Type) -> [k] -> Type) a = [a]
type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a 
Instance details

Defined in Data.SOP.NP

type CollapseTo (POP :: (k -> Type) -> [[k]] -> Type) a = [[a]]

class HCollapse (h :: (k -> Type) -> l -> Type) where #

Methods

hcollapse :: forall (xs :: l) a. SListIN h xs => h (K a :: k -> Type) xs -> CollapseTo h a #

Instances

Instances details
HCollapse (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN SOP xs => SOP (K a) xs -> CollapseTo SOP a #

HCollapse (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hcollapse :: forall (xs :: l) a. SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HCollapse (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN POP xs => POP (K a) xs -> CollapseTo POP a #

HCollapse (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hcollapse :: forall (xs :: l) a. SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

Folding and sequencing

class HTraverse_ (h :: (k -> Type) -> l -> Type) where #

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> h f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g ()) -> h f xs -> g () #

Instances

Instances details
HTraverse_ (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () #

HTraverse_ (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () #

HTraverse_ (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () #

HTraverse_ (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hctraverse_ :: forall c (xs :: l) g proxy f. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: forall (xs :: l) g f. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

hcfoldMap :: forall k l h c (xs :: l) m proxy f. (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> h f xs -> m #

hcfor_ :: forall k l h c (xs :: l) g proxy f. (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall (a :: k). c a => f a -> g ()) -> g () #

class HAp h => HSequence (h :: (k -> Type) -> l -> Type) where #

Methods

hsequence' :: forall (xs :: l) f (g :: k -> Type). (SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> h f xs -> g (h f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> h f xs -> g (h f' xs) #

Instances

Instances details
HSequence (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) #

HSequence (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) #

HSequence (POP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) #

HSequence (NP :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

hsequence' :: forall (xs :: l) f (g :: k0 -> Type). (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: forall c (xs :: l) g proxy f f'. (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: forall (xs :: l) g f f'. (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

hsequence :: forall l h (xs :: l) f. (SListIN h xs, SListIN (Prod h) xs, HSequence h, Applicative f) => h f xs -> f (h I xs) #

hsequenceK :: forall k l h (xs :: l) f a. (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a) :: k -> Type) xs -> f (h (K a :: k -> Type) xs) #

hctraverse :: forall l h c (xs :: l) g proxy f. (HSequence h, AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> h f xs -> g (h I xs) #

hcfor :: forall l h c (xs :: l) g proxy f. (HSequence h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g a) -> g (h I xs) #

Expanding sums to products

class HExpand (h :: (k -> Type) -> l -> Type) where #

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod h) xs => (forall (x :: k). f x) -> h f xs -> Prod h f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod h) c xs => proxy c -> (forall (x :: k). c x => f x) -> h f xs -> Prod h f xs #

Instances

Instances details
HExpand (SOP :: (k -> Type) -> [[k]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod SOP) xs => (forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod SOP) c xs => proxy c -> (forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs #

HExpand (NS :: (k -> Type) -> [k] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

hexpand :: forall (xs :: l) f. SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: forall c (xs :: l) proxy f. AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

Transformation of index lists and coercions

class ((Same h1 :: (k2 -> Type) -> l2 -> Type) ~ h2, (Same h2 :: (k1 -> Type) -> l1 -> Type) ~ h1) => HTrans (h1 :: (k1 -> Type) -> l1 -> Type) (h2 :: (k2 -> Type) -> l2 -> Type) where #

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod h1) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> h1 f xs -> h2 g ys #

hcoerce :: forall (f :: k1 -> Type) (g :: k2 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod h1) (LiftedCoercible f g) xs ys, HTrans h1 h2) => h1 f xs -> h2 g ys #

Instances

Instances details
HTrans (SOP :: (k1 -> Type) -> [[k1]] -> Type) (SOP :: (k2 -> Type) -> [[k2]] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod SOP) (LiftedCoercible f g) xs ys, HTrans SOP SOP) => SOP f xs -> SOP g ys #

HTrans (NS :: (k1 -> Type) -> [k1] -> Type) (NS :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NS

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod NS) (LiftedCoercible f g) xs ys, HTrans NS NS) => NS f xs -> NS g ys #

HTrans (POP :: (k1 -> Type) -> [[k1]] -> Type) (POP :: (k2 -> Type) -> [[k2]] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod POP) (LiftedCoercible f g) xs ys, HTrans POP POP) => POP f xs -> POP g ys #

HTrans (NP :: (k1 -> Type) -> [k1] -> Type) (NP :: (k2 -> Type) -> [k2] -> Type) 
Instance details

Defined in Data.SOP.NP

Methods

htrans :: forall c (xs :: l1) (ys :: l2) proxy f g. AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: forall (f :: k10 -> Type) (g :: k20 -> Type) (xs :: l1) (ys :: l2). (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

hfromI :: forall l1 k2 l2 h1 (f :: k2 -> Type) (xs :: l1) (ys :: l2) h2. (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys #

htoI :: forall k1 l1 l2 h1 (f :: k1 -> Type) (xs :: l1) (ys :: l2) h2. (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys #

Partial operations

fromList :: forall k (xs :: [k]) a. SListI xs => [a] -> Maybe (NP (K a :: k -> Type) xs) #

Utilities

Basic functors

newtype K a (b :: k) #

Constructors

K a 

Instances

Instances details
Eq2 (K :: Type -> Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> K a c -> K b d -> Bool #

Ord2 (K :: Type -> Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> K a c -> K b d -> Ordering #

Read2 (K :: Type -> Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] #

Show2 (K :: Type -> Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> K a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [K a b] -> ShowS #

NFData2 (K :: Type -> Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> K a b -> () #

Functor (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a0 -> b) -> K a a0 -> K a b #

(<$) :: a0 -> K a b -> K a a0 #

Monoid a => Applicative (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a0 -> K a a0 #

(<*>) :: K a (a0 -> b) -> K a a0 -> K a b #

liftA2 :: (a0 -> b -> c) -> K a a0 -> K a b -> K a c #

(*>) :: K a a0 -> K a b -> K a b #

(<*) :: K a a0 -> K a b -> K a a0 #

Foldable (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => K a m -> m #

foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m #

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

foldr :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

toList :: K a a0 -> [a0] #

null :: K a a0 -> Bool #

length :: K a a0 -> Int #

elem :: Eq a0 => a0 -> K a a0 -> Bool #

maximum :: Ord a0 => K a a0 -> a0 #

minimum :: Ord a0 => K a a0 -> a0 #

sum :: Num a0 => K a a0 -> a0 #

product :: Num a0 => K a a0 -> a0 #

Traversable (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

sequenceA :: Applicative f => K a (f a0) -> f (K a a0) #

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

sequence :: Monad m => K a (m a0) -> m (K a a0) #

Eq a => Eq1 (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a0 -> b -> Bool) -> K a a0 -> K a b -> Bool #

Ord a => Ord1 (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a0 -> b -> Ordering) -> K a a0 -> K a b -> Ordering #

Read a => Read1 (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (K a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [K a a0] #

Show a => Show1 (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

NFData a => NFData1 (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a0 -> ()) -> K a a0 -> () #

Eq a => Eq (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: K a b -> K a b -> Bool #

(/=) :: K a b -> K a b -> Bool #

Ord a => Ord (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: K a b -> K a b -> Ordering #

(<) :: K a b -> K a b -> Bool #

(<=) :: K a b -> K a b -> Bool #

(>) :: K a b -> K a b -> Bool #

(>=) :: K a b -> K a b -> Bool #

max :: K a b -> K a b -> K a b #

min :: K a b -> K a b -> K a b #

Read a => Read (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (K a b) #

readList :: ReadS [K a b] #

readPrec :: ReadPrec (K a b) #

readListPrec :: ReadPrec [K a b] #

Show a => Show (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> K a b -> ShowS #

show :: K a b -> String #

showList :: [K a b] -> ShowS #

Generic (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: K a b -> K a b -> K a b #

sconcat :: NonEmpty (K a b) -> K a b #

stimes :: Integral b0 => b0 -> K a b -> K a b #

Monoid a => Monoid (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: K a b #

mappend :: K a b -> K a b -> K a b #

mconcat :: [K a b] -> K a b #

NFData a => NFData (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: K a b -> () #

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 #

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 #

type Rep (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (K a b) = D1 ('MetaData "K" "Data.SOP.BasicFunctors" "sop-core-0.5.0.0-inplace" 'True) (C1 ('MetaCons "K" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type DatatypeInfoOf (K a b) Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (K a b) = 'Newtype "Data.SOP.BasicFunctors" "K" ('Constructor "K")
type Code (K a b) Source # 
Instance details

Defined in Generics.SOP.Instances

type Code (K a b) = '['[a]]

unK :: forall k a (b :: k). K a b -> a #

newtype I a #

Constructors

I a 

Instances

Instances details
Monad I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

return :: a -> I a #

Functor I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

Applicative I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a -> I a #

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

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

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

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

Foldable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

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

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

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

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

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

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

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

toList :: I a -> [a] #

null :: I a -> Bool #

length :: I a -> Int #

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

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

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

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

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

Traversable I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

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

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

Eq1 I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

Ord1 I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

Read1 I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

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

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

Show1 I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

NFData1 I 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

Eq a => Eq (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

Ord a => Ord (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: I a -> I a -> Ordering #

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

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

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

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

max :: I a -> I a -> I a #

min :: I a -> I a -> I a #

Read a => Read (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (I a) #

readList :: ReadS [I a] #

readPrec :: ReadPrec (I a) #

readListPrec :: ReadPrec [I a] #

Show a => Show (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

show :: I a -> String #

showList :: [I a] -> ShowS #

Generic (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

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

Methods

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

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

Semigroup a => Semigroup (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

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

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

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

Monoid a => Monoid (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: I a #

mappend :: I a -> I a -> I a #

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

NFData a => NFData (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: I a -> () #

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 #

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 #

type Rep (I a) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (I a) = D1 ('MetaData "I" "Data.SOP.BasicFunctors" "sop-core-0.5.0.0-inplace" 'True) (C1 ('MetaCons "I" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type DatatypeInfoOf (I a) Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (I a) = 'Newtype "Data.SOP.BasicFunctors" "I" ('Constructor "I")
type Code (I a) Source # 
Instance details

Defined in Generics.SOP.Instances

type Code (I a) = '['[a]]

unI :: I a -> a #

newtype ((f :: l -> Type) :.: (g :: k -> l)) (p :: k) #

Constructors

Comp (f (g p)) 

Instances

Instances details
(Functor f, Functor g) => Functor (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b #

(<$) :: a -> (f :.: g) b -> (f :.: g) a #

(Applicative f, Applicative g) => Applicative (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

(Foldable f, Foldable g) => Foldable (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => (f :.: g) m -> m #

foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m #

foldMap' :: Monoid m => (a -> m) -> (f :.: g) a -> m #

foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b #

foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b #

foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b #

foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b #

foldr1 :: (a -> a -> a) -> (f :.: g) a -> a #

foldl1 :: (a -> a -> a) -> (f :.: g) a -> a #

toList :: (f :.: g) a -> [a] #

null :: (f :.: g) a -> Bool #

length :: (f :.: g) a -> Int #

elem :: Eq a => a -> (f :.: g) a -> Bool #

maximum :: Ord a => (f :.: g) a -> a #

minimum :: Ord a => (f :.: g) a -> a #

sum :: Num a => (f :.: g) a -> a #

product :: Num a => (f :.: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) #

sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) #

mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) #

sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) #

(Eq1 f, Eq1 g) => Eq1 (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> (f :.: g) a -> (f :.: g) b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> (f :.: g) a -> (f :.: g) b -> Ordering #

(Read1 f, Read1 g) => Read1 (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g) => Show1 (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :.: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :.: g) a] -> ShowS #

(NFData1 f, NFData1 g) => NFData1 (f :.: g) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> (f :.: g) a -> () #

(Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: (f :.: g) a -> (f :.: g) a -> Bool #

(/=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: (f :.: g) a -> (f :.: g) a -> Ordering #

(<) :: (f :.: g) a -> (f :.: g) a -> Bool #

(<=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>=) :: (f :.: g) a -> (f :.: g) a -> Bool #

max :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

min :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

(Read1 f, Read1 g, Read a) => Read ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS ((f :.: g) a) #

readList :: ReadS [(f :.: g) a] #

readPrec :: ReadPrec ((f :.: g) a) #

readListPrec :: ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g, Show a) => Show ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> (f :.: g) a -> ShowS #

show :: (f :.: g) a -> String #

showList :: [(f :.: g) a] -> ShowS #

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

Defined in Data.SOP.BasicFunctors

Associated Types

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

Methods

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

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

Semigroup (f (g x)) => Semigroup ((f :.: g) x) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x #

sconcat :: NonEmpty ((f :.: g) x) -> (f :.: g) x #

stimes :: Integral b => b -> (f :.: g) x -> (f :.: g) x #

Monoid (f (g x)) => Monoid ((f :.: g) x) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: (f :.: g) x #

mappend :: (f :.: g) x -> (f :.: g) x -> (f :.: g) x #

mconcat :: [(f :.: g) x] -> (f :.: g) x #

NFData (f (g a)) => NFData ((f :.: g) a) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: (f :.: g) a -> () #

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 #

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 #

type Rep ((f :.: g) p) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep ((f :.: g) p) = D1 ('MetaData ":.:" "Data.SOP.BasicFunctors" "sop-core-0.5.0.0-inplace" 'True) (C1 ('MetaCons "Comp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (g p)))))
type DatatypeInfoOf ((f :.: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf ((f :.: g) p) = 'Newtype "Data.SOP.BasicFunctors" ":.:" ('Constructor "Comp")
type Code ((f :.: g) p) Source # 
Instance details

Defined in Generics.SOP.Instances

type Code ((f :.: g) p) = '['[f (g p)]]

unComp :: forall l k f (g :: k -> l) (p :: k). (f :.: g) p -> f (g p) #

Mapping functions

mapII :: (a -> b) -> I a -> I b #

mapIK :: forall k a b (c :: k). (a -> b) -> I a -> K b c #

mapKI :: forall k a b (c :: k). (a -> b) -> K a c -> I b #

mapKK :: forall k1 k2 a b (c :: k1) (d :: k2). (a -> b) -> K a c -> K b d #

mapIII :: (a -> b -> c) -> I a -> I b -> I c #

mapIIK :: forall k a b c (d :: k). (a -> b -> c) -> I a -> I b -> K c d #

mapIKI :: forall k a b c (d :: k). (a -> b -> c) -> I a -> K b d -> I c #

mapIKK :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> I a -> K b d -> K c e #

mapKII :: forall k a b c (d :: k). (a -> b -> c) -> K a d -> I b -> I c #

mapKIK :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> I b -> K c e #

mapKKI :: forall k1 k2 a b c (d :: k1) (e :: k2). (a -> b -> c) -> K a d -> K b e -> I c #

mapKKK :: forall k1 k2 k3 a b c (d :: k1) (e :: k2) (f :: k3). (a -> b -> c) -> K a d -> K b e -> K c f #

Mapping constraints

class (AllF c xs, SListI xs) => All (c :: k -> Constraint) (xs :: [k]) #

Minimal complete definition

cpara_SList

Instances

Instances details
All (c :: k -> Constraint) ('[] :: [k]) 
Instance details

Defined in Data.SOP.Constraint

Methods

cpara_SList :: proxy c -> r '[] -> (forall (y :: k0) (ys :: [k0]). (c y, All c ys) => r ys -> r (y ': ys)) -> r '[] #

(c x, All c xs) => All (c :: a -> Constraint) (x ': xs :: [a]) 
Instance details

Defined in Data.SOP.Constraint

Methods

cpara_SList :: proxy c -> r '[] -> (forall (y :: k) (ys :: [k]). (c y, All c ys) => r ys -> r (y ': ys)) -> r (x ': xs) #

type All2 (c :: k -> Constraint) = All (All c) #

cpara_SList :: All c xs => proxy c -> r ('[] :: [k]) -> (forall (y :: k) (ys :: [k]). (c y, All c ys) => r ys -> r (y ': ys)) -> r xs #

ccase_SList :: forall k c (xs :: [k]) proxy r. All c xs => proxy c -> r ('[] :: [k]) -> (forall (y :: k) (ys :: [k]). (c y, All c ys) => r (y ': ys)) -> r xs #

class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) #

Instances

Instances details
(SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) 
Instance details

Defined in Data.SOP.Constraint

class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]]) #

Instances

Instances details
(AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]]) 
Instance details

Defined in Data.SOP.Constraint

type family AllN (h :: (k -> Type) -> l -> Type) (c :: k -> Constraint) :: l -> Constraint #

Instances

Instances details
type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (NS :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c
type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NS

type AllN (SOP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) = All2 c
type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (NP :: (k -> Type) -> [k] -> Type) (c :: k -> Constraint) = All c
type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllN (POP :: (k -> Type) -> [[k]] -> Type) (c :: k -> Constraint) = All2 c

type family AllZipN (h :: (k -> Type) -> l -> Type) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint #

Instances

Instances details
type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (NP :: (k -> Type) -> [k] -> Type) (c :: a -> b -> Constraint) = AllZip c
type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) 
Instance details

Defined in Data.SOP.NP

type AllZipN (POP :: (k -> Type) -> [[k]] -> Type) (c :: a -> b -> Constraint) = AllZip2 c

Other constraints

class f (g x) => Compose (f :: k -> Constraint) (g :: k1 -> k) (x :: k1) #

Instances

Instances details
f (g x) => Compose (f :: k1 -> Constraint) (g :: k2 -> k1) (x :: k2) 
Instance details

Defined in Data.SOP.Constraint

class (f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) #

Instances

Instances details
(f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) 
Instance details

Defined in Data.SOP.Constraint

class Top (x :: k) #

Instances

Instances details
Top (x :: k) 
Instance details

Defined in Data.SOP.Constraint

class Coercible (f x) (g y) => LiftedCoercible (f :: k -> k1) (g :: k2 -> k1) (x :: k) (y :: k2) #

Instances

Instances details
Coercible (f x) (g y) => LiftedCoercible (f :: k1 -> k2) (g :: k3 -> k2) (x :: k1) (y :: k3) 
Instance details

Defined in Data.SOP.Constraint

type family SameShapeAs (xs :: [a]) (ys :: [b]) where ... #

Equations

SameShapeAs ('[] :: [a]) (ys :: [b]) = ys ~ ('[] :: [b]) 
SameShapeAs (x ': xs :: [a1]) (ys :: [a2]) = ys ~ (Head ys ': Tail ys) 

Singletons

data SList (a :: [k]) where #

Constructors

SNil :: forall k. SList ('[] :: [k]) 
SCons :: forall k (xs :: [k]) (x :: k). SListI xs => SList (x ': xs) 

Instances

Instances details
Eq (SList xs) 
Instance details

Defined in Data.SOP.Sing

Methods

(==) :: SList xs -> SList xs -> Bool #

(/=) :: SList xs -> SList xs -> Bool #

Ord (SList xs) 
Instance details

Defined in Data.SOP.Sing

Methods

compare :: SList xs -> SList xs -> Ordering #

(<) :: SList xs -> SList xs -> Bool #

(<=) :: SList xs -> SList xs -> Bool #

(>) :: SList xs -> SList xs -> Bool #

(>=) :: SList xs -> SList xs -> Bool #

max :: SList xs -> SList xs -> SList xs #

min :: SList xs -> SList xs -> SList xs #

Show (SList xs) 
Instance details

Defined in Data.SOP.Sing

Methods

showsPrec :: Int -> SList xs -> ShowS #

show :: SList xs -> String #

showList :: [SList xs] -> ShowS #

type SListI = All (Top :: k -> Constraint) #

type SListI2 = All (SListI :: [k] -> Constraint) #

sList :: forall k (xs :: [k]). SListI xs => SList xs #

para_SList :: forall k (xs :: [k]) r. SListI xs => r ('[] :: [k]) -> (forall (y :: k) (ys :: [k]). SListI ys => r ys -> r (y ': ys)) -> r xs #

case_SList :: forall k (xs :: [k]) r. SListI xs => r ('[] :: [k]) -> (forall (y :: k) (ys :: [k]). SListI ys => r (y ': ys)) -> r xs #

Shape of type-level lists

data Shape (a :: [k]) where #

Constructors

ShapeNil :: forall k. Shape ('[] :: [k]) 
ShapeCons :: forall k (xs :: [k]) (x :: k). SListI xs => Shape xs -> Shape (x ': xs) 

Instances

Instances details
Eq (Shape xs) 
Instance details

Defined in Data.SOP.Sing

Methods

(==) :: Shape xs -> Shape xs -> Bool #

(/=) :: Shape xs -> Shape xs -> Bool #

Ord (Shape xs) 
Instance details

Defined in Data.SOP.Sing

Methods

compare :: Shape xs -> Shape xs -> Ordering #

(<) :: Shape xs -> Shape xs -> Bool #

(<=) :: Shape xs -> Shape xs -> Bool #

(>) :: Shape xs -> Shape xs -> Bool #

(>=) :: Shape xs -> Shape xs -> Bool #

max :: Shape xs -> Shape xs -> Shape xs #

min :: Shape xs -> Shape xs -> Shape xs #

Show (Shape xs) 
Instance details

Defined in Data.SOP.Sing

Methods

showsPrec :: Int -> Shape xs -> ShowS #

show :: Shape xs -> String #

showList :: [Shape xs] -> ShowS #

shape :: forall k (xs :: [k]). SListI xs => Shape xs #

lengthSList :: forall k (xs :: [k]) proxy. SListI xs => proxy xs -> Int #

Re-exports

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

return :: a -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

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

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

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

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

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

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

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

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

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

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

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

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

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

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

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

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

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

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

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

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

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

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

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Data t => Data (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) #

toConstr :: Proxy t -> Constr #

dataTypeOf :: Proxy t -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

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 #

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 #

type Rep1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))
type DatatypeInfoOf (Proxy t) Source # 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (Proxy t) = 'ADT "Data.Proxy" "Proxy" '['Constructor "Proxy"] '['[] :: [StrictnessInfo]]
type Code (Proxy t) Source # 
Instance details

Defined in Generics.SOP.Instances

type Code (Proxy t) = '['[] :: [Type]]