Safe Haskell | None |
---|---|
Language | GHC2021 |
GHC.Hs.Pat
Contents
Synopsis
- data Pat p
- = WildPat (XWildPat p)
- | VarPat (XVarPat p) (LIdP p)
- | LazyPat (XLazyPat p) (LPat p)
- | AsPat (XAsPat p) (LIdP p) (LPat p)
- | ParPat (XParPat p) (LPat p)
- | BangPat (XBangPat p) (LPat p)
- | ListPat (XListPat p) [LPat p]
- | TuplePat (XTuplePat p) [LPat p] Boxity
- | OrPat (XOrPat p) (NonEmpty (LPat p))
- | SumPat (XSumPat p) (LPat p) ConTag SumWidth
- | ConPat {
- pat_con_ext :: XConPat p
- pat_con :: XRec p (ConLikeP p)
- pat_args :: HsConPatDetails p
- | ViewPat (XViewPat p) (LHsExpr p) (LPat p)
- | SplicePat (XSplicePat p) (HsUntypedSplice p)
- | LitPat (XLitPat p) (HsLit p)
- | NPat (XNPat p) (XRec p (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)
- | NPlusKPat (XNPlusKPat p) (LIdP p) (XRec p (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)
- | SigPat (XSigPat p) (LPat p) (HsPatSigType (NoGhcTc p))
- | EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p))
- | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p))
- | XPat !(XXPat p)
- type LPat p = XRec p (Pat p)
- isInvisArgPat :: Pat p -> Bool
- isInvisArgLPat :: UnXRec p => LPat p -> Bool
- isVisArgPat :: Pat p -> Bool
- isVisArgLPat :: UnXRec p => LPat p -> Bool
- data EpAnnSumPat = EpAnnSumPat {
- sumPatParens :: (EpaLocation, EpaLocation)
- sumPatVbarsBefore :: [EpToken "|"]
- sumPatVbarsAfter :: [EpToken "|"]
- data ConPatTc = ConPatTc {}
- type family ConLikeP x
- data HsPatExpansion a b = HsPatExpanded a b
- data XXPatGhcTc
- type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p))
- hsConPatArgs :: UnXRec p => HsConPatDetails p -> [LPat p]
- data HsRecFields p arg = HsRecFields {
- rec_ext :: !(XHsRecFields p)
- rec_flds :: [LHsRecField p arg]
- rec_dotdot :: Maybe (XRec p RecFieldsDotDot)
- data HsFieldBind lhs rhs = HsFieldBind {}
- type LHsFieldBind p id arg = XRec p (HsFieldBind id arg)
- type HsRecField p arg = HsFieldBind (LFieldOcc p) arg
- type LHsRecField p arg = XRec p (HsRecField p arg)
- type HsRecUpdField p q = HsFieldBind (LFieldOcc p) (LHsExpr q)
- type LHsRecUpdField p q = XRec p (HsRecUpdField p q)
- newtype RecFieldsDotDot = RecFieldsDotDot {}
- hsRecFields :: forall (p :: Pass) arg. HsRecFields (GhcPass p) arg -> [IdGhcP p]
- hsRecFieldSel :: forall (p :: Pass) arg. HsRecField (GhcPass p) arg -> IdGhcP p
- hsRecFieldId :: HsRecField GhcTc arg -> Id
- hsRecFieldsArgs :: forall (p :: Pass) arg. HsRecFields (GhcPass p) arg -> [arg]
- mkPrefixConPat :: DataCon -> [LPat GhcTc] -> [Type] -> LPat GhcTc
- mkCharLitPat :: SourceText -> Char -> LPat GhcTc
- mkNilPat :: Type -> LPat GhcTc
- isSimplePat :: forall (x :: Pass). LPat (GhcPass x) -> Maybe (IdP (GhcPass x))
- isPatSyn :: LPat GhcTc -> Bool
- looksLazyPatBind :: HsBind GhcTc -> Bool
- isBangedLPat :: forall (p :: Pass). LPat (GhcPass p) -> Bool
- gParPat :: forall (p :: Pass). IsPass p => LPat (GhcPass p) -> Pat (GhcPass p)
- patNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> Pat (GhcPass p) -> Bool
- parenthesizePat :: forall (p :: Pass). IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p)
- isIrrefutableHsPat :: forall (p :: Pass). IsPass p => Bool -> (ConLikeP (GhcPass p) -> Bool) -> LPat (GhcPass p) -> Bool
- isBoringHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool
- collectEvVarsPat :: Pat GhcTc -> Bag EvVar
- collectEvVarsPats :: [Pat GhcTc] -> Bag EvVar
- pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc
- pprConArgs :: forall (p :: Pass). (OutputableBndrId p, Outputable (Anno (IdGhcP p))) => HsConPatDetails (GhcPass p) -> SDoc
- pprLPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> SDoc
Documentation
Pattern
Constructors
WildPat (XWildPat p) | Wildcard Pattern, i.e. |
VarPat (XVarPat p) (LIdP p) | Variable Pattern, e.g. |
LazyPat (XLazyPat p) (LPat p) | Lazy Pattern, e.g. |
AsPat (XAsPat p) (LIdP p) (LPat p) | As pattern, e.g. |
ParPat (XParPat p) (LPat p) | Parenthesised pattern, e.g. |
BangPat (XBangPat p) (LPat p) | Bang pattern, e.g. |
ListPat (XListPat p) [LPat p] | Syntactic List, e.g. |
TuplePat | Tuple pattern, e.g. |
OrPat (XOrPat p) (NonEmpty (LPat p)) | Or Pattern, e.g. Since: ghc-9.12.1 |
SumPat (XSumPat p) (LPat p) ConTag SumWidth | Anonymous sum pattern, e.g. |
ConPat | Constructor Pattern, e.g. |
Fields
| |
ViewPat (XViewPat p) (LHsExpr p) (LPat p) | View Pattern, e.g. |
SplicePat (XSplicePat p) (HsUntypedSplice p) | Splice Pattern, e.g. |
LitPat (XLitPat p) (HsLit p) | Literal Pattern Used for non-overloaded literal patterns: Int#, Char#, Int, Char, String, etc. |
NPat (XNPat p) (XRec p (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p) | Natural Pattern, used for all overloaded literals, including overloaded Strings
with |
NPlusKPat (XNPlusKPat p) (LIdP p) (XRec p (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p) | n+k pattern, e.g. |
SigPat (XSigPat p) (LPat p) (HsPatSigType (NoGhcTc p)) | Pattern with a type signature, e.g. |
EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) | Embed the syntax of types into patterns, e.g. |
InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) | Type abstraction which brings into scope type variables associated with invisible forall.
E.g. |
XPat !(XXPat p) | TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension |
Instances
OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # | |
Data (Pat GhcPs) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcPs -> c (Pat GhcPs) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcPs) Source # toConstr :: Pat GhcPs -> Constr Source # dataTypeOf :: Pat GhcPs -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcPs)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcPs)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcPs -> Pat GhcPs Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcPs -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcPs -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcPs -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcPs -> m (Pat GhcPs) Source # | |
Data (Pat GhcRn) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcRn -> c (Pat GhcRn) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcRn) Source # toConstr :: Pat GhcRn -> Constr Source # dataTypeOf :: Pat GhcRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcRn)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcRn)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcRn -> Pat GhcRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcRn -> m (Pat GhcRn) Source # | |
Data (Pat GhcTc) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcTc -> c (Pat GhcTc) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pat GhcTc) Source # toConstr :: Pat GhcTc -> Constr Source # dataTypeOf :: Pat GhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pat GhcTc)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pat GhcTc)) Source # gmapT :: (forall b. Data b => b -> b) -> Pat GhcTc -> Pat GhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pat GhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Pat GhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pat GhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pat GhcTc -> m (Pat GhcTc) Source # | |
type Anno (Pat (GhcPass p)) Source # | |
Defined in GHC.Hs.Pat | |
type Anno [LocatedA (Pat (GhcPass p))] Source # | |
Defined in GHC.Hs.Expr |
isInvisArgPat :: Pat p -> Bool Source #
isVisArgPat :: Pat p -> Bool Source #
data EpAnnSumPat Source #
Constructors
EpAnnSumPat | |
Fields
|
Instances
NoAnn EpAnnSumPat Source # | |
Defined in GHC.Hs.Pat Methods noAnn :: EpAnnSumPat Source # | |
Data EpAnnSumPat Source # | |
Defined in GHC.Hs.Pat Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpAnnSumPat -> c EpAnnSumPat Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpAnnSumPat Source # toConstr :: EpAnnSumPat -> Constr Source # dataTypeOf :: EpAnnSumPat -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpAnnSumPat) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpAnnSumPat) Source # gmapT :: (forall b. Data b => b -> b) -> EpAnnSumPat -> EpAnnSumPat Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnSumPat -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpAnnSumPat -> r Source # gmapQ :: (forall d. Data d => d -> u) -> EpAnnSumPat -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpAnnSumPat -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpAnnSumPat -> m EpAnnSumPat Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnSumPat -> m EpAnnSumPat Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpAnnSumPat -> m EpAnnSumPat Source # |
This is the extension field for ConPat, added after typechecking It adds quite a few extra fields, to support elaboration of pattern matching.
Constructors
ConPatTc | |
Fields
|
Instances
Data ConPatTc Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConPatTc -> c ConPatTc Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConPatTc Source # toConstr :: ConPatTc -> Constr Source # dataTypeOf :: ConPatTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConPatTc) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConPatTc) Source # gmapT :: (forall b. Data b => b -> b) -> ConPatTc -> ConPatTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConPatTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConPatTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ConPatTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConPatTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConPatTc -> m ConPatTc Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConPatTc -> m ConPatTc Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConPatTc -> m ConPatTc Source # |
data HsPatExpansion a b Source #
Constructors
HsPatExpanded a b |
Instances
(Outputable a, Outputable b) => Outputable (HsPatExpansion a b) Source # | |
Defined in GHC.Hs.Pat Methods ppr :: HsPatExpansion a b -> SDoc Source # | |
(Data a, Data b) => Data (HsPatExpansion a b) Source # | |
Defined in GHC.Hs.Pat Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsPatExpansion a b -> c (HsPatExpansion a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatExpansion a b) Source # toConstr :: HsPatExpansion a b -> Constr Source # dataTypeOf :: HsPatExpansion a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatExpansion a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatExpansion a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsPatExpansion a b -> HsPatExpansion a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsPatExpansion a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatExpansion a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) Source # |
data XXPatGhcTc Source #
Extension constructor for Pat, added after typechecking.
Constructors
CoPat | Coercion Pattern (translation only) During desugaring a (CoPat co pat) turns into a cast with |
Fields
| |
ExpansionPat (Pat GhcRn) (Pat GhcTc) | Pattern expansion: original pattern, and desugared pattern, for RebindableSyntax and other overloaded syntax such as OverloadedLists. See Note [Rebindable syntax and XXExprGhcRn]. |
Instances
Data XXPatGhcTc Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> XXPatGhcTc -> c XXPatGhcTc Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c XXPatGhcTc Source # toConstr :: XXPatGhcTc -> Constr Source # dataTypeOf :: XXPatGhcTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c XXPatGhcTc) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c XXPatGhcTc) Source # gmapT :: (forall b. Data b => b -> b) -> XXPatGhcTc -> XXPatGhcTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> XXPatGhcTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> XXPatGhcTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> XXPatGhcTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> XXPatGhcTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> XXPatGhcTc -> m XXPatGhcTc Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> XXPatGhcTc -> m XXPatGhcTc Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> XXPatGhcTc -> m XXPatGhcTc Source # |
type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p)) Source #
Haskell Constructor Pattern Details
hsConPatArgs :: UnXRec p => HsConPatDetails p -> [LPat p] Source #
data HsRecFields p arg Source #
Haskell Record Fields
HsRecFields is used only for patterns and expressions (not data type declarations)
Constructors
HsRecFields | |
Fields
|
Instances
(Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ LocatedE RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # | |
Defined in GHC.Hs.Pat Methods ppr :: HsRecFields p arg -> SDoc Source # | |
Data body => Data (HsRecFields GhcPs body) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcPs body -> c (HsRecFields GhcPs body) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcPs body) Source # toConstr :: HsRecFields GhcPs body -> Constr Source # dataTypeOf :: HsRecFields GhcPs body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcPs body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcPs body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) Source # | |
Data body => Data (HsRecFields GhcRn body) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcRn body -> c (HsRecFields GhcRn body) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcRn body) Source # toConstr :: HsRecFields GhcRn body -> Constr Source # dataTypeOf :: HsRecFields GhcRn body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcRn body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcRn body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) Source # | |
Data body => Data (HsRecFields GhcTc body) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcTc body -> c (HsRecFields GhcTc body) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecFields GhcTc body) Source # toConstr :: HsRecFields GhcTc body -> Constr Source # dataTypeOf :: HsRecFields GhcTc body -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecFields GhcTc body)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecFields GhcTc body)) Source # gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) Source # |
data HsFieldBind lhs rhs Source #
Haskell Field Binding
Constructors
HsFieldBind | |
Instances
Functor (HsFieldBind lhs) Source # | |
Defined in Language.Haskell.Syntax.Pat Methods fmap :: (a -> b) -> HsFieldBind lhs a -> HsFieldBind lhs b Source # (<$) :: a -> HsFieldBind lhs b -> HsFieldBind lhs a Source # | |
Foldable (HsFieldBind lhs) Source # | |
Defined in Language.Haskell.Syntax.Pat Methods fold :: Monoid m => HsFieldBind lhs m -> m Source # foldMap :: Monoid m => (a -> m) -> HsFieldBind lhs a -> m Source # foldMap' :: Monoid m => (a -> m) -> HsFieldBind lhs a -> m Source # foldr :: (a -> b -> b) -> b -> HsFieldBind lhs a -> b Source # foldr' :: (a -> b -> b) -> b -> HsFieldBind lhs a -> b Source # foldl :: (b -> a -> b) -> b -> HsFieldBind lhs a -> b Source # foldl' :: (b -> a -> b) -> b -> HsFieldBind lhs a -> b Source # foldr1 :: (a -> a -> a) -> HsFieldBind lhs a -> a Source # foldl1 :: (a -> a -> a) -> HsFieldBind lhs a -> a Source # toList :: HsFieldBind lhs a -> [a] Source # null :: HsFieldBind lhs a -> Bool Source # length :: HsFieldBind lhs a -> Int Source # elem :: Eq a => a -> HsFieldBind lhs a -> Bool Source # maximum :: Ord a => HsFieldBind lhs a -> a Source # minimum :: Ord a => HsFieldBind lhs a -> a Source # sum :: Num a => HsFieldBind lhs a -> a Source # product :: Num a => HsFieldBind lhs a -> a Source # | |
Traversable (HsFieldBind lhs) Source # | |
Defined in Language.Haskell.Syntax.Pat Methods traverse :: Applicative f => (a -> f b) -> HsFieldBind lhs a -> f (HsFieldBind lhs b) Source # sequenceA :: Applicative f => HsFieldBind lhs (f a) -> f (HsFieldBind lhs a) Source # mapM :: Monad m => (a -> m b) -> HsFieldBind lhs a -> m (HsFieldBind lhs b) Source # sequence :: Monad m => HsFieldBind lhs (m a) -> m (HsFieldBind lhs a) Source # | |
(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsFieldBind p arg) Source # | |
Defined in GHC.Hs.Pat Methods ppr :: HsFieldBind p arg -> SDoc Source # | |
(Data a, Data b) => Data (HsFieldBind a b) Source # | |
Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsFieldBind a b -> c (HsFieldBind a b) Source # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsFieldBind a b) Source # toConstr :: HsFieldBind a b -> Constr Source # dataTypeOf :: HsFieldBind a b -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsFieldBind a b)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsFieldBind a b)) Source # gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsFieldBind a b -> HsFieldBind a b Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldBind a b -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldBind a b -> r Source # gmapQ :: (forall d. Data d => d -> u) -> HsFieldBind a b -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldBind a b -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) Source # | |
type Anno (HsFieldBind lhs rhs) Source # | |
Defined in GHC.Hs.Pat |
type LHsFieldBind p id arg = XRec p (HsFieldBind id arg) Source #
Located Haskell Record Field
type HsRecField p arg = HsFieldBind (LFieldOcc p) arg Source #
Haskell Record Field
type LHsRecField p arg = XRec p (HsRecField p arg) Source #
Located Haskell Record Field
type HsRecUpdField p q = HsFieldBind (LFieldOcc p) (LHsExpr q) Source #
Haskell Record Update Field
type LHsRecUpdField p q = XRec p (HsRecUpdField p q) Source #
Located Haskell Record Update Field
newtype RecFieldsDotDot Source #
Newtype to be able to have a specific XRec instance for the Int in rec_dotdot
Constructors
RecFieldsDotDot | |
Fields |
Instances
hsRecFields :: forall (p :: Pass) arg. HsRecFields (GhcPass p) arg -> [IdGhcP p] Source #
hsRecFieldSel :: forall (p :: Pass) arg. HsRecField (GhcPass p) arg -> IdGhcP p Source #
hsRecFieldId :: HsRecField GhcTc arg -> Id Source #
hsRecFieldsArgs :: forall (p :: Pass) arg. HsRecFields (GhcPass p) arg -> [arg] Source #
mkCharLitPat :: SourceText -> Char -> LPat GhcTc Source #
isSimplePat :: forall (x :: Pass). LPat (GhcPass x) -> Maybe (IdP (GhcPass x)) Source #
Is the pattern any of combination of:
- (pat)
- pat :: Type
- ~pat
- !pat
- x (variable)
gParPat :: forall (p :: Pass). IsPass p => LPat (GhcPass p) -> Pat (GhcPass p) Source #
Parenthesize a pattern without token information
patNeedsParens :: forall (p :: Pass). IsPass p => PprPrec -> Pat (GhcPass p) -> Bool Source #
returns patNeedsParens
p patTrue
if the pattern pat
needs
parentheses under precedence p
.
parenthesizePat :: forall (p :: Pass). IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) Source #
checks if parenthesizePat
p pat
is true, and
if so, surrounds patNeedsParens
p patpat
with a ParPat
. Otherwise, it simply returns pat
.
Arguments
:: forall (p :: Pass). IsPass p | |
=> Bool | Are we in a |
-> (ConLikeP (GhcPass p) -> Bool) | How to check whether the |
-> LPat (GhcPass p) | The (located) pattern to check |
-> Bool |
isIrrefutableHsPat p
is true if matching against p
cannot fail
in the sense of falling through to the next pattern.
(NB: this is not quite the same as the (silly) defn
in 3.17.2 of the Haskell 98 report.)
If isIrrefutableHsPat returns True
, the pattern is definitely irrefutable.
However, isIrrefutableHsPat returns False
if it's in doubt. It's a
best effort guess with the information we have available:
- we sometimes call
isIrrefutableHsPat
from the renamer, in which case we don't have type information to hand. This means we can't properly handle GADTs, nor the result TyCon of COMPLETE pragmas. - even when calling
isIrrefutableHsPat
in the typechecker, we don't keep track of any long distance information like the pattern-match checker does.
isBoringHsPat :: forall (p :: Pass). OutputableBndrId p => LPat (GhcPass p) -> Bool Source #
Is this pattern boring from the perspective of pattern-match checking, i.e. introduces no new pieces of long-distance information which could influence pattern-match checking?
See Note [Boring patterns].
pprParendLPat :: forall (p :: Pass). OutputableBndrId p => PprPrec -> LPat (GhcPass p) -> SDoc Source #
pprConArgs :: forall (p :: Pass). (OutputableBndrId p, Outputable (Anno (IdGhcP p))) => HsConPatDetails (GhcPass p) -> SDoc Source #
Orphan instances
OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # | |
(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsFieldBind p arg) Source # | |
Methods ppr :: HsFieldBind p arg -> SDoc Source # | |
(Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ LocatedE RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # | |
Methods ppr :: HsRecFields p arg -> SDoc Source # |