Safe Haskell | None |
---|---|
Language | Haskell2010 |
generics-eot
tries to be a library for datatype generic programming
that is easy to understand. "eot" stands for "eithers of tuples".
A tutorial on how to use generics-eot
can be found here:
https://generics-eot.readthedocs.io/.
Documentation
An instance (
) allows us toHasEot
a
- convert values of an arbitrary algebraic datatype
a
to and from a generic representation (
) (seeEot
atoEot
andfromEot
). - extract meta information about the type
a
(seedatatype
).
Once an algebraic datatype has an instance for Generic
it
automatically gets one for HasEot
.
Eot
is a type level function that maps arbitrary ADTs to isomorphic
generic representations. Here's an example:
data Foo = A Int Bool | B String
would be mapped to:
Either (Int, (Bool, ())) (Either (String, ()) Void)
These representations follow these rules:
- The choice between constructors is mapped to right-nested
Either
s. - There's always a so-called end-marker
Void
. It's an invalid choice (andVoid
is uninhabited to make sure you don't accidentally create such a value). So e.g.data Foo = A
would be mapped toEither () Void
, and a type with no constructors is mapped toVoid
. - The fields of one constructor are mapped to right-nested tuples.
- Again there's always an end-marker, this time of type
()
. A constructor with three fieldsa
,b
,c
is mapped to(a, (b, (c, ())))
, one fielda
is mapped to(a, ())
, and no fields are mapped to()
(just the end-marker).
These rules (and the end-markers) are necessary to make sure generic functions know exactly which parts of the generic representation are field types and which parts belong to the generic skeleton.
Meta Information
Type for meta information about ADTs.
Datatype | |
|
data Constructor Source #
Instances
Eq Constructor Source # | |
Defined in Generics.Eot.Datatype (==) :: Constructor -> Constructor -> Bool # (/=) :: Constructor -> Constructor -> Bool # | |
Show Constructor Source # | |
Defined in Generics.Eot.Datatype showsPrec :: Int -> Constructor -> ShowS # show :: Constructor -> String # showList :: [Constructor] -> ShowS # |
Type that represents meta information about fields of one constructor.
Selectors [String] | Record constructor, containing the list of the selector names. |
NoSelectors Int | Constructor with fields, but without selector names. The argument gives the number of fields. |
NoFields | Constructor without fields. |
Useful Re-exports
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
data Proxy (t :: k) :: forall k. k -> Type #
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,
is a safer alternative to the
Proxy
:: Proxy
a'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
Instances
Generic1 (Proxy :: k -> Type) | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> 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 # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |
Uninhabited data type
Since: base-4.8.0.0
Instances
Eq Void | Since: base-4.8.0.0 |
Data Void | Since: base-4.8.0.0 |
Defined in Data.Void gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Void -> c Void # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Void # dataTypeOf :: Void -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Void) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Void) # gmapT :: (forall b. Data b => b -> b) -> Void -> Void # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Void -> r # gmapQ :: (forall d. Data d => d -> u) -> Void -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Void -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Void -> m Void # | |
Ord Void | Since: base-4.8.0.0 |
Read Void | Reading a Since: base-4.8.0.0 |
Show Void | Since: base-4.8.0.0 |
Ix Void | Since: base-4.8.0.0 |
Generic Void | |
Semigroup Void | Since: base-4.9.0.0 |
Exception Void | Since: base-4.8.0.0 |
Defined in Data.Void toException :: Void -> SomeException # fromException :: SomeException -> Maybe Void # displayException :: Void -> String # | |
type Rep Void | Since: base-4.8.0.0 |