1 -- -----------------------------------------------------------------------------
3 -- (c) The University of Glasgow, 1997-2006
7 -- -----------------------------------------------------------------------------
26 #include "HsVersions.h"
28 import Data.Char ( ord, chr, isDigit, digitToInt, intToDigit,
30 import Numeric ( showIntAtBase )
32 import GHC.Ptr ( Ptr(..) )
35 -- -----------------------------------------------------------------------------
38 -- We can't write the decoder as efficiently as we'd like without
39 -- resorting to unboxed extensions, unfortunately. I tried to write
40 -- an IO version of this function, but GHC can't eliminate boxed
41 -- results from an IO-returning function.
43 -- We assume we can ignore overflow when parsing a multibyte character here.
44 -- To make this safe, we add extra sentinel bytes to unparsed UTF-8 sequences
45 -- before decoding them (see StringBuffer.hs).
47 {-# INLINE utf8DecodeChar# #-}
48 utf8DecodeChar# :: Addr# -> (# Char#, Addr# #)
50 let ch0 = word2Int# (indexWord8OffAddr# a# 0#) in
52 _ | ch0 <=# 0x7F# -> (# chr# ch0, a# `plusAddr#` 1# #)
54 | ch0 >=# 0xC0# && ch0 <=# 0xDF# ->
55 let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
56 if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
57 (# chr# (((ch0 -# 0xC0#) `uncheckedIShiftL#` 6#) +#
61 | ch0 >=# 0xE0# && ch0 <=# 0xEF# ->
62 let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
63 if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
64 let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
65 if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
66 (# chr# (((ch0 -# 0xE0#) `uncheckedIShiftL#` 12#) +#
67 ((ch1 -# 0x80#) `uncheckedIShiftL#` 6#) +#
71 | ch0 >=# 0xF0# && ch0 <=# 0xF8# ->
72 let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
73 if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
74 let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
75 if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
76 let ch3 = word2Int# (indexWord8OffAddr# a# 3#) in
77 if ch3 <# 0x80# || ch3 >=# 0xC0# then fail 3# else
78 (# chr# (((ch0 -# 0xF0#) `uncheckedIShiftL#` 18#) +#
79 ((ch1 -# 0x80#) `uncheckedIShiftL#` 12#) +#
80 ((ch2 -# 0x80#) `uncheckedIShiftL#` 6#) +#
84 | otherwise -> fail 1#
86 -- all invalid sequences end up here:
87 fail n = (# '\0'#, a# `plusAddr#` n #)
88 -- '\xFFFD' would be the usual replacement character, but
89 -- that's a valid symbol in Haskell, so will result in a
90 -- confusing parse error later on. Instead we use '\0' which
91 -- will signal a lexer error immediately.
93 utf8DecodeChar :: Ptr Word8 -> (Char, Ptr Word8)
94 utf8DecodeChar (Ptr a#) =
95 case utf8DecodeChar# a# of (# c#, b# #) -> ( C# c#, Ptr b# )
97 -- UTF-8 is cleverly designed so that we can always figure out where
98 -- the start of the current character is, given any position in a
99 -- stream. This function finds the start of the previous character,
100 -- assuming there *is* a previous character.
101 utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8)
102 utf8PrevChar p = utf8CharStart (p `plusPtr` (-1))
104 utf8CharStart :: Ptr Word8 -> IO (Ptr Word8)
105 utf8CharStart p = go p
106 where go p = do w <- peek p
107 if w >= 0x80 && w < 0xC0
108 then go (p `plusPtr` (-1))
111 utf8DecodeString :: Ptr Word8 -> Int -> IO [Char]
112 STRICT2(utf8DecodeString)
113 utf8DecodeString (Ptr a#) (I# len#)
116 end# = addr2Int# (a# `plusAddr#` len#)
119 | addr2Int# p# >=# end# = return []
121 case utf8DecodeChar# p# of
126 countUTF8Chars :: Ptr Word8 -> Int -> IO Int
127 countUTF8Chars ptr bytes = go ptr 0
129 end = ptr `plusPtr` bytes
133 | ptr >= end = return n
135 case utf8DecodeChar# (unPtr ptr) of
136 (# _, a #) -> go (Ptr a) (n+1)
138 unPtr :: Ptr a -> Addr#
141 utf8EncodeChar :: Char -> Ptr Word8 -> IO (Ptr Word8)
142 utf8EncodeChar c ptr =
145 _ | x > 0 && x <= 0x007f -> do
146 poke ptr (fromIntegral x)
147 return (ptr `plusPtr` 1)
148 -- NB. '\0' is encoded as '\xC0\x80', not '\0'. This is so that we
149 -- can have 0-terminated UTF-8 strings (see GHC.Base.unpackCStringUtf8).
151 poke ptr (fromIntegral (0xC0 .|. ((x `shiftR` 6) .&. 0x1F)))
152 pokeElemOff ptr 1 (fromIntegral (0x80 .|. (x .&. 0x3F)))
153 return (ptr `plusPtr` 2)
155 poke ptr (fromIntegral (0xE0 .|. (x `shiftR` 12) .&. 0x0F))
156 pokeElemOff ptr 1 (fromIntegral (0x80 .|. (x `shiftR` 6) .&. 0x3F))
157 pokeElemOff ptr 2 (fromIntegral (0x80 .|. (x .&. 0x3F)))
158 return (ptr `plusPtr` 3)
160 poke ptr (fromIntegral (0xF0 .|. (x `shiftR` 18)))
161 pokeElemOff ptr 1 (fromIntegral (0x80 .|. ((x `shiftR` 12) .&. 0x3F)))
162 pokeElemOff ptr 2 (fromIntegral (0x80 .|. ((x `shiftR` 6) .&. 0x3F)))
163 pokeElemOff ptr 3 (fromIntegral (0x80 .|. (x .&. 0x3F)))
164 return (ptr `plusPtr` 4)
166 utf8EncodeString :: Ptr Word8 -> String -> IO ()
167 utf8EncodeString ptr str = go ptr str
171 ptr' <- utf8EncodeChar c ptr
174 utf8EncodedLength :: String -> Int
175 utf8EncodedLength str = go 0 str
179 | ord c > 0 && ord c <= 0x007f = go (n+1) cs
180 | ord c <= 0x07ff = go (n+2) cs
181 | ord c <= 0xffff = go (n+3) cs
182 | otherwise = go (n+4) cs
184 -- -----------------------------------------------------------------------------
188 This is the main name-encoding and decoding function. It encodes any
189 string into a string that is acceptable as a C name. This is done
190 right before we emit a symbol name into the compiled C or asm code.
191 Z-encoding of strings is cached in the FastString interface, so we
192 never encode the same string more than once.
194 The basic encoding scheme is this.
196 * Tuples (,,,) are coded as Z3T
198 * Alphabetic characters (upper and lower) and digits
199 all translate to themselves;
200 except 'Z', which translates to 'ZZ'
201 and 'z', which translates to 'zz'
202 We need both so that we can preserve the variable/tycon distinction
204 * Most other printable characters translate to 'zx' or 'Zx' for some
205 alphabetic character x
207 * The others translate as 'znnnU' where 'nnn' is the decimal number
211 --------------------------
223 (# #) Z1H unboxed 1-tuple (note the space)
224 (#,,,,#) Z5H unboxed 5-tuple
225 (NB: There is no Z1T nor Z0H.)
228 type UserString = String -- As the user typed it
229 type EncodedString = String -- Encoded form
232 zEncodeString :: UserString -> EncodedString
233 zEncodeString cs = case maybe_tuple cs of
234 Just n -> n -- Tuples go to Z2T etc
238 go (c:cs) = encode_ch c ++ go cs
240 unencodedChar :: Char -> Bool -- True for chars that don't need encoding
241 unencodedChar 'Z' = False
242 unencodedChar 'z' = False
243 unencodedChar c = c >= 'a' && c <= 'z'
244 || c >= 'A' && c <= 'Z'
245 || c >= '0' && c <= '9'
247 encode_ch :: Char -> EncodedString
248 encode_ch c | unencodedChar c = [c] -- Common case first
251 encode_ch '(' = "ZL" -- Needed for things like (,), and (->)
252 encode_ch ')' = "ZR" -- For symmetry with (
272 encode_ch '\'' = "zq"
273 encode_ch '\\' = "zr"
278 encode_ch c = 'z' : if isDigit (head hex_str) then hex_str
280 where hex_str = showHex (ord c) "U"
281 -- ToDo: we could improve the encoding here in various ways.
282 -- eg. strings of unicode characters come out as 'z1234Uz5678U', we
283 -- could remove the 'U' in the middle (the 'z' works as a separator).
285 showHex = showIntAtBase 16 intToDigit
286 -- needed because prior to GHC 6.2, Numeric.showHex added a "0x" prefix
288 zDecodeString :: EncodedString -> UserString
289 zDecodeString [] = []
290 zDecodeString ('Z' : d : rest)
291 | isDigit d = decode_tuple d rest
292 | otherwise = decode_upper d : zDecodeString rest
293 zDecodeString ('z' : d : rest)
294 | isDigit d = decode_num_esc d rest
295 | otherwise = decode_lower d : zDecodeString rest
296 zDecodeString (c : rest) = c : zDecodeString rest
298 decode_upper, decode_lower :: Char -> Char
300 decode_upper 'L' = '('
301 decode_upper 'R' = ')'
302 decode_upper 'M' = '['
303 decode_upper 'N' = ']'
304 decode_upper 'C' = ':'
305 decode_upper 'Z' = 'Z'
306 decode_upper ch = {-pprTrace "decode_upper" (char ch)-} ch
308 decode_lower 'z' = 'z'
309 decode_lower 'a' = '&'
310 decode_lower 'b' = '|'
311 decode_lower 'c' = '^'
312 decode_lower 'd' = '$'
313 decode_lower 'e' = '='
314 decode_lower 'g' = '>'
315 decode_lower 'h' = '#'
316 decode_lower 'i' = '.'
317 decode_lower 'l' = '<'
318 decode_lower 'm' = '-'
319 decode_lower 'n' = '!'
320 decode_lower 'p' = '+'
321 decode_lower 'q' = '\''
322 decode_lower 'r' = '\\'
323 decode_lower 's' = '/'
324 decode_lower 't' = '*'
325 decode_lower 'u' = '_'
326 decode_lower 'v' = '%'
327 decode_lower ch = {-pprTrace "decode_lower" (char ch)-} ch
329 -- Characters not having a specific code are coded as z224U (in hex)
330 decode_num_esc :: Char -> EncodedString -> UserString
331 decode_num_esc d rest
332 = go (digitToInt d) rest
334 go n (c : rest) | isHexDigit c = go (16*n + digitToInt c) rest
335 go n ('U' : rest) = chr n : zDecodeString rest
336 go n other = error ("decode_num_esc: " ++ show n ++ ' ':other)
338 decode_tuple :: Char -> EncodedString -> UserString
340 = go (digitToInt d) rest
342 -- NB. recurse back to zDecodeString after decoding the tuple, because
343 -- the tuple might be embedded in a longer name.
344 go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
345 go 0 ('T':rest) = "()" ++ zDecodeString rest
346 go n ('T':rest) = '(' : replicate (n-1) ',' ++ ")" ++ zDecodeString rest
347 go 1 ('H':rest) = "(# #)" ++ zDecodeString rest
348 go n ('H':rest) = '(' : '#' : replicate (n-1) ',' ++ "#)" ++ zDecodeString rest
349 go n other = error ("decode_tuple: " ++ show n ++ ' ':other)
352 Tuples are encoded as
354 for 3-tuples or unboxed 3-tuples respectively. No other encoding starts
357 * "(# #)" is the tycon for an unboxed 1-tuple (not 0-tuple)
358 There are no unboxed 0-tuples.
360 * "()" is the tycon for a boxed 0-tuple.
361 There are no boxed 1-tuples.
364 maybe_tuple :: UserString -> Maybe EncodedString
366 maybe_tuple "(# #)" = Just("Z1H")
367 maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
368 (n, '#' : ')' : _) -> Just ('Z' : shows (n+1) "H")
370 maybe_tuple "()" = Just("Z0T")
371 maybe_tuple ('(' : cs) = case count_commas (0::Int) cs of
372 (n, ')' : _) -> Just ('Z' : shows (n+1) "T")
374 maybe_tuple _ = Nothing
376 count_commas :: Int -> String -> (Int, String)
377 count_commas n (',' : cs) = count_commas (n+1) cs
378 count_commas n cs = (n,cs)