| Copyright | (c) 2021 Rudy Matela |
|---|---|
| License | 3-Clause BSD (see the file LICENSE) |
| Maintainer | Rudy Matela <rudy@matela.com.br> |
| Safe Haskell | None |
| Language | Haskell2010 |
Conjure.Conjurable
Description
This module is part of Conjure.
This defines the Conjurable typeclass
and utilities involving it.
You are probably better off importing Conjure.
Synopsis
- type Reification1 = (Expr, Expr, Maybe Expr, Maybe [[Expr]])
- type Reification = [Reification1] -> [Reification1]
- class Typeable a => Conjurable a where
- conjureArgumentHoles :: a -> [Expr]
- conjureEquality :: a -> Maybe Expr
- conjureTiers :: a -> Maybe [[Expr]]
- conjureSubTypes :: a -> Reification
- conjureType :: Conjurable a => a -> Reification
- reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
- reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr
- canonicalApplication :: Conjurable f => String -> f -> Expr
- canonicalVarApplication :: Conjurable f => String -> f -> Expr
- conjureIfs :: Conjurable f => f -> [Expr]
- conjureTiersFor :: Conjurable f => f -> Expr -> [[Expr]]
- conjureMkEquation :: Conjurable f => f -> Expr -> Expr -> Expr
Documentation
type Reification1 = (Expr, Expr, Maybe Expr, Maybe [[Expr]]) Source #
Single reification of some functions over a type as Exprs.
A hole, an if function, an equality function and tiers.
type Reification = [Reification1] -> [Reification1] Source #
A reification over a collection of types.
Represented as a transformation of a list to a list.
class Typeable a => Conjurable a where Source #
Class of Conjurable types.
Functions are Conjurable
if all their arguments are Conjurable, Listable and Showable.
For atomic types that are Listable,
instances are defined as:
instance Conjurable Atomic where conjureTiers = reifyTiers
For atomic types that are both Listable and Eq,
instances are defined as:
instance Conjurable Atomic where conjureTiers = reifyTiers conjureEquality = reifyEquality
For types with subtypes, instances are defined as:
instance Conjurable Composite where
conjureTiers = reifyTiers
conjureEquality = reifyEquality
conjureSubTypes x = conjureType y
. conjureType z
. conjureType w
where
(Composite ... y ... z ... w ...) = xAbove x, y, z and w are just proxies.
The Proxy type was avoided for backwards compatibility.
Please see the source code of Conjure.Conjurable for more examples.
(cf. reifyTiers, reifyEquality, conjureType)
Minimal complete definition
Nothing
Methods
conjureArgumentHoles :: a -> [Expr] Source #
conjureEquality :: a -> Maybe Expr Source #
conjureTiers :: a -> Maybe [[Expr]] Source #
conjureSubTypes :: a -> Reification Source #
Instances
conjureType :: Conjurable a => a -> Reification Source #
reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]] Source #
Reifies equality to be used in a conjurable type.
This is to be used
in the definition of conjureTiers
of Conjurable typeclass instances:
instance ... => Conjurable <Type> where ... conjureTiers = reifyTiers ...
reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr Source #
Reifies equality to be used in a conjurable type.
This is to be used
in the definition of conjureEquality
of Conjurable typeclass instances:
instance ... => Conjurable <Type> where ... conjureEquality = reifyEquality ...
canonicalApplication :: Conjurable f => String -> f -> Expr Source #
canonicalVarApplication :: Conjurable f => String -> f -> Expr Source #
conjureIfs :: Conjurable f => f -> [Expr] Source #
conjureTiersFor :: Conjurable f => f -> Expr -> [[Expr]] Source #
conjureMkEquation :: Conjurable f => f -> Expr -> Expr -> Expr Source #