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

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Rewrite.Match.Types

Contents

Description

UPattern matching on type-level AST fragments for refactorings.

Synopsis

Types

pattern ForallType :: forall dom. TyVarList dom -> Type dom -> Type dom Source #

Forall types ( forall x y . type )

pattern CtxType :: forall dom. Context dom -> Type dom -> Type dom Source #

Type with a context ( forall x y . type )

pattern FunctionType :: forall dom. Type dom -> Type dom -> Type dom Source #

Function types ( a -> b )

pattern TupleType :: forall dom. TypeList dom -> Type dom Source #

Tuple types ( (a,b) )

pattern UnboxedTupleType :: forall dom. TypeList dom -> Type dom Source #

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

pattern ListType :: forall dom. Type dom -> Type dom Source #

List type with special syntax ( [a] )

pattern ParArrayType :: forall dom. Type dom -> Type dom Source #

Parallel array type ( [:a:] )

pattern TypeApp :: forall dom. Type dom -> Type dom -> Type dom Source #

Type application ( F a )

pattern InfixTypeApp :: forall dom. Type dom -> Operator dom -> Type dom -> Type dom Source #

Infix type constructor ( (a <: b) )

pattern ParenType :: forall dom. Type dom -> Type dom Source #

Type surrounded by parentheses ( (T a) )

pattern VarType :: forall dom. Name dom -> Type dom Source #

Type variable or constructor ( a )

pattern KindedType :: forall dom. Type dom -> Kind dom -> Type dom Source #

Type with explicit kind signature ( a :: * )

pattern BangType :: forall dom. Type dom -> Type dom Source #

Strict type marked with !.

pattern LazyType :: forall dom. Type dom -> Type dom Source #

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

pattern UnpackType :: forall dom. Type dom -> Type dom Source #

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

pattern NoUnpackType :: forall dom. Type dom -> Type dom Source #

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

pattern WildcardType :: forall dom. Type dom Source #

A wildcard type ( _ ) with -XPartialTypeSignatures

pattern NamedWildcardType :: forall dom. Name dom -> Type dom Source #

A named wildcard type ( _t ) with -XPartialTypeSignatures

pattern SpliceType :: forall dom. Splice dom -> Type dom Source #

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

pattern QuasiQuoteType :: forall dom. QuasiQuote dom -> Type dom Source #

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

pattern PromotedIntType :: forall dom. Integer -> Type dom Source #

Numeric value promoted to the type level.

pattern PromotedStringType :: forall dom. String -> Type dom Source #

String value promoted to the type level.

pattern PromotedConType :: forall dom. Name dom -> Type dom Source #

A data constructor value promoted to the type level.

pattern PromotedListType :: forall dom. TypeList dom -> Type dom Source #

A list of elements as a type.

pattern PromotedTupleType :: forall dom. TypeList dom -> Type dom Source #

A tuple of elements as a type.

pattern PromotedUnitType :: forall dom. Type dom Source #

Kind of the unit value ().

Type variable

pattern TyVarDecl :: forall dom. Name dom -> TyVar dom Source #

Type variable declaration

pattern KindedTyVarDecl :: forall dom. Name dom -> Kind dom -> TyVar dom Source #

Kinded type variable declaration ( v :: * )

Contexts

pattern Context :: forall dom. Assertion dom -> Context dom Source #

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

Assertions

pattern ClassAssert :: forall dom. Name dom -> TypeList dom -> Assertion dom Source #

Class assertion (Cls x)

pattern InfixAssert :: forall dom. Type dom -> Operator dom -> Type dom -> Assertion dom Source #

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

pattern ImplicitAssert :: forall dom. Name dom -> Type dom -> Assertion dom Source #

Assertion for implicit parameter binding ( ?cmp :: a -> a -> Bool )

pattern TupleAssert :: forall dom. [Assertion dom] -> Assertion dom Source #

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