ghc-lib-parser-9.2.3.20220527: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Hs.Lit

Description

Source-language literals

Synopsis

Documentation

data OverLitTc Source #

Constructors

OverLitTc 

Instances

Instances details
Data OverLitTc Source # 
Instance details

Defined in GHC.Hs.Lit

Methods

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

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

toConstr :: OverLitTc -> Constr #

dataTypeOf :: OverLitTc -> DataType #

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

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

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

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

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

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

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

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

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

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

convertLit :: HsLit (GhcPass p1) -> HsLit (GhcPass p2) Source #

Convert a literal from one index type to another

pmPprHsLit :: HsLit (GhcPass 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

Orphan instances

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

Methods

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

Outputable (HsLit (GhcPass p)) Source # 
Instance details

Methods

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