Remove Distribution.Compat.Char from compat again
[ghc-hetmet.git] / utils / ext-core / Language / Core / Encoding.hs
1 {-# OPTIONS -fno-warn-name-shadowing #-}
2
3 module Language.Core.Encoding where
4
5 import Data.Char
6 import Numeric
7
8 -- tjc: TODO: Copied straight out of Encoding.hs.
9 -- Ugh, maybe we can avoid this copy-pasta...
10
11 -- -----------------------------------------------------------------------------
12 -- The Z-encoding
13
14 {-
15 This is the main name-encoding and decoding function.  It encodes any
16 string into a string that is acceptable as a C name.  This is done
17 right before we emit a symbol name into the compiled C or asm code.
18 Z-encoding of strings is cached in the FastString interface, so we
19 never encode the same string more than once.
20
21 The basic encoding scheme is this.  
22
23 * Tuples (,,,) are coded as Z3T
24
25 * Alphabetic characters (upper and lower) and digits
26         all translate to themselves; 
27         except 'Z', which translates to 'ZZ'
28         and    'z', which translates to 'zz'
29   We need both so that we can preserve the variable/tycon distinction
30
31 * Most other printable characters translate to 'zx' or 'Zx' for some
32         alphabetic character x
33
34 * The others translate as 'znnnU' where 'nnn' is the decimal number
35         of the character
36
37         Before          After
38         --------------------------
39         Trak            Trak
40         foo_wib         foozuwib
41         >               zg
42         >1              zg1
43         foo#            foozh
44         foo##           foozhzh
45         foo##1          foozhzh1
46         fooZ            fooZZ   
47         :+              ZCzp
48         ()              Z0T     0-tuple
49         (,,,,)          Z5T     5-tuple  
50         (# #)           Z1H     unboxed 1-tuple (note the space)
51         (#,,,,#)        Z5H     unboxed 5-tuple
52                 (NB: There is no Z1T nor Z0H.)
53 -}
54
55 type UserString = String        -- As the user typed it
56 type EncodedString = String     -- Encoded form
57
58
59 zEncodeString :: UserString -> EncodedString
60 zEncodeString cs = case maybe_tuple cs of
61                 Just n  -> n            -- Tuples go to Z2T etc
62                 Nothing -> go cs
63           where
64                 go []     = []
65                 go (c:cs) = encode_ch c ++ go cs
66
67 unencodedChar :: Char -> Bool   -- True for chars that don't need encoding
68 unencodedChar 'Z' = False
69 unencodedChar 'z' = False
70 unencodedChar c   =  c >= 'a' && c <= 'z'
71                   || c >= 'A' && c <= 'Z'
72                   || c >= '0' && c <= '9'
73
74 encode_ch :: Char -> EncodedString
75 encode_ch c | unencodedChar c = [c]     -- Common case first
76
77 -- Constructors
78 encode_ch '('  = "ZL"   -- Needed for things like (,), and (->)
79 encode_ch ')'  = "ZR"   -- For symmetry with (
80 encode_ch '['  = "ZM"
81 encode_ch ']'  = "ZN"
82 encode_ch ':'  = "ZC"
83 encode_ch 'Z'  = "ZZ"
84
85 -- Variables
86 encode_ch 'z'  = "zz"
87 encode_ch '&'  = "za"
88 encode_ch '|'  = "zb"
89 encode_ch '^'  = "zc"
90 encode_ch '$'  = "zd"
91 encode_ch '='  = "ze"
92 encode_ch '>'  = "zg"
93 encode_ch '#'  = "zh"
94 encode_ch '.'  = "zi"
95 encode_ch '<'  = "zl"
96 encode_ch '-'  = "zm"
97 encode_ch '!'  = "zn"
98 encode_ch '+'  = "zp"
99 encode_ch '\'' = "zq"
100 encode_ch '\\' = "zr"
101 encode_ch '/'  = "zs"
102 encode_ch '*'  = "zt"
103 encode_ch '_'  = "zu"
104 encode_ch '%'  = "zv"
105 encode_ch c    = 'z' : if isDigit (head hex_str) then hex_str
106                                                  else '0':hex_str
107   where hex_str = showHex (ord c) "U"
108   -- ToDo: we could improve the encoding here in various ways.
109   -- eg. strings of unicode characters come out as 'z1234Uz5678U', we
110   -- could remove the 'U' in the middle (the 'z' works as a separator).
111
112         showHex = showIntAtBase 16 intToDigit
113         -- needed because prior to GHC 6.2, Numeric.showHex added a "0x" prefix
114
115 zDecodeString :: EncodedString -> UserString
116 zDecodeString [] = []
117 zDecodeString ('Z' : d : rest) 
118   | isDigit d = decode_tuple   d rest
119   | otherwise = decode_upper   d : zDecodeString rest
120 zDecodeString ('z' : d : rest)
121   | isDigit d = decode_num_esc d rest
122   | otherwise = decode_lower   d : zDecodeString rest
123 zDecodeString (c   : rest) = c : zDecodeString rest
124
125 decode_upper, decode_lower :: Char -> Char
126
127 decode_upper 'L' = '('
128 decode_upper 'R' = ')'
129 decode_upper 'M' = '['
130 decode_upper 'N' = ']'
131 decode_upper 'C' = ':'
132 decode_upper 'Z' = 'Z'
133 decode_upper ch  = {-pprTrace "decode_upper" (char ch)-} ch
134                 
135 decode_lower 'z' = 'z'
136 decode_lower 'a' = '&'
137 decode_lower 'b' = '|'
138 decode_lower 'c' = '^'
139 decode_lower 'd' = '$'
140 decode_lower 'e' = '='
141 decode_lower 'g' = '>'
142 decode_lower 'h' = '#'
143 decode_lower 'i' = '.'
144 decode_lower 'l' = '<'
145 decode_lower 'm' = '-'
146 decode_lower 'n' = '!'
147 decode_lower 'p' = '+'
148 decode_lower 'q' = '\''
149 decode_lower 'r' = '\\'
150 decode_lower 's' = '/'
151 decode_lower 't' = '*'
152 decode_lower 'u' = '_'
153 decode_lower 'v' = '%'
154 decode_lower ch  = {-pprTrace "decode_lower" (char ch)-} ch
155
156 -- Characters not having a specific code are coded as z224U (in hex)
157 decode_num_esc :: Char -> EncodedString -> UserString
158 decode_num_esc d rest
159   = go (digitToInt d) rest
160   where
161     go n (c : rest) | isHexDigit c = go (16*n + digitToInt c) rest
162     go n ('U' : rest)           = chr n : zDecodeString rest
163     go n other = error ("decode_num_esc: " ++ show n ++  ' ':other)
164
165 decode_tuple :: Char -> EncodedString -> UserString
166 decode_tuple d rest
167   = go (digitToInt d) rest
168   where
169         -- NB. recurse back to zDecodeString after decoding the tuple, because
170         -- the tuple might be embedded in a longer name.
171     go n (c : rest) | isDigit c = go (10*n + digitToInt c) rest
172     go 0 ('T':rest)     = "()" ++ zDecodeString rest
173     go n ('T':rest)     = '(' : replicate (n-1) ',' ++ ")" ++ zDecodeString rest
174     go 1 ('H':rest)     = "(# #)" ++ zDecodeString rest
175     go n ('H':rest)     = '(' : '#' : replicate (n-1) ',' ++ "#)" ++ zDecodeString rest
176     go n other = error ("decode_tuple: " ++ show n ++ ' ':other)
177
178 {-
179 Tuples are encoded as
180         Z3T or Z3H
181 for 3-tuples or unboxed 3-tuples respectively.  No other encoding starts 
182         Z<digit>
183
184 * "(# #)" is the tycon for an unboxed 1-tuple (not 0-tuple)
185   There are no unboxed 0-tuples.  
186
187 * "()" is the tycon for a boxed 0-tuple.
188   There are no boxed 1-tuples.
189 -}
190
191 maybe_tuple :: UserString -> Maybe EncodedString
192
193 maybe_tuple "(# #)" = Just("Z1H")
194 maybe_tuple ('(' : '#' : cs) = case count_commas (0::Int) cs of
195                                  (n, '#' : ')' : _) -> Just ('Z' : shows (n+1) "H")
196                                  _                  -> Nothing
197 maybe_tuple "()" = Just("Z0T")
198 maybe_tuple ('(' : cs)       = case count_commas (0::Int) cs of
199                                  (n, ')' : _) -> Just ('Z' : shows (n+1) "T")
200                                  _            -> Nothing
201 maybe_tuple _                = Nothing
202
203 count_commas :: Int -> String -> (Int, String)
204 count_commas n (',' : cs) = count_commas (n+1) cs
205 count_commas n cs         = (n,cs)
206