haskell-tools-rewrite-0.9.0.0: Facilities for generating new parts of the Haskell-Tools AST

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Rewrite.Create.Types

Contents

Description

Generation of type-level AST fragments for refactorings. The bindings defined here create a the annotated version of the AST constructor with the same name. For example, mkTyForall creates the annotated version of the TyForall AST constructor.

Synopsis

Generation of types

mkForallType :: [TyVar dom] -> Type dom -> Type dom Source #

Forall types ( forall x y . type )

mkTypeVar' :: Name -> TyVar dom Source #

Simplified creation of type variables

mkCtxType :: Context dom -> Type dom -> Type dom Source #

Type with a context ( forall x y . type )

mkFunctionType :: Type dom -> Type dom -> Type dom Source #

Function types ( a -> b )

mkTupleType :: [Type dom] -> Type dom Source #

Tuple types ( (a,b) )

mkUnboxedTupleType :: [Type dom] -> Type dom Source #

Unboxed tuple types ( (#a,b#) )

mkListType :: Type dom -> Type dom Source #

List type with special syntax ( [a] )

mkParArrayType :: Type dom -> Type dom Source #

Parallel array type ( [:a:] )

mkTypeApp :: Type dom -> Type dom -> Type dom Source #

Type application ( F a )

mkInfixTypeApp :: Type dom -> Operator dom -> Type dom -> Type dom Source #

Infix type constructor ( (a <: b) )

mkParenType :: Type dom -> Type dom Source #

Type surrounded by parentheses ( (T a) )

mkTypeVar :: Name dom -> TyVar dom Source #

Creates a simple type variable

mkKindedTypeVar :: Name dom -> Kind dom -> TyVar dom Source #

Creates a type variable with kind specification ( t :: * )

mkVarType :: Name dom -> Type dom Source #

Type variable or constructor ( a )

mkKindedType :: Type dom -> Kind dom -> Type dom Source #

Type with explicit kind signature ( a :: * )

mkBangType :: Type dom -> Type dom Source #

Strict type marked with !.

mkLazyType :: Type dom -> Type dom Source #

Lazy type marked with ~. (Should only be used if Strict or StrictData language extension is used)

mkUnpackType :: Type dom -> Type dom Source #

Strict type marked with UNPACK pragma. (Usually contains the bang mark.)

mkNoUnpackType :: Type dom -> Type dom Source #

Strict type marked with UNPACK pragma. (Usually contains the bang mark.)

mkWildcardType :: Type dom Source #

A wildcard type ( _ ) with -XPartialTypeSignatures

mkNamedWildcardType :: Name dom -> Type dom Source #

A named wildcard type ( _t ) with -XPartialTypeSignatures

mkSpliceType :: Splice dom -> Type dom Source #

A Template Haskell splice type ( $(genType) ).

mkQuasiQuoteType :: QuasiQuote dom -> Type dom Source #

A Template Haskell quasi-quote type ( [quoter| ... ] ).

mkPromotedIntType :: Integer -> Type dom Source #

Numeric value promoted to the kind level.

mkPromotedStringType :: String -> Type dom Source #

String value promoted to the kind level.

mkPromotedConType :: Name dom -> Type dom Source #

A data constructor value promoted to the kind level.

mkPromotedListType :: [Type dom] -> Type dom Source #

A list of elements as a kind.

mkPromotedTupleType :: [Type dom] -> Type dom Source #

A tuple of elements as a kind.

mkPromotedUnitType :: Type dom Source #

Kind of the unit value ().

Generation of contexts

mkContext :: Assertion dom -> Context dom Source #

Creates a context of assertions ( C a => ... )

Generation of assertions

mkClassAssert :: Name dom -> [Type dom] -> Assertion dom Source #

Class assertion (Cls x)

mkInfixAssert :: Type dom -> Operator dom -> Type dom -> Assertion dom Source #

Infix class assertion, also contains type equations ( a ~ X y )

mkImplicitAssert :: Name dom -> Type dom -> Assertion dom Source #

Creates an assertion for implicit parameter binding ( ?cmp :: a -> a -> Bool )

mkTupleAssertion :: [Assertion dom] -> Assertion dom Source #

Creates a list of assertions ( (Eq a, Show a) )