... |
... |
@@ -10,6 +10,7 @@ import qualified Data.ByteString.Internal as BSI |
10
|
10
|
import GHC.IO (unsafePerformIO)
|
11
|
11
|
#endif
|
12
|
12
|
|
|
13
|
+import Data.Char
|
13
|
14
|
import GHC.Prelude
|
14
|
15
|
import GHC.Platform
|
15
|
16
|
import GHC.Types.SrcLoc (pprUserRealSpan, srcSpanFile)
|
... |
... |
@@ -82,7 +83,7 @@ objcopy --remove-section .ipe <your-exe> |
82
|
83
|
upx <your-exe>
|
83
|
84
|
```
|
84
|
85
|
|
85
|
|
-The .ipe section starts with a magic 64-bit word "IPE\nIPE\n`, encoded as ascii.
|
|
86
|
+The .ipe section starts with a magic 64-bit word "IPE\0IPE\0`, encoded as ascii.
|
86
|
87
|
|
87
|
88
|
The RTS checks to see if the .ipe section starts with the magic word. If the
|
88
|
89
|
section has been stripped then it won't start with the magic word and the
|
... |
... |
@@ -132,7 +133,7 @@ emitIpeBufferListNode this_mod ents dus0 = do |
132
|
133
|
strings_bytes = compress defaultCompressionLevel uncompressed_strings
|
133
|
134
|
|
134
|
135
|
strings :: [CmmStatic]
|
135
|
|
- strings = [CmmString strings_bytes]
|
|
136
|
+ strings = [CmmString (ipe_header `mappend` strings_bytes)]
|
136
|
137
|
|
137
|
138
|
uncompressed_entries :: BS.ByteString
|
138
|
139
|
uncompressed_entries = toIpeBufferEntries (platformByteOrder platform) cg_ipes
|
... |
... |
@@ -141,17 +142,31 @@ emitIpeBufferListNode this_mod ents dus0 = do |
141
|
142
|
entries_bytes = compress defaultCompressionLevel uncompressed_entries
|
142
|
143
|
|
143
|
144
|
entries :: [CmmStatic]
|
144
|
|
- entries = [CmmString entries_bytes]
|
|
145
|
+ entries = [CmmString (ipe_header `mappend` entries_bytes)]
|
145
|
146
|
|
146
|
147
|
ipe_buffer_lbl :: CLabel
|
147
|
148
|
ipe_buffer_lbl = mkIPELabel this_mod
|
148
|
149
|
|
|
150
|
+ -- A string which fits into one 64-bit word.
|
|
151
|
+ ipe_header_word :: Word64
|
|
152
|
+ ipe_header_word = stringToWord64BE "IPE\0IPE\0"
|
|
153
|
+
|
|
154
|
+ -- Convert 8 bytes to Word64 using big-endian interpretation
|
|
155
|
+ stringToWord64BE :: String -> Word64
|
|
156
|
+ stringToWord64BE = foldl' (\acc b -> GHC.Prelude.shiftL acc 8 .|. fromIntegral (ord b)) 0
|
|
157
|
+
|
149
|
158
|
-- A magic word we can use to see if the IPE information has been stripped
|
150
|
159
|
-- or not
|
151
|
160
|
-- See Note [IPE Stripping and magic words]
|
152
|
|
- -- "IPE\nIPE\n", null terminated.
|
153
|
|
- ipe_header :: CmmStatic
|
154
|
|
- ipe_header = CmmStaticLit (CmmInt 0x4950450049504500 W64)
|
|
161
|
+ -- On little-endian machines, it is reversed
|
|
162
|
+ -- so that when the first word of the string is read then it literally
|
|
163
|
+ -- reads IPE\0IPE\0 in hex dumps.
|
|
164
|
+ ipe_header :: BS.ByteString
|
|
165
|
+ ipe_header = BSL.toStrict . BSB.toLazyByteString $
|
|
166
|
+ case platformByteOrder platform of
|
|
167
|
+ LittleEndian -> BSB.word64LE ipe_header_word
|
|
168
|
+ BigEndian -> BSB.word64BE ipe_header_word
|
|
169
|
+
|
155
|
170
|
|
156
|
171
|
ipe_buffer_node :: [CmmStatic]
|
157
|
172
|
ipe_buffer_node = map CmmStaticLit
|
... |
... |
@@ -197,12 +212,12 @@ emitIpeBufferListNode this_mod ents dus0 = do |
197
|
212
|
-- Emit the strings table
|
198
|
213
|
emitDecl $ CmmData
|
199
|
214
|
(Section IPE strings_lbl)
|
200
|
|
- (CmmStaticsRaw strings_lbl (ipe_header : strings))
|
|
215
|
+ (CmmStaticsRaw strings_lbl strings)
|
201
|
216
|
|
202
|
217
|
-- Emit the list of IPE buffer entries
|
203
|
218
|
emitDecl $ CmmData
|
204
|
219
|
(Section IPE entries_lbl)
|
205
|
|
- (CmmStaticsRaw entries_lbl (ipe_header : entries))
|
|
220
|
+ (CmmStaticsRaw entries_lbl entries)
|
206
|
221
|
|
207
|
222
|
-- Emit the IPE buffer list node
|
208
|
223
|
emitDecl $ CmmData
|