Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Pat id
- = WildPat (PostTc id Type)
- | VarPat 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]
- | PArrPat [LPat id] (PostTc id Type)
- | ConPatIn (Located id) (HsConPatDetails id)
- | ConPatOut { }
- | ViewPat (LHsExpr id) (LPat id) (PostTc id Type)
- | SplicePat (HsSplice id)
- | QuasiQuotePat (HsQuasiQuote id)
- | LitPat HsLit
- | NPat (HsOverLit id) (Maybe (SyntaxExpr id)) (SyntaxExpr id)
- | NPlusKPat (Located id) (HsOverLit id) (SyntaxExpr id) (SyntaxExpr id)
- | SigPatIn (LPat id) (HsWithBndrs id (LHsType 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)
- data HsConDetails arg rec
- 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 {
- hsRecFieldId :: Located id
- hsRecFieldArg :: arg
- hsRecPun :: Bool
- type LHsRecField id arg = Located (HsRecField id arg)
- hsRecFields :: HsRecFields id arg -> [id]
- mkPrefixConPat :: DataCon -> [OutPat id] -> [Type] -> OutPat id
- mkCharLitPat :: String -> Char -> OutPat id
- mkNilPat :: Type -> OutPat id
- isStrictHsBind :: HsBind id -> Bool
- looksLazyPatBind :: HsBind id -> Bool
- isStrictLPat :: LPat id -> Bool
- hsPatNeedsParens :: Pat a -> Bool
- isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool
- pprParendLPat :: OutputableBndr name => LPat name -> SDoc
- pprConArgs :: OutputableBndr id => HsConPatDetails id -> SDoc
Documentation
WildPat (PostTc id Type) | |
VarPat 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] | |
PArrPat [LPat id] (PostTc id Type) | |
ConPatIn (Located id) (HsConPatDetails id) | |
ConPatOut | |
ViewPat (LHsExpr id) (LPat id) (PostTc id Type) | |
SplicePat (HsSplice id) | |
QuasiQuotePat (HsQuasiQuote id) | |
LitPat HsLit | |
NPat (HsOverLit id) (Maybe (SyntaxExpr id)) (SyntaxExpr id) | |
NPlusKPat (Located id) (HsOverLit id) (SyntaxExpr id) (SyntaxExpr id) | |
SigPatIn (LPat id) (HsWithBndrs id (LHsType id)) | |
SigPatOut (LPat id) Type | |
CoPat HsWrapper (Pat id) Type |
DataId id => Data (Pat id) | |
OutputableBndr name => Outputable (Pat name) | |
Typeable (* -> *) Pat |
data HsConDetails arg rec Source
(Data arg, Data rec) => Data (HsConDetails arg rec) | |
Typeable (* -> * -> *) HsConDetails | |
Typeable ([arg] -> HsConDetails arg rec) (PrefixCon arg rec) | |
Typeable (rec -> HsConDetails arg rec) (RecCon arg rec) | |
Typeable (arg -> arg -> HsConDetails arg rec) (InfixCon arg rec) |
type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id)) Source
hsConPatArgs :: HsConPatDetails id -> [LPat id] Source
data HsRecFields id arg Source
HsRecFields | |
|
(Data id, Data arg) => Data (HsRecFields id arg) | |
(OutputableBndr id, Outputable arg) => Outputable (HsRecFields id arg) | |
Typeable (* -> * -> *) HsRecFields |
data HsRecField id arg Source
HsRecField | |
|
(Data id, Data arg) => Data (HsRecField id arg) | |
(OutputableBndr id, Outputable arg) => Outputable (HsRecField id arg) | |
Typeable (* -> * -> *) HsRecField |
type LHsRecField id arg = Located (HsRecField id arg) Source
hsRecFields :: HsRecFields id arg -> [id] Source
mkCharLitPat :: String -> Char -> OutPat id Source
isStrictHsBind :: HsBind id -> Bool Source
looksLazyPatBind :: HsBind id -> Bool Source
isStrictLPat :: LPat id -> Bool Source
hsPatNeedsParens :: Pat a -> Bool Source
isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool Source
pprParendLPat :: OutputableBndr name => LPat name -> SDoc Source
pprConArgs :: OutputableBndr id => HsConPatDetails id -> SDoc Source