model-0.5: Derive a model of a data type using Generics

Safe HaskellSafe
LanguageHaskell2010

Data.Model.Types

Contents

Description

A model for simple algebraic data types.

Synopsis

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)

Constructors

TypeModel 

Fields

  • typeName :: Type exRef

    The type application corresponding to the type

  • typeEnv :: TypeEnv adtName consName inRef exRef

    The environment in which the type is defined

Instances
(Eq exRef, Eq adtName, Eq consName, Eq inRef) => Eq (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

(/=) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

(Ord exRef, Ord adtName, Ord consName, Ord inRef) => Ord (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Ordering #

(<) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

(<=) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

(>) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

(>=) :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> Bool #

max :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef #

min :: TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef -> TypeModel adtName consName inRef exRef #

(Show exRef, Show adtName, Show consName, Show inRef) => Show (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> TypeModel adtName consName inRef exRef -> ShowS #

show :: TypeModel adtName consName inRef exRef -> String #

showList :: [TypeModel adtName consName inRef exRef] -> ShowS #

Generic (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (TypeModel adtName consName inRef exRef) :: Type -> Type #

Methods

from :: TypeModel adtName consName inRef exRef -> Rep (TypeModel adtName consName inRef exRef) x #

to :: Rep (TypeModel adtName consName inRef exRef) x -> TypeModel adtName consName inRef exRef #

(NFData exRef, NFData adtName, NFData consName, NFData inRef) => NFData (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: TypeModel adtName consName inRef exRef -> () #

(Functor t, Pretty (t Name), Pretty exRef, Ord exRef, Show exRef, Convertible adtName String, Convertible consName String, Convertible iref String) => Pretty (TypeModel adtName consName (t iref) exRef) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> TypeModel adtName consName (t iref) exRef -> Doc #

pPrint :: TypeModel adtName consName (t iref) exRef -> Doc #

pPrintList :: PrettyLevel -> [TypeModel adtName consName (t iref) exRef] -> Doc #

type Rep (TypeModel adtName consName inRef exRef) Source # 
Instance details

Defined in Data.Model.Types

type Rep (TypeModel adtName consName inRef exRef) = D1 (MetaData "TypeModel" "Data.Model.Types" "model-0.5-9pTavxk2UCWIOTiByR8qw8" False) (C1 (MetaCons "TypeModel" PrefixI True) (S1 (MetaSel (Just "typeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Type exRef)) :*: S1 (MetaSel (Just "typeEnv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (TypeEnv adtName consName inRef exRef))))

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)

Constructors

ADT 

Fields

Instances
Functor (ADT name consName) Source # 
Instance details

Defined in Data.Model.Types

Methods

fmap :: (a -> b) -> ADT name consName a -> ADT name consName b #

(<$) :: a -> ADT name consName b -> ADT name consName a #

Foldable (ADT name consName) Source # 
Instance details

Defined in Data.Model.Types

Methods

fold :: Monoid m => ADT name consName m -> m #

foldMap :: Monoid m => (a -> m) -> ADT name consName a -> m #

foldr :: (a -> b -> b) -> b -> ADT name consName a -> b #

foldr' :: (a -> b -> b) -> b -> ADT name consName a -> b #

foldl :: (b -> a -> b) -> b -> ADT name consName a -> b #

foldl' :: (b -> a -> b) -> b -> ADT name consName a -> b #

foldr1 :: (a -> a -> a) -> ADT name consName a -> a #

foldl1 :: (a -> a -> a) -> ADT name consName a -> a #

toList :: ADT name consName a -> [a] #

null :: ADT name consName a -> Bool #

length :: ADT name consName a -> Int #

elem :: Eq a => a -> ADT name consName a -> Bool #

maximum :: Ord a => ADT name consName a -> a #

minimum :: Ord a => ADT name consName a -> a #

sum :: Num a => ADT name consName a -> a #

product :: Num a => ADT name consName a -> a #

Traversable (ADT name consName) Source # 
Instance details

Defined in Data.Model.Types

Methods

traverse :: Applicative f => (a -> f b) -> ADT name consName a -> f (ADT name consName b) #

sequenceA :: Applicative f => ADT name consName (f a) -> f (ADT name consName a) #

mapM :: Monad m => (a -> m b) -> ADT name consName a -> m (ADT name consName b) #

sequence :: Monad m => ADT name consName (m a) -> m (ADT name consName a) #

(Eq name, Eq consName, Eq ref) => Eq (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: ADT name consName ref -> ADT name consName ref -> Bool #

(/=) :: ADT name consName ref -> ADT name consName ref -> Bool #

(Ord name, Ord consName, Ord ref) => Ord (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: ADT name consName ref -> ADT name consName ref -> Ordering #

(<) :: ADT name consName ref -> ADT name consName ref -> Bool #

(<=) :: ADT name consName ref -> ADT name consName ref -> Bool #

(>) :: ADT name consName ref -> ADT name consName ref -> Bool #

(>=) :: ADT name consName ref -> ADT name consName ref -> Bool #

max :: ADT name consName ref -> ADT name consName ref -> ADT name consName ref #

min :: ADT name consName ref -> ADT name consName ref -> ADT name consName ref #

(Show name, Show consName, Show ref) => Show (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> ADT name consName ref -> ShowS #

show :: ADT name consName ref -> String #

showList :: [ADT name consName ref] -> ShowS #

Generic (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (ADT name consName ref) :: Type -> Type #

Methods

from :: ADT name consName ref -> Rep (ADT name consName ref) x #

to :: Rep (ADT name consName ref) x -> ADT name consName ref #

(NFData name, NFData consName, NFData ref) => NFData (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: ADT name consName ref -> () #

(Pretty n, Pretty cn, Pretty r) => Pretty (ADT n cn r) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> ADT n cn r -> Doc #

pPrint :: ADT n cn r -> Doc #

pPrintList :: PrettyLevel -> [ADT n cn r] -> Doc #

type Rep (ADT name consName ref) Source # 
Instance details

Defined in Data.Model.Types

type Rep (ADT name consName ref) = D1 (MetaData "ADT" "Data.Model.Types" "model-0.5-9pTavxk2UCWIOTiByR8qw8" False) (C1 (MetaCons "ADT" PrefixI True) (S1 (MetaSel (Just "declName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 name) :*: (S1 (MetaSel (Just "declNumParameters") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8) :*: S1 (MetaSel (Just "declCons") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (ConTree consName ref))))))

data ConTree name ref Source #

Constructors are assembled in a binary tree

Constructors

Con 

Fields

  • constrName :: name

    The constructor name, unique in the data type

  • constrFields :: Fields name ref

    Constructor fields, they can be either unnamed (Left case) or named (Right case) If they are named, they must all be named

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 constructors

Instances
Functor (ConTree name) Source # 
Instance details

Defined in Data.Model.Types

Methods

fmap :: (a -> b) -> ConTree name a -> ConTree name b #

(<$) :: a -> ConTree name b -> ConTree name a #

Foldable (ConTree name) Source # 
Instance details

Defined in Data.Model.Types

Methods

fold :: Monoid m => ConTree name m -> m #

foldMap :: Monoid m => (a -> m) -> ConTree name a -> m #

foldr :: (a -> b -> b) -> b -> ConTree name a -> b #

foldr' :: (a -> b -> b) -> b -> ConTree name a -> b #

foldl :: (b -> a -> b) -> b -> ConTree name a -> b #

foldl' :: (b -> a -> b) -> b -> ConTree name a -> b #

foldr1 :: (a -> a -> a) -> ConTree name a -> a #

foldl1 :: (a -> a -> a) -> ConTree name a -> a #

toList :: ConTree name a -> [a] #

null :: ConTree name a -> Bool #

length :: ConTree name a -> Int #

elem :: Eq a => a -> ConTree name a -> Bool #

maximum :: Ord a => ConTree name a -> a #

minimum :: Ord a => ConTree name a -> a #

sum :: Num a => ConTree name a -> a #

product :: Num a => ConTree name a -> a #

Traversable (ConTree name) Source # 
Instance details

Defined in Data.Model.Types

Methods

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

sequenceA :: Applicative f => ConTree name (f a) -> f (ConTree name a) #

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

sequence :: Monad m => ConTree name (m a) -> m (ConTree name a) #

(Eq name, Eq ref) => Eq (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: ConTree name ref -> ConTree name ref -> Bool #

(/=) :: ConTree name ref -> ConTree name ref -> Bool #

(Ord name, Ord ref) => Ord (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: ConTree name ref -> ConTree name ref -> Ordering #

(<) :: ConTree name ref -> ConTree name ref -> Bool #

(<=) :: ConTree name ref -> ConTree name ref -> Bool #

(>) :: ConTree name ref -> ConTree name ref -> Bool #

(>=) :: ConTree name ref -> ConTree name ref -> Bool #

max :: ConTree name ref -> ConTree name ref -> ConTree name ref #

min :: ConTree name ref -> ConTree name ref -> ConTree name ref #

(Show name, Show ref) => Show (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> ConTree name ref -> ShowS #

show :: ConTree name ref -> String #

showList :: [ConTree name ref] -> ShowS #

Generic (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (ConTree name ref) :: Type -> Type #

Methods

from :: ConTree name ref -> Rep (ConTree name ref) x #

to :: Rep (ConTree name ref) x -> ConTree name ref #

(NFData name, NFData ref) => NFData (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: ConTree name ref -> () #

(Pretty name, Pretty ref) => Pretty (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> ConTree name ref -> Doc #

pPrint :: ConTree name ref -> Doc #

pPrintList :: PrettyLevel -> [ConTree name ref] -> Doc #

type Rep (ConTree name ref) Source # 
Instance details

Defined in Data.Model.Types

type Fields name ref = Either [Type ref] [(name, Type ref)] Source #

data Type ref Source #

A type

Constructors

TypeCon ref

Type constructor (Bool,Maybe,..)

TypeApp (Type ref) (Type ref)

Type application

Instances
Functor Type Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

Foldable Type Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

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

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

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

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

toList :: Type a -> [a] #

null :: Type a -> Bool #

length :: Type a -> Int #

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

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

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

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

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

Traversable Type Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

Eq ref => Eq (Type ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: Type ref -> Type ref -> Bool #

(/=) :: Type ref -> Type ref -> Bool #

Ord ref => Ord (Type ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: Type ref -> Type ref -> Ordering #

(<) :: Type ref -> Type ref -> Bool #

(<=) :: Type ref -> Type ref -> Bool #

(>) :: Type ref -> Type ref -> Bool #

(>=) :: Type ref -> Type ref -> Bool #

max :: Type ref -> Type ref -> Type ref #

min :: Type ref -> Type ref -> Type ref #

Show ref => Show (Type ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> Type ref -> ShowS #

show :: Type ref -> String #

showList :: [Type ref] -> ShowS #

Generic (Type ref) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (Type ref) :: Type -> Type #

Methods

from :: Type ref -> Rep (Type ref) x #

to :: Rep (Type ref) x -> Type ref #

NFData ref => NFData (Type ref) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: Type ref -> () #

Pretty r => Pretty (Type r) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Type r -> Doc #

pPrint :: Type r -> Doc #

pPrintList :: PrettyLevel -> [Type r] -> Doc #

(Pretty name, Pretty ref) => Pretty (name, Fields name ref) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> (name, Fields name ref) -> Doc #

pPrint :: (name, Fields name ref) -> Doc #

pPrintList :: PrettyLevel -> [(name, Fields name ref)] -> Doc #

(Pretty name, Pretty ref) => Pretty (Fields name ref) Source # 
Instance details

Defined in Data.Model.Pretty

Methods

pPrintPrec :: PrettyLevel -> Rational -> Fields name ref -> Doc #

pPrint :: Fields name ref -> Doc #

pPrintList :: PrettyLevel -> [Fields name ref] -> Doc #

type Rep (Type ref) Source # 
Instance details

Defined in Data.Model.Types

data TypeN r Source #

Another representation of a type, sometime easier to work with

Constructors

TypeN r [TypeN r] 
Instances
Functor TypeN Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

Foldable TypeN Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

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

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

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

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

toList :: TypeN a -> [a] #

null :: TypeN a -> Bool #

length :: TypeN a -> Int #

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

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

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

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

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

Traversable TypeN Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

Eq r => Eq (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: TypeN r -> TypeN r -> Bool #

(/=) :: TypeN r -> TypeN r -> Bool #

Ord r => Ord (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: TypeN r -> TypeN r -> Ordering #

(<) :: TypeN r -> TypeN r -> Bool #

(<=) :: TypeN r -> TypeN r -> Bool #

(>) :: TypeN r -> TypeN r -> Bool #

(>=) :: TypeN r -> TypeN r -> Bool #

max :: TypeN r -> TypeN r -> TypeN r #

min :: TypeN r -> TypeN r -> TypeN r #

Read r => Read (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Show r => Show (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> TypeN r -> ShowS #

show :: TypeN r -> String #

showList :: [TypeN r] -> ShowS #

Generic (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (TypeN r) :: Type -> Type #

Methods

from :: TypeN r -> Rep (TypeN r) x #

to :: Rep (TypeN r) x -> TypeN r #

NFData r => NFData (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: TypeN r -> () #

Pretty r => Pretty (TypeN r) Source # 
Instance details

Defined in Data.Model.Pretty

type Rep (TypeN r) Source # 
Instance details

Defined in Data.Model.Types

nestedTypeNs :: TypeN t -> [TypeN t] Source #

Returns the list of nested TypeNs

>>> nestedTypeNs $ TypeN "F" [TypeN "G" [],TypeN "Z" []]
[TypeN "F" [TypeN "G" [],TypeN "Z" []],TypeN "G" [],TypeN "Z" []]
>>> nestedTypeNs $ TypeN "F" [TypeN "G" [TypeN "H" [TypeN "L" []]],TypeN "Z" []]
[TypeN "F" [TypeN "G" [TypeN "H" [TypeN "L" []]],TypeN "Z" []],TypeN "G" [TypeN "H" [TypeN "L" []]],TypeN "H" [TypeN "L" []],TypeN "L" [],TypeN "Z" []]

data TypeRef name Source #

A reference to a type

Constructors

TypVar Word8

Type variable

TypRef name

Type reference

Instances
Functor TypeRef Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

Foldable TypeRef Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

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

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

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

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

toList :: TypeRef a -> [a] #

null :: TypeRef a -> Bool #

length :: TypeRef a -> Int #

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

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

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

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

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

Traversable TypeRef Source # 
Instance details

Defined in Data.Model.Types

Methods

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

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

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

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

Eq name => Eq (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: TypeRef name -> TypeRef name -> Bool #

(/=) :: TypeRef name -> TypeRef name -> Bool #

Ord name => Ord (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: TypeRef name -> TypeRef name -> Ordering #

(<) :: TypeRef name -> TypeRef name -> Bool #

(<=) :: TypeRef name -> TypeRef name -> Bool #

(>) :: TypeRef name -> TypeRef name -> Bool #

(>=) :: TypeRef name -> TypeRef name -> Bool #

max :: TypeRef name -> TypeRef name -> TypeRef name #

min :: TypeRef name -> TypeRef name -> TypeRef name #

Show name => Show (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> TypeRef name -> ShowS #

show :: TypeRef name -> String #

showList :: [TypeRef name] -> ShowS #

Generic (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep (TypeRef name) :: Type -> Type #

Methods

from :: TypeRef name -> Rep (TypeRef name) x #

to :: Rep (TypeRef name) x -> TypeRef name #

NFData name => NFData (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: TypeRef name -> () #

Pretty n => Pretty (TypeRef n) Source # 
Instance details

Defined in Data.Model.Pretty

type Rep (TypeRef name) Source # 
Instance details

Defined in Data.Model.Types

type Rep (TypeRef name) = D1 (MetaData "TypeRef" "Data.Model.Types" "model-0.5-9pTavxk2UCWIOTiByR8qw8" False) (C1 (MetaCons "TypVar" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word8)) :+: C1 (MetaCons "TypRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 name)))

Names

newtype Name Source #

Simple name

Constructors

Name String 
Instances
Eq Name Source # 
Instance details

Defined in Data.Model.Types

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in Data.Model.Types

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in Data.Model.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: Name -> () #

Pretty Name Source # 
Instance details

Defined in Data.Model.Pretty

type Rep Name Source # 
Instance details

Defined in Data.Model.Types

type Rep Name = D1 (MetaData "Name" "Data.Model.Types" "model-0.5-9pTavxk2UCWIOTiByR8qw8" True) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data QualName Source #

A fully qualified Haskell name

Constructors

QualName 
Instances
Eq QualName Source # 
Instance details

Defined in Data.Model.Types

Ord QualName Source # 
Instance details

Defined in Data.Model.Types

Show QualName Source # 
Instance details

Defined in Data.Model.Types

Generic QualName Source # 
Instance details

Defined in Data.Model.Types

Associated Types

type Rep QualName :: Type -> Type #

Methods

from :: QualName -> Rep QualName x #

to :: Rep QualName x -> QualName #

NFData QualName Source # 
Instance details

Defined in Data.Model.Types

Methods

rnf :: QualName -> () #

Pretty QualName Source # 
Instance details

Defined in Data.Model.Pretty

Convertible String QualName Source # 
Instance details

Defined in Data.Model.Types

Convertible QualName String Source # 
Instance details

Defined in Data.Model.Types

type Rep QualName Source # 
Instance details

Defined in Data.Model.Types

qualName :: QualName -> String Source #

Return the qualified name, minus the package name.

>>> qualName (QualName {pkgName = "ab", mdlName = "cd.ef", locName = "gh"})
"cd.ef.gh"

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

typeN :: Type r -> TypeN r Source #

Convert from Type to TypeN

typeA :: TypeN ref -> Type ref Source #

Convert from TypeN to Type

contree :: [(name, Fields name ref)] -> Maybe (ConTree name ref) Source #

Convert a (possibly empty) list of constructors in (maybe) a ConTree

constructors :: ConTree name ref -> [(name, Fields name ref)] 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

conTreeNameMap :: (name -> name2) -> ConTree name t -> ConTree name2 t Source #

Map over a constructor tree names

conTreeNameFold :: Monoid a => (name -> a) -> ConTree name t -> a Source #

Fold 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

type HADT = ADT String String HTypeRef Source #

Haskell ADT

type HType = Type HTypeRef Source #

Haskell Type

type HTypeRef = TypeRef QualName Source #

Reference to an Haskell Type

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)

getHRef :: TypeRef a -> Maybe a Source #

Extract reference

Re-exports

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, 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
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: 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 #

fail :: String -> 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 #

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) #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

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

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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 #

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

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 #

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) 
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 #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

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)

Since: base-4.6.0.0

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