hsExprTest-3.6.5: Expression Testing
Safe HaskellUnsafe
LanguageHaskell2010

Test.Expr.Types

Description

Functions for working with Template Haskell type representation.

(c) 2018–2021 Vladimír Štill

Synopsis

Documentation

arity :: Type -> Int #

uncurryType :: Type -> ([Type], Type) #

Get a list of types of all arguments and the return type. All context are stripped.

isFunctionType :: Type -> Bool #

Is the top-level type constructor a fully applied (->)?

hasInstance :: Type -> Name -> Q Bool #

Does given type have instance of given class?

normalizeContext :: Type -> Type #

Merge type contexts which can be merged. Note: this functions works correctly only if none of the quantifiers shadows any type variable. This seems to be the case both for reified types (where multiple contexts occur for class methods) and for [t| … |] expressions.

getTVars :: Type -> Set Name #

Extract all type variables from a type.

regenTVars :: String -> Type -> Q Type #

rewriteAnnotations :: Type -> Type #

stripAnnotations :: Type -> Type #

unannotate :: Type -> (Type, Type) #

unannotate t ≈ (stripAnnotations t, rewriteAnnotations t)

type TestAs α β = α #

Intended to be used with the teacher's solution: foo :: a `TestAs` Positive a -> b `TestAs` Large b -> Bool

Type Substitution

type Substitution = [(Name, Type)] #

Type substitution. Please note that substitution is ordered, i.e. s1 = [(a, VarT b), (b, ConT Int)] is different from s2 = [(b, ConT Int), (a, VarT b)] as for a -> b // s1 produces Int -> Int while a -> b // s2 produces b -> Int.

substitute :: Substitution -> Type -> Type #

(//) :: Type -> Substitution -> Type infixl 9 #

type Renaming = [(Name, Name)] #

Renaming of type variables. Similar to Substitution, Renaming is ordered.

rename :: Renaming -> Type -> Type #

Unification

data UniTypeId #

Constructors

LeftType 
RightType 
BothTypes 

Instances

Instances details
Data UniTypeId # 
Instance details

Defined in Test.Expr.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UniTypeId -> c UniTypeId

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UniTypeId

toConstr :: UniTypeId -> Constr

dataTypeOf :: UniTypeId -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UniTypeId)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UniTypeId)

gmapT :: (forall b. Data b => b -> b) -> UniTypeId -> UniTypeId

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UniTypeId -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UniTypeId -> r

gmapQ :: (forall d. Data d => d -> u) -> UniTypeId -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> UniTypeId -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UniTypeId -> m UniTypeId

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UniTypeId -> m UniTypeId

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UniTypeId -> m UniTypeId

Read UniTypeId # 
Instance details

Defined in Test.Expr.Types

Methods

readsPrec :: Int -> ReadS UniTypeId

readList :: ReadS [UniTypeId]

readPrec :: ReadPrec UniTypeId

readListPrec :: ReadPrec [UniTypeId]

Show UniTypeId # 
Instance details

Defined in Test.Expr.Types

Methods

showsPrec :: Int -> UniTypeId -> ShowS

show :: UniTypeId -> String

showList :: [UniTypeId] -> ShowS

Eq UniTypeId # 
Instance details

Defined in Test.Expr.Types

Methods

(==) :: UniTypeId -> UniTypeId -> Bool

(/=) :: UniTypeId -> UniTypeId -> Bool

Lift UniTypeId # 
Instance details

Defined in Test.Expr.Types

Methods

lift :: Quote m => UniTypeId -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => UniTypeId -> Code m UniTypeId

data TypeOrder #

Instances

Instances details
Data TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypeOrder -> c TypeOrder

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TypeOrder

toConstr :: TypeOrder -> Constr

dataTypeOf :: TypeOrder -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TypeOrder)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TypeOrder)

gmapT :: (forall b. Data b => b -> b) -> TypeOrder -> TypeOrder

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypeOrder -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypeOrder -> r

gmapQ :: (forall d. Data d => d -> u) -> TypeOrder -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypeOrder -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypeOrder -> m TypeOrder

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeOrder -> m TypeOrder

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypeOrder -> m TypeOrder

Read TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

readsPrec :: Int -> ReadS TypeOrder

readList :: ReadS [TypeOrder]

readPrec :: ReadPrec TypeOrder

readListPrec :: ReadPrec [TypeOrder]

Show TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

showsPrec :: Int -> TypeOrder -> ShowS

show :: TypeOrder -> String

showList :: [TypeOrder] -> ShowS

Eq TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

(==) :: TypeOrder -> TypeOrder -> Bool

(/=) :: TypeOrder -> TypeOrder -> Bool

PartialOrder TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

pcompare :: TypeOrder -> TypeOrder -> Maybe Ordering #

comparable :: TypeOrder -> TypeOrder -> Bool #

lte :: TypeOrder -> TypeOrder -> Bool #

gte :: TypeOrder -> TypeOrder -> Bool #

lt :: TypeOrder -> TypeOrder -> Bool #

gt :: TypeOrder -> TypeOrder -> Bool #

eq :: TypeOrder -> TypeOrder -> Bool #

Lift TypeOrder # 
Instance details

Defined in Test.Expr.Types

Methods

lift :: Quote m => TypeOrder -> m Exp

liftTyped :: forall (m :: Type -> Type). Quote m => TypeOrder -> Code m TypeOrder

unify :: Type -> Type -> Q (Either (UniTypeId, String) (TypeOrder, Type, Substitution)) #

Unify two types

There are certain limitations, i.e. some unifyable types will not be unified: * higher rank types (nested foralls) are not supported * explicit parenthesis in types are not supported * explicit kind signatures will work only it they are exactly matching (i.e. type variable with kind signature cannot be unified with a constructor or a variable without kind signature) * quantified type variables have proper kind signatures only if they had them in both of the original types * type contexts cannot be simplified, so we can get contexts which constraints such as Functor [] and types misjudged as TUnifiable instead of the actual ordering

unifyingSubstitution :: Type -> Type -> Either (UniTypeId, String) Substitution #

Outputs unification of two types, the types must not share any type variables.

Printing

ppty :: Type -> String #

Print a simplified type, more similar to the type printed by GHCi. There are some serious limitations: * the namespaces of types are stripped, regardless of its correctness * explicit foralls are strippend, regardless of need for kind signatures in them