ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

FieldLabel

Synopsis

Documentation

type FieldLabelString = FastString Source

Field labels are just represented as strings; they are not necessarily unique (even within a module)

type FieldLabelEnv = FastStringEnv FieldLabel Source

A map from labels to all the auxiliary information

data FieldLbl a Source

Fields in an algebraic record type

Constructors

FieldLabel 

Fields

Instances

Functor FieldLbl 

Methods

fmap :: (a -> b) -> FieldLbl a -> FieldLbl b Source

(<$) :: a -> FieldLbl b -> FieldLbl a Source

Foldable FieldLbl 

Methods

fold :: Monoid m => FieldLbl m -> m Source

foldMap :: Monoid m => (a -> m) -> FieldLbl a -> m Source

foldr :: (a -> b -> b) -> b -> FieldLbl a -> b Source

foldr' :: (a -> b -> b) -> b -> FieldLbl a -> b Source

foldl :: (b -> a -> b) -> b -> FieldLbl a -> b Source

foldl' :: (b -> a -> b) -> b -> FieldLbl a -> b Source

foldr1 :: (a -> a -> a) -> FieldLbl a -> a Source

foldl1 :: (a -> a -> a) -> FieldLbl a -> a Source

toList :: FieldLbl a -> [a] Source

null :: FieldLbl a -> Bool Source

length :: FieldLbl a -> Int Source

elem :: Eq a => a -> FieldLbl a -> Bool Source

maximum :: Ord a => FieldLbl a -> a Source

minimum :: Ord a => FieldLbl a -> a Source

sum :: Num a => FieldLbl a -> a Source

product :: Num a => FieldLbl a -> a Source

Traversable FieldLbl 

Methods

traverse :: Applicative f => (a -> f b) -> FieldLbl a -> f (FieldLbl b) Source

sequenceA :: Applicative f => FieldLbl (f a) -> f (FieldLbl a) Source

mapM :: Monad m => (a -> m b) -> FieldLbl a -> m (FieldLbl b) Source

sequence :: Monad m => FieldLbl (m a) -> m (FieldLbl a) Source

Eq a => Eq (FieldLbl a) 

Methods

(==) :: FieldLbl a -> FieldLbl a -> Bool

(/=) :: FieldLbl a -> FieldLbl a -> Bool

Data a => Data (FieldLbl a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldLbl a -> c (FieldLbl a) Source

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FieldLbl a) Source

toConstr :: FieldLbl a -> Constr Source

dataTypeOf :: FieldLbl a -> DataType Source

dataCast1 :: Typeable (TYPE Lifted -> TYPE Lifted) t => (forall d. Data d => c (t d)) -> Maybe (c (FieldLbl a)) Source

dataCast2 :: Typeable (TYPE Lifted -> TYPE Lifted -> TYPE Lifted) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FieldLbl a)) Source

gmapT :: (forall b. Data b => b -> b) -> FieldLbl a -> FieldLbl a Source

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r Source

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldLbl a -> r Source

gmapQ :: (forall d. Data d => d -> u) -> FieldLbl a -> [u] Source

gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldLbl a -> u Source

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldLbl a -> m (FieldLbl a) Source

Outputable a => Outputable (FieldLbl a) 
Binary a => Binary (FieldLbl a) 

mkFieldLabelOccs :: FieldLabelString -> OccName -> Bool -> FieldLbl OccName Source

Record selector OccNames are built from the underlying field name and the name of the first data constructor of the type, to support duplicate record field names. See Note [Why selector names include data constructors].