ghc-8.4.4: The GHC API

Safe HaskellNone
LanguageHaskell2010

HsLit

Synopsis

Documentation

data HsLit x Source #

Haskell Literal

Constructors

HsChar (XHsChar x) Char

Character

HsCharPrim (XHsCharPrim x) Char

Unboxed character

HsString (XHsString x) FastString

String

HsStringPrim (XHsStringPrim x) ByteString

Packed bytes

HsInt (XHsInt x) IntegralLit

Genuinely an Int; arises from TcGenDeriv, and from TRANSLATION

HsIntPrim (XHsIntPrim x) Integer

literal Int#

HsWordPrim (XHsWordPrim x) Integer

literal Word#

HsInt64Prim (XHsInt64Prim x) Integer

literal Int64#

HsWord64Prim (XHsWord64Prim x) Integer

literal Word64#

HsInteger (XHsInteger x) Integer Type

Genuinely an integer; arises only from TRANSLATION (overloaded literals are done with HsOverLit)

HsRat (XHsRat x) FractionalLit Type

Genuinely a rational; arises only from TRANSLATION (overloaded literals are done with HsOverLit)

HsFloatPrim (XHsFloatPrim x) FractionalLit

Unboxed Float

HsDoublePrim (XHsDoublePrim x) FractionalLit

Unboxed Double

Instances
Eq (HsLit x) # 
Instance details

Defined in HsLit

Methods

(==) :: HsLit x -> HsLit x -> Bool #

(/=) :: HsLit x -> HsLit x -> Bool #

DataId x => Data (HsLit x) # 
Instance details

Defined in HsLit

Methods

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

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

toConstr :: HsLit x -> Constr Source #

dataTypeOf :: HsLit x -> DataType Source #

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

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

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

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

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

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

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

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

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

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

SourceTextX x => Outputable (HsLit x) # 
Instance details

Defined in HsLit

Methods

ppr :: HsLit x -> SDoc Source #

pprPrec :: Rational -> HsLit x -> SDoc Source #

data HsOverLit p Source #

Haskell Overloaded Literal

Instances
Eq (HsOverLit p) # 
Instance details

Defined in HsLit

Methods

(==) :: HsOverLit p -> HsOverLit p -> Bool #

(/=) :: HsOverLit p -> HsOverLit p -> Bool #

DataId p => Data (HsOverLit p) # 
Instance details

Defined in HsLit

Methods

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

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

toConstr :: HsOverLit p -> Constr Source #

dataTypeOf :: HsOverLit p -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord (HsOverLit p) # 
Instance details

Defined in HsLit

(SourceTextX p, OutputableBndrId p) => Outputable (HsOverLit p) # 
Instance details

Defined in HsLit

data OverLitVal Source #

Overloaded Literal Value

Constructors

HsIntegral !IntegralLit

Integer-looking literals;

HsFractional !FractionalLit

Frac-looking literals

HsIsString !SourceText !FastString

String-looking literals

Instances
Eq OverLitVal # 
Instance details

Defined in HsLit

Data OverLitVal # 
Instance details

Defined in HsLit

Methods

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

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

toConstr :: OverLitVal -> Constr Source #

dataTypeOf :: OverLitVal -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord OverLitVal # 
Instance details

Defined in HsLit

Outputable OverLitVal # 
Instance details

Defined in HsLit

convertLit :: ConvertIdX a b => HsLit a -> HsLit b Source #

Convert a literal from one index type to another, updating the annotations according to the relevant Convertable instance

pmPprHsLit :: SourceTextX x => HsLit x -> SDoc Source #

pmPprHsLit pretty prints literals and is used when pretty printing pattern match warnings. All are printed the same (i.e., without hashes if they are primitive and not wrapped in constructors if they are boxed). This happens mainly for too reasons: * We do not want to expose their internal representation * The warnings become too messy

isCompoundHsLit :: HsLit x -> Bool Source #

Returns True for compound literals that will need parentheses.

isCompoundHsOverLit :: HsOverLit x -> Bool Source #

Returns True for compound overloaded literals that will need parentheses when used in an argument position.