ghc-6.12.1: The GHC APISource codeContentsIndex
HsPat
Documentation
data Pat id Source
Constructors
WildPat PostTcType
VarPat id
VarPatOut id (DictBinds id)
LazyPat (LPat id)
AsPat (Located id) (LPat id)
ParPat (LPat id)
BangPat (LPat id)
ListPat [LPat id] PostTcType
TuplePat [LPat id] Boxity PostTcType
PArrPat [LPat id] PostTcType
ConPatIn (Located id) (HsConPatDetails id)
ConPatOut
pat_con :: Located DataCon
pat_tvs :: [TyVar]
pat_dicts :: [id]
pat_binds :: DictBinds id
pat_args :: HsConPatDetails id
pat_ty :: Type
ViewPat (LHsExpr id) (LPat id) PostTcType
QuasiQuotePat (HsQuasiQuote id)
LitPat HsLit
NPat (HsOverLit id) (Maybe (SyntaxExpr id)) (SyntaxExpr id)
NPlusKPat (Located id) (HsOverLit id) (SyntaxExpr id) (SyntaxExpr id)
TypePat (LHsType id)
SigPatIn (LPat id) (LHsType id)
SigPatOut (LPat id) Type
CoPat HsWrapper (Pat id) Type
show/hide Instances
type InPat id = LPat idSource
type OutPat id = LPat idSource
type LPat id = Located (Pat id)Source
data HsConDetails arg rec Source
Constructors
PrefixCon [arg]
RecCon rec
InfixCon arg arg
type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id))Source
hsConPatArgs :: HsConPatDetails id -> [LPat id]Source
data HsRecFields id arg Source
Constructors
HsRecFields
rec_flds :: [HsRecField id arg]
rec_dotdot :: Maybe Int
show/hide Instances
data HsRecField id arg Source
Constructors
HsRecField
hsRecFieldId :: Located id
hsRecFieldArg :: arg
hsRecPun :: Bool
show/hide Instances
hsRecFields :: HsRecFields id arg -> [id]Source
data HsQuasiQuote id Source
Constructors
HsQuasiQuote id id SrcSpan FastString
show/hide Instances
mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat idSource
mkCharLitPat :: Char -> OutPat idSource
mkNilPat :: Type -> OutPat idSource
mkCoPat :: HsWrapper -> Pat id -> Type -> Pat idSource
mkCoPatCoI :: CoercionI -> Pat id -> Type -> Pat idSource
isBangHsBind :: HsBind id -> BoolSource
hsPatNeedsParens :: Pat a -> BoolSource
patsAreAllCons :: [Pat id] -> BoolSource
isConPat :: Pat id -> BoolSource
isSigPat :: Pat id -> BoolSource
isWildPat :: Pat id -> BoolSource
patsAreAllLits :: [Pat id] -> BoolSource
isLitPat :: Pat id -> BoolSource
isIrrefutableHsPat :: OutputableBndr id => LPat id -> BoolSource
Produced by Haddock version 2.6.0