[project @ 2006-01-06 16:30:17 by simonmar]
[ghc-hetmet.git] / ghc / compiler / utils / Encoding.hs
1 {-# OPTIONS_GHC -O #-}
2 -- -----------------------------------------------------------------------------
3 --
4 -- (c) The University of Glasgow, 1997-2003
5 --
6 -- Character encodings 
7 --
8 -- -----------------------------------------------------------------------------
9
10 module Encoding ( 
11         -- * UTF-8
12         utf8DecodeChar#,
13         utf8PrevChar,
14         utf8CharStart,
15         utf8DecodeChar,
16         utf8DecodeString,
17         utf8EncodeChar,
18         utf8EncodeString,
19         utf8EncodedLength,
20         countUTF8Chars,
21
22         -- * Latin-1
23         latin1DecodeChar,
24         latin1EncodeChar,
25
26         -- * Z-encoding
27         zEncodeString,
28         zDecodeString
29   ) where
30
31 #define COMPILING_FAST_STRING
32 #include "HsVersions.h"
33 import Foreign
34 import Data.Char        ( ord, chr, isDigit, digitToInt, isHexDigit )
35 import Numeric          ( showHex )
36
37 import GHC.Ptr          ( Ptr(..) )
38 import GHC.Base
39
40 -- -----------------------------------------------------------------------------
41 -- Latin-1
42
43 latin1DecodeChar ptr = do
44   w <- peek ptr
45   return (unsafeChr (fromIntegral w), ptr `plusPtr` 1)
46
47 latin1EncodeChar c ptr = do
48   poke ptr (fromIntegral (ord c))
49   return (ptr `plusPtr` 1)
50
51 -- -----------------------------------------------------------------------------
52 -- UTF-8
53
54 -- We can't write the decoder as efficiently as we'd like without
55 -- resorting to unboxed extensions, unfortunately.  I tried to write
56 -- an IO version of this function, but GHC can't eliminate boxed
57 -- results from an IO-returning function.
58 --
59 -- We assume we can ignore overflow when parsing a multibyte character here.
60 -- To make this safe, we add extra sentinel bytes to unparsed UTF-8 sequences
61 -- before decoding them (see StringBuffer.hs).
62
63 {-# INLINE utf8DecodeChar# #-}
64 utf8DecodeChar# :: Addr# -> (# Char#, Addr# #)
65 utf8DecodeChar# a# =
66   let ch0 = word2Int# (indexWord8OffAddr# a# 0#) in
67   case () of 
68     _ | ch0 <=# 0x7F# -> (# chr# ch0, a# `plusAddr#` 1# #)
69
70       | ch0 >=# 0xC0# && ch0 <=# 0xDF# ->
71         let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
72         if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
73         (# chr# (((ch0 -# 0xC0#) `uncheckedIShiftL#` 6#) +#
74                   (ch1 -# 0x80#)),
75            a# `plusAddr#` 2# #)
76
77       | ch0 >=# 0xE0# && ch0 <=# 0xEF# ->
78         let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
79         if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
80         let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
81         if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
82         (# chr# (((ch0 -# 0xE0#) `uncheckedIShiftL#` 12#) +#
83                  ((ch1 -# 0x80#) `uncheckedIShiftL#` 6#)  +#
84                   (ch2 -# 0x80#)),
85            a# `plusAddr#` 3# #)
86
87      | ch0 >=# 0xF0# && ch0 <=# 0xF8# ->
88         let ch1 = word2Int# (indexWord8OffAddr# a# 1#) in
89         if ch1 <# 0x80# || ch1 >=# 0xC0# then fail 1# else
90         let ch2 = word2Int# (indexWord8OffAddr# a# 2#) in
91         if ch2 <# 0x80# || ch2 >=# 0xC0# then fail 2# else
92         let ch3 = word2Int# (indexWord8OffAddr# a# 3#) in
93         if ch3 <# 0x80# || ch3 >=# 0xC0# then fail 3# else
94         (# chr# (((ch0 -# 0xF0#) `uncheckedIShiftL#` 18#) +#
95                  ((ch1 -# 0x80#) `uncheckedIShiftL#` 12#) +#
96                  ((ch2 -# 0x80#) `uncheckedIShiftL#` 6#)  +#
97                   (ch3 -# 0x80#)),
98            a# `plusAddr#` 4# #)
99
100       | otherwise -> fail 1#
101   where
102         -- all invalid sequences end up here:
103         fail n = (# '\0'#, a# `plusAddr#` n #)
104         -- '\xFFFD' would be the usual replacement character, but
105         -- that's a valid symbol in Haskell, so will result in a
106         -- confusing parse error later on.  Instead we use '\0' which
107         -- will signal a lexer error immediately.
108
109 utf8DecodeChar :: Ptr Word8 -> (Char, Ptr Word8)
110 utf8DecodeChar (Ptr a#) = ( C# c#, Ptr b# )
111   where (# c#, b# #) = utf8DecodeChar# a#
112
113 -- UTF-8 is cleverly designed so that we can always figure out where
114 -- the start of the current character is, given any position in a
115 -- stream.  This function finds the start of the previous character,
116 -- assuming there *is* a previous character.
117 utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8)
118 utf8PrevChar p = utf8CharStart (p `plusPtr` (-1))
119
120 utf8CharStart :: Ptr Word8 -> IO (Ptr Word8)
121 utf8CharStart p = go p
122  where go p = do w <- peek p
123                  if (w .&. 0xC0) == 0x80
124                         then go (p `plusPtr` (-1))
125                         else return p
126
127 utf8DecodeString :: Ptr Word8 -> Int -> IO [Char]
128 STRICT2(utf8DecodeString)
129 utf8DecodeString (Ptr a#) (I# len#)
130   = unpack a#
131   where
132     end# = addr2Int# (a# `plusAddr#` len#)
133
134     unpack p#
135         | addr2Int# p# >=# end# = return []
136         | otherwise  =
137         case utf8DecodeChar# p# of
138            (# c#, q# #) -> do
139                 chs <- unpack q#
140                 return (C# c# : chs)
141
142 countUTF8Chars :: Ptr Word8 -> Int -> IO Int
143 countUTF8Chars ptr bytes = go ptr 0
144   where
145         end = ptr `plusPtr` bytes
146
147         STRICT2(go)
148         go ptr n 
149            | ptr >= end = return n
150            | otherwise  = do
151                 case utf8DecodeChar# (unPtr ptr) of
152                   (# c, a #) -> go (Ptr a) (n+1)
153
154 unPtr (Ptr a) = a
155
156 utf8EncodeChar c ptr =
157   let x = ord c in
158   case () of
159     _ | x > 0 && x <= 0x007f -> do
160           poke ptr (fromIntegral x)
161           return (ptr `plusPtr` 1)
162         -- NB. '\0' is encoded as '\xC0\x80', not '\0'.  This is so that we
163         -- can have 0-terminated UTF-8 strings (see GHC.Base.unpackCStringUtf8).
164       | x <= 0x07ff -> do
165           poke ptr (fromIntegral (0xC0 .|. ((x `shiftR` 6) .&. 0x1F)))
166           pokeElemOff ptr 1 (fromIntegral (0x80 .|. (x .&. 0x3F)))
167           return (ptr `plusPtr` 2)
168       | x <= 0xffff -> do
169           poke ptr (fromIntegral (0xE0 .|. (x `shiftR` 12) .&. 0x0F))
170           pokeElemOff ptr 1 (fromIntegral (0x80 .|. (x `shiftR` 6) .&. 0x3F))
171           pokeElemOff ptr 2 (fromIntegral (0x80 .|. (x .&. 0x3F)))
172           return (ptr `plusPtr` 3)
173       | otherwise -> do
174           poke ptr (fromIntegral (0xF0 .|. (x `shiftR` 18)))
175           pokeElemOff ptr 1 (fromIntegral (0x80 .|. ((x `shiftR` 12) .&. 0x3F)))
176           pokeElemOff ptr 2 (fromIntegral (0x80 .|. ((x `shiftR` 6) .&. 0x3F)))
177           pokeElemOff ptr 3 (fromIntegral (0x80 .|. (x .&. 0x3F)))
178           return (ptr `plusPtr` 4)
179
180 utf8EncodeString :: Ptr Word8 -> String -> IO ()
181 utf8EncodeString ptr str = go ptr str
182   where STRICT2(go)
183         go ptr [] = return ()
184         go ptr (c:cs) = do
185           ptr' <- utf8EncodeChar c ptr
186           go ptr' cs
187
188 utf8EncodedLength :: String -> Int
189 utf8EncodedLength str = go 0 str
190   where STRICT2(go)
191         go n [] = n
192         go n (c:cs)
193           | ord c > 0 && ord c <= 0x007f = go (n+1) cs
194           | ord c <= 0x07ff = go (n+2) cs
195           | ord c <= 0xffff = go (n+3) cs       
196           | otherwise       = go (n+4) cs       
197
198 -- -----------------------------------------------------------------------------
199 -- The Z-encoding
200
201 {-
202 This is the main name-encoding and decoding function.  It encodes any
203 string into a string that is acceptable as a C name.  This is the name
204 by which things are known right through the compiler.
205
206 The basic encoding scheme is this.  
207
208 * Tuples (,,,) are coded as Z3T
209
210 * Alphabetic characters (upper and lower) and digits
211         all translate to themselves; 
212         except 'Z', which translates to 'ZZ'
213         and    'z', which translates to 'zz'
214   We need both so that we can preserve the variable/tycon distinction
215
216 * Most other printable characters translate to 'zx' or 'Zx' for some
217         alphabetic character x
218
219 * The others translate as 'znnnU' where 'nnn' is the decimal number
220         of the character
221
222         Before          After
223         --------------------------
224         Trak            Trak
225         foo_wib         foozuwib
226         >               zg
227         >1              zg1
228         foo#            foozh
229         foo##           foozhzh
230         foo##1          foozhzh1
231         fooZ            fooZZ   
232         :+              ZCzp
233         ()              Z0T     0-tuple
234         (,,,,)          Z5T     5-tuple  
235         (# #)           Z1H     unboxed 1-tuple (note the space)
236         (#,,,,#)        Z5H     unboxed 5-tuple
237                 (NB: There is no Z1T nor Z0H.)
238 -}
239
240 type UserString = String        -- As the user typed it
241 type EncodedString = String     -- Encoded form
242
243
244 zEncodeString :: UserString -> EncodedString
245 zEncodeString cs = case maybe_tuple cs of
246                 Just n  -> n            -- Tuples go to Z2T etc
247                 Nothing -> go cs
248           where
249                 go []     = []
250                 go (c:cs) = encode_ch c ++ go cs
251
252 unencodedChar :: Char -> Bool   -- True for chars that don't need encoding
253 unencodedChar 'Z' = False
254 unencodedChar 'z' = False
255 unencodedChar c   =  c >= 'a' && c <= 'z'
256                   || c >= 'A' && c <= 'Z'
257                   || c >= '0' && c <= '9'
258
259 encode_ch :: Char -> EncodedString
260 encode_ch c | unencodedChar c = [c]     -- Common case first
261
262 -- Constructors
263 encode_ch '('  = "ZL"   -- Needed for things like (,), and (->)
264 encode_ch ')'  = "ZR"   -- For symmetry with (
265 encode_ch '['  = "ZM"
266 encode_ch ']'  = "ZN"
267 encode_ch ':'  = "ZC"
268 encode_ch 'Z'  = "ZZ"
269
270 -- Variables
271 encode_ch 'z'  = "zz"
272 encode_ch '&'  = "za"
273 encode_ch '|'  = "zb"
274 encode_ch '^'  = "zc"
275 encode_ch '$'  = "zd"
276 encode_ch '='  = "ze"
277 encode_ch '>'  = "zg"
278 encode_ch '#'  = "zh"
279 encode_ch '.'  = "zi"
280 encode_ch '<'  = "zl"
281 encode_ch '-'  = "zm"
282 encode_ch '!'  = "zn"
283 encode_ch '+'  = "zp"
284 encode_ch '\'' = "zq"
285 encode_ch '\\' = "zr"
286 encode_ch '/'  = "zs"
287 encode_ch '*'  = "zt"
288 encode_ch '_'  = "zu"
289 encode_ch '%'  = "zv"
290 encode_ch c    = 'z' : if isDigit (head hex_str) then hex_str
291                                                  else '0':hex_str
292   where hex_str = showHex (ord c) "U"
293   -- ToDo: we could improve the encoding here in various ways.
294   -- eg. strings of unicode characters come out as 'z1234Uz5678U', we
295   -- could remove the 'U' in the middle (the 'z' works as a separator).
296
297 zDecodeString :: EncodedString -> UserString
298 zDecodeString [] = []
299 zDecodeString ('Z' : d : rest) 
300   | isDigit d = decode_tuple   d rest
301   | otherwise = decode_upper   d : zDecodeString rest
302 zDecodeString ('z' : d : rest)
303   | isDigit d = decode_num_esc d rest
304   | otherwise = decode_lower   d : zDecodeString rest
305 zDecodeString (c   : rest) = c : zDecodeString rest
306
307 decode_upper, decode_lower :: Char -> Char
308
309 decode_upper 'L' = '('
310 decode_upper 'R' = ')'
311 decode_upper 'M' = '['
312 decode_upper 'N' = ']'
313 decode_upper 'C' = ':'
314 decode_upper 'Z' = 'Z'
315 decode_upper ch  = {-pprTrace "decode_upper" (char ch)-} ch
316                 
317 decode_lower 'z' = 'z'
318 decode_lower 'a' = '&'
319 decode_lower 'b' = '|'
320 decode_lower 'c' = '^'
321 decode_lower 'd' = '$'
322 decode_lower 'e' = '='
323 decode_lower 'g' = '>'
324 decode_lower 'h' = '#'
325 decode_lower 'i' = '.'
326 decode_lower 'l' = '<'
327 decode_lower 'm' = '-'
328 decode_lower 'n' = '!'
329 decode_lower 'p' = '+'
330 decode_lower 'q' = '\''
331 decode_lower 'r' = '\\'
332 decode_lower 's' = '/'
333 decode_lower 't' = '*'
334 decode_lower 'u' = '_'
335 decode_lower 'v' = '%'
336 decode_lower ch  = {-pprTrace "decode_lower" (char ch)-} ch
337
338 -- Characters not having a specific code are coded as z224U (in hex)
339 decode_num_esc d rest
340   = go (digitToInt d) rest
341   where
342     go n (c : rest) | isHexDigit c = go (16*n + digitToInt c) rest
343     go n ('U' : rest)           = chr n : zDecodeString rest
344     go n other = error ("decode_num_esc: " ++ show n ++  ' ':other)
345
346 decode_tuple :: Char -> EncodedString -> UserString
347 decode_tuple d rest
348   = go (digitToInt d) rest
349   where
350         -- NB. recurse back to zDecodeString after decoding the tuple, because
351         -- the tuple might be embedded in a longer name.
352     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
353     go 0 ('T':rest)     = "()" ++ zDecodeString rest
354     go n ('T':rest)     = '(' : replicate (n-1) ',' ++ ")" ++ zDecodeString rest
355     go 1 ('H':rest)     = "(# #)" ++ zDecodeString rest
356     go n ('H':rest)     = '(' : '#' : replicate (n-1) ',' ++ "#)" ++ zDecodeString rest
357     go n other = error ("decode_tuple: " ++ show n ++ ' ':other)
358
359 {-
360 Tuples are encoded as
361         Z3T or Z3H
362 for 3-tuples or unboxed 3-tuples respectively.  No other encoding starts 
363         Z<digit>
364
365 * "(# #)" is the tycon for an unboxed 1-tuple (not 0-tuple)
366   There are no unboxed 0-tuples.  
367
368 * "()" is the tycon for a boxed 0-tuple.
369   There are no boxed 1-tuples.
370 -}
371
372 maybe_tuple :: UserString -> Maybe EncodedString
373
374 maybe_tuple "(# #)" = Just("Z1H")
375 maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
376                                  (n, '#' : ')' : cs) -> Just ('Z' : shows (n+1) "H")
377                                  other               -> Nothing
378 maybe_tuple "()" = Just("Z0T")
379 maybe_tuple ('(' : cs)       = case count_commas (0::Int) cs of
380                                  (n, ')' : cs) -> Just ('Z' : shows (n+1) "T")
381                                  other         -> Nothing
382 maybe_tuple other            = Nothing
383
384 count_commas :: Int -> String -> (Int, String)
385 count_commas n (',' : cs) = count_commas (n+1) cs
386 count_commas n cs         = (n,cs)