Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
A model for simple algebraic data types.
- data TypeModel adtName consName inRef exRef = TypeModel {}
- type TypeEnv adtName consName inRef exRef = Map exRef (ADT adtName consName inRef)
- typeADTs :: TypeModel adtName consName inRef k -> [ADT adtName consName inRef]
- data ADT name consName ref = ADT {}
- data ConTree name ref
- = Con {
- constrName :: name
- constrFields :: Either [Type ref] [(name, Type ref)]
- | ConTree (ConTree name ref) (ConTree name ref)
- = Con {
- data Type ref
- data TypeN r = TypeN r [TypeN r]
- data TypeRef name
- data Name = Name String
- data QualName = QualName {}
- qualName :: QualName -> String
- adtNamesMap :: (adtName1 -> adtName2) -> (consName1 -> consName2) -> ADT adtName1 consName1 ref -> ADT adtName2 consName2 ref
- typeN :: Type r -> TypeN r
- typeA :: TypeN ref -> Type ref
- constructors :: ConTree t t1 -> [ConTree t t1]
- constructorInfo :: Eq consName => consName -> ConTree consName t -> Maybe ([Bool], [Type t])
- conTreeNameMap :: (name -> name2) -> ConTree name t -> ConTree name2 t
- conTreeTypeMap :: (Type t -> Type ref) -> ConTree name t -> ConTree name ref
- conTreeTypeList :: ConTree name t -> [Type t]
- conTreeTypeFoldMap :: Monoid a => (Type t -> a) -> ConTree name t -> a
- fieldsTypes :: Either [b] [(a, b)] -> [b]
- fieldsNames :: Either t [(a, t1)] -> [t1]
- type HTypeEnv = TypeEnv String String (TypeRef QualName) QualName
- type HTypeModel = TypeModel String String (TypeRef QualName) QualName
- type HADT = ADT String String HTypeRef
- type HType = Type HTypeRef
- type HTypeRef = TypeRef QualName
- solve :: (Ord k, Show k) => k -> Map k a -> a
- solveAll :: (Functor f, Show k, Ord k) => Map k b -> f k -> f b
- unVar :: TypeRef t -> t
- getHRef :: TypeRef a -> Maybe a
- module GHC.Generics
- data Proxy k t :: forall k. k -> * = Proxy
Model
data TypeModel adtName consName inRef exRef Source #
The complete model of a type, a reference to the type plus its environment:
- adtName: type used to represent the name of a data type
- consName: type used to represent the name of a constructor
- inRef: type used to represent a reference to a type or a type variable inside the data type definition (for example
HTypeRef
) - exRef: type used to represent a reference to a type in the type name (for example
QualName
)
(Eq adtName, Eq inRef, Eq consName, Eq exRef) => Eq (TypeModel adtName consName inRef exRef) Source # | |
(Ord adtName, Ord inRef, Ord consName, Ord exRef) => Ord (TypeModel adtName consName inRef exRef) Source # | |
(Show adtName, Show inRef, Show consName, Show exRef) => Show (TypeModel adtName consName inRef exRef) Source # | |
Generic (TypeModel adtName consName inRef exRef) Source # | |
(NFData adtName, NFData inRef, NFData consName, NFData exRef) => NFData (TypeModel adtName consName inRef exRef) Source # | |
type Rep (TypeModel adtName consName inRef exRef) Source # | |
type TypeEnv adtName consName inRef exRef = Map exRef (ADT adtName consName inRef) Source #
A map of all the ADTs that are directly or indirectly referred by a type, indexed by a type reference
typeADTs :: TypeModel adtName consName inRef k -> [ADT adtName consName inRef] Source #
The ADTs defined in the TypeModel
data ADT name consName ref Source #
Simple algebraic data type (not a GADT):
- declName: type used to represent the name of the data type
- consName: type used to represent the name of a constructor
- ref: type used to represent a reference to a type or a type variable inside the data type definition (for example
HTypeRef
)
Functor (ADT name consName) Source # | |
Foldable (ADT name consName) Source # | |
Traversable (ADT name consName) Source # | |
(Eq consName, Eq ref, Eq name) => Eq (ADT name consName ref) Source # | |
(Ord consName, Ord ref, Ord name) => Ord (ADT name consName ref) Source # | |
(Show consName, Show ref, Show name) => Show (ADT name consName ref) Source # | |
Generic (ADT name consName ref) Source # | |
(NFData consName, NFData ref, NFData name) => NFData (ADT name consName ref) Source # | |
type Rep (ADT name consName ref) Source # | |
data ConTree name ref Source #
Constructors are assembled in a binary tree
Con | |
| |
ConTree (ConTree name ref) (ConTree name ref) | Constructor tree. Constructors are disposed in an optimally balanced, right heavier tree: For example, the data type: data N = One | Two | Three | Four | Five Would have its contructors ordered in the following tree: | | | One Two Three | Four Five To get a list of constructor in declaration order, use |
Functor (ConTree name) Source # | |
Foldable (ConTree name) Source # | |
Traversable (ConTree name) Source # | |
(Eq ref, Eq name) => Eq (ConTree name ref) Source # | |
(Ord ref, Ord name) => Ord (ConTree name ref) Source # | |
(Show ref, Show name) => Show (ConTree name ref) Source # | |
Generic (ConTree name ref) Source # | |
(NFData ref, NFData name) => NFData (ConTree name ref) Source # | |
type Rep (ConTree name ref) Source # | |
A type
Another representation of a type, sometime easier to work with
A reference to a type
Functor TypeRef Source # | |
Foldable TypeRef Source # | |
Traversable TypeRef Source # | |
Eq name => Eq (TypeRef name) Source # | |
Ord name => Ord (TypeRef name) Source # | |
Show name => Show (TypeRef name) Source # | |
Generic (TypeRef name) Source # | |
NFData name => NFData (TypeRef name) Source # | |
type Rep (TypeRef name) Source # | |
Names
Simple name
A fully qualified Haskell name
Model Utilities
adtNamesMap :: (adtName1 -> adtName2) -> (consName1 -> consName2) -> ADT adtName1 consName1 ref -> ADT adtName2 consName2 ref Source #
Map over the names of an ADT and of its constructors
constructors :: ConTree t t1 -> [ConTree t t1] Source #
Return the list of constructors in definition order
constructorInfo :: Eq consName => consName -> ConTree consName t -> Maybe ([Bool], [Type t]) Source #
Return the binary encoding and parameter types of a constructor The binary encoding is the sequence of Left (False) and Right (True) turns needed to reach the constructor from the constructor tree root. constructorInfo :: Eq consName => consName -> ADT name consName ref -> Maybe ([Bool], [Type ref]) constructorInfo consName dt = declCons dt >>= ((first reverse $) . loc [])
conTreeNameMap :: (name -> name2) -> ConTree name t -> ConTree name2 t Source #
Map over a constructor tree names
conTreeTypeMap :: (Type t -> Type ref) -> ConTree name t -> ConTree name ref Source #
Map on the constructor types (used for example when eliminating variables)
conTreeTypeList :: ConTree name t -> [Type t] Source #
Extract list of types in a constructor tree
conTreeTypeFoldMap :: Monoid a => (Type t -> a) -> ConTree name t -> a Source #
Fold over the types in a constructor tree
fieldsTypes :: Either [b] [(a, b)] -> [b] Source #
Return just the field types
fieldsNames :: Either t [(a, t1)] -> [t1] Source #
Return just the field names (or an empty list if unspecified)
Handy aliases
Utilities
solve :: (Ord k, Show k) => k -> Map k a -> a Source #
Solve a key in an environment, returns an error if the key is missing
solveAll :: (Functor f, Show k, Ord k) => Map k b -> f k -> f b Source #
Solve all references in a data structure, using the given environment
unVar :: TypeRef t -> t Source #
Remove variable references (for example if we know that a type is fully saturated and cannot contain variables)
Re-exports
module GHC.Generics
data Proxy k t :: forall k. k -> * #
A concrete, poly-kinded proxy type
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Generic1 (Proxy *) | |
Alternative (Proxy *) | |
MonadPlus (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy k t) | |
Semigroup (Proxy k s) | |
Monoid (Proxy k s) | |
NFData (Proxy k a) | Since: 1.4.0.0 |
type Rep1 (Proxy *) | |
type Rep (Proxy k t) | |