ghc-9.6.0.20230210: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Hs.Pat

Synopsis

Documentation

data Pat p Source #

Constructors

WildPat (XWildPat p)

Wildcard Pattern The sole reason for a type on a WildPat is to support hsPatType :: Pat Id -> Type

VarPat (XVarPat p) (LIdP p)

Variable Pattern

LazyPat (XLazyPat p) (LPat p)

Lazy Pattern ^ - AnnKeywordId : AnnTilde

AsPat (XAsPat p) (LIdP p) !(LHsToken "@" p) (LPat p)

As pattern ^ - AnnKeywordId : AnnAt

ParPat 

Fields

BangPat (XBangPat p) (LPat p)

Bang pattern ^ - AnnKeywordId : AnnBang

ListPat (XListPat p) [LPat p]

Syntactic List

TuplePat (XTuplePat p) [LPat p] Boxity

Tuple sub-patterns

SumPat (XSumPat p) (LPat p) ConTag SumWidth

Anonymous sum pattern

ConPat

Constructor Pattern

ViewPat

Fields

SplicePat

Fields

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

NPlusKPat (XNPlusKPat p) (LIdP p) (XRec p (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)

n+k pattern

SigPat

Fields

XPat !(XXPat p) 

Instances

Instances details
Data (Pat GhcPs) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 #

OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: Pat (GhcPass p) -> SDoc Source #

type Anno (Pat (GhcPass p)) Source # 
Instance details

Defined in GHC.Hs.Pat

type LPat p = XRec p (Pat p) Source #

data EpAnnSumPat Source #

Instances

Instances details
Data EpAnnSumPat Source # 
Instance details

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 #

data ConPatTc 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

  • cpt_arg_tys :: [Type]

    The universal arg types 1-1 with the universal tyvars of the constructor/pattern synonym Use (conLikeResTy pat_con cpt_arg_tys) to get the type of the pattern

  • cpt_tvs :: [TyVar]

    Existentially bound type variables in correctly-scoped order e.g. [k:* x:k]

  • cpt_dicts :: [EvVar]

    Ditto *coercion variables* and *dictionaries* One reason for putting coercion variable here I think is to ensure their kinds are zonked

  • cpt_binds :: TcEvBinds

    Bindings involving those dictionaries

  • cpt_wrap :: HsWrapper

    Extra wrapper to pass to the matcher Only relevant for pattern-synonyms; ignored for data cons

Instances

Instances details
Data ConPatTc Source # 
Instance details

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 #

type family ConLikeP x Source #

Instances

Instances details
type ConLikeP GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

data HsPatExpansion a b Source #

Constructors

HsPatExpanded a b 

Instances

Instances details
(Data a, Data b) => Data (HsPatExpansion a b) Source # 
Instance details

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 #

(Outputable a, Outputable b) => Outputable (HsPatExpansion a b) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsPatExpansion a b -> SDoc 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 co on the scrutinee, followed by a match on pat.

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 HsExpansion].

Instances

Instances details
Data XXPatGhcTc Source # 
Instance details

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 (HsConPatTyArg (NoGhcTc p)) (LPat p) (HsRecFields p (LPat p)) Source #

Haskell Constructor Pattern Details

hsConPatArgs :: forall p. UnXRec p => HsConPatDetails p -> [LPat p] Source #

data HsConPatTyArg p Source #

Type argument in a data constructor pattern, e.g. the @a in f (Just @a x) = ....

Constructors

HsConPatTyArg !(LHsToken "@" p) (HsPatSigType p) 

Instances

Instances details
Data (HsConPatTyArg GhcPs) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcPs -> c (HsConPatTyArg GhcPs) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcPs) Source #

toConstr :: HsConPatTyArg GhcPs -> Constr Source #

dataTypeOf :: HsConPatTyArg GhcPs -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcPs)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcPs)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcPs -> HsConPatTyArg GhcPs Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcPs -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcPs -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcPs -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcPs -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcPs -> m (HsConPatTyArg GhcPs) Source #

Data (HsConPatTyArg GhcRn) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcRn -> c (HsConPatTyArg GhcRn) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcRn) Source #

toConstr :: HsConPatTyArg GhcRn -> Constr Source #

dataTypeOf :: HsConPatTyArg GhcRn -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcRn)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcRn)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcRn -> HsConPatTyArg GhcRn Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcRn -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcRn -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcRn -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcRn -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcRn -> m (HsConPatTyArg GhcRn) Source #

Data (HsConPatTyArg GhcTc) Source # 
Instance details

Defined in GHC.Hs.Instances

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsConPatTyArg GhcTc -> c (HsConPatTyArg GhcTc) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsConPatTyArg GhcTc) Source #

toConstr :: HsConPatTyArg GhcTc -> Constr Source #

dataTypeOf :: HsConPatTyArg GhcTc -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsConPatTyArg GhcTc)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsConPatTyArg GhcTc)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsConPatTyArg GhcTc -> HsConPatTyArg GhcTc Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcTc -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsConPatTyArg GhcTc -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsConPatTyArg GhcTc -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsConPatTyArg GhcTc -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsConPatTyArg GhcTc -> m (HsConPatTyArg GhcTc) Source #

Outputable (HsPatSigType p) => Outputable (HsConPatTyArg p) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsConPatTyArg p -> SDoc Source #

data HsRecFields p arg Source #

Haskell Record Fields

HsRecFields is used only for patterns and expressions (not data type declarations)

Constructors

HsRecFields 

Instances

Instances details
Data body => Data (HsRecFields GhcPs body) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 #

(Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ Located RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecFields p arg -> SDoc Source #

data HsFieldBind lhs rhs Source #

Haskell Field Binding

For details on above see Note [exact print annotations] in GHC.Parser.Annotation

Constructors

HsFieldBind 

Fields

Instances

Instances details
Foldable (HsFieldBind lhs) Source # 
Instance details

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 # 
Instance details

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 #

Functor (HsFieldBind lhs) Source # 
Instance details

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 #

(Data a, Data b) => Data (HsFieldBind a b) Source # 
Instance details

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 #

(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsFieldBind p arg) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsFieldBind p arg -> SDoc Source #

type Anno (HsFieldBind lhs rhs) Source # 
Instance details

Defined in GHC.Hs.Pat

type Anno (HsFieldBind lhs rhs) = SrcSpanAnnA

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 = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr p) Source #

Haskell Record Update Field

type LHsRecUpdField p = XRec p (HsRecUpdField p) 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 

Instances

Instances details
Data RecFieldsDotDot Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RecFieldsDotDot -> c RecFieldsDotDot Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RecFieldsDotDot Source #

toConstr :: RecFieldsDotDot -> Constr Source #

dataTypeOf :: RecFieldsDotDot -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RecFieldsDotDot) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RecFieldsDotDot) Source #

gmapT :: (forall b. Data b => b -> b) -> RecFieldsDotDot -> RecFieldsDotDot Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldsDotDot -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RecFieldsDotDot -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> RecFieldsDotDot -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RecFieldsDotDot -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RecFieldsDotDot -> m RecFieldsDotDot Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldsDotDot -> m RecFieldsDotDot Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RecFieldsDotDot -> m RecFieldsDotDot Source #

Eq RecFieldsDotDot Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Ord RecFieldsDotDot Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

type Anno RecFieldsDotDot Source # 
Instance details

Defined in GHC.Hs.Pat

hsRecFields :: forall p arg. UnXRec p => HsRecFields p arg -> [XCFieldOcc p] Source #

hsRecFieldSel :: forall p arg. UnXRec p => HsRecField p arg -> XCFieldOcc p Source #

hsRecFieldsArgs :: forall p arg. UnXRec p => HsRecFields p arg -> [arg] Source #

isSimplePat :: LPat (GhcPass x) -> Maybe (IdP (GhcPass x)) Source #

Is the pattern any of combination of:

  • (pat)
  • pat :: Type
  • ~pat
  • !pat
  • x (variable)

gParPat :: LPat (GhcPass pass) -> Pat (GhcPass pass) Source #

Parenthesize a pattern without token information

patNeedsParens :: forall p. IsPass p => PprPrec -> Pat (GhcPass p) -> Bool Source #

patNeedsParens p pat returns True if the pattern pat needs parentheses under precedence p.

parenthesizePat :: IsPass p => PprPrec -> LPat (GhcPass p) -> LPat (GhcPass p) Source #

parenthesizePat p pat checks if patNeedsParens p pat is true, and if so, surrounds pat with a ParPat. Otherwise, it simply returns pat.

Orphan instances

Outputable (HsPatSigType p) => Outputable (HsConPatTyArg p) Source # 
Instance details

Methods

ppr :: HsConPatTyArg p -> SDoc Source #

OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # 
Instance details

Methods

ppr :: Pat (GhcPass p) -> SDoc Source #

(Outputable p, OutputableBndr p, Outputable arg) => Outputable (HsFieldBind p arg) Source # 
Instance details

Methods

ppr :: HsFieldBind p arg -> SDoc Source #

(Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ Located RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # 
Instance details

Methods

ppr :: HsRecFields p arg -> SDoc Source #