Safe Haskell | None |
---|---|
Language | Haskell2010 |
Codes and interpretations
Synopsis
- type Rep a = SOP I (Code a)
- class All SListI (Code a) => Generic (a :: *) where
- class HasDatatypeInfo a where
- type DatatypeInfoOf a :: DatatypeInfo
- type IsProductType (a :: *) (xs :: [*]) = (Generic a, Code a ~ '[xs])
- type IsEnumType (a :: *) = (Generic a, All ((~) '[]) (Code a))
- type IsWrappedType (a :: *) (x :: *) = (Generic a, Code a ~ '['[x]])
- type IsNewtype (a :: *) (x :: *) = (IsWrappedType a x, Coercible a x)
Documentation
class All SListI (Code a) => Generic (a :: *) where Source #
The class of representable datatypes.
The SOP approach to generic programming is based on viewing
datatypes as a representation (Rep
) built from the sum of
products of its components. The components of are datatype
are specified using the Code
type family.
The isomorphism between the original Haskell datatype and its
representation is witnessed by the methods of this class,
from
and to
. So for instances of this class, the following
laws should (in general) hold:
to
.
from
===id
:: a -> afrom
.
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
, ...) instanceGeneric
T -- empty instanceHasDatatypeInfo
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 -- derivesHasDatatypeInfo
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.
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 ] ]
Converts from a value to its structural representation.
from :: (GFrom a, Generic a, Rep a ~ SOP I (GCode a)) => a -> Rep a Source #
Converts from a value to its structural representation.
Converts from a structural representation back to the original value.
to :: (GTo a, Generic a, Rep a ~ SOP I (GCode a)) => Rep a -> a Source #
Converts from a structural representation back to the original value.
Instances
Generic Bool Source # | |
Generic Ordering Source # | |
Generic () Source # | |
Generic DataRep Source # | |
Generic ConstrRep Source # | |
Generic Fixity Source # | |
Generic FormatAdjustment Source # | |
Defined in Generics.SOP.Instances type Code FormatAdjustment :: [[*]] Source # | |
Generic FormatSign Source # | |
Defined in Generics.SOP.Instances type Code FormatSign :: [[*]] Source # from :: FormatSign -> Rep FormatSign Source # to :: Rep FormatSign -> FormatSign Source # | |
Generic FieldFormat Source # | |
Defined in Generics.SOP.Instances type Code FieldFormat :: [[*]] Source # from :: FieldFormat -> Rep FieldFormat Source # to :: Rep FieldFormat -> FieldFormat Source # | |
Generic FormatParse Source # | |
Defined in Generics.SOP.Instances type Code FormatParse :: [[*]] Source # from :: FormatParse -> Rep FormatParse Source # to :: Rep FormatParse -> FormatParse Source # | |
Generic Version Source # | |
Generic PatternMatchFail Source # | |
Defined in Generics.SOP.Instances type Code PatternMatchFail :: [[*]] Source # | |
Generic RecSelError Source # | |
Defined in Generics.SOP.Instances type Code RecSelError :: [[*]] Source # from :: RecSelError -> Rep RecSelError Source # to :: Rep RecSelError -> RecSelError Source # | |
Generic RecConError Source # | |
Defined in Generics.SOP.Instances type Code RecConError :: [[*]] Source # from :: RecConError -> Rep RecConError Source # to :: Rep RecConError -> RecConError Source # | |
Generic RecUpdError Source # | |
Defined in Generics.SOP.Instances type Code RecUpdError :: [[*]] Source # from :: RecUpdError -> Rep RecUpdError Source # to :: Rep RecUpdError -> RecUpdError Source # | |
Generic NoMethodError Source # | |
Defined in Generics.SOP.Instances type Code NoMethodError :: [[*]] Source # from :: NoMethodError -> Rep NoMethodError Source # to :: Rep NoMethodError -> NoMethodError Source # | |
Generic NonTermination Source # | |
Defined in Generics.SOP.Instances type Code NonTermination :: [[*]] Source # from :: NonTermination -> Rep NonTermination Source # to :: Rep NonTermination -> NonTermination Source # | |
Generic NestedAtomically Source # | |
Defined in Generics.SOP.Instances type Code NestedAtomically :: [[*]] Source # | |
Generic Errno Source # | |
Generic BlockedIndefinitelyOnMVar Source # | |
Defined in Generics.SOP.Instances type Code BlockedIndefinitelyOnMVar :: [[*]] Source # | |
Generic BlockedIndefinitelyOnSTM Source # | |
Defined in Generics.SOP.Instances type Code BlockedIndefinitelyOnSTM :: [[*]] Source # | |
Generic Deadlock Source # | |
Generic AssertionFailed Source # | |
Defined in Generics.SOP.Instances type Code AssertionFailed :: [[*]] Source # from :: AssertionFailed -> Rep AssertionFailed Source # to :: Rep AssertionFailed -> AssertionFailed Source # | |
Generic AsyncException Source # | |
Defined in Generics.SOP.Instances type Code AsyncException :: [[*]] Source # from :: AsyncException -> Rep AsyncException Source # to :: Rep AsyncException -> AsyncException Source # | |
Generic ArrayException Source # | |
Defined in Generics.SOP.Instances type Code ArrayException :: [[*]] Source # from :: ArrayException -> Rep ArrayException Source # to :: Rep ArrayException -> ArrayException Source # | |
Generic ExitCode Source # | |
Generic BufferMode Source # | |
Defined in Generics.SOP.Instances type Code BufferMode :: [[*]] Source # from :: BufferMode -> Rep BufferMode Source # to :: Rep BufferMode -> BufferMode Source # | |
Generic Newline Source # | |
Generic NewlineMode Source # | |
Defined in Generics.SOP.Instances type Code NewlineMode :: [[*]] Source # from :: NewlineMode -> Rep NewlineMode Source # to :: Rep NewlineMode -> NewlineMode Source # | |
Generic SeekMode Source # | |
Generic MaskingState Source # | |
Defined in Generics.SOP.Instances type Code MaskingState :: [[*]] Source # from :: MaskingState -> Rep MaskingState Source # to :: Rep MaskingState -> MaskingState Source # | |
Generic IOException Source # | |
Defined in Generics.SOP.Instances type Code IOException :: [[*]] Source # from :: IOException -> Rep IOException Source # to :: Rep IOException -> IOException Source # | |
Generic ErrorCall Source # | |
Generic ArithException Source # | |
Defined in Generics.SOP.Instances type Code ArithException :: [[*]] Source # from :: ArithException -> Rep ArithException Source # to :: Rep ArithException -> ArithException Source # | |
Generic All Source # | |
Generic Any Source # | |
Generic CChar Source # | |
Generic CSChar Source # | |
Generic CUChar Source # | |
Generic CShort Source # | |
Generic CUShort Source # | |
Generic CInt Source # | |
Generic CUInt Source # | |
Generic CLong Source # | |
Generic CULong Source # | |
Generic CLLong Source # | |
Generic CULLong Source # | |
Generic CFloat Source # | |
Generic CDouble Source # | |
Generic CPtrdiff Source # | |
Generic CSize Source # | |
Generic CWchar Source # | |
Generic CSigAtomic Source # | |
Defined in Generics.SOP.Instances type Code CSigAtomic :: [[*]] Source # from :: CSigAtomic -> Rep CSigAtomic Source # to :: Rep CSigAtomic -> CSigAtomic Source # | |
Generic CClock Source # | |
Generic CTime Source # | |
Generic CUSeconds Source # | |
Generic CSUSeconds Source # | |
Defined in Generics.SOP.Instances type Code CSUSeconds :: [[*]] Source # from :: CSUSeconds -> Rep CSUSeconds Source # to :: Rep CSUSeconds -> CSUSeconds Source # | |
Generic CIntPtr Source # | |
Generic CUIntPtr Source # | |
Generic CIntMax Source # | |
Generic CUIntMax Source # | |
Generic IOMode Source # | |
Generic Lexeme Source # | |
Generic Number Source # | |
Generic GeneralCategory Source # | |
Defined in Generics.SOP.Instances type Code GeneralCategory :: [[*]] Source # from :: GeneralCategory -> Rep GeneralCategory Source # to :: Rep GeneralCategory -> GeneralCategory Source # | |
Generic [a] Source # | |
Generic (Maybe a) Source # | |
Generic (Complex a) Source # | |
Generic (Fixed a) Source # | |
Generic (ArgOrder a) Source # | |
Generic (OptDescr a) Source # | |
Generic (ArgDescr a) Source # | |
Generic (First a) Source # | |
Generic (Last a) Source # | |
Generic (Dual a) Source # | |
Generic (Endo a) Source # | |
Generic (Sum a) Source # | |
Generic (Product a) Source # | |
Generic (Down a) Source # | |
Generic (I a) Source # | |
Generic (Either a b) Source # | |
Generic (a, b) Source # | |
Generic (Proxy t) Source # | |
Generic (a, b, c) Source # | |
Generic (K a b) Source # | |
Generic (a, b, c, d) Source # | |
Generic (a, b, c, d, e) Source # | |
Generic ((f :.: g) p) Source # | |
Generic (a, b, c, d, e, f) Source # | |
Generic (a, b, c, d, e, f, g) Source # | |
Generic (a, b, c, d, e, f, g, h) Source # | |
Generic (a, b, c, d, e, f, g, h, i) Source # | |
Generic (a, b, c, d, e, f, g, h, i, j) Source # | |
Generic (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 # | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
Defined in Generics.SOP.Instances | |
Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
Defined in Generics.SOP.Instances 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 # | |
Defined in Generics.SOP.Instances 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 # | |
Defined in Generics.SOP.Instances 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) :: [[*]] Source # 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 # | |
Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) :: [[*]] Source # from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source # to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) Source # |
class HasDatatypeInfo a where Source #
A class of datatypes that have associated metadata.
It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.
You typically don't define instances of this class by hand, but
rather derive the class instance automatically. See the documentation
of Generic
for the options.
type DatatypeInfoOf a :: DatatypeInfo Source #
Type-level datatype info
datatypeInfo :: proxy a -> DatatypeInfo (Code a) Source #
Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.
datatypeInfo :: (GDatatypeInfo a, GCode a ~ Code a) => proxy a -> DatatypeInfo (Code a) Source #
Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.
Instances
type IsProductType (a :: *) (xs :: [*]) = (Generic a, Code a ~ '[xs]) Source #
Constraint that captures that a datatype is a product type, i.e., a type with a single constructor.
It also gives access to the code for the arguments of that constructor.
Since: 0.3.1.0
type IsEnumType (a :: *) = (Generic a, All ((~) '[]) (Code a)) Source #
Constraint that captures that a datatype is an enumeration type, i.e., none of the constructors have any arguments.
Since: 0.3.1.0
type IsWrappedType (a :: *) (x :: *) = (Generic a, Code a ~ '['[x]]) Source #
Constraint that captures that a datatype is a single-constructor, single-field datatype. This always holds for newtype-defined types, but it can also be true for data-defined types.
The constraint also gives access to the type that is wrapped.
Since: 0.3.1.0