ghc-lib-parser-0.20220501: The GHC API, decoupled from GHC versions
Safe HaskellNone
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) (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 Arity

Anonymous sum pattern

ConPat

Constructor Pattern

ViewPat (XViewPat p) (LHsExpr p) (LPat p)

View Pattern

SplicePat (XSplicePat p) (HsSplice p)

Splice Pattern (Includes quasi-quotes)

LitPat (XLitPat p) (HsLit p)

Literal Pattern Used for *non-overloaded* literal patterns: Int, 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 (XSigPat p) (LPat p) (HsPatSigType (NoGhcTc p))

Pattern with a type signature

XPat !(XXPat p) 

Instances

Instances details
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) #

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

toConstr :: Pat GhcTc -> Constr #

dataTypeOf :: Pat GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: Pat GhcRn -> Constr #

dataTypeOf :: Pat GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

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) #

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

toConstr :: Pat GhcPs -> Constr #

dataTypeOf :: Pat GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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 #

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

toConstr :: EpAnnSumPat -> Constr #

dataTypeOf :: EpAnnSumPat -> DataType #

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

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

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

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

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

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

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

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

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

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

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 #

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

toConstr :: ConPatTc -> Constr #

dataTypeOf :: ConPatTc -> DataType #

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

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

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

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

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

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

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

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

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

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

type family ConLikeP x Source #

Instances

Instances details
type ConLikeP GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type ConLikeP GhcPs 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) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsPatExpansion a b) #

toConstr :: HsPatExpansion a b -> Constr #

dataTypeOf :: HsPatExpansion a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsPatExpansion a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsPatExpansion a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsPatExpansion a b -> HsPatExpansion a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsPatExpansion a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsPatExpansion a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsPatExpansion a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsPatExpansion a b -> m (HsPatExpansion a b) #

(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 #

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

toConstr :: XXPatGhcTc -> Constr #

dataTypeOf :: XXPatGhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Haskell Constructor Pattern Details

hsConPatArgs :: forall p. 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

Instances details
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) #

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

toConstr :: HsRecFields GhcTc body -> Constr #

dataTypeOf :: HsRecFields GhcTc body -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcTc body -> HsRecFields GhcTc body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcTc body -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcTc body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcTc body -> m (HsRecFields GhcTc body) #

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) #

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

toConstr :: HsRecFields GhcRn body -> Constr #

dataTypeOf :: HsRecFields GhcRn body -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcRn body -> HsRecFields GhcRn body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcRn body -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcRn body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcRn body -> m (HsRecFields GhcRn body) #

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) #

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

toConstr :: HsRecFields GhcPs body -> Constr #

dataTypeOf :: HsRecFields GhcPs body -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> HsRecFields GhcPs body -> HsRecFields GhcPs body #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsRecFields GhcPs body -> r #

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

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsRecFields GhcPs body -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsRecFields GhcPs body -> m (HsRecFields GhcPs body) #

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

Defined in Language.Haskell.Syntax.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
Functor (HsFieldBind lhs) Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

fmap :: (a -> b) -> HsFieldBind lhs a -> HsFieldBind lhs b #

(<$) :: a -> HsFieldBind lhs b -> HsFieldBind lhs a #

Foldable (HsFieldBind lhs) Source # 
Instance details

Defined in Language.Haskell.Syntax.Pat

Methods

fold :: Monoid m => HsFieldBind lhs m -> m #

foldMap :: Monoid m => (a -> m) -> HsFieldBind lhs a -> m #

foldMap' :: Monoid m => (a -> m) -> HsFieldBind lhs a -> m #

foldr :: (a -> b -> b) -> b -> HsFieldBind lhs a -> b #

foldr' :: (a -> b -> b) -> b -> HsFieldBind lhs a -> b #

foldl :: (b -> a -> b) -> b -> HsFieldBind lhs a -> b #

foldl' :: (b -> a -> b) -> b -> HsFieldBind lhs a -> b #

foldr1 :: (a -> a -> a) -> HsFieldBind lhs a -> a #

foldl1 :: (a -> a -> a) -> HsFieldBind lhs a -> a #

toList :: HsFieldBind lhs a -> [a] #

null :: HsFieldBind lhs a -> Bool #

length :: HsFieldBind lhs a -> Int #

elem :: Eq a => a -> HsFieldBind lhs a -> Bool #

maximum :: Ord a => HsFieldBind lhs a -> a #

minimum :: Ord a => HsFieldBind lhs a -> a #

sum :: Num a => HsFieldBind lhs a -> a #

product :: Num a => HsFieldBind lhs a -> a #

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) #

sequenceA :: Applicative f => HsFieldBind lhs (f a) -> f (HsFieldBind lhs a) #

mapM :: Monad m => (a -> m b) -> HsFieldBind lhs a -> m (HsFieldBind lhs b) #

sequence :: Monad m => HsFieldBind lhs (m a) -> m (HsFieldBind lhs a) #

(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) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (HsFieldBind a b) #

toConstr :: HsFieldBind a b -> Constr #

dataTypeOf :: HsFieldBind a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (HsFieldBind a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (HsFieldBind a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> HsFieldBind a b -> HsFieldBind a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldBind a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HsFieldBind a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> HsFieldBind a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HsFieldBind a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HsFieldBind a b -> m (HsFieldBind a b) #

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

Defined in Language.Haskell.Syntax.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

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

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

Methods

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