Safe Haskell | None |
---|---|
Language | GHC2021 |
Source-language literals
Synopsis
- module Language.Haskell.Syntax.Lit
- convertLit :: forall (p1 :: Pass) (p2 :: Pass). HsLit (GhcPass p1) -> HsLit (GhcPass p2)
- hsLitNeedsParens :: PprPrec -> HsLit x -> Bool
- hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool
- negateOverLitVal :: OverLitVal -> OverLitVal
- overLitType :: HsOverLit GhcTc -> Type
- pmPprHsLit :: forall (x :: Pass). HsLit (GhcPass x) -> SDoc
- pprXOverLit :: forall (p :: Pass). GhcPass p -> XOverLit (GhcPass p) -> SDoc
- data OverLitRn = OverLitRn {}
- data OverLitTc = OverLitTc {
- ol_rebindable :: Bool
- ol_witness :: HsExpr GhcTc
- ol_type :: Type
Documentation
module Language.Haskell.Syntax.Lit
convertLit :: forall (p1 :: Pass) (p2 :: Pass). HsLit (GhcPass p1) -> HsLit (GhcPass p2) Source #
Convert a literal from one index type to another
hsLitNeedsParens :: PprPrec -> HsLit x -> Bool Source #
returns hsLitNeedsParens
p lTrue
if a literal l
needs
to be parenthesized under precedence p
.
See Note [Printing of literals in Core] in GHC.Types.Literal for the reasoning.
hsOverLitNeedsParens :: PprPrec -> HsOverLit x -> Bool Source #
returns hsOverLitNeedsParens
p olTrue
if an overloaded literal
ol
needs to be parenthesized under precedence p
.
pmPprHsLit :: forall (x :: Pass). 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
Instances
Data OverLitRn Source # | |
Defined in GHC.Hs.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OverLitRn -> c OverLitRn # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitRn # toConstr :: OverLitRn -> Constr # dataTypeOf :: OverLitRn -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitRn) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitRn) # gmapT :: (forall b. Data b => b -> b) -> OverLitRn -> OverLitRn # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitRn -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitRn -> r # gmapQ :: (forall d. Data d => d -> u) -> OverLitRn -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitRn -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn # |
OverLitTc | |
|
Instances
Data OverLitTc Source # | |
Defined in GHC.Hs.Instances 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 # |
Orphan instances
Outputable OverLitVal Source # | |
ppr :: OverLitVal -> SDoc Source # | |
Outputable (HsLit (GhcPass p)) Source # | |
OutputableBndrId p => Outputable (HsOverLit (GhcPass p)) Source # | |
Eq (XXOverLit p) => Eq (HsOverLit p) Source # | |
Ord (XXOverLit p) => Ord (HsOverLit p) Source # | |