ghc-9.0.2: 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) (Located (IdP p))

Variable Pattern

LazyPat (XLazyPat p) (LPat p)

Lazy Pattern ^ - AnnKeywordId : AnnTilde

AsPat (XAsPat p) (Located (IdP p)) (LPat p)

As pattern ^ - AnnKeywordId : AnnAt

ParPat (XParPat p) (LPat p)

Parenthesised pattern See Note [Parens in HsSyn] in GHC.Hs.Expr ^ - AnnKeywordId : AnnOpen '(', AnnClose ')'

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 Arity

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) (Located (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)

Natural Pattern

NPlusKPat (XNPlusKPat p) (Located (IdP p)) (Located (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)

n+k pattern

SigPat

Fields

XPat !(XXPat p)

Trees that Grow extension point for new constructors

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 #

pprPrec :: Rational -> Pat (GhcPass p) -> SDoc Source #

type LPat p = XRec p Pat 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
     

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 #

data CoPat Source #

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.

Constructors

CoPat 

Fields

Instances

Instances details
Data CoPat 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) -> CoPat -> c CoPat Source #

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

toConstr :: CoPat -> Constr Source #

dataTypeOf :: CoPat -> DataType Source #

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

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

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

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

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

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

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

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

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

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

data ListPatTc Source #

Instances

Instances details
Data ListPatTc 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) -> ListPatTc -> c ListPatTc Source #

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

toConstr :: ListPatTc -> Constr Source #

dataTypeOf :: ListPatTc -> DataType Source #

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

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

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

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

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

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

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

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

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

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ListPatTc -> m ListPatTc 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

type HsConPatDetails p = HsConDetails (LPat p) (HsRecFields p (LPat p)) Source #

Haskell Constructor Pattern Details

data HsRecFields p arg Source #

Haskell Record Fields

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

Constructors

HsRecFields 

Fields

Instances

Instances details
Foldable (HsRecFields p) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

fold :: Monoid m => HsRecFields p m -> m Source #

foldMap :: Monoid m => (a -> m) -> HsRecFields p a -> m Source #

foldMap' :: Monoid m => (a -> m) -> HsRecFields p a -> m Source #

foldr :: (a -> b -> b) -> b -> HsRecFields p a -> b Source #

foldr' :: (a -> b -> b) -> b -> HsRecFields p a -> b Source #

foldl :: (b -> a -> b) -> b -> HsRecFields p a -> b Source #

foldl' :: (b -> a -> b) -> b -> HsRecFields p a -> b Source #

foldr1 :: (a -> a -> a) -> HsRecFields p a -> a Source #

foldl1 :: (a -> a -> a) -> HsRecFields p a -> a Source #

toList :: HsRecFields p a -> [a] Source #

null :: HsRecFields p a -> Bool Source #

length :: HsRecFields p a -> Int Source #

elem :: Eq a => a -> HsRecFields p a -> Bool Source #

maximum :: Ord a => HsRecFields p a -> a Source #

minimum :: Ord a => HsRecFields p a -> a Source #

sum :: Num a => HsRecFields p a -> a Source #

product :: Num a => HsRecFields p a -> a Source #

Traversable (HsRecFields p) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

traverse :: Applicative f => (a -> f b) -> HsRecFields p a -> f (HsRecFields p b) Source #

sequenceA :: Applicative f => HsRecFields p (f a) -> f (HsRecFields p a) Source #

mapM :: Monad m => (a -> m b) -> HsRecFields p a -> m (HsRecFields p b) Source #

sequence :: Monad m => HsRecFields p (m a) -> m (HsRecFields p a) Source #

Functor (HsRecFields p) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

fmap :: (a -> b) -> HsRecFields p a -> HsRecFields p b Source #

(<$) :: a -> HsRecFields p b -> HsRecFields p a Source #

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 (HsRecFields p arg) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecFields p arg -> SDoc Source #

pprPrec :: Rational -> HsRecFields p arg -> SDoc Source #

data HsRecField' id arg Source #

Haskell Record Field

For details on above see note [Api annotations] in GHC.Parser.Annotation

Constructors

HsRecField 

Fields

Instances

Instances details
Foldable (HsRecField' id) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

fold :: Monoid m => HsRecField' id m -> m Source #

foldMap :: Monoid m => (a -> m) -> HsRecField' id a -> m Source #

foldMap' :: Monoid m => (a -> m) -> HsRecField' id a -> m Source #

foldr :: (a -> b -> b) -> b -> HsRecField' id a -> b Source #

foldr' :: (a -> b -> b) -> b -> HsRecField' id a -> b Source #

foldl :: (b -> a -> b) -> b -> HsRecField' id a -> b Source #

foldl' :: (b -> a -> b) -> b -> HsRecField' id a -> b Source #

foldr1 :: (a -> a -> a) -> HsRecField' id a -> a Source #

foldl1 :: (a -> a -> a) -> HsRecField' id a -> a Source #

toList :: HsRecField' id a -> [a] Source #

null :: HsRecField' id a -> Bool Source #

length :: HsRecField' id a -> Int Source #

elem :: Eq a => a -> HsRecField' id a -> Bool Source #

maximum :: Ord a => HsRecField' id a -> a Source #

minimum :: Ord a => HsRecField' id a -> a Source #

sum :: Num a => HsRecField' id a -> a Source #

product :: Num a => HsRecField' id a -> a Source #

Traversable (HsRecField' id) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

traverse :: Applicative f => (a -> f b) -> HsRecField' id a -> f (HsRecField' id b) Source #

sequenceA :: Applicative f => HsRecField' id (f a) -> f (HsRecField' id a) Source #

mapM :: Monad m => (a -> m b) -> HsRecField' id a -> m (HsRecField' id b) Source #

sequence :: Monad m => HsRecField' id (m a) -> m (HsRecField' id a) Source #

Functor (HsRecField' id) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

fmap :: (a -> b) -> HsRecField' id a -> HsRecField' id b Source #

(<$) :: a -> HsRecField' id b -> HsRecField' id a Source #

(Data id, Data arg) => Data (HsRecField' id arg) 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) -> HsRecField' id arg -> c (HsRecField' id arg) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsRecField' id arg) Source #

toConstr :: HsRecField' id arg -> Constr Source #

dataTypeOf :: HsRecField' id arg -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsRecField' id arg)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsRecField' id arg)) Source #

gmapT :: (forall b. Data b => b -> b) -> HsRecField' id arg -> HsRecField' id arg Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecField' id arg -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> HsRecField' id arg -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecField' id arg -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecField' id arg -> m (HsRecField' id arg) Source #

(Outputable p, Outputable arg) => Outputable (HsRecField' p arg) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecField' p arg -> SDoc Source #

pprPrec :: Rational -> HsRecField' p arg -> SDoc Source #

type LHsRecField' p arg = Located (HsRecField' p arg) Source #

Located Haskell Record Field

type HsRecField p arg = HsRecField' (FieldOcc p) arg Source #

Haskell Record Field

type LHsRecField p arg = Located (HsRecField p arg) Source #

Located Haskell Record Field

type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p) Source #

Haskell Record Update Field

type LHsRecUpdField p = Located (HsRecUpdField p) Source #

Located Haskell Record Update Field

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

Is the pattern any of combination of:

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

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.