{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module GHC.Types.Literal
(
Literal(..)
, LitNumType(..)
, mkLitInt, mkLitIntWrap, mkLitIntWrapC, mkLitIntUnchecked
, mkLitWord, mkLitWordWrap, mkLitWordWrapC, mkLitWordUnchecked
, mkLitInt8, mkLitInt8Wrap, mkLitInt8Unchecked
, mkLitWord8, mkLitWord8Wrap, mkLitWord8Unchecked
, mkLitInt16, mkLitInt16Wrap, mkLitInt16Unchecked
, mkLitWord16, mkLitWord16Wrap, mkLitWord16Unchecked
, mkLitInt32, mkLitInt32Wrap, mkLitInt32Unchecked
, mkLitWord32, mkLitWord32Wrap, mkLitWord32Unchecked
, mkLitInt64, mkLitInt64Wrap, mkLitInt64Unchecked
, mkLitWord64, mkLitWord64Wrap, mkLitWord64Unchecked
, mkLitFloat, mkLitDouble
, mkLitChar, mkLitString
, mkLitBigNat
, mkLitNumber, mkLitNumberWrap
, literalType
, pprLiteral
, litNumIsSigned
, litNumRange
, litNumCheckRange
, litNumWrap
, litNumCoerce
, litNumNarrow
, litNumBitSize
, isMinBound
, isMaxBound
, litIsDupable, litIsTrivial, litIsLifted
, inCharRange
, isZeroLit, isOneLit
, litFitsInChar
, litValue, mapLitValue
, isLitValue_maybe, isLitRubbish
, narrowInt8Lit, narrowInt16Lit, narrowInt32Lit, narrowInt64Lit
, narrowWord8Lit, narrowWord16Lit, narrowWord32Lit, narrowWord64Lit
, convertToIntLit, convertToWordLit
, charToIntLit, intToCharLit
, floatToIntLit, intToFloatLit, doubleToIntLit, intToDoubleLit
, nullAddrLit, floatToDoubleLit, doubleToFloatLit
) where
import GHC.Prelude
import GHC.Builtin.Types.Prim
import GHC.Core.Type( Type, RuntimeRepType, mkForAllTy, mkTyVarTy, typeOrConstraintKind )
import GHC.Core.TyCo.Compare( nonDetCmpType )
import GHC.Types.Var
import GHC.Utils.Outputable
import GHC.Data.FastString
import GHC.Types.Basic
import GHC.Utils.Binary
import GHC.Settings.Constants
import GHC.Platform
import GHC.Utils.Panic
import GHC.Utils.Encoding
import Data.ByteString (ByteString)
import Data.Int
import Data.Word
import Data.Char
import Data.Data ( Data )
import GHC.Exts( isTrue#, dataToTag#, (<#) )
import Numeric ( fromRat )
data Literal
= LitChar Char
| LitNumber !LitNumType !Integer
| LitString !ByteString
| LitNullAddr
| LitRubbish
TypeOrConstraint
RuntimeRepType
| LitFloat Rational
| LitDouble Rational
| LitLabel FastString (Maybe Int) FunctionOrData
deriving Typeable Literal
Literal -> DataType
Literal -> Constr
(forall b. Data b => b -> b) -> Literal -> Literal
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Literal -> u
forall u. (forall d. Data d => d -> u) -> Literal -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Literal
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Literal -> c Literal
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Literal)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Literal -> m Literal
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Literal -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Literal -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Literal -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Literal -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Literal -> r
gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal
$cgmapT :: (forall b. Data b => b -> b) -> Literal -> Literal
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Literal)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Literal)
dataTypeOf :: Literal -> DataType
$cdataTypeOf :: Literal -> DataType
toConstr :: Literal -> Constr
$ctoConstr :: Literal -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Literal
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Literal
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Literal -> c Literal
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Literal -> c Literal
Data
data LitNumType
= LitNumBigNat
| LitNumInt
| LitNumInt8
| LitNumInt16
| LitNumInt32
| LitNumInt64
| LitNumWord
| LitNumWord8
| LitNumWord16
| LitNumWord32
| LitNumWord64
deriving (Typeable LitNumType
LitNumType -> DataType
LitNumType -> Constr
(forall b. Data b => b -> b) -> LitNumType -> LitNumType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> LitNumType -> u
forall u. (forall d. Data d => d -> u) -> LitNumType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LitNumType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LitNumType -> c LitNumType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LitNumType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LitNumType)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> LitNumType -> m LitNumType
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LitNumType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> LitNumType -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> LitNumType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> LitNumType -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> LitNumType -> r
gmapT :: (forall b. Data b => b -> b) -> LitNumType -> LitNumType
$cgmapT :: (forall b. Data b => b -> b) -> LitNumType -> LitNumType
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LitNumType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LitNumType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LitNumType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c LitNumType)
dataTypeOf :: LitNumType -> DataType
$cdataTypeOf :: LitNumType -> DataType
toConstr :: LitNumType -> Constr
$ctoConstr :: LitNumType -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LitNumType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c LitNumType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LitNumType -> c LitNumType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> LitNumType -> c LitNumType
Data,Int -> LitNumType
LitNumType -> Int
LitNumType -> [LitNumType]
LitNumType -> LitNumType
LitNumType -> LitNumType -> [LitNumType]
LitNumType -> LitNumType -> LitNumType -> [LitNumType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LitNumType -> LitNumType -> LitNumType -> [LitNumType]
$cenumFromThenTo :: LitNumType -> LitNumType -> LitNumType -> [LitNumType]
enumFromTo :: LitNumType -> LitNumType -> [LitNumType]
$cenumFromTo :: LitNumType -> LitNumType -> [LitNumType]
enumFromThen :: LitNumType -> LitNumType -> [LitNumType]
$cenumFromThen :: LitNumType -> LitNumType -> [LitNumType]
enumFrom :: LitNumType -> [LitNumType]
$cenumFrom :: LitNumType -> [LitNumType]
fromEnum :: LitNumType -> Int
$cfromEnum :: LitNumType -> Int
toEnum :: Int -> LitNumType
$ctoEnum :: Int -> LitNumType
pred :: LitNumType -> LitNumType
$cpred :: LitNumType -> LitNumType
succ :: LitNumType -> LitNumType
$csucc :: LitNumType -> LitNumType
Enum,LitNumType -> LitNumType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LitNumType -> LitNumType -> Bool
$c/= :: LitNumType -> LitNumType -> Bool
== :: LitNumType -> LitNumType -> Bool
$c== :: LitNumType -> LitNumType -> Bool
Eq,Eq LitNumType
LitNumType -> LitNumType -> Bool
LitNumType -> LitNumType -> Ordering
LitNumType -> LitNumType -> LitNumType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LitNumType -> LitNumType -> LitNumType
$cmin :: LitNumType -> LitNumType -> LitNumType
max :: LitNumType -> LitNumType -> LitNumType
$cmax :: LitNumType -> LitNumType -> LitNumType
>= :: LitNumType -> LitNumType -> Bool
$c>= :: LitNumType -> LitNumType -> Bool
> :: LitNumType -> LitNumType -> Bool
$c> :: LitNumType -> LitNumType -> Bool
<= :: LitNumType -> LitNumType -> Bool
$c<= :: LitNumType -> LitNumType -> Bool
< :: LitNumType -> LitNumType -> Bool
$c< :: LitNumType -> LitNumType -> Bool
compare :: LitNumType -> LitNumType -> Ordering
$ccompare :: LitNumType -> LitNumType -> Ordering
Ord)
litNumIsSigned :: LitNumType -> Bool
litNumIsSigned :: LitNumType -> Bool
litNumIsSigned LitNumType
nt = case LitNumType
nt of
LitNumType
LitNumBigNat -> Bool
False
LitNumType
LitNumInt -> Bool
True
LitNumType
LitNumInt8 -> Bool
True
LitNumType
LitNumInt16 -> Bool
True
LitNumType
LitNumInt32 -> Bool
True
LitNumType
LitNumInt64 -> Bool
True
LitNumType
LitNumWord -> Bool
False
LitNumType
LitNumWord8 -> Bool
False
LitNumType
LitNumWord16 -> Bool
False
LitNumType
LitNumWord32 -> Bool
False
LitNumType
LitNumWord64 -> Bool
False
litNumBitSize :: Platform -> LitNumType -> Maybe Word
litNumBitSize :: Platform -> LitNumType -> Maybe Word
litNumBitSize Platform
platform LitNumType
nt = case LitNumType
nt of
LitNumType
LitNumBigNat -> forall a. Maybe a
Nothing
LitNumType
LitNumInt -> forall a. a -> Maybe a
Just (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Platform -> Int
platformWordSizeInBits Platform
platform))
LitNumType
LitNumInt8 -> forall a. a -> Maybe a
Just Word
8
LitNumType
LitNumInt16 -> forall a. a -> Maybe a
Just Word
16
LitNumType
LitNumInt32 -> forall a. a -> Maybe a
Just Word
32
LitNumType
LitNumInt64 -> forall a. a -> Maybe a
Just Word
64
LitNumType
LitNumWord -> forall a. a -> Maybe a
Just (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Platform -> Int
platformWordSizeInBits Platform
platform))
LitNumType
LitNumWord8 -> forall a. a -> Maybe a
Just Word
8
LitNumType
LitNumWord16 -> forall a. a -> Maybe a
Just Word
16
LitNumType
LitNumWord32 -> forall a. a -> Maybe a
Just Word
32
LitNumType
LitNumWord64 -> forall a. a -> Maybe a
Just Word
64
instance Binary LitNumType where
put_ :: BinHandle -> LitNumType -> IO ()
put_ BinHandle
bh LitNumType
numTyp = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh (forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Enum a => a -> Int
fromEnum LitNumType
numTyp))
get :: BinHandle -> IO LitNumType
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Enum a => Int -> a
toEnum (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h))
instance Binary Literal where
put_ :: BinHandle -> Literal -> IO ()
put_ BinHandle
bh (LitChar Char
aa) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
0; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Char
aa
put_ BinHandle
bh (LitString ByteString
ab) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
1; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh ByteString
ab
put_ BinHandle
bh (Literal
LitNullAddr) = BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
2
put_ BinHandle
bh (LitFloat Rational
ah) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
3; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Rational
ah
put_ BinHandle
bh (LitDouble Rational
ai) = do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
4; forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Rational
ai
put_ BinHandle
bh (LitLabel FastString
aj Maybe Int
mb FunctionOrData
fod)
= do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
5
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FastString
aj
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Maybe Int
mb
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh FunctionOrData
fod
put_ BinHandle
bh (LitNumber LitNumType
nt Integer
i)
= do BinHandle -> Word8 -> IO ()
putByte BinHandle
bh Word8
6
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh LitNumType
nt
forall a. Binary a => BinHandle -> a -> IO ()
put_ BinHandle
bh Integer
i
put_ BinHandle
_ lit :: Literal
lit@(LitRubbish {}) = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary LitRubbish" (forall a. Outputable a => a -> SDoc
ppr Literal
lit)
get :: BinHandle -> IO Literal
get BinHandle
bh = do
Word8
h <- BinHandle -> IO Word8
getByte BinHandle
bh
case Word8
h of
Word8
0 -> do
Char
aa <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (Char -> Literal
LitChar Char
aa)
Word8
1 -> do
ByteString
ab <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> Literal
LitString ByteString
ab)
Word8
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return (Literal
LitNullAddr)
Word8
3 -> do
Rational
ah <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (Rational -> Literal
LitFloat Rational
ah)
Word8
4 -> do
Rational
ai <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (Rational -> Literal
LitDouble Rational
ai)
Word8
5 -> do
FastString
aj <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Maybe Int
mb <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
FunctionOrData
fod <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (FastString -> Maybe Int -> FunctionOrData -> Literal
LitLabel FastString
aj Maybe Int
mb FunctionOrData
fod)
Word8
6 -> do
LitNumType
nt <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
Integer
i <- forall a. Binary a => BinHandle -> IO a
get BinHandle
bh
forall (m :: * -> *) a. Monad m => a -> m a
return (LitNumType -> Integer -> Literal
LitNumber LitNumType
nt Integer
i)
Word8
_ -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"Binary:Literal" (forall doc. IsLine doc => Int -> doc
int (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
h))
instance Outputable Literal where
ppr :: Literal -> SDoc
ppr = (SDoc -> SDoc) -> Literal -> SDoc
pprLiteral forall a. a -> a
id
instance Eq Literal where
Literal
a == :: Literal -> Literal -> Bool
== Literal
b = forall a. Ord a => a -> a -> Ordering
compare Literal
a Literal
b forall a. Eq a => a -> a -> Bool
== Ordering
EQ
instance Ord Literal where
compare :: Literal -> Literal -> Ordering
compare = Literal -> Literal -> Ordering
cmpLit
mkLitNumberWrap :: Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap :: Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
nt Integer
i = case LitNumType
nt of
LitNumType
LitNumInt -> case Platform -> PlatformWordSize
platformWordSize Platform
platform of
PlatformWordSize
PW4 -> forall a. (Integral a, Num a) => Literal
wrap @Int32
PlatformWordSize
PW8 -> forall a. (Integral a, Num a) => Literal
wrap @Int64
LitNumType
LitNumWord -> case Platform -> PlatformWordSize
platformWordSize Platform
platform of
PlatformWordSize
PW4 -> forall a. (Integral a, Num a) => Literal
wrap @Word32
PlatformWordSize
PW8 -> forall a. (Integral a, Num a) => Literal
wrap @Word64
LitNumType
LitNumInt8 -> forall a. (Integral a, Num a) => Literal
wrap @Int8
LitNumType
LitNumInt16 -> forall a. (Integral a, Num a) => Literal
wrap @Int16
LitNumType
LitNumInt32 -> forall a. (Integral a, Num a) => Literal
wrap @Int32
LitNumType
LitNumInt64 -> forall a. (Integral a, Num a) => Literal
wrap @Int64
LitNumType
LitNumWord8 -> forall a. (Integral a, Num a) => Literal
wrap @Word8
LitNumType
LitNumWord16 -> forall a. (Integral a, Num a) => Literal
wrap @Word16
LitNumType
LitNumWord32 -> forall a. (Integral a, Num a) => Literal
wrap @Word32
LitNumType
LitNumWord64 -> forall a. (Integral a, Num a) => Literal
wrap @Word64
LitNumType
LitNumBigNat
| Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0 -> forall a. HasCallStack => String -> a
panic String
"mkLitNumberWrap: trying to create a negative BigNat"
| Bool
otherwise -> LitNumType -> Integer -> Literal
LitNumber LitNumType
nt Integer
i
where
wrap :: forall a. (Integral a, Num a) => Literal
wrap :: forall a. (Integral a, Num a) => Literal
wrap = LitNumType -> Integer -> Literal
LitNumber LitNumType
nt (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: a))
litNumWrap :: Platform -> Literal -> Literal
litNumWrap :: Platform -> Literal -> Literal
litNumWrap Platform
platform (LitNumber LitNumType
nt Integer
i) = Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
nt Integer
i
litNumWrap Platform
_ Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"litNumWrap" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
litNumCoerce :: LitNumType -> Platform -> Literal -> Literal
litNumCoerce :: LitNumType -> Platform -> Literal -> Literal
litNumCoerce LitNumType
pt Platform
platform (LitNumber LitNumType
_nt Integer
i) = Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
pt Integer
i
litNumCoerce LitNumType
_ Platform
_ Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"litNumWrapCoerce: not a number" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
litNumNarrow :: LitNumType -> Platform -> Literal -> Literal
litNumNarrow :: LitNumType -> Platform -> Literal -> Literal
litNumNarrow LitNumType
pt Platform
platform (LitNumber LitNumType
nt Integer
i)
= case Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
pt Integer
i of
LitNumber LitNumType
_ Integer
j -> Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
nt Integer
j
Literal
l -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"litNumNarrow: got invalid literal" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
litNumNarrow LitNumType
_ Platform
_ Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"litNumNarrow: invalid literal" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
litNumCheckRange :: Platform -> LitNumType -> Integer -> Bool
litNumCheckRange :: Platform -> LitNumType -> Integer -> Bool
litNumCheckRange Platform
platform LitNumType
nt Integer
i =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Integer
i forall a. Ord a => a -> a -> Bool
>=) Maybe Integer
m_lower Bool -> Bool -> Bool
&&
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
True (Integer
i forall a. Ord a => a -> a -> Bool
<=) Maybe Integer
m_upper
where
(Maybe Integer
m_lower, Maybe Integer
m_upper) = Platform -> LitNumType -> (Maybe Integer, Maybe Integer)
litNumRange Platform
platform LitNumType
nt
litNumRange :: Platform -> LitNumType -> (Maybe Integer, Maybe Integer)
litNumRange :: Platform -> LitNumType -> (Maybe Integer, Maybe Integer)
litNumRange Platform
platform LitNumType
nt = case LitNumType
nt of
LitNumType
LitNumInt -> (forall a. a -> Maybe a
Just (Platform -> Integer
platformMinInt Platform
platform), forall a. a -> Maybe a
Just (Platform -> Integer
platformMaxInt Platform
platform))
LitNumType
LitNumWord -> (forall a. a -> Maybe a
Just Integer
0, forall a. a -> Maybe a
Just (Platform -> Integer
platformMaxWord Platform
platform))
LitNumType
LitNumInt8 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Int8
LitNumType
LitNumInt16 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Int16
LitNumType
LitNumInt32 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Int32
LitNumType
LitNumInt64 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Int64
LitNumType
LitNumWord8 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Word8
LitNumType
LitNumWord16 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Word16
LitNumType
LitNumWord32 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Word32
LitNumType
LitNumWord64 -> forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range @Word64
LitNumType
LitNumBigNat -> (forall a. a -> Maybe a
Just Integer
0, forall a. Maybe a
Nothing)
where
bounded_range :: forall a . (Integral a, Bounded a) => (Maybe Integer,Maybe Integer)
bounded_range :: forall a. (Integral a, Bounded a) => (Maybe Integer, Maybe Integer)
bounded_range = case forall a. (Bounded a, Integral a) => (Integer, Integer)
boundedRange @a of
(Integer
mi,Integer
ma) -> (forall a. a -> Maybe a
Just Integer
mi, forall a. a -> Maybe a
Just Integer
ma)
mkLitNumber :: Platform -> LitNumType -> Integer -> Literal
mkLitNumber :: Platform -> LitNumType -> Integer -> Literal
mkLitNumber Platform
platform LitNumType
nt Integer
i =
forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Platform -> LitNumType -> Integer -> Bool
litNumCheckRange Platform
platform LitNumType
nt Integer
i) (forall doc. IsLine doc => Integer -> doc
integer Integer
i)
(LitNumType -> Integer -> Literal
LitNumber LitNumType
nt Integer
i)
mkLitInt :: Platform -> Integer -> Literal
mkLitInt :: Platform -> Integer -> Literal
mkLitInt Platform
platform Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Platform -> Integer -> Bool
platformInIntRange Platform
platform Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x)
(Integer -> Literal
mkLitIntUnchecked Integer
x)
mkLitIntWrap :: Platform -> Integer -> Literal
mkLitIntWrap :: Platform -> Integer -> Literal
mkLitIntWrap Platform
platform Integer
i = Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
LitNumInt Integer
i
mkLitIntUnchecked :: Integer -> Literal
mkLitIntUnchecked :: Integer -> Literal
mkLitIntUnchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumInt Integer
i
mkLitIntWrapC :: Platform -> Integer -> (Literal, Bool)
mkLitIntWrapC :: Platform -> Integer -> (Literal, Bool)
mkLitIntWrapC Platform
platform Integer
i = (Literal
n, Integer
i forall a. Eq a => a -> a -> Bool
/= Integer
i')
where
n :: Literal
n@(LitNumber LitNumType
_ Integer
i') = Platform -> Integer -> Literal
mkLitIntWrap Platform
platform Integer
i
mkLitWord :: Platform -> Integer -> Literal
mkLitWord :: Platform -> Integer -> Literal
mkLitWord Platform
platform Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Platform -> Integer -> Bool
platformInWordRange Platform
platform Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x)
(Integer -> Literal
mkLitWordUnchecked Integer
x)
mkLitWordWrap :: Platform -> Integer -> Literal
mkLitWordWrap :: Platform -> Integer -> Literal
mkLitWordWrap Platform
platform Integer
i = Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
LitNumWord Integer
i
mkLitWordUnchecked :: Integer -> Literal
mkLitWordUnchecked :: Integer -> Literal
mkLitWordUnchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumWord Integer
i
mkLitWordWrapC :: Platform -> Integer -> (Literal, Bool)
mkLitWordWrapC :: Platform -> Integer -> (Literal, Bool)
mkLitWordWrapC Platform
platform Integer
i = (Literal
n, Integer
i forall a. Eq a => a -> a -> Bool
/= Integer
i')
where
n :: Literal
n@(LitNumber LitNumType
_ Integer
i') = Platform -> Integer -> Literal
mkLitWordWrap Platform
platform Integer
i
mkLitInt8 :: Integer -> Literal
mkLitInt8 :: Integer -> Literal
mkLitInt8 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Int8 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitInt8Unchecked Integer
x)
mkLitInt8Wrap :: Integer -> Literal
mkLitInt8Wrap :: Integer -> Literal
mkLitInt8Wrap Integer
i = Integer -> Literal
mkLitInt8Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Int8))
mkLitInt8Unchecked :: Integer -> Literal
mkLitInt8Unchecked :: Integer -> Literal
mkLitInt8Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumInt8 Integer
i
mkLitWord8 :: Integer -> Literal
mkLitWord8 :: Integer -> Literal
mkLitWord8 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Word8 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitWord8Unchecked Integer
x)
mkLitWord8Wrap :: Integer -> Literal
mkLitWord8Wrap :: Integer -> Literal
mkLitWord8Wrap Integer
i = Integer -> Literal
mkLitWord8Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word8))
mkLitWord8Unchecked :: Integer -> Literal
mkLitWord8Unchecked :: Integer -> Literal
mkLitWord8Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumWord8 Integer
i
mkLitInt16 :: Integer -> Literal
mkLitInt16 :: Integer -> Literal
mkLitInt16 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Int16 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitInt16Unchecked Integer
x)
mkLitInt16Wrap :: Integer -> Literal
mkLitInt16Wrap :: Integer -> Literal
mkLitInt16Wrap Integer
i = Integer -> Literal
mkLitInt16Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Int16))
mkLitInt16Unchecked :: Integer -> Literal
mkLitInt16Unchecked :: Integer -> Literal
mkLitInt16Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumInt16 Integer
i
mkLitWord16 :: Integer -> Literal
mkLitWord16 :: Integer -> Literal
mkLitWord16 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Word16 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitWord16Unchecked Integer
x)
mkLitWord16Wrap :: Integer -> Literal
mkLitWord16Wrap :: Integer -> Literal
mkLitWord16Wrap Integer
i = Integer -> Literal
mkLitWord16Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word16))
mkLitWord16Unchecked :: Integer -> Literal
mkLitWord16Unchecked :: Integer -> Literal
mkLitWord16Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumWord16 Integer
i
mkLitInt32 :: Integer -> Literal
mkLitInt32 :: Integer -> Literal
mkLitInt32 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Int32 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitInt32Unchecked Integer
x)
mkLitInt32Wrap :: Integer -> Literal
mkLitInt32Wrap :: Integer -> Literal
mkLitInt32Wrap Integer
i = Integer -> Literal
mkLitInt32Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Int32))
mkLitInt32Unchecked :: Integer -> Literal
mkLitInt32Unchecked :: Integer -> Literal
mkLitInt32Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumInt32 Integer
i
mkLitWord32 :: Integer -> Literal
mkLitWord32 :: Integer -> Literal
mkLitWord32 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Word32 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitWord32Unchecked Integer
x)
mkLitWord32Wrap :: Integer -> Literal
mkLitWord32Wrap :: Integer -> Literal
mkLitWord32Wrap Integer
i = Integer -> Literal
mkLitWord32Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word32))
mkLitWord32Unchecked :: Integer -> Literal
mkLitWord32Unchecked :: Integer -> Literal
mkLitWord32Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumWord32 Integer
i
mkLitInt64 :: Integer -> Literal
mkLitInt64 :: Integer -> Literal
mkLitInt64 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Int64 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitInt64Unchecked Integer
x)
mkLitInt64Wrap :: Integer -> Literal
mkLitInt64Wrap :: Integer -> Literal
mkLitInt64Wrap Integer
i = Integer -> Literal
mkLitInt64Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Int64))
mkLitInt64Unchecked :: Integer -> Literal
mkLitInt64Unchecked :: Integer -> Literal
mkLitInt64Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumInt64 Integer
i
mkLitWord64 :: Integer -> Literal
mkLitWord64 :: Integer -> Literal
mkLitWord64 Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange @Word64 Integer
x) (forall doc. IsLine doc => Integer -> doc
integer Integer
x) (Integer -> Literal
mkLitWord64Unchecked Integer
x)
mkLitWord64Wrap :: Integer -> Literal
mkLitWord64Wrap :: Integer -> Literal
mkLitWord64Wrap Integer
i = Integer -> Literal
mkLitWord64Unchecked (forall a. Integral a => a -> Integer
toInteger (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
i :: Word64))
mkLitWord64Unchecked :: Integer -> Literal
mkLitWord64Unchecked :: Integer -> Literal
mkLitWord64Unchecked Integer
i = LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumWord64 Integer
i
mkLitFloat :: Rational -> Literal
mkLitFloat :: Rational -> Literal
mkLitFloat = Rational -> Literal
LitFloat
mkLitDouble :: Rational -> Literal
mkLitDouble :: Rational -> Literal
mkLitDouble = Rational -> Literal
LitDouble
mkLitChar :: Char -> Literal
mkLitChar :: Char -> Literal
mkLitChar = Char -> Literal
LitChar
mkLitString :: String -> Literal
mkLitString :: String -> Literal
mkLitString [] = ByteString -> Literal
LitString forall a. Monoid a => a
mempty
mkLitString String
s = ByteString -> Literal
LitString (String -> ByteString
utf8EncodeByteString String
s)
mkLitBigNat :: Integer -> Literal
mkLitBigNat :: Integer -> Literal
mkLitBigNat Integer
x = forall a. HasCallStack => Bool -> SDoc -> a -> a
assertPpr (Integer
x forall a. Ord a => a -> a -> Bool
>= Integer
0) (forall doc. IsLine doc => Integer -> doc
integer Integer
x)
(LitNumType -> Integer -> Literal
LitNumber LitNumType
LitNumBigNat Integer
x)
isLitRubbish :: Literal -> Bool
isLitRubbish :: Literal -> Bool
isLitRubbish (LitRubbish {}) = Bool
True
isLitRubbish Literal
_ = Bool
False
inBoundedRange :: forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange :: forall a. (Bounded a, Integral a) => Integer -> Bool
inBoundedRange Integer
x = Integer
x forall a. Ord a => a -> a -> Bool
>= forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a) Bool -> Bool -> Bool
&&
Integer
x forall a. Ord a => a -> a -> Bool
<= forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a)
boundedRange :: forall a. (Bounded a, Integral a) => (Integer,Integer)
boundedRange :: forall a. (Bounded a, Integral a) => (Integer, Integer)
boundedRange = (forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a), forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a))
isMinBound :: Platform -> Literal -> Bool
isMinBound :: Platform -> Literal -> Bool
isMinBound Platform
_ (LitChar Char
c) = Char
c forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
minBound
isMinBound Platform
platform (LitNumber LitNumType
nt Integer
i) = case LitNumType
nt of
LitNumType
LitNumInt -> Integer
i forall a. Eq a => a -> a -> Bool
== Platform -> Integer
platformMinInt Platform
platform
LitNumType
LitNumInt8 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: Int8)
LitNumType
LitNumInt16 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: Int16)
LitNumType
LitNumInt32 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: Int32)
LitNumType
LitNumInt64 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: Int64)
LitNumType
LitNumWord -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
LitNumType
LitNumWord8 -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
LitNumType
LitNumWord16 -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
LitNumType
LitNumWord32 -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
LitNumType
LitNumWord64 -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
LitNumType
LitNumBigNat -> Integer
i forall a. Eq a => a -> a -> Bool
== Integer
0
isMinBound Platform
_ Literal
_ = Bool
False
isMaxBound :: Platform -> Literal -> Bool
isMaxBound :: Platform -> Literal -> Bool
isMaxBound Platform
_ (LitChar Char
c) = Char
c forall a. Eq a => a -> a -> Bool
== forall a. Bounded a => a
maxBound
isMaxBound Platform
platform (LitNumber LitNumType
nt Integer
i) = case LitNumType
nt of
LitNumType
LitNumInt -> Integer
i forall a. Eq a => a -> a -> Bool
== Platform -> Integer
platformMaxInt Platform
platform
LitNumType
LitNumInt8 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int8)
LitNumType
LitNumInt16 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int16)
LitNumType
LitNumInt32 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int32)
LitNumType
LitNumInt64 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Int64)
LitNumType
LitNumWord -> Integer
i forall a. Eq a => a -> a -> Bool
== Platform -> Integer
platformMaxWord Platform
platform
LitNumType
LitNumWord8 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Word8)
LitNumType
LitNumWord16 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Word16)
LitNumType
LitNumWord32 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Word32)
LitNumType
LitNumWord64 -> Integer
i forall a. Eq a => a -> a -> Bool
== forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: Word64)
LitNumType
LitNumBigNat -> Bool
False
isMaxBound Platform
_ Literal
_ = Bool
False
inCharRange :: Char -> Bool
inCharRange :: Char -> Bool
inCharRange Char
c = Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\0' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Int -> Char
chr Int
tARGET_MAX_CHAR
isZeroLit :: Literal -> Bool
isZeroLit :: Literal -> Bool
isZeroLit (LitNumber LitNumType
_ Integer
0) = Bool
True
isZeroLit (LitFloat Rational
0) = Bool
True
isZeroLit (LitDouble Rational
0) = Bool
True
isZeroLit Literal
_ = Bool
False
isOneLit :: Literal -> Bool
isOneLit :: Literal -> Bool
isOneLit (LitNumber LitNumType
_ Integer
1) = Bool
True
isOneLit (LitFloat Rational
1) = Bool
True
isOneLit (LitDouble Rational
1) = Bool
True
isOneLit Literal
_ = Bool
False
litValue :: Literal -> Integer
litValue :: Literal -> Integer
litValue Literal
l = case Literal -> Maybe Integer
isLitValue_maybe Literal
l of
Just Integer
x -> Integer
x
Maybe Integer
Nothing -> forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"litValue" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
isLitValue_maybe :: Literal -> Maybe Integer
isLitValue_maybe :: Literal -> Maybe Integer
isLitValue_maybe (LitChar Char
c) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. Integral a => a -> Integer
toInteger forall a b. (a -> b) -> a -> b
$ Char -> Int
ord Char
c
isLitValue_maybe (LitNumber LitNumType
_ Integer
i) = forall a. a -> Maybe a
Just Integer
i
isLitValue_maybe Literal
_ = forall a. Maybe a
Nothing
mapLitValue :: Platform -> (Integer -> Integer) -> Literal -> Literal
mapLitValue :: Platform -> (Integer -> Integer) -> Literal -> Literal
mapLitValue Platform
_ Integer -> Integer
f (LitChar Char
c) = Char -> Literal
mkLitChar (Char -> Char
fchar Char
c)
where fchar :: Char -> Char
fchar = Int -> Char
chr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Integer
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Integral a => a -> Integer
toInteger forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord
mapLitValue Platform
platform Integer -> Integer
f (LitNumber LitNumType
nt Integer
i) = Platform -> LitNumType -> Integer -> Literal
mkLitNumberWrap Platform
platform LitNumType
nt (Integer -> Integer
f Integer
i)
mapLitValue Platform
_ Integer -> Integer
_ Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"mapLitValue" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
charToIntLit, intToCharLit,
floatToIntLit, intToFloatLit,
doubleToIntLit, intToDoubleLit,
floatToDoubleLit, doubleToFloatLit
:: Literal -> Literal
narrowLit' :: forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' :: forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' LitNumType
nt' (LitNumber LitNumType
_ Integer
i) = LitNumType -> Integer -> Literal
LitNumber LitNumType
nt' (forall a. Integral a => a -> Integer
toInteger (forall a. Num a => Integer -> a
fromInteger Integer
i :: a))
narrowLit' LitNumType
_ Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"narrowLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
narrowInt8Lit, narrowInt16Lit, narrowInt32Lit, narrowInt64Lit,
narrowWord8Lit, narrowWord16Lit, narrowWord32Lit, narrowWord64Lit :: Literal -> Literal
narrowInt8Lit :: Literal -> Literal
narrowInt8Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Int8 LitNumType
LitNumInt8
narrowInt16Lit :: Literal -> Literal
narrowInt16Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Int16 LitNumType
LitNumInt16
narrowInt32Lit :: Literal -> Literal
narrowInt32Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Int32 LitNumType
LitNumInt32
narrowInt64Lit :: Literal -> Literal
narrowInt64Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Int64 LitNumType
LitNumInt64
narrowWord8Lit :: Literal -> Literal
narrowWord8Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Word8 LitNumType
LitNumWord8
narrowWord16Lit :: Literal -> Literal
narrowWord16Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Word16 LitNumType
LitNumWord16
narrowWord32Lit :: Literal -> Literal
narrowWord32Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Word32 LitNumType
LitNumWord32
narrowWord64Lit :: Literal -> Literal
narrowWord64Lit = forall a. Integral a => LitNumType -> Literal -> Literal
narrowLit' @Word64 LitNumType
LitNumWord64
convertToWordLit, convertToIntLit :: Platform -> Literal -> Literal
convertToWordLit :: Platform -> Literal -> Literal
convertToWordLit Platform
platform (LitNumber LitNumType
_nt Integer
i) = Platform -> Integer -> Literal
mkLitWordWrap Platform
platform Integer
i
convertToWordLit Platform
_platform Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"convertToWordLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
convertToIntLit :: Platform -> Literal -> Literal
convertToIntLit Platform
platform (LitNumber LitNumType
_nt Integer
i) = Platform -> Integer -> Literal
mkLitIntWrap Platform
platform Integer
i
convertToIntLit Platform
_platform Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"convertToIntLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
charToIntLit :: Literal -> Literal
charToIntLit (LitChar Char
c) = Integer -> Literal
mkLitIntUnchecked (forall a. Integral a => a -> Integer
toInteger (Char -> Int
ord Char
c))
charToIntLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"charToIntLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
intToCharLit :: Literal -> Literal
intToCharLit (LitNumber LitNumType
_ Integer
i) = Char -> Literal
LitChar (Int -> Char
chr (forall a. Num a => Integer -> a
fromInteger Integer
i))
intToCharLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"intToCharLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
floatToIntLit :: Literal -> Literal
floatToIntLit (LitFloat Rational
f) = Integer -> Literal
mkLitIntUnchecked (forall a b. (RealFrac a, Integral b) => a -> b
truncate Rational
f)
floatToIntLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"floatToIntLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
intToFloatLit :: Literal -> Literal
intToFloatLit (LitNumber LitNumType
_ Integer
i) = Rational -> Literal
LitFloat (forall a. Num a => Integer -> a
fromInteger Integer
i)
intToFloatLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"intToFloatLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
doubleToIntLit :: Literal -> Literal
doubleToIntLit (LitDouble Rational
f) = Integer -> Literal
mkLitIntUnchecked (forall a b. (RealFrac a, Integral b) => a -> b
truncate Rational
f)
doubleToIntLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"doubleToIntLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
intToDoubleLit :: Literal -> Literal
intToDoubleLit (LitNumber LitNumType
_ Integer
i) = Rational -> Literal
LitDouble (forall a. Num a => Integer -> a
fromInteger Integer
i)
intToDoubleLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"intToDoubleLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
floatToDoubleLit :: Literal -> Literal
floatToDoubleLit (LitFloat Rational
f) = Rational -> Literal
LitDouble Rational
f
floatToDoubleLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"floatToDoubleLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
doubleToFloatLit :: Literal -> Literal
doubleToFloatLit (LitDouble Rational
d) = Rational -> Literal
LitFloat Rational
d
doubleToFloatLit Literal
l = forall a. HasCallStack => String -> SDoc -> a
pprPanic String
"doubleToFloatLit" (forall a. Outputable a => a -> SDoc
ppr Literal
l)
nullAddrLit :: Literal
nullAddrLit :: Literal
nullAddrLit = Literal
LitNullAddr
litIsTrivial :: Literal -> Bool
litIsTrivial :: Literal -> Bool
litIsTrivial (LitString ByteString
_) = Bool
False
litIsTrivial (LitNumber LitNumType
nt Integer
_) = case LitNumType
nt of
LitNumType
LitNumBigNat -> Bool
False
LitNumType
LitNumInt -> Bool
True
LitNumType
LitNumInt8 -> Bool
True
LitNumType
LitNumInt16 -> Bool
True
LitNumType
LitNumInt32 -> Bool
True
LitNumType
LitNumInt64 -> Bool
True
LitNumType
LitNumWord -> Bool
True
LitNumType
LitNumWord8 -> Bool
True
LitNumType
LitNumWord16 -> Bool
True
LitNumType
LitNumWord32 -> Bool
True
LitNumType
LitNumWord64 -> Bool
True
litIsTrivial Literal
_ = Bool
True
litIsDupable :: Platform -> Literal -> Bool
litIsDupable :: Platform -> Literal -> Bool
litIsDupable Platform
platform Literal
x = case Literal
x of
LitNumber LitNumType
nt Integer
i -> case LitNumType
nt of
LitNumType
LitNumBigNat -> Integer
i forall a. Ord a => a -> a -> Bool
<= Platform -> Integer
platformMaxWord Platform
platform forall a. Num a => a -> a -> a
* Integer
8
LitNumType
LitNumInt -> Bool
True
LitNumType
LitNumInt8 -> Bool
True
LitNumType
LitNumInt16 -> Bool
True
LitNumType
LitNumInt32 -> Bool
True
LitNumType
LitNumInt64 -> Bool
True
LitNumType
LitNumWord -> Bool
True
LitNumType
LitNumWord8 -> Bool
True
LitNumType
LitNumWord16 -> Bool
True
LitNumType
LitNumWord32 -> Bool
True
LitNumType
LitNumWord64 -> Bool
True
LitString ByteString
_ -> Bool
False
Literal
_ -> Bool
True
litFitsInChar :: Literal -> Bool
litFitsInChar :: Literal -> Bool
litFitsInChar (LitNumber LitNumType
_ Integer
i) = Integer
i forall a. Ord a => a -> a -> Bool
>= forall a. Integral a => a -> Integer
toInteger (Char -> Int
ord forall a. Bounded a => a
minBound)
Bool -> Bool -> Bool
&& Integer
i forall a. Ord a => a -> a -> Bool
<= forall a. Integral a => a -> Integer
toInteger (Char -> Int
ord forall a. Bounded a => a
maxBound)
litFitsInChar Literal
_ = Bool
False
litIsLifted :: Literal -> Bool
litIsLifted :: Literal -> Bool
litIsLifted (LitNumber LitNumType
nt Integer
_) = case LitNumType
nt of
LitNumType
LitNumBigNat -> Bool
True
LitNumType
LitNumInt -> Bool
False
LitNumType
LitNumInt8 -> Bool
False
LitNumType
LitNumInt16 -> Bool
False
LitNumType
LitNumInt32 -> Bool
False
LitNumType
LitNumInt64 -> Bool
False
LitNumType
LitNumWord -> Bool
False
LitNumType
LitNumWord8 -> Bool
False
LitNumType
LitNumWord16 -> Bool
False
LitNumType
LitNumWord32 -> Bool
False
LitNumType
LitNumWord64 -> Bool
False
litIsLifted Literal
_ = Bool
False
literalType :: Literal -> Type
literalType :: Literal -> RuntimeRepType
literalType Literal
LitNullAddr = RuntimeRepType
addrPrimTy
literalType (LitChar Char
_) = RuntimeRepType
charPrimTy
literalType (LitString ByteString
_) = RuntimeRepType
addrPrimTy
literalType (LitFloat Rational
_) = RuntimeRepType
floatPrimTy
literalType (LitDouble Rational
_) = RuntimeRepType
doublePrimTy
literalType (LitLabel FastString
_ Maybe Int
_ FunctionOrData
_) = RuntimeRepType
addrPrimTy
literalType (LitNumber LitNumType
lt Integer
_) = case LitNumType
lt of
LitNumType
LitNumBigNat -> RuntimeRepType
byteArrayPrimTy
LitNumType
LitNumInt -> RuntimeRepType
intPrimTy
LitNumType
LitNumInt8 -> RuntimeRepType
int8PrimTy
LitNumType
LitNumInt16 -> RuntimeRepType
int16PrimTy
LitNumType
LitNumInt32 -> RuntimeRepType
int32PrimTy
LitNumType
LitNumInt64 -> RuntimeRepType
int64PrimTy
LitNumType
LitNumWord -> RuntimeRepType
wordPrimTy
LitNumType
LitNumWord8 -> RuntimeRepType
word8PrimTy
LitNumType
LitNumWord16 -> RuntimeRepType
word16PrimTy
LitNumType
LitNumWord32 -> RuntimeRepType
word32PrimTy
LitNumType
LitNumWord64 -> RuntimeRepType
word64PrimTy
literalType (LitRubbish TypeOrConstraint
torc RuntimeRepType
rep)
= ForAllTyBinder -> RuntimeRepType -> RuntimeRepType
mkForAllTy (forall var argf. var -> argf -> VarBndr var argf
Bndr TyVar
a ForAllTyFlag
Inferred) (TyVar -> RuntimeRepType
mkTyVarTy TyVar
a)
where
a :: TyVar
a = RuntimeRepType -> TyVar
mkTemplateKindVar (TypeOrConstraint -> RuntimeRepType -> RuntimeRepType
typeOrConstraintKind TypeOrConstraint
torc RuntimeRepType
rep)
cmpLit :: Literal -> Literal -> Ordering
cmpLit :: Literal -> Literal -> Ordering
cmpLit (LitChar Char
a) (LitChar Char
b) = Char
a forall a. Ord a => a -> a -> Ordering
`compare` Char
b
cmpLit (LitString ByteString
a) (LitString ByteString
b) = ByteString
a forall a. Ord a => a -> a -> Ordering
`compare` ByteString
b
cmpLit (Literal
LitNullAddr) (Literal
LitNullAddr) = Ordering
EQ
cmpLit (LitFloat Rational
a) (LitFloat Rational
b) = Rational
a forall a. Ord a => a -> a -> Ordering
`compare` Rational
b
cmpLit (LitDouble Rational
a) (LitDouble Rational
b) = Rational
a forall a. Ord a => a -> a -> Ordering
`compare` Rational
b
cmpLit (LitLabel FastString
a Maybe Int
_ FunctionOrData
_) (LitLabel FastString
b Maybe Int
_ FunctionOrData
_) = FastString
a FastString -> FastString -> Ordering
`lexicalCompareFS` FastString
b
cmpLit (LitNumber LitNumType
nt1 Integer
a) (LitNumber LitNumType
nt2 Integer
b)
= (LitNumType
nt1 forall a. Ord a => a -> a -> Ordering
`compare` LitNumType
nt2) forall a. Monoid a => a -> a -> a
`mappend` (Integer
a forall a. Ord a => a -> a -> Ordering
`compare` Integer
b)
cmpLit (LitRubbish TypeOrConstraint
tc1 RuntimeRepType
b1) (LitRubbish TypeOrConstraint
tc2 RuntimeRepType
b2) = (TypeOrConstraint
tc1 forall a. Ord a => a -> a -> Ordering
`compare` TypeOrConstraint
tc2) forall a. Monoid a => a -> a -> a
`mappend`
(RuntimeRepType
b1 RuntimeRepType -> RuntimeRepType -> Ordering
`nonDetCmpType` RuntimeRepType
b2)
cmpLit Literal
lit1 Literal
lit2
| Int# -> Bool
isTrue# (forall a. a -> Int#
dataToTag# Literal
lit1 Int# -> Int# -> Int#
<# forall a. a -> Int#
dataToTag# Literal
lit2) = Ordering
LT
| Bool
otherwise = Ordering
GT
pprLiteral :: (SDoc -> SDoc) -> Literal -> SDoc
pprLiteral :: (SDoc -> SDoc) -> Literal -> SDoc
pprLiteral SDoc -> SDoc
_ (LitChar Char
c) = Char -> SDoc
pprPrimChar Char
c
pprLiteral SDoc -> SDoc
_ (LitString ByteString
s) = ByteString -> SDoc
pprHsBytes ByteString
s
pprLiteral SDoc -> SDoc
_ (Literal
LitNullAddr) = forall doc. IsLine doc => String -> doc
text String
"__NULL"
pprLiteral SDoc -> SDoc
_ (LitFloat Rational
f) = forall doc. IsLine doc => Float -> doc
float (forall a. RealFloat a => Rational -> a
fromRat Rational
f) forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
primFloatSuffix
pprLiteral SDoc -> SDoc
_ (LitDouble Rational
d) = forall doc. IsLine doc => Double -> doc
double (forall a. RealFloat a => Rational -> a
fromRat Rational
d) forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
primDoubleSuffix
pprLiteral SDoc -> SDoc
_ (LitNumber LitNumType
nt Integer
i)
= case LitNumType
nt of
LitNumType
LitNumBigNat -> forall doc. IsLine doc => Integer -> doc
integer Integer
i
LitNumType
LitNumInt -> Integer -> SDoc
pprPrimInt Integer
i
LitNumType
LitNumInt8 -> Integer -> SDoc
pprPrimInt8 Integer
i
LitNumType
LitNumInt16 -> Integer -> SDoc
pprPrimInt16 Integer
i
LitNumType
LitNumInt32 -> Integer -> SDoc
pprPrimInt32 Integer
i
LitNumType
LitNumInt64 -> Integer -> SDoc
pprPrimInt64 Integer
i
LitNumType
LitNumWord -> Integer -> SDoc
pprPrimWord Integer
i
LitNumType
LitNumWord8 -> Integer -> SDoc
pprPrimWord8 Integer
i
LitNumType
LitNumWord16 -> Integer -> SDoc
pprPrimWord16 Integer
i
LitNumType
LitNumWord32 -> Integer -> SDoc
pprPrimWord32 Integer
i
LitNumType
LitNumWord64 -> Integer -> SDoc
pprPrimWord64 Integer
i
pprLiteral SDoc -> SDoc
add_par (LitLabel FastString
l Maybe Int
mb FunctionOrData
fod) =
SDoc -> SDoc
add_par (forall doc. IsLine doc => String -> doc
text String
"__label" forall doc. IsLine doc => doc -> doc -> doc
<+> SDoc
b forall doc. IsLine doc => doc -> doc -> doc
<+> forall a. Outputable a => a -> SDoc
ppr FunctionOrData
fod)
where b :: SDoc
b = case Maybe Int
mb of
Maybe Int
Nothing -> FastString -> SDoc
pprHsString FastString
l
Just Int
x -> forall doc. IsLine doc => doc -> doc
doubleQuotes (forall doc. IsLine doc => FastString -> doc
ftext FastString
l forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => String -> doc
text (Char
'@'forall a. a -> [a] -> [a]
:forall a. Show a => a -> String
show Int
x))
pprLiteral SDoc -> SDoc
_ (LitRubbish TypeOrConstraint
torc RuntimeRepType
rep)
= forall doc. IsLine doc => String -> doc
text String
"RUBBISH" forall doc. IsLine doc => doc -> doc -> doc
<> SDoc
pp_tc forall doc. IsLine doc => doc -> doc -> doc
<> forall doc. IsLine doc => doc -> doc
parens (forall a. Outputable a => a -> SDoc
ppr RuntimeRepType
rep)
where
pp_tc :: SDoc
pp_tc = case TypeOrConstraint
torc of
TypeOrConstraint
TypeLike -> forall doc. IsOutput doc => doc
empty
TypeOrConstraint
ConstraintLike -> forall doc. IsLine doc => String -> doc
text String
"[c]"