ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

Language.Haskell.Syntax.Pat

Synopsis

Documentation

data Pat p Source #

Pattern

Constructors

WildPat (XWildPat p)

Wildcard Pattern, i.e. _

VarPat (XVarPat p) (LIdP p)

Variable Pattern, e.g. x

LazyPat (XLazyPat p) (LPat p)

Lazy Pattern, e.g. ~x

exactprint: the location of ~ is captured using AnnKeywordId : AnnTilde

AsPat (XAsPat p) (LIdP p) (LPat p)

As pattern, e.g. x@pat

exactprint: the location of @ is captured using EpToken "@"

ParPat (XParPat p) (LPat p)

Parenthesised pattern, e.g. (x)

exactprint: the location of parentheses is captured using EpToken "(" and EpToken ")"

BangPat (XBangPat p) (LPat p)

Bang pattern, e.g. !x

exactprint: the location of ! is captured using AnnKeywordId : AnnBang

ListPat (XListPat p) [LPat p]

Syntactic List, e.g. [x] or [x,y]. Note that [] and (x:xs) patterns are both represented using ConPat.

exactprint: the location of brackets is captured using AnnKeywordId : AnnOpenS and AnnCloseS respectively.

TuplePat

Tuple pattern, e.g. (x, y) (boxed tuples) or (# x, y #) (requires -XUnboxedTuples)

exactprint: the location of parens is captured using AnnKeywordId : AnnOpenP and AnnCloseP in case of boxed tuples or AnnOpenPH and AnnClosePH in case of unboxed tuples.

Fields

  • (XTuplePat p)

    After typechecking, holds the types of the tuple components

  • [LPat p]

    Tuple sub-patterns

  • Boxity
     
OrPat (XOrPat p) (NonEmpty (LPat p))

Or Pattern, e.g. (pat_1; ...; pat_n). Used by -XOrPatterns

Since: ghc-9.12.1

SumPat (XSumPat p) (LPat p) ConTag SumWidth

Anonymous sum pattern, e.g. (# x | #). Used by -XUnboxedSums

exactprint: the location of (# and #) is captured using AnnKeywordId : AnnOpenPH and AnnClosePH respectively.

ConPat

Constructor Pattern, e.g. (), [] or Nothing

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

View Pattern, e.g. someFun -> pat. Used by -XViewPatterns

exactprint: the location of -> is captured using AnnKeywordId : AnnRarrow

SplicePat (XSplicePat p) (HsUntypedSplice p)

Splice Pattern, e.g. $(pat)

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 -XOverloadedStrings

exactprint: the location of - (for negative literals) is captured using AnnKeywordId : AnnMinus

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

n+k pattern, e.g. n+1, used by -XNPlusKPatterns

SigPat (XSigPat p) (LPat p) (HsPatSigType (NoGhcTc p))

Pattern with a type signature, e.g. x :: Int

exactprint: the location of :: is captured using AnnKeywordId : AnnDcolon

EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p))

Embed the syntax of types into patterns, e.g. fn (type t) = rhs. Enabled by -XExplicitNamespaces in conjunction with -XRequiredTypeArguments.

exactprint: the location of the type keyword is captured using EpToken "type"

InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p))

Type abstraction which brings into scope type variables associated with invisible forall. E.g. fn @t ... = rhs. Used by -XTypeAbstractions.

exactprint: the location of @ is captured by EpToken "@"

XPat !(XXPat p)

TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension

Instances

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

Defined in GHC.Hs.Pat

Methods

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

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

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

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

Defined in GHC.Hs.Pat

type Anno [LocatedA (Pat (GhcPass p))] Source # 
Instance details

Defined in GHC.Hs.Expr

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

Haskell Constructor Pattern Details

data HsConPatTyArg p Source #

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

Constructors

HsConPatTyArg !(XConPatTyArg p) (HsTyPat p) 

Instances

Instances details
Outputable (HsTyPat p) => Outputable (HsConPatTyArg p) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsConPatTyArg p -> SDoc Source #

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

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

toConstr :: HsConPatTyArg GhcPs -> Constr #

dataTypeOf :: HsConPatTyArg GhcPs -> DataType #

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: HsConPatTyArg GhcRn -> Constr #

dataTypeOf :: HsConPatTyArg GhcRn -> DataType #

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

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

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

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

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

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

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

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

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

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

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

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

toConstr :: HsConPatTyArg GhcTc -> Constr #

dataTypeOf :: HsConPatTyArg GhcTc -> DataType #

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

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

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

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

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

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

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

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

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

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

type family XConPatTyArg p Source #

Instances

Instances details
type XConPatTyArg GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPatTyArg GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XConPatTyArg GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

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
(Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ LocatedE RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # 
Instance details

Defined in GHC.Hs.Pat

Methods

ppr :: HsRecFields p arg -> SDoc 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) #

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

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

type family XHsRecFields p Source #

Instances

Instances details
type XHsRecFields GhcPs Source # 
Instance details

Defined in GHC.Hs.Pat

type XHsRecFields GhcRn Source # 
Instance details

Defined in GHC.Hs.Pat

type XHsRecFields GhcTc Source # 
Instance details

Defined in GHC.Hs.Pat

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

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

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

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 q = HsFieldBind (LAmbiguousFieldOcc 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 

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 #

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

toConstr :: RecFieldsDotDot -> Constr #

dataTypeOf :: RecFieldsDotDot -> DataType #

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

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

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

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

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

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

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

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

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

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

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

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