ghc-6.10.2: The GHC APIContentsIndex
HsPat
Documentation
data Pat id
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 id
type OutPat id = LPat id
type LPat id = Located (Pat id)
data HsConDetails arg rec
Constructors
PrefixCon [arg]
RecCon rec
InfixCon arg arg
type HsConPatDetails id = HsConDetails (LPat id) (HsRecFields id (LPat id))
hsConPatArgs :: HsConPatDetails id -> [LPat id]
data HsRecFields id arg
Constructors
HsRecFields
rec_flds :: [HsRecField id arg]
rec_dotdot :: Maybe Int
show/hide Instances
data HsRecField id arg
Constructors
HsRecField
hsRecFieldId :: Located id
hsRecFieldArg :: arg
hsRecPun :: Bool
show/hide Instances
hsRecFields :: HsRecFields id arg -> [id]
data HsQuasiQuote id
Constructors
HsQuasiQuote id id SrcSpan FastString
show/hide Instances
mkPrefixConPat :: DataCon -> [OutPat id] -> Type -> OutPat id
mkCharLitPat :: Char -> OutPat id
mkNilPat :: Type -> OutPat id
mkCoPat :: HsWrapper -> Pat id -> Type -> Pat id
mkCoPatCoI :: CoercionI -> Pat id -> Type -> Pat id
isBangHsBind :: HsBind id -> Bool
patsAreAllCons :: [Pat id] -> Bool
isConPat :: Pat id -> Bool
isSigPat :: Pat id -> Bool
isWildPat :: Pat id -> Bool
patsAreAllLits :: [Pat id] -> Bool
isLitPat :: Pat id -> Bool
isIrrefutableHsPat :: OutputableBndr id => LPat id -> Bool
Produced by Haddock version 2.4.2