(original) (raw)
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, StandaloneDeriving, MagicHash, UnboxedTuples #-} {-# OPTIONS_HADDOCK not-home #-}
#include "MachDeps.h" #if SIZEOF_HSWORD == 4 #define DIGITS 9 #define BASE 1000000000 #elif SIZEOF_HSWORD == 8 #define DIGITS 18 #define BASE 1000000000000000000 #else #error Please define DIGITS and BASE
#endif
module GHC.Show ( Show(..), ShowS,
[shows](GHC.Show.html#shows), [showChar](GHC.Show.html#showChar), [showString](GHC.Show.html#showString), [showMultiLineString](GHC.Show.html#showMultiLineString),
[showParen](GHC.Show.html#showParen), [showList__](GHC.Show.html#showList%5F%5F), [showCommaSpace](GHC.Show.html#showCommaSpace), [showSpace](GHC.Show.html#showSpace),
[showLitChar](GHC.Show.html#showLitChar), [showLitString](GHC.Show.html#showLitString), [protectEsc](GHC.Show.html#protectEsc),
[intToDigit](GHC.Show.html#intToDigit), [showSignedInt](GHC.Show.html#showSignedInt),
[appPrec](GHC.Show.html#appPrec), [appPrec1](GHC.Show.html#appPrec1),
[asciiTab](GHC.Show.html#asciiTab),) where
import GHC.Base import GHC.List ((!!), foldr1, break) import GHC.Num import GHC.Stack.Types import GHC.Tuple (Solo (..))
class Show a where {-# MINIMAL showsPrec | show #-}
[showsPrec](GHC.Show.html#showsPrec) :: [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int)
-> [a](#local-6989586621679529317)
-> [ShowS](GHC.Show.html#ShowS)
[show](GHC.Show.html#show) :: [a](#local-6989586621679529317) -> [String](GHC.Base.html#String)
[showList](GHC.Show.html#showList) :: [[a](#local-6989586621679529317)] -> [ShowS](GHC.Show.html#ShowS)
[showsPrec](GHC.Show.html#showsPrec) Int_ a x String s = a -> String forall a. Show a => a -> String show a x String -> ShowS forall a. [a] -> [a] -> [a] ++ String s show a x = a -> ShowS forall a. Show a => a -> ShowS shows a x String "" showList [a] ls String s = (a -> ShowS) -> [a] -> ShowS forall a. (a -> ShowS) -> [a] -> ShowS showList__ a -> ShowS forall a. Show a => a -> ShowS shows [a] ls String s
showList__ :: (a -> ShowS) -> [a] -> ShowS showList__ :: forall a. (a -> ShowS) -> [a] -> ShowS showList__ a -> ShowS _ [] String s = String "[]" String -> ShowS forall a. [a] -> [a] -> [a] ++ String s showList__ a -> ShowS showx (a x:[a] xs) String s = Char '[' Char -> ShowS forall a. a -> [a] -> [a] : a -> ShowS showx a x ([a] -> String showl [a] xs) where showl :: [a] -> String showl [] = Char ']' Char -> ShowS forall a. a -> [a] -> [a] : String s showl (a y:[a] ys) = Char ',' Char -> ShowS forall a. a -> [a] -> [a] : a -> ShowS showx a y ([a] -> String showl [a] ys)
appPrec :: Int appPrec = Int# -> Int I# Int# 10#
appPrec1 :: Int appPrec1 = Int# -> Int I# Int# 11#
deriving instance Show ()
deriving instance Show a => Show (Solo a)
instance Show a => Show [a] where {-# SPECIALISE instance Show [String] #-} {-# SPECIALISE instance Show [Char] #-} {-# SPECIALISE instance Show [Int] #-} showsPrec :: Int -> [a] -> ShowS showsPrec Int _ = [a] -> ShowS forall a. Show a => [a] -> ShowS showList
deriving instance Show Ordering
instance Show Char where showsPrec :: Int -> Char -> ShowS showsPrec Int _ Char ''' = String -> ShowS showString String "'\''" showsPrec Int _ Char c = Char -> ShowS showChar Char ''' ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showLitChar Char c ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showChar Char '''
showList :: String -> ShowSshowList String cs = Char -> ShowS showChar Char '"' ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showLitString String cs ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showChar Char '"'
instance Show Int where showsPrec :: Int -> Int -> ShowS showsPrec = Int -> Int -> ShowS showSignedInt
instance Show Word where showsPrec :: Int -> Word -> ShowS showsPrec Int _ (W# Word# w) = Word# -> ShowS showWord Word# w
showWord :: Word# -> ShowS
showWord :: Word# -> ShowS
showWord Word#
w# String
cs
| Int# -> Bool
isTrue# (Word#
w# Word# -> Word# -> Int#
ltWord# Word#
10##) = Char# -> Char
C# (Int# -> Char#
chr# (Char# -> Int#
ord# Char#
'0'# Int# -> Int# -> Int#
+# Word# -> Int#
word2Int# Word#
w#)) Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs
| Bool
otherwise = case Int# -> Char#
chr# (Char# -> Int#
ord# Char#
'0'# Int# -> Int# -> Int#
+# Word# -> Int#
word2Int# (Word#
w# Word# -> Word# -> Word#
remWord# Word#
10##)) of
Char#
c# ->
Word# -> ShowS
showWord (Word#
w# Word# -> Word# -> Word#
quotWord# Word#
10##) (Char# -> Char
C# Char#
c# Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs)
deriving instance Show a => Show (Maybe a)
deriving instance Show a => Show (NonEmpty a)
instance Show TyCon where showsPrec :: Int -> TyCon -> ShowS showsPrec Int p (TyCon Word# _ Word# _ Module _ TrName tc_name Int# _ KindRep _) = Int -> TrName -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p TrName tc_name
instance Show TrName where showsPrec :: Int -> TrName -> ShowS showsPrec Int _ (TrNameS Addr# s) = String -> ShowS showString (Addr# -> String unpackCStringUtf8# Addr# s) showsPrec Int _ (TrNameD String s) = String -> ShowS showString String s
instance Show Module where showsPrec :: Int -> Module -> ShowS showsPrec Int _ (Module TrName p TrName m) = TrName -> ShowS forall a. Show a => a -> ShowS shows TrName p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (Char ':' Char -> ShowS forall a. a -> [a] -> [a] :) ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . TrName -> ShowS forall a. Show a => a -> ShowS shows TrName m
instance Show CallStack where showsPrec :: Int -> CallStack -> ShowS showsPrec Int _ = [(String, SrcLoc)] -> ShowS forall a. Show a => a -> ShowS shows ([(String, SrcLoc)] -> ShowS) -> (CallStack -> [(String, SrcLoc)]) -> CallStack -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . CallStack -> [(String, SrcLoc)] getCallStack
instance (Show a, Show b) => Show (a,b) where showsPrec :: Int -> (a, b) -> ShowS showsPrec Int _ (a a,b b) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b] String s
instance (Show a, Show b, Show c) => Show (a, b, c) where showsPrec :: Int -> (a, b, c) -> ShowS showsPrec Int _ (a a,b b,c c) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c] String s
instance (Show a, Show b, Show c, Show d) => Show (a, b, c, d) where showsPrec :: Int -> (a, b, c, d) -> ShowS showsPrec Int _ (a a,b b,c c,d d) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d] String s
instance (Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) where showsPrec :: Int -> (a, b, c, d, e) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f) => Show (a,b,c,d,e,f) where showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a,b,c,d,e,f,g) where showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a,b,c,d,e,f,g,h) where showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a,b,c,d,e,f,g,h,i) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a,b,c,d,e,f,g,h,i,j) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a,b,c,d,e,f,g,h,i,j,k) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j,k k) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j, k -> ShowS forall a. Show a => a -> ShowS shows k k] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a,b,c,d,e,f,g,h,i,j,k,l) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j,k k,l l) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j, k -> ShowS forall a. Show a => a -> ShowS shows k k, l -> ShowS forall a. Show a => a -> ShowS shows l l] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a,b,c,d,e,f,g,h,i,j,k,l,m) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j,k k,l l,m m) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j, k -> ShowS forall a. Show a => a -> ShowS shows k k, l -> ShowS forall a. Show a => a -> ShowS shows l l, m -> ShowS forall a. Show a => a -> ShowS shows m m] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j,k k,l l,m m,n n) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j, k -> ShowS forall a. Show a => a -> ShowS shows k k, l -> ShowS forall a. Show a => a -> ShowS shows l l, m -> ShowS forall a. Show a => a -> ShowS shows m m, n -> ShowS forall a. Show a => a -> ShowS shows n n] String s
instance (Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a,b,c,d,e,f,g,h,i,j,k,l,m,n,o) where showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS showsPrec Int _ (a a,b b,c c,d d,e e,f f,g g,h h,i i,j j,k k,l l,m m,n n,o o) String s = [ShowS] -> ShowS show_tuple [a -> ShowS forall a. Show a => a -> ShowS shows a a, b -> ShowS forall a. Show a => a -> ShowS shows b b, c -> ShowS forall a. Show a => a -> ShowS shows c c, d -> ShowS forall a. Show a => a -> ShowS shows d d, e -> ShowS forall a. Show a => a -> ShowS shows e e, f -> ShowS forall a. Show a => a -> ShowS shows f f, g -> ShowS forall a. Show a => a -> ShowS shows g g, h -> ShowS forall a. Show a => a -> ShowS shows h h, i -> ShowS forall a. Show a => a -> ShowS shows i i, j -> ShowS forall a. Show a => a -> ShowS shows j j, k -> ShowS forall a. Show a => a -> ShowS shows k k, l -> ShowS forall a. Show a => a -> ShowS shows l l, m -> ShowS forall a. Show a => a -> ShowS shows m m, n -> ShowS forall a. Show a => a -> ShowS shows n n, o -> ShowS forall a. Show a => a -> ShowS shows o o] String s
show_tuple :: [ShowS] -> ShowS show_tuple :: [ShowS] -> ShowS show_tuple [ShowS] ss = Char -> ShowS showChar Char '(' ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . (ShowS -> ShowS -> ShowS) -> [ShowS] -> ShowS forall a. (a -> a -> a) -> [a] -> a foldr1 (\ShowS s ShowS r -> ShowS s ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showChar Char ',' ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . ShowS r) [ShowS] ss ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showChar Char ')'
shows :: (Show a) => a -> ShowS shows :: forall a. Show a => a -> ShowS shows = Int -> a -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 0
showChar :: Char -> ShowS showChar :: Char -> ShowS showChar = (:)
showString :: String -> ShowS showString :: String -> ShowS showString = String -> ShowS forall a. [a] -> [a] -> [a] (++)
showParen :: Bool -> ShowS -> ShowS showParen :: Bool -> ShowS -> ShowS showParen Bool b ShowS p = if Bool b then Char -> ShowS showChar Char '(' ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . ShowS p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Char -> ShowS showChar Char ')' else ShowS p
showSpace :: ShowS showSpace :: ShowS showSpace = \ String xs -> Char ' ' Char -> ShowS forall a. a -> [a] -> [a] : String xs
showCommaSpace :: ShowS showCommaSpace :: ShowS showCommaSpace = String -> ShowS showString String ", "
showLitChar :: Char -> ShowS showLitChar :: Char -> ShowS showLitChar Char c String s | Char c Char -> Char -> Bool forall a. Ord a => a -> a -> Bool > Char '\DEL' = Char -> ShowS showChar Char '\' ((Char -> Bool) -> ShowS -> ShowS protectEsc Char -> Bool isDec (Int -> ShowS forall a. Show a => a -> ShowS shows (Char -> Int ord Char c)) String s) showLitChar Char '\DEL' String s = String -> ShowS showString String "\DEL" String s showLitChar Char '\' String s = String -> ShowS showString String "\\" String s showLitChar Char c String s | Char c Char -> Char -> Bool forall a. Ord a => a -> a -> Bool >= Char ' ' = Char -> ShowS showChar Char c String s showLitChar Char '\a' String s = String -> ShowS showString String "\a" String s showLitChar Char '\b' String s = String -> ShowS showString String "\b" String s showLitChar Char '\f' String s = String -> ShowS showString String "\f" String s showLitChar Char '\n' String s = String -> ShowS showString String "\n" String s showLitChar Char '\r' String s = String -> ShowS showString String "\r" String s showLitChar Char '\t' String s = String -> ShowS showString String "\t" String s showLitChar Char '\v' String s = String -> ShowS showString String "\v" String s showLitChar Char '\SO' String s = (Char -> Bool) -> ShowS -> ShowS protectEsc (Char -> Char -> Bool forall a. Eq a => a -> a -> Bool == Char 'H') (String -> ShowS showString String "\SO") String s showLitChar Char c String s = String -> ShowS showString (Char '\' Char -> ShowS forall a. a -> [a] -> [a] : [String] asciiTab[String] -> Int -> String forall a. [a] -> Int -> a !!Char -> Int ord Char c) String s
showLitString :: String -> ShowS
showLitString :: String -> ShowS showLitString [] String s = String s showLitString (Char '"' : String cs) String s = String -> ShowS showString String "\"" (String -> ShowS showLitString String cs String s) showLitString (Char c : String cs) String s = Char -> ShowS showLitChar Char c (String -> ShowS showLitString String cs String s)
showMultiLineString :: String -> [String]
showMultiLineString :: String -> [String] showMultiLineString String str = Char -> String -> [String] go Char '"' String str where go :: Char -> String -> [String] go Char ch String s = case (Char -> Bool) -> String -> (String, String) forall a. (a -> Bool) -> [a] -> ([a], [a]) break (Char -> Char -> Bool forall a. Eq a => a -> a -> Bool == Char '\n') String s of (String l, Char _:s' :: String s'@(Char _:String _)) -> (Char ch Char -> ShowS forall a. a -> [a] -> [a] : String -> ShowS showLitString String l String "\n\") String -> [String] -> [String] forall a. a -> [a] -> [a] : Char -> String -> [String] go Char '\' String s' (String l, String "\n") -> [Char ch Char -> ShowS forall a. a -> [a] -> [a] : String -> ShowS showLitString String l String "\n""] (String l, String _) -> [Char ch Char -> ShowS forall a. a -> [a] -> [a] : String -> ShowS showLitString String l String """]
isDec :: Char -> Bool isDec :: Char -> Bool isDec Char c = Char c Char -> Char -> Bool forall a. Ord a => a -> a -> Bool >= Char '0' Bool -> Bool -> Bool && Char c Char -> Char -> Bool forall a. Ord a => a -> a -> Bool <= Char '9'
protectEsc :: (Char -> Bool) -> ShowS -> ShowS protectEsc :: (Char -> Bool) -> ShowS -> ShowS protectEsc Char -> Bool p ShowS f = ShowS f ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . ShowS cont where cont :: ShowS cont s :: String s@(Char c:String _) | Char -> Bool p Char c = String "\&" String -> ShowS forall a. [a] -> [a] -> [a] ++ String s cont String s = String s
asciiTab :: [String] asciiTab :: [String] asciiTab = [String "NUL", String "SOH", String "STX", String "ETX", String "EOT", String "ENQ", String "ACK", String "BEL", String "BS", String "HT", String "LF", String "VT", String "FF", String "CR", String "SO", String "SI", String "DLE", String "DC1", String "DC2", String "DC3", String "DC4", String "NAK", String "SYN", String "ETB", String "CAN", String "EM", String "SUB", String "ESC", String "FS", String "GS", String "RS", String "US", String "SP"]
intToDigit :: Int -> Char intToDigit :: Int -> Char intToDigit (I# Int# i) | Int# -> Bool isTrue# (Int# i Int# -> Int# -> Int# >=# Int# 0#) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int# i Int# -> Int# -> Int# <=# Int# 9#) = Int -> Char unsafeChr (Char -> Int ord Char '0' Int -> Int -> Int forall a. Num a => a -> a -> a + Int# -> Int I# Int# i) | Int# -> Bool isTrue# (Int# i Int# -> Int# -> Int# >=# Int# 10#) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int# i Int# -> Int# -> Int# <=# Int# 15#) = Int -> Char unsafeChr (Char -> Int ord Char 'a' Int -> Int -> Int forall a. Num a => a -> a -> a + Int# -> Int I# Int# i Int -> Int -> Int forall a. Num a => a -> a -> a - Int 10) | Bool otherwise = String -> Char forall a. String -> a errorWithoutStackTrace (String "Char.intToDigit: not a digit " String -> ShowS forall a. [a] -> [a] -> [a] ++ Int -> String forall a. Show a => a -> String show (Int# -> Int I# Int# i))
showSignedInt :: Int -> Int -> ShowS showSignedInt :: Int -> Int -> ShowS showSignedInt (I# Int# p) (I# Int# n) String r | Int# -> Bool isTrue# (Int# n Int# -> Int# -> Int# <# Int# 0#) Bool -> Bool -> Bool && Int# -> Bool isTrue# (Int# p Int# -> Int# -> Int# ># Int# 6#) = Char '(' Char -> ShowS forall a. a -> [a] -> [a] : Int# -> ShowS itos Int# n (Char ')' Char -> ShowS forall a. a -> [a] -> [a] : String r) | Bool otherwise = Int# -> ShowS itos Int# n String r
itos :: Int# -> String -> String itos :: Int# -> ShowS itos Int# n# String cs | Int# -> Bool isTrue# (Int# n# Int# -> Int# -> Int# <# Int# 0#) = let !(I# Int# minInt#) = Int minInt in if Int# -> Bool isTrue# (Int# n# Int# -> Int# -> Int# ==# Int# minInt#)
then Char'-' Char -> ShowS
forall a. a -> [a] -> [a]
: (case Int#
n# Int# -> Int# -> (# Int#, Int# #)
quotRemInt# Int#
10# of
(# Int#
q, Int#
r #) ->
Int# -> ShowS
itos' (Int# -> Int#
negateInt# Int#
q) (Int# -> ShowS
itos' (Int# -> Int#
negateInt# Int#
r) String
cs))
else Char
'-' Char -> ShowS
forall a. a -> [a] -> [a]
: Int# -> ShowS
itos' (Int# -> Int#
negateInt# Int#
n#) String
cs
| Bool
otherwise = Int# -> ShowS
itos' Int#
n# String
cs
where
itos' :: Int# -> String -> String
itos' :: Int# -> ShowS
itos' Int#
x# String
cs'
| Int# -> Bool
isTrue# (Int#
x# Int# -> Int# -> Int#
<# Int#
10#) = Char# -> Char
C# (Int# -> Char#
chr# (Char# -> Int#
ord# Char#
'0'# Int# -> Int# -> Int#
+# Int#
x#)) Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs'
| Bool
otherwise = case Int#
x# Int# -> Int# -> (# Int#, Int# #)
quotRemInt# Int#
10# of
(# Int#
q, Int#
r #) ->
case Int# -> Char#
chr# (Char# -> Int#
ord# Char#
'0'# Int# -> Int# -> Int#
+# Int#
r) of
Char#
c# ->
Int# -> ShowS
itos' Int#
q (Char# -> Char
C# Char#
c# Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs')
instance Show Integer where showsPrec :: Int -> Integer -> ShowS showsPrec Int p (IS Int# i) String r = Int -> Int -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Int# -> Int I# Int# i) String r showsPrec Int p Integer n String r | Int p Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 6 Bool -> Bool -> Bool && Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = Char '(' Char -> ShowS forall a. a -> [a] -> [a] : Integer -> ShowS integerToString Integer n (Char ')' Char -> ShowS forall a. a -> [a] -> [a] : String r)
| Boolotherwise = Integer -> ShowS integerToString Integer n String r showList :: [Integer] -> ShowS showList = (Integer -> ShowS) -> [Integer] -> ShowS forall a. (a -> ShowS) -> [a] -> ShowS showList__ (Int -> Integer -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 0)
instance Show Natural where showsPrec :: Int -> Natural -> ShowS showsPrec Int p (NS Word# w) = Int -> Word -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Word# -> Word W# Word# w) showsPrec Int p Natural n = Int -> Integer -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int p (Natural -> Integer integerFromNatural Natural n)
integerToString :: Integer -> String -> String integerToString :: Integer -> ShowS integerToString Integer n0 String cs0 | Integer n0 Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = Char '-' Char -> ShowS forall a. a -> [a] -> [a] : Integer -> ShowS integerToString' (- Integer n0) String cs0 | Bool otherwise = Integer -> ShowS integerToString' Integer n0 String cs0 where integerToString' :: Integer -> String -> String integerToString' :: Integer -> ShowS integerToString' Integer n String cs | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < BASE = jhead (fromInteger n) cs | Bool otherwise = [Integer] -> ShowS jprinth (Integer -> Integer -> [Integer] jsplitf (BASE*BASE) n) cs
[jsplitf](#local-6989586621679528276) :: [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer) -> [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer) -> [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)]
jsplitf :: Integer -> Integer -> [Integer]jsplitf Integer p Integer n | Integer p Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool > Integer n = [Integer n] | Bool otherwise = Integer -> [Integer] -> [Integer] jsplith Integer p (Integer -> Integer -> [Integer] jsplitf (Integer pInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer p) Integer n)
[jsplith](#local-6989586621679528272) :: [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer) -> [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)] -> [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)]
jsplith :: Integer -> [Integer] -> [Integer]jsplith Integer
p (Integer
n:[Integer]
ns) =
case Integer
n Integer -> Integer -> (# Integer, Integer #)
integerQuotRem# Integer
p of
(# Integer
q, Integer
r #) ->
if Integer
q Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 then Integer
q Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Integer
r Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
else Integer
r Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
jsplith Integer
_ [] = String -> [Integer]
forall a. String -> a
errorWithoutStackTrace String
"jsplith: []"
[jsplitb](#local-6989586621679528266) :: [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer) -> [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)] -> [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)]
jsplitb :: Integer -> [Integer] -> [Integer]jsplitb Integer
_ [] = []
jsplitb Integer
p (Integer
n:[Integer]
ns) = case Integer
n Integer -> Integer -> (# Integer, Integer #)
integerQuotRem# Integer
p of
(# Integer
q, Integer
r #) ->
Integer
q Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Integer
r Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: Integer -> [Integer] -> [Integer]
jsplitb Integer
p [Integer]
ns
[jprinth](#local-6989586621679528277) :: [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)] -> [String](GHC.Base.html#String) -> [String](GHC.Base.html#String)
jprinth :: [Integer] -> ShowSjprinth (Integer
n:[Integer]
ns) String
cs =
case Integer
n Integer -> Integer -> (# Integer, Integer #)
integerQuotRem# BASE of
(# Integer
q', Integer
r' #) ->
let q :: Int
q = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
q'
r :: Int
r = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
r'
in if Int
q Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int -> ShowS
jhead Int
q ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
jblock Int
r ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [Integer] -> ShowS
jprintb [Integer]
ns String
cs
else Int -> ShowS
jhead Int
r ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [Integer] -> ShowS
jprintb [Integer]
ns String
cs
jprinth [] String
_ = ShowS
forall a. String -> a
errorWithoutStackTrace String
"jprinth []"
[jprintb](#local-6989586621679528250) :: [[Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)] -> [String](GHC.Base.html#String) -> [String](GHC.Base.html#String)
jprintb :: [Integer] -> ShowSjprintb [] String
cs = String
cs
jprintb (Integer
n:[Integer]
ns) String
cs = case Integer
n Integer -> Integer -> (# Integer, Integer #)
integerQuotRem# BASE of
(# Integer
q', Integer
r' #) ->
let q :: Int
q = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
q'
r :: Int
r = Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
r'
in Int -> ShowS
jblock Int
q ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ Int -> ShowS
jblock Int
r ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ [Integer] -> ShowS
jprintb [Integer]
ns String
cs
[jhead](#local-6989586621679528278) :: [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int) -> [String](GHC.Base.html#String) -> [String](GHC.Base.html#String)
jhead :: Int -> ShowSjhead Int
n String
cs
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
10 = case Int -> Char
unsafeChr (Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) of
c :: Char
c@(C# Char#
_) -> Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs
| Bool
otherwise = case Int -> Char
unsafeChr (Char -> Int
ord Char
'0' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
r) of
c :: Char
c@(C# Char#
_) -> Int -> ShowS
jhead Int
q (Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs)
where
(Int
q, Int
r) = Int
n Int -> Int -> (Int, Int)
quotRemInt Int
10
jblock :: Int -> ShowSjblock = Int -> Int -> ShowS jblock' DIGITS
[jblock'](#local-6989586621679528232) :: [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int) -> [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int) -> [String](GHC.Base.html#String) -> [String](GHC.Base.html#String)
jblock' :: Int -> Int -> ShowSjblock' Int d Int n String cs | Int d Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 1 = case Int -> Char unsafeChr (Char -> Int ord Char '0' Int -> Int -> Int forall a. Num a => a -> a -> a + Int n) of c :: Char c@(C# Char# _) -> Char c Char -> ShowS forall a. a -> [a] -> [a] : String cs | Bool otherwise = case Int -> Char unsafeChr (Char -> Int ord Char '0' Int -> Int -> Int forall a. Num a => a -> a -> a + Int r) of c :: Char c@(C# Char# _) -> Int -> Int -> ShowS jblock' (Int d Int -> Int -> Int forall a. Num a => a -> a -> a - Int
q, Int
r) = Int
n Int -> Int -> (Int, Int)
quotRemInt Int
10
instance Show KindRep where showsPrec :: Int -> KindRep -> ShowS showsPrec Int d (KindRepVar Int v) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepVar " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> Int -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 Int v showsPrec Int d (KindRepTyConApp TyCon p [KindRep] q) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepTyConApp " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> TyCon -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 TyCon p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String " " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> [KindRep] -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 [KindRep] q showsPrec Int d (KindRepApp KindRep p KindRep q) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepApp " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> KindRep -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 KindRep p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String " " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> KindRep -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 KindRep q showsPrec Int d (KindRepFun KindRep p KindRep q) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepFun " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> KindRep -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 KindRep p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String " " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> KindRep -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 KindRep q showsPrec Int d (KindRepTYPE RuntimeRep rep) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepTYPE " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> RuntimeRep -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 RuntimeRep rep showsPrec Int d (KindRepTypeLitS TypeLitSort p Addr# q) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepTypeLitS " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> TypeLitSort -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 TypeLitSort p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String " " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> String -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 (Addr# -> String unpackCString# Addr# q) showsPrec Int d (KindRepTypeLitD TypeLitSort p String q) = Bool -> ShowS -> ShowS showParen (Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 10) (ShowS -> ShowS) -> ShowS -> ShowS forall a b. (a -> b) -> a -> b $ String -> ShowS showString String "KindRepTypeLitD " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> TypeLitSort -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 TypeLitSort p ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ShowS showString String " " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . Int -> String -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 11 String q
deriving instance Show RuntimeRep
deriving instance Show VecCount
deriving instance Show VecElem
deriving instance Show TypeLitSort