| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Language.Haskell.Syntax.Pat
Synopsis
- data Pat p- = WildPat (XWildPat p)
- | VarPat (XVarPat p) (LIdP p)
- | LazyPat (XLazyPat p) (LPat p)
- | AsPat (XAsPat p) (LIdP p) !(LHsToken "@" p) (LPat p)
- | ParPat (XParPat p) !(LHsToken "(" p) (LPat p) !(LHsToken ")" p)
- | BangPat (XBangPat p) (LPat p)
- | ListPat (XListPat p) [LPat p]
- | TuplePat (XTuplePat p) [LPat p] Boxity
- | SumPat (XSumPat p) (LPat p) ConTag SumWidth
- | ConPat { - pat_con_ext :: XConPat p
- pat_con :: XRec p (ConLikeP p)
- pat_args :: HsConPatDetails p
 
- | ViewPat (XViewPat p) (LHsExpr p) (LPat p)
- | SplicePat (XSplicePat p) (HsUntypedSplice p)
- | LitPat (XLitPat p) (HsLit p)
- | NPat (XNPat p) (XRec p (HsOverLit p)) (Maybe (SyntaxExpr p)) (SyntaxExpr p)
- | NPlusKPat (XNPlusKPat p) (LIdP p) (XRec p (HsOverLit p)) (HsOverLit p) (SyntaxExpr p) (SyntaxExpr p)
- | SigPat (XSigPat p) (LPat p) (HsPatSigType (NoGhcTc p))
- | XPat !(XXPat p)
 
- type LPat p = XRec p (Pat p)
- type family ConLikeP x
- type HsConPatDetails p = HsConDetails (HsConPatTyArg (NoGhcTc p)) (LPat p) (HsRecFields p (LPat p))
- hsConPatArgs :: forall p. UnXRec p => HsConPatDetails p -> [LPat p]
- data HsConPatTyArg p = HsConPatTyArg !(LHsToken "@" p) (HsPatSigType p)
- data HsRecFields p arg = HsRecFields {- rec_flds :: [LHsRecField p arg]
- rec_dotdot :: Maybe (XRec p RecFieldsDotDot)
 
- data HsFieldBind lhs rhs = HsFieldBind {}
- type LHsFieldBind p id arg = XRec p (HsFieldBind id arg)
- type HsRecField p arg = HsFieldBind (LFieldOcc p) arg
- type LHsRecField p arg = XRec p (HsRecField p arg)
- type HsRecUpdField p = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr p)
- type LHsRecUpdField p = XRec p (HsRecUpdField p)
- newtype RecFieldsDotDot = RecFieldsDotDot {}
- hsRecFields :: forall p arg. UnXRec p => HsRecFields p arg -> [XCFieldOcc p]
- hsRecFieldSel :: forall p arg. UnXRec p => HsRecField p arg -> XCFieldOcc p
- hsRecFieldsArgs :: forall p arg. UnXRec p => HsRecFields p arg -> [arg]
Documentation
Pattern
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
 ^ -  | 
| AsPat (XAsPat p) (LIdP p) !(LHsToken "@" p) (LPat p) | As pattern
 ^ -  | 
| ParPat | |
| BangPat (XBangPat p) (LPat p) | Bang pattern
 ^ -  | 
| 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 | 
| Fields 
 | |
| ViewPat | |
| 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
| Data (Pat GhcPs) Source # | |
| Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pat GhcPs -> c (Pat GhcPs) # 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 # | |
| 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 # | |
| 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) # | |
| OutputableBndrId p => Outputable (Pat (GhcPass p)) Source # | |
| type Anno (Pat (GhcPass p)) Source # | |
| Defined in GHC.Hs.Pat | |
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
| Data (HsConPatTyArg GhcPs) Source # | |
| Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> 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 # | |
| 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 # | |
| 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) # | |
| Outputable (HsPatSigType p) => Outputable (HsConPatTyArg p) Source # | |
| 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 | |
| Fields 
 | |
Instances
| Data body => Data (HsRecFields GhcPs body) Source # | |
| Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HsRecFields GhcPs body -> c (HsRecFields GhcPs body) # 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 # | |
| 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 # | |
| 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) # | |
| (Outputable arg, Outputable (XRec p (HsRecField p arg)), XRec p RecFieldsDotDot ~ Located RecFieldsDotDot) => Outputable (HsRecFields p arg) Source # | |
| 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 | |
Instances
| Foldable (HsFieldBind lhs) Source # | |
| 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 # | |
| 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) # | |
| Functor (HsFieldBind lhs) Source # | |
| Defined in Language.Haskell.Syntax.Pat Methods fmap :: (a -> b) -> HsFieldBind lhs a -> HsFieldBind lhs b # (<$) :: a -> HsFieldBind lhs b -> HsFieldBind lhs a # | |
| (Data a, Data b) => Data (HsFieldBind a b) Source # | |
| Defined in GHC.Hs.Instances Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> HsFieldBind a b -> c (HsFieldBind a b) # 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 # | |
| Defined in GHC.Hs.Pat Methods ppr :: HsFieldBind p arg -> SDoc Source # | |
| type Anno (HsFieldBind lhs rhs) Source # | |
| Defined in GHC.Hs.Pat | |
type LHsFieldBind p id arg = XRec p (HsFieldBind id arg) Source #
Located Haskell Record Field
type HsRecField p arg = HsFieldBind (LFieldOcc p) arg Source #
Haskell Record Field
type LHsRecField p arg = XRec p (HsRecField p arg) Source #
Located Haskell Record Field
type HsRecUpdField p = 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 | |
| Fields | |
Instances
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 #