Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Pat id
- = WildPat (PostTc id Type)
- | VarPat (Located id)
- | LazyPat (LPat id)
- | AsPat (Located id) (LPat id)
- | ParPat (LPat id)
- | BangPat (LPat id)
- | ListPat [LPat id] (PostTc id Type) (Maybe (PostTc id Type, SyntaxExpr id))
- | TuplePat [LPat id] Boxity [PostTc id Type]
- | SumPat (LPat id) ConTag Arity (PostTc id [Type])
- | PArrPat [LPat id] (PostTc id Type)
- | ConPatIn (Located id) (HsConPatDetails id)
- | ConPatOut { }
- | ViewPat (LHsExpr id) (LPat id) (PostTc id Type)
- | SplicePat (HsSplice id)
- | LitPat HsLit
- | NPat (Located (HsOverLit id)) (Maybe (SyntaxExpr id)) (SyntaxExpr id) (PostTc id Type)
- | NPlusKPat (Located id) (Located (HsOverLit id)) (HsOverLit id) (SyntaxExpr id) (SyntaxExpr id) (PostTc id Type)
- | SigPatIn (LPat id) (LHsSigWcType id)
- | SigPatOut (LPat id) Type
- | CoPat HsWrapper (Pat id) Type
- type InPat id = LPat id
- type OutPat id = LPat id
- type LPat id = Located (Pat id)
- type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id))
- hsConPatArgs :: HsConPatDetails id -> [LPat id]
- data HsRecFields id arg = HsRecFields {
- rec_flds :: [LHsRecField id arg]
- rec_dotdot :: Maybe Int
- data HsRecField' id arg = HsRecField {
- hsRecFieldLbl :: Located id
- hsRecFieldArg :: arg
- hsRecPun :: Bool
- type LHsRecField' id arg = Located (HsRecField' id arg)
- type HsRecField id arg = HsRecField' (FieldOcc id) arg
- type LHsRecField id arg = Located (HsRecField id arg)
- type HsRecUpdField id = HsRecField' (AmbiguousFieldOcc id) (LHsExpr id)
- type LHsRecUpdField id = Located (HsRecUpdField id)
- hsRecFields :: HsRecFields id arg -> [PostRn id id]
- hsRecFieldSel :: HsRecField name arg -> Located (PostRn name name)
- hsRecFieldId :: HsRecField Id arg -> Located Id
- hsRecFieldsArgs :: HsRecFields id arg -> [arg]
- hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc Id) arg -> Located Id
- hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc Id) arg -> LFieldOcc Id
- hsRecUpdFieldRdr :: HsRecUpdField id -> Located RdrName
- mkPrefixConPat :: DataCon -> [OutPat id] -> [Type] -> OutPat id
- mkCharLitPat :: SourceText -> Char -> OutPat id
- mkNilPat :: Type -> OutPat id
- looksLazyPatBind :: HsBind id -> Bool
- isBangedLPat :: LPat id -> Bool
- isBangedPatBind :: HsBind id -> Bool
- hsPatNeedsParens :: Pat a -> Bool
- isIrrefutableHsPat :: OutputableBndrId id => LPat id -> Bool
- collectEvVarsPats :: [Pat id] -> Bag EvVar
- pprParendLPat :: OutputableBndrId name => LPat name -> SDoc
- pprConArgs :: OutputableBndrId id => HsConPatDetails id -> SDoc
Documentation
Pattern
WildPat (PostTc id Type) | Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type |
VarPat (Located id) | Variable Pattern |
LazyPat (LPat id) | Lazy Pattern
^ - |
AsPat (Located id) (LPat id) | As pattern
^ - |
ParPat (LPat id) | Parenthesised pattern
See Note [Parens in HsSyn] in HsExpr
^ - |
BangPat (LPat id) | Bang pattern
^ - |
ListPat [LPat id] (PostTc id Type) (Maybe (PostTc id Type, SyntaxExpr id)) | Syntactic List
|
TuplePat [LPat id] Boxity [PostTc id Type] | Tuple sub-patterns
|
SumPat (LPat id) ConTag Arity (PostTc id [Type]) | Anonymous sum pattern
|
PArrPat [LPat id] (PostTc id Type) |
|
ConPatIn (Located id) (HsConPatDetails id) | Constructor Pattern In |
ConPatOut | Constructor Pattern Out |
ViewPat (LHsExpr id) (LPat id) (PostTc id Type) | View Pattern |
SplicePat (HsSplice id) | Splice Pattern (Includes quasi-quotes) |
LitPat HsLit | Literal Pattern Used for *non-overloaded* literal patterns: Int, Int, Char, String, etc. |
NPat (Located (HsOverLit id)) (Maybe (SyntaxExpr id)) (SyntaxExpr id) (PostTc id Type) | Natural Pattern |
NPlusKPat (Located id) (Located (HsOverLit id)) (HsOverLit id) (SyntaxExpr id) (SyntaxExpr id) (PostTc id Type) | n+k pattern |
SigPatIn (LPat id) (LHsSigWcType id) | Pattern with a type signature |
SigPatOut (LPat id) Type | Pattern with a type signature |
CoPat HsWrapper (Pat id) Type | Coercion Pattern |
DataId id => Data (Pat id) # | |
OutputableBndrId name => Outputable (Pat name) # | |
type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id)) Source #
Haskell Constructor Pattern Details
hsConPatArgs :: HsConPatDetails id -> [LPat id] Source #
data HsRecFields id arg Source #
Haskell Record Fields
HsRecFields is used only for patterns and expressions (not data type declarations)
HsRecFields | |
|
Functor (HsRecFields id) # | |
Foldable (HsRecFields id) # | |
Traversable (HsRecFields id) # | |
(DataId id, Data arg) => Data (HsRecFields id arg) # | |
Outputable arg => Outputable (HsRecFields id arg) # | |
data HsRecField' id arg Source #
Haskell Record Field
For details on above see note [Api annotations] in ApiAnnotation
HsRecField | |
|
Functor (HsRecField' id) # | |
Foldable (HsRecField' id) # | |
Traversable (HsRecField' id) # | |
(Data arg, Data id) => Data (HsRecField' id arg) # | |
(Outputable id, Outputable arg) => Outputable (HsRecField' id arg) # | |
type LHsRecField' id arg = Located (HsRecField' id arg) Source #
Located Haskell Record Field
type HsRecField id arg = HsRecField' (FieldOcc id) arg Source #
Haskell Record Field
type LHsRecField id arg = Located (HsRecField id arg) Source #
Located Haskell Record Field
type HsRecUpdField id = HsRecField' (AmbiguousFieldOcc id) (LHsExpr id) Source #
Haskell Record Update Field
type LHsRecUpdField id = Located (HsRecUpdField id) Source #
Located Haskell Record Update Field
hsRecFields :: HsRecFields id arg -> [PostRn id id] Source #
hsRecFieldSel :: HsRecField name arg -> Located (PostRn name name) Source #
hsRecFieldId :: HsRecField Id arg -> Located Id Source #
hsRecFieldsArgs :: HsRecFields id arg -> [arg] Source #
hsRecUpdFieldId :: HsRecField' (AmbiguousFieldOcc Id) arg -> Located Id Source #
hsRecUpdFieldOcc :: HsRecField' (AmbiguousFieldOcc Id) arg -> LFieldOcc Id Source #
hsRecUpdFieldRdr :: HsRecUpdField id -> Located RdrName Source #
mkCharLitPat :: SourceText -> Char -> OutPat id Source #
looksLazyPatBind :: HsBind id -> Bool Source #
isBangedLPat :: LPat id -> Bool Source #
isBangedPatBind :: HsBind id -> Bool Source #
hsPatNeedsParens :: Pat a -> Bool Source #
isIrrefutableHsPat :: OutputableBndrId id => LPat id -> Bool Source #
pprParendLPat :: OutputableBndrId name => LPat name -> SDoc Source #
pprConArgs :: OutputableBndrId id => HsConPatDetails id -> SDoc Source #