{-# LANGUAGE MagicHash #-}
module GHC.CmmToAsm.Ppr (
castFloatToWord8Array,
castDoubleToWord8Array,
floatToBytes,
doubleToBytes,
pprASCII,
pprString,
pprFileEmbed,
pprSectionHeader
)
where
import GHC.Prelude
import GHC.Utils.Asm
import GHC.Cmm.CLabel
import GHC.Cmm
import GHC.CmmToAsm.Config
import GHC.Data.FastString
import GHC.Utils.Outputable
import GHC.Platform
import qualified Data.Array.Unsafe as U ( castSTUArray )
import Data.Array.ST
import Control.Monad.ST
import Data.Word
import Data.Bits
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import GHC.Exts
import GHC.Word
castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8)
castFloatToWord8Array :: forall s. STUArray s Int Float -> ST s (STUArray s Int Word8)
castFloatToWord8Array = STUArray s Int Float -> ST s (STUArray s Int Word8)
forall s ix a b. STUArray s ix a -> ST s (STUArray s ix b)
U.castSTUArray
castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8)
castDoubleToWord8Array :: forall s. STUArray s Int Double -> ST s (STUArray s Int Word8)
castDoubleToWord8Array = STUArray s Int Double -> ST s (STUArray s Int Word8)
forall s ix a b. STUArray s ix a -> ST s (STUArray s ix b)
U.castSTUArray
floatToBytes :: Float -> [Int]
floatToBytes :: Float -> [Int]
floatToBytes Float
f
= (forall s. ST s [Int]) -> [Int]
forall a. (forall s. ST s a) -> a
runST (do
STUArray s Int Float
arr <- (Int, Int) -> ST s (STUArray s Int Float)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ ((Int
0::Int),Int
3)
STUArray s Int Float -> Int -> Float -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Float
arr Int
0 Float
f
STUArray s Int Word8
arr <- STUArray s Int Float -> ST s (STUArray s Int Word8)
forall s. STUArray s Int Float -> ST s (STUArray s Int Word8)
castFloatToWord8Array STUArray s Int Float
arr
Word8
i0 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
0
Word8
i1 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
1
Word8
i2 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
2
Word8
i3 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
3
[Int] -> ST s [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word8 -> Int) -> [Word8] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Word8
i0,Word8
i1,Word8
i2,Word8
i3])
)
doubleToBytes :: Double -> [Int]
doubleToBytes :: Double -> [Int]
doubleToBytes Double
d
= (forall s. ST s [Int]) -> [Int]
forall a. (forall s. ST s a) -> a
runST (do
STUArray s Int Double
arr <- (Int, Int) -> ST s (STUArray s Int Double)
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
(i, i) -> m (a i e)
newArray_ ((Int
0::Int),Int
7)
STUArray s Int Double -> Int -> Double -> ST s ()
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> e -> m ()
writeArray STUArray s Int Double
arr Int
0 Double
d
STUArray s Int Word8
arr <- STUArray s Int Double -> ST s (STUArray s Int Word8)
forall s. STUArray s Int Double -> ST s (STUArray s Int Word8)
castDoubleToWord8Array STUArray s Int Double
arr
Word8
i0 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
0
Word8
i1 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
1
Word8
i2 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
2
Word8
i3 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
3
Word8
i4 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
4
Word8
i5 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
5
Word8
i6 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
6
Word8
i7 <- STUArray s Int Word8 -> Int -> ST s Word8
forall (a :: * -> * -> *) e (m :: * -> *) i.
(MArray a e m, Ix i) =>
a i e -> i -> m e
readArray STUArray s Int Word8
arr Int
7
[Int] -> ST s [Int]
forall (m :: * -> *) a. Monad m => a -> m a
return ((Word8 -> Int) -> [Word8] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral [Word8
i0,Word8
i1,Word8
i2,Word8
i3,Word8
i4,Word8
i5,Word8
i6,Word8
i7])
)
pprASCII :: ByteString -> SDoc
pprASCII :: ByteString -> SDoc
pprASCII ByteString
str
= String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ (Word8 -> String -> String) -> String -> ByteString -> String
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
BS.foldr (\Word8
w String
s -> Word8 -> String
do1 Word8
w String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s) String
"" ByteString
str
where
do1 :: Word8 -> String
do1 :: Word8 -> String
do1 Word8
w | Word8
0x09 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w = String
"\\t"
| Word8
0x0A Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w = String
"\\n"
| Word8
0x22 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w = String
"\\\""
| Word8
0x5C Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w = String
"\\\\"
| Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
>= Word8
0x20 Bool -> Bool -> Bool
&& Word8
w Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> Bool
<= Word8
0x7E = [Word8 -> Char
chr' Word8
w]
| Bool
otherwise = Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Word8 -> String
octal Word8
w
chr' :: Word8 -> Char
chr' :: Word8 -> Char
chr' (W8# Word#
w#) = Char# -> Char
C# (Int# -> Char#
chr# (Word# -> Int#
word2Int# Word#
w#))
octal :: Word8 -> String
octal :: Word8 -> String
octal Word8
w = [ Word8 -> Char
chr' (Word8
ord0 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ (Word8
w Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
6) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x07)
, Word8 -> Char
chr' (Word8
ord0 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ (Word8
w Word8 -> Int -> Word8
forall a. Bits a => a -> Int -> a
`unsafeShiftR` Int
3) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x07)
, Word8 -> Char
chr' (Word8
ord0 Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
w Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.&. Word8
0x07)
]
ord0 :: Word8
ord0 = Word8
0x30
pprString :: ByteString -> SDoc
pprString :: ByteString -> SDoc
pprString ByteString
bs = String -> SDoc
text String
"\t.string " SDoc -> SDoc -> SDoc
<> SDoc -> SDoc
doubleQuotes (ByteString -> SDoc
pprASCII ByteString
bs)
pprFileEmbed :: FilePath -> SDoc
pprFileEmbed :: String -> SDoc
pprFileEmbed String
path
= String -> SDoc
text String
"\t.incbin "
SDoc -> SDoc -> SDoc
<> String -> SDoc
pprFilePathString String
path
SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
"\n\t.byte 0"
pprSectionHeader :: NCGConfig -> Section -> SDoc
NCGConfig
config (Section SectionType
t CLabel
suffix) =
case Platform -> OS
platformOS (NCGConfig -> Platform
ncgPlatform NCGConfig
config) of
OS
OSAIX -> SectionType -> SDoc
pprXcoffSectionHeader SectionType
t
OS
OSDarwin -> SectionType -> SDoc
pprDarwinSectionHeader SectionType
t
OS
OSMinGW32 -> NCGConfig -> SDoc -> SectionType -> CLabel -> SDoc
pprGNUSectionHeader NCGConfig
config (Char -> SDoc
char Char
'$') SectionType
t CLabel
suffix
OS
_ -> NCGConfig -> SDoc -> SectionType -> CLabel -> SDoc
pprGNUSectionHeader NCGConfig
config (Char -> SDoc
char Char
'.') SectionType
t CLabel
suffix
pprGNUSectionHeader :: NCGConfig -> SDoc -> SectionType -> CLabel -> SDoc
NCGConfig
config SDoc
sep SectionType
t CLabel
suffix =
String -> SDoc
text String
".section " SDoc -> SDoc -> SDoc
<> PtrString -> SDoc
ptext PtrString
header SDoc -> SDoc -> SDoc
<> SDoc
subsection SDoc -> SDoc -> SDoc
<> SDoc
flags
where
platform :: Platform
platform = NCGConfig -> Platform
ncgPlatform NCGConfig
config
splitSections :: Bool
splitSections = NCGConfig -> Bool
ncgSplitSections NCGConfig
config
subsection :: SDoc
subsection
| Bool
splitSections = SDoc
sep SDoc -> SDoc -> SDoc
<> CLabel -> SDoc
forall a. Outputable a => a -> SDoc
ppr CLabel
suffix
| Bool
otherwise = SDoc
empty
header :: PtrString
header = case SectionType
t of
SectionType
Text -> String -> PtrString
sLit String
".text"
SectionType
Data -> String -> PtrString
sLit String
".data"
SectionType
ReadOnlyData | OS
OSMinGW32 <- Platform -> OS
platformOS Platform
platform
-> String -> PtrString
sLit String
".rdata"
| Bool
otherwise -> String -> PtrString
sLit String
".rodata"
SectionType
RelocatableReadOnlyData | OS
OSMinGW32 <- Platform -> OS
platformOS Platform
platform
-> String -> PtrString
sLit String
".rdata$rel.ro"
| Bool
otherwise -> String -> PtrString
sLit String
".data.rel.ro"
SectionType
UninitialisedData -> String -> PtrString
sLit String
".bss"
SectionType
ReadOnlyData16 | OS
OSMinGW32 <- Platform -> OS
platformOS Platform
platform
-> String -> PtrString
sLit String
".rdata$cst16"
| Bool
otherwise -> String -> PtrString
sLit String
".rodata.cst16"
SectionType
CString
| OS
OSMinGW32 <- Platform -> OS
platformOS Platform
platform
-> String -> PtrString
sLit String
".rdata"
| Bool
otherwise -> String -> PtrString
sLit String
".rodata.str"
OtherSection String
_ ->
String -> PtrString
forall a. String -> a
panic String
"PprBase.pprGNUSectionHeader: unknown section type"
flags :: SDoc
flags = case SectionType
t of
SectionType
CString
| OS
OSMinGW32 <- Platform -> OS
platformOS Platform
platform
-> SDoc
empty
| Bool
otherwise -> String -> SDoc
text String
",\"aMS\"," SDoc -> SDoc -> SDoc
<> Platform -> String -> SDoc
sectionType Platform
platform String
"progbits" SDoc -> SDoc -> SDoc
<> String -> SDoc
text String
",1"
SectionType
_ -> SDoc
empty
pprXcoffSectionHeader :: SectionType -> SDoc
SectionType
t = String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ case SectionType
t of
SectionType
Text -> String
".csect .text[PR]"
SectionType
Data -> String
".csect .data[RW]"
SectionType
ReadOnlyData -> String
".csect .text[PR] # ReadOnlyData"
SectionType
RelocatableReadOnlyData -> String
".csect .text[PR] # RelocatableReadOnlyData"
SectionType
ReadOnlyData16 -> String
".csect .text[PR] # ReadOnlyData16"
SectionType
CString -> String
".csect .text[PR] # CString"
SectionType
UninitialisedData -> String
".csect .data[BS]"
OtherSection String
_ ->
String -> String
forall a. String -> a
panic String
"PprBase.pprXcoffSectionHeader: unknown section type"
pprDarwinSectionHeader :: SectionType -> SDoc
SectionType
t =
PtrString -> SDoc
ptext (PtrString -> SDoc) -> PtrString -> SDoc
forall a b. (a -> b) -> a -> b
$ case SectionType
t of
SectionType
Text -> String -> PtrString
sLit String
".text"
SectionType
Data -> String -> PtrString
sLit String
".data"
SectionType
ReadOnlyData -> String -> PtrString
sLit String
".const"
SectionType
RelocatableReadOnlyData -> String -> PtrString
sLit String
".const_data"
SectionType
UninitialisedData -> String -> PtrString
sLit String
".data"
SectionType
ReadOnlyData16 -> String -> PtrString
sLit String
".const"
SectionType
CString -> String -> PtrString
sLit String
".section\t__TEXT,__cstring,cstring_literals"
OtherSection String
_ ->
String -> PtrString
forall a. String -> a
panic String
"PprBase.pprDarwinSectionHeader: unknown section type"