Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Source-language literals
Synopsis
- module Language.Haskell.Syntax.Lit
- data OverLitRn = OverLitRn {}
- data OverLitTc = OverLitTc {
- ol_rebindable :: Bool
- ol_witness :: HsExpr GhcTc
- ol_type :: Type
- pprXOverLit :: GhcPass p -> XOverLit (GhcPass p) -> SDoc
- overLitType :: HsOverLit GhcTc -> Type
- convertLit :: HsLit (GhcPass p1) -> HsLit (GhcPass p2)
- pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc
- pmPprHsLit :: HsLit (GhcPass x) -> SDoc
Documentation
module Language.Haskell.Syntax.Lit
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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitRn Source # toConstr :: OverLitRn -> Constr Source # dataTypeOf :: OverLitRn -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitRn) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitRn) Source # gmapT :: (forall b. Data b => b -> b) -> OverLitRn -> OverLitRn Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitRn -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitRn -> r Source # gmapQ :: (forall d. Data d => d -> u) -> OverLitRn -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitRn -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitRn -> m OverLitRn Source # |
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 Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OverLitTc Source # toConstr :: OverLitTc -> Constr Source # dataTypeOf :: OverLitTc -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OverLitTc) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OverLitTc) Source # gmapT :: (forall b. Data b => b -> b) -> OverLitTc -> OverLitTc Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OverLitTc -> r Source # gmapQ :: (forall d. Data d => d -> u) -> OverLitTc -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> OverLitTc -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OverLitTc -> m OverLitTc Source # |
convertLit :: HsLit (GhcPass p1) -> HsLit (GhcPass p2) Source #
Convert a literal from one index type to another
pp_st_suffix :: SourceText -> SDoc -> SDoc -> SDoc Source #
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