ghc-9.6.1: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Types.SourceText

Contents

Description

Source text

Keeping Source Text for source to source conversions

Synopsis

Documentation

data SourceText Source #

Constructors

SourceText String 
NoSourceText

For when code is generated, e.g. TH, deriving. The pretty printer will then make its own representation of the item.

Instances

Instances details
Data SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceText -> c SourceText Source #

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

toConstr :: SourceText -> Constr Source #

dataTypeOf :: SourceText -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Binary SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: SourceText -> SDoc Source #

Eq SourceText Source # 
Instance details

Defined in GHC.Types.SourceText

type Anno (SourceText, RuleName) Source # 
Instance details

Defined in GHC.Hs.Decls

pprWithSourceText :: SourceText -> SDoc -> SDoc Source #

Special combinator for showing string literals.

Literals

data IntegralLit Source #

Integral Literal

Used (instead of Integer) to represent negative zegative zero which is required for NegativeLiterals extension to correctly parse `-0::Double` as negative zero. See also #13211.

Constructors

IL 

Instances

Instances details
Data IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntegralLit -> c IntegralLit Source #

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

toConstr :: IntegralLit -> Constr Source #

dataTypeOf :: IntegralLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

ppr :: IntegralLit -> SDoc Source #

Eq IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

Ord IntegralLit Source # 
Instance details

Defined in GHC.Types.SourceText

data FractionalLit Source #

Fractional Literal

Used (instead of Rational) to represent exactly the floating point literal that we encountered in the user's source program. This allows us to pretty-print exactly what the user wrote, which is important e.g. for floating point numbers that can't represented as Doubles (we used to via Double for pretty-printing). See also #2245. Note [FractionalLit representation] in GHC.HsToCore.Match.Literal The actual value then is: sign * fl_signi * (fl_exp_base^fl_exp) where sign = if fl_neg then (-1) else 1

For example FL { fl_neg = True, fl_signi = 5.3, fl_exp = 4, fl_exp_base = Base10 } denotes -5300

Constructors

FL 

Fields

Instances

Instances details
Data FractionalLit Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FractionalLit -> c FractionalLit Source #

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

toConstr :: FractionalLit -> Constr Source #

dataTypeOf :: FractionalLit -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show FractionalLit Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable FractionalLit Source # 
Instance details

Defined in GHC.Types.SourceText

Eq FractionalLit Source #

Be wary of using this instance to compare for equal *values* when exponents are large. The same value expressed in different syntactic form won't compare as equal when any of the exponents is >= 100.

Instance details

Defined in GHC.Types.SourceText

Ord FractionalLit Source #

Be wary of using this instance to compare for equal *values* when exponents are large. The same value expressed in different syntactic form won't compare as equal when any of the exponents is >= 100.

Instance details

Defined in GHC.Types.SourceText

data StringLiteral Source #

A String Literal in the source, including its original raw format for use by source to source manipulation tools.

Instances

Instances details
Data StringLiteral Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StringLiteral -> c StringLiteral Source #

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

toConstr :: StringLiteral -> Constr Source #

dataTypeOf :: StringLiteral -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Binary StringLiteral Source # 
Instance details

Defined in GHC.Types.SourceText

Outputable StringLiteral Source # 
Instance details

Defined in GHC.Types.SourceText

Eq StringLiteral Source # 
Instance details

Defined in GHC.Types.SourceText

type Anno StringLiteral Source # 
Instance details

Defined in GHC.Hs.Binds

integralFractionalLit :: Bool -> Integer -> FractionalLit Source #

The integer should already be negated if it's negative.

mkSourceFractionalLit :: String -> Bool -> Integer -> Integer -> FractionalExponentBase -> FractionalLit Source #

The arguments should already be negated if they are negative.

data FractionalExponentBase Source #

Constructors

Base2 
Base10 

Instances

Instances details
Data FractionalExponentBase Source # 
Instance details

Defined in GHC.Types.SourceText

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FractionalExponentBase -> c FractionalExponentBase Source #

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

toConstr :: FractionalExponentBase -> Constr Source #

dataTypeOf :: FractionalExponentBase -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show FractionalExponentBase Source # 
Instance details

Defined in GHC.Types.SourceText

Eq FractionalExponentBase Source # 
Instance details

Defined in GHC.Types.SourceText

Ord FractionalExponentBase Source # 
Instance details

Defined in GHC.Types.SourceText