never executed always true always false
    1 {-# LANGUAGE CPP #-}
    2 {-# LANGUAGE MagicHash #-}
    3 
    4 -----------------------------------------------------------------------------
    5 --
    6 -- Pretty-printing assembly language
    7 --
    8 -- (c) The University of Glasgow 1993-2005
    9 --
   10 -----------------------------------------------------------------------------
   11 
   12 module GHC.CmmToAsm.Ppr (
   13         doubleToBytes,
   14         pprASCII,
   15         pprString,
   16         pprFileEmbed,
   17         pprSectionHeader
   18 )
   19 
   20 where
   21 
   22 import GHC.Prelude
   23 
   24 import GHC.Utils.Asm
   25 import GHC.Cmm.CLabel
   26 import GHC.Cmm
   27 import GHC.CmmToAsm.Config
   28 import GHC.Utils.Outputable as SDoc
   29 import qualified GHC.Utils.Ppr as Pretty
   30 import GHC.Utils.Panic
   31 import GHC.Platform
   32 
   33 import qualified Data.Array.Unsafe as U ( castSTUArray )
   34 import Data.Array.ST
   35 
   36 import Control.Monad.ST
   37 
   38 import Data.Word
   39 import Data.ByteString (ByteString)
   40 import qualified Data.ByteString as BS
   41 import GHC.Exts
   42 import GHC.Word
   43 
   44 #if !MIN_VERSION_base(4,16,0)
   45 word8ToWord# :: Word# -> Word#
   46 word8ToWord# w = w
   47 {-# INLINE word8ToWord# #-}
   48 #endif
   49 
   50 -- -----------------------------------------------------------------------------
   51 -- Converting floating-point literals to integrals for printing
   52 
   53 -- ToDo: this code is currently shared between SPARC and LLVM.
   54 --       Similar functions for (single precision) floats are
   55 --       present in the SPARC backend only. We need to fix both
   56 --       LLVM and SPARC.
   57 
   58 castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int Word8)
   59 castDoubleToWord8Array = U.castSTUArray
   60 
   61 -- floatToBytes and doubleToBytes convert to the host's byte
   62 -- order.  Providing that we're not cross-compiling for a
   63 -- target with the opposite endianness, this should work ok
   64 -- on all targets.
   65 
   66 -- ToDo: this stuff is very similar to the shenanigans in PprAbs,
   67 -- could they be merged?
   68 
   69 doubleToBytes :: Double -> [Int]
   70 doubleToBytes d
   71    = runST (do
   72         arr <- newArray_ ((0::Int),7)
   73         writeArray arr 0 d
   74         arr <- castDoubleToWord8Array arr
   75         i0 <- readArray arr 0
   76         i1 <- readArray arr 1
   77         i2 <- readArray arr 2
   78         i3 <- readArray arr 3
   79         i4 <- readArray arr 4
   80         i5 <- readArray arr 5
   81         i6 <- readArray arr 6
   82         i7 <- readArray arr 7
   83         return (map fromIntegral [i0,i1,i2,i3,i4,i5,i6,i7])
   84      )
   85 
   86 -- ---------------------------------------------------------------------------
   87 -- Printing ASCII strings.
   88 --
   89 -- Print as a string and escape non-printable characters.
   90 -- This is similar to charToC in GHC.Utils.Misc
   91 
   92 pprASCII :: ByteString -> SDoc
   93 pprASCII str
   94   -- Transform this given literal bytestring to escaped string and construct
   95   -- the literal SDoc directly.
   96   -- See #14741
   97   -- and Note [Pretty print ASCII when AsmCodeGen]
   98   --
   99   -- We work with a `Doc` instead of an `SDoc` because there is no need to carry
  100   -- an `SDocContext` that we don't use. It leads to nicer (STG) code.
  101   = docToSDoc (BS.foldr f Pretty.empty str)
  102     where
  103        f :: Word8 -> Pretty.Doc -> Pretty.Doc
  104        f w s = do1 w Pretty.<> s
  105 
  106        do1 :: Word8 -> Pretty.Doc
  107        do1 w | 0x09 == w = Pretty.text "\\t"
  108              | 0x0A == w = Pretty.text "\\n"
  109              | 0x22 == w = Pretty.text "\\\""
  110              | 0x5C == w = Pretty.text "\\\\"
  111                -- ASCII printable characters range
  112              | w >= 0x20 && w <= 0x7E = Pretty.char (chr' w)
  113              | otherwise = Pretty.sizedText 4 xs
  114                 where
  115                  !xs = [ '\\', x0, x1, x2] -- octal
  116                  !x0 = chr' (ord0 + (w `unsafeShiftR` 6) .&. 0x07)
  117                  !x1 = chr' (ord0 + (w `unsafeShiftR` 3) .&. 0x07)
  118                  !x2 = chr' (ord0 + w .&. 0x07)
  119                  !ord0 = 0x30 -- = ord '0'
  120 
  121        -- we know that the Chars we create are in the ASCII range
  122        -- so we bypass the check in "chr"
  123        chr' :: Word8 -> Char
  124        chr' (W8# w#) = C# (chr# (word2Int# (word8ToWord# w#)))
  125 
  126 
  127 -- | Emit a ".string" directive
  128 pprString :: ByteString -> SDoc
  129 pprString bs = text "\t.string " <> doubleQuotes (pprASCII bs)
  130 
  131 -- | Emit a ".incbin" directive
  132 --
  133 -- A NULL byte is added after the binary data.
  134 pprFileEmbed :: FilePath -> SDoc
  135 pprFileEmbed path
  136    = text "\t.incbin "
  137      <> pprFilePathString path -- proper escape (see #16389)
  138      <> text "\n\t.byte 0"
  139 
  140 {-
  141 Note [Embedding large binary blobs]
  142 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  143 
  144 To embed a blob of binary data (e.g. an UTF-8 encoded string) into the generated
  145 code object, we have several options:
  146 
  147    1. Generate a ".byte" directive for each byte. This is what was done in the past
  148       (see Note [Pretty print ASCII when AsmCodeGen]).
  149 
  150    2. Generate a single ".string"/".asciz" directive for the whole sequence of
  151       bytes. Bytes in the ASCII printable range are rendered as characters and
  152       other values are escaped (e.g., "\t", "\077", etc.).
  153 
  154    3. Create a temporary file into which we dump the binary data and generate a
  155       single ".incbin" directive. The assembler will include the binary file for
  156       us in the generated output object.
  157 
  158 Now the code generator uses either (2) or (3), depending on the binary blob
  159 size.  Using (3) for small blobs adds too much overhead (see benchmark results
  160 in #16190), so we only do it when the size is above a threshold (500K at the
  161 time of writing).
  162 
  163 The threshold is configurable via the `-fbinary-blob-threshold` flag.
  164 
  165 -}
  166 
  167 
  168 {-
  169 Note [Pretty print ASCII when AsmCodeGen]
  170 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  171 Previously, when generating assembly code, we created SDoc with
  172 `(ptext . sLit)` for every bytes in literal bytestring, then
  173 combine them using `hcat`.
  174 
  175 When handling literal bytestrings with millions of bytes,
  176 millions of SDoc would be created and to combine, leading to
  177 high memory usage.
  178 
  179 Now we escape the given bytestring to string directly and construct
  180 SDoc only once. This improvement could dramatically decrease the
  181 memory allocation from 4.7GB to 1.3GB when embedding a 3MB literal
  182 string in source code. See #14741 for profiling results.
  183 -}
  184 
  185 -- ----------------------------------------------------------------------------
  186 -- Printing section headers.
  187 --
  188 -- If -split-section was specified, include the suffix label, otherwise just
  189 -- print the section type. For Darwin, where subsections-for-symbols are
  190 -- used instead, only print section type.
  191 --
  192 -- For string literals, additional flags are specified to enable merging of
  193 -- identical strings in the linker. With -split-sections each string also gets
  194 -- a unique section to allow strings from unused code to be GC'd.
  195 
  196 pprSectionHeader :: NCGConfig -> Section -> SDoc
  197 pprSectionHeader config (Section t suffix) =
  198  case platformOS (ncgPlatform config) of
  199    OSAIX     -> pprXcoffSectionHeader t
  200    OSDarwin  -> pprDarwinSectionHeader t
  201    _         -> pprGNUSectionHeader config t suffix
  202 
  203 pprGNUSectionHeader :: NCGConfig -> SectionType -> CLabel -> SDoc
  204 pprGNUSectionHeader config t suffix =
  205   hcat [text ".section ", header, subsection, flags]
  206   where
  207     sep
  208       | OSMinGW32 <- platformOS platform = char '$'
  209       | otherwise                        = char '.'
  210     platform      = ncgPlatform config
  211     splitSections = ncgSplitSections config
  212     subsection
  213       | splitSections = sep <> pdoc platform suffix
  214       | otherwise     = empty
  215     header = case t of
  216       Text -> text ".text"
  217       Data -> text ".data"
  218       ReadOnlyData  | OSMinGW32 <- platformOS platform
  219                                 -> text ".rdata"
  220                     | otherwise -> text ".rodata"
  221       RelocatableReadOnlyData | OSMinGW32 <- platformOS platform
  222                                 -- Concept does not exist on Windows,
  223                                 -- So map these to R/O data.
  224                                           -> text ".rdata$rel.ro"
  225                               | otherwise -> text ".data.rel.ro"
  226       UninitialisedData -> text ".bss"
  227       ReadOnlyData16 | OSMinGW32 <- platformOS platform
  228                                  -> text ".rdata$cst16"
  229                      | otherwise -> text ".rodata.cst16"
  230       CString
  231         | OSMinGW32 <- platformOS platform
  232                     -> text ".rdata"
  233         | otherwise -> text ".rodata.str"
  234       OtherSection _ ->
  235         panic "PprBase.pprGNUSectionHeader: unknown section type"
  236     flags = case t of
  237       CString
  238         | OSMinGW32 <- platformOS platform
  239                     -> empty
  240         | otherwise -> text ",\"aMS\"," <> sectionType platform "progbits" <> text ",1"
  241       _ -> empty
  242 
  243 -- XCOFF doesn't support relocating label-differences, so we place all
  244 -- RO sections into .text[PR] sections
  245 pprXcoffSectionHeader :: SectionType -> SDoc
  246 pprXcoffSectionHeader t = case t of
  247   Text                    -> text ".csect .text[PR]"
  248   Data                    -> text ".csect .data[RW]"
  249   ReadOnlyData            -> text ".csect .text[PR] # ReadOnlyData"
  250   RelocatableReadOnlyData -> text ".csect .text[PR] # RelocatableReadOnlyData"
  251   ReadOnlyData16          -> text ".csect .text[PR] # ReadOnlyData16"
  252   CString                 -> text ".csect .text[PR] # CString"
  253   UninitialisedData       -> text ".csect .data[BS]"
  254   OtherSection _          -> panic "pprXcoffSectionHeader: unknown section type"
  255 
  256 pprDarwinSectionHeader :: SectionType -> SDoc
  257 pprDarwinSectionHeader t = case t of
  258   Text                    -> text ".text"
  259   Data                    -> text ".data"
  260   ReadOnlyData            -> text ".const"
  261   RelocatableReadOnlyData -> text ".const_data"
  262   UninitialisedData       -> text ".data"
  263   ReadOnlyData16          -> text ".const"
  264   CString                 -> text ".section\t__TEXT,__cstring,cstring_literals"
  265   OtherSection _          -> panic "pprDarwinSectionHeader: unknown section type"