[project @ 1997-06-09 07:25:54 by sof]
[ghc-hetmet.git] / ghc / compiler / utils / StringBuffer.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1997
3 %
4 \section{String buffers}
5
6 Buffers for scanning string input stored in external arrays.
7
8 \begin{code}
9 #include "HsVersions.h"
10
11 module StringBuffer
12        (
13         StringBuffer,
14
15          -- creation
16         hGetStringBuffer,  -- :: FilePath       -> IO StringBuffer
17         freeStringBuffer,  -- :: StringBuffer   -> IO ()
18
19          -- Lookup
20         currentChar,      -- :: StringBuffer -> Char
21         currentChar#,     -- :: StringBuffer -> Char#
22         indexSBuffer,     -- :: StringBuffer -> Int -> Char
23         indexSBuffer#,    -- :: StringBuffer -> Int# -> Char#
24          -- relative lookup, i.e, currentChar = lookAhead 0
25         lookAhead,        -- :: StringBuffer -> Int  -> Char
26         lookAhead#,       -- :: StringBuffer -> Int# -> Char#
27         
28          -- moving the end point of the current lexeme.
29         setCurrentPos#,   -- :: StringBuffer -> Int# -> StringBuffer
30         incLexeme,        -- :: StringBuffer -> StringBuffer
31         decLexeme,        -- :: StringBuffer -> StringBuffer
32
33          -- move the start and end lexeme pointer on by x units.        
34         stepOn,           -- :: StringBuffer -> StringBuffer
35         stepOnBy#,        -- :: StringBuffer -> Int# -> StringBuffer
36         stepOnTo#,        -- :: StringBuffer -> Int# -> StringBuffer
37         stepOnUntil,      -- :: (Char -> Bool) -> StringBuffer -> StringBuffer
38         stepOverLexeme,   -- :: StringBuffer   -> StringBuffer
39         scanNumLit,       -- :: Int -> StringBuffer -> (Int, StringBuffer)
40         expandWhile,      -- :: (Char -> Bool) -> StringBuffer -> StringBuffer
41         expandUntilMatch, -- :: StrinBuffer -> String -> StringBuffer
42          -- at or beyond end of buffer?
43         bufferExhausted,  -- :: StringBuffer -> Bool
44         emptyLexeme,      -- :: StringBuffer -> Bool
45
46          -- matching
47         prefixMatch,       -- :: StringBuffer -> String -> Bool
48         untilEndOfString#, -- :: StringBuffer -> Int#
49         untilEndOfChar#,   -- :: StringBuffer -> Int#
50         untilChar#,        -- :: StringBuffer -> Char# -> Int#
51
52          -- conversion
53         lexemeToString,     -- :: StringBuffer -> String
54         lexemeToByteArray,  -- :: StringBuffer -> _ByteArray Int
55         lexemeToFastString, -- :: StringBuffer -> FastString
56         lexemeToBuffer,     -- :: StringBuffer -> StringBuffer
57
58         FastString,
59         _ByteArray
60        ) where
61
62 #if __GLASGOW_HASKELL__ <= 200
63 import PreludeGlaST
64 import PreludeGlaMisc
65 import HandleHack
66 import Ubiq
67 #else
68 import GlaExts
69 import Foreign
70 import IOBase
71 import IOHandle
72 import ST
73 import STBase
74 import Char (isDigit)
75 # if __GLASGOW_HASKELL__ == 202
76 import PrelBase ( Char(..) )
77 # endif
78 #endif
79 import PrimPacked
80 import FastString
81
82 \end{code} 
83
84 \begin{code}
85 data StringBuffer
86  = StringBuffer
87      Addr#
88 --     ForeignObj#  -- the data
89      Int#         -- length
90      Int#         -- lexeme start
91      Int#         -- current pos
92 \end{code}
93
94 \begin{code}
95
96 hGetStringBuffer :: FilePath -> IO StringBuffer
97 hGetStringBuffer fname =
98 --    trace ("Renamer: opening " ++ fname) $
99     openFile fname ReadMode >>= \ hndl ->
100     hFileSize hndl          >>= \ len@(J# _ _ d#) ->
101     let len_i = fromInteger len in
102       -- Allocate an array for system call to store its bytes into.
103       -- ToDo: make it robust
104 --    trace (show ((len_i::Int)+1)) $
105     (_casm_ `` %r=(char *)malloc(sizeof(char)*(int)%0); '' (len_i::Int))  `CCALL_THEN` \ arr@(A# a#) ->
106     if addr2Int# a# ==# 0# then
107        failWith MkIOError(hndl,UserError,("hGetStringBuffer: Could not allocate "++show len_i ++ " bytes"))
108     else
109
110 --   _casm_ `` %r=NULL; ''                                   `thenPrimIO` \ free_p ->
111 --    makeForeignObj arr free_p                              `thenPrimIO` \ fo@(_ForeignObj fo#) ->
112      _readHandle hndl        >>= \ hndl_ ->
113      _writeHandle hndl hndl_ >>
114      let ptr = _filePtr hndl_ in
115      _ccall_ fread arr (1::Int) len_i ptr                     `CCALL_THEN` \  (I# read#) ->
116 --     trace ("DEBUG: opened " ++ fname ++ show (I# read#)) $
117      hClose hndl                     >>
118      if read# ==# 0# then -- EOF or other error
119         failWith MkIOError(hndl,UserError,"hGetStringBuffer: EOF reached or some other error")
120      else
121         -- Add a sentinel NUL
122         _casm_ `` ((char *)%0)[(int)%1]=(char)0; '' arr (I# (read# -# 1#)) `CCALL_THEN` \ () ->
123         return (StringBuffer a# read# 0# 0#)
124
125 freeStringBuffer :: StringBuffer -> IO ()
126 freeStringBuffer (StringBuffer a# _ _ _) =
127  _casm_ `` free((char *)%0); '' (A# a#) `CCALL_THEN` \ () ->
128  return ()
129
130 unsafeWriteBuffer :: StringBuffer -> Int# -> Char# -> StringBuffer
131 unsafeWriteBuffer s@(StringBuffer a _ _ _) i# ch# =
132  unsafePerformPrimIO (
133    _casm_ `` ((char *)%0)[(int)%1]=(char)%2; '' (A# a) (I# i#) (C# ch#) `thenPrimIO` \ () ->
134    returnPrimIO s)
135
136 \end{code}
137
138 Lookup
139
140 \begin{code}
141 currentChar# :: StringBuffer -> Char#
142 currentChar# (StringBuffer fo# _ _ current#) = indexCharOffAddr# fo# current#
143
144 currentChar  :: StringBuffer -> Char
145 currentChar sb = case currentChar# sb of c -> C# c
146
147 indexSBuffer# :: StringBuffer -> Int# -> Char#
148 indexSBuffer# (StringBuffer fo# _ _ _) i# = indexCharOffAddr# fo# i#
149
150 indexSBuffer :: StringBuffer -> Int -> Char
151 indexSBuffer sb (I# i#) = case indexSBuffer# sb i# of c -> C# c
152
153  -- relative lookup, i.e, currentChar = lookAhead 0
154 lookAhead# :: StringBuffer -> Int# -> Char#
155 lookAhead# (StringBuffer fo# _ _ c#) i# = indexCharOffAddr# fo# (c# +# i#)
156
157 lookAhead :: StringBuffer -> Int  -> Char
158 lookAhead sb (I# i#) = case lookAhead# sb i# of c -> C# c
159
160 \end{code}
161
162  moving the start point of the current lexeme.
163
164 \begin{code}
165  -- moving the end point of the current lexeme.
166 setCurrentPos# :: StringBuffer -> Int# -> StringBuffer
167 setCurrentPos# (StringBuffer fo l# s# c#) i# =
168  StringBuffer fo l# s# (c# +# i#)
169
170 -- augmenting the current lexeme by one.
171 incLexeme :: StringBuffer -> StringBuffer
172 incLexeme (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# +# 1#)
173
174 decLexeme :: StringBuffer -> StringBuffer
175 decLexeme (StringBuffer fo l# s# c#) = StringBuffer fo l# s# (c# -# 1#)
176
177 \end{code}
178
179 -- move the start and end point of the buffer on by
180 -- x units.        
181
182 \begin{code}
183 stepOn :: StringBuffer -> StringBuffer
184 stepOn (StringBuffer fo l# s# c#) = StringBuffer fo l# (s# +# 1#) (s# +# 1#) -- assume they're the same.
185
186 stepOnBy# :: StringBuffer -> Int# -> StringBuffer
187 stepOnBy# (StringBuffer fo# l# s# c#) i# = 
188  case s# +# i# of
189   new_s# -> StringBuffer fo# l# new_s# new_s#
190
191 -- jump to pos.
192 stepOnTo# :: StringBuffer -> Int# -> StringBuffer
193 stepOnTo# (StringBuffer fo l _ _) s# = StringBuffer fo l s# s#
194
195 stepOnUntil :: (Char -> Bool) -> StringBuffer -> StringBuffer
196 stepOnUntil pred (StringBuffer fo l# s# c#) =
197  loop c#
198   where
199    loop c# = 
200     case indexCharOffAddr# fo c# of
201      ch# | pred (C# ch#) -> StringBuffer fo l# c# c#
202          | ch# `eqChar#` '\NUL'# && c# >=# l# -> StringBuffer fo l# l# l# -- EOB, return immediately.
203          | otherwise     -> loop (c# +# 1#)
204
205 stepOverLexeme :: StringBuffer -> StringBuffer
206 stepOverLexeme (StringBuffer fo l s# c#) = StringBuffer fo l c# c#
207
208 expandWhile :: (Char -> Bool) -> StringBuffer -> StringBuffer
209 expandWhile pred (StringBuffer fo l# s# c#) =
210  loop c#
211   where
212    loop c# = 
213     case indexCharOffAddr# fo c# of
214      ch# | pred (C# ch#) -> loop (c# +# 1#)
215          | ch# `eqChar#` '\NUL'# && c# >=# l# -> StringBuffer fo l# l# l# -- EOB, return immediately.
216          | otherwise     -> StringBuffer fo l# s# c#
217
218
219 scanNumLit :: Int -> StringBuffer -> (Int,StringBuffer)
220 scanNumLit (I# acc#) (StringBuffer fo l# s# c#) =
221  loop acc# c#
222   where
223    loop acc# c# = 
224     case indexCharOffAddr# fo c# of
225      ch# | isDigit (C# ch#) -> loop (acc# *# 10# +# (ord# ch# -# ord# '0'#)) (c# +# 1#)
226          | ch# `eqChar#` '\NUL'# && c# >=# l# -> (I# acc#, StringBuffer fo l# l# l#) -- EOB, return immediately.
227          | otherwise        -> (I# acc#,StringBuffer fo l# s# c#)
228
229
230 expandUntilMatch :: StringBuffer -> String -> StringBuffer
231 expandUntilMatch (StringBuffer fo l# s# c#) str =
232   loop c# str
233   where
234    loop c# [] = StringBuffer fo l# s# c#
235    loop c# ((C# x#):xs) =
236      if indexCharOffAddr# fo c# `eqChar#` x# then
237         loop (c# +# 1#) xs
238      else
239         loop (c# +# 1#) str
240 \end{code}
241
242 \begin{code}
243    -- at or beyond end of buffer?
244 bufferExhausted :: StringBuffer -> Bool
245 bufferExhausted (StringBuffer fo l# _ c#) = c# >=# l#
246
247 emptyLexeme :: StringBuffer -> Bool
248 emptyLexeme (StringBuffer fo l# s# c#) = s# ==# c#
249
250  -- matching
251 prefixMatch :: StringBuffer -> String -> Maybe StringBuffer
252 prefixMatch (StringBuffer fo l# s# c#) str =
253   loop c# str
254   where
255    loop c# [] = Just (StringBuffer fo l# s# c#)
256    loop c# ((C# x#):xs) =
257      if indexCharOffAddr# fo c# `eqChar#` x# then
258         loop (c# +# 1#) xs
259      else
260         Nothing
261
262 untilEndOfString# :: StringBuffer -> StringBuffer
263 untilEndOfString# (StringBuffer fo l# s# c#) = 
264  loop c# 
265  where
266   loop c# =
267    case indexCharOffAddr# fo c# of
268     '\"'# ->
269        case indexCharOffAddr# fo (c# -# 1#) of
270         '\\'# ->       
271                   -- looks like an escaped something or other to me,
272                   -- better count the number of "\\"s that are immediately
273                   -- preceeding to decide if the " is escaped.
274               let
275                odd_slashes flg i# =
276                 case indexCharOffAddr# fo i# of
277                  '\\'# -> odd_slashes (not flg) (i# -# 1#)
278                  _     -> flg
279               in
280               if odd_slashes True (c# -# 2#) then
281                   -- odd number, " is ecaped.
282                   loop (c# +# 1#)
283               else  -- a real end of string delimiter after all.
284                   StringBuffer fo l# s# c#
285         _ -> StringBuffer fo l# s# c#
286     '\NUL'# ->
287         if c# >=# l# then -- hit sentinel, this doesn't look too good..
288            StringBuffer fo l# l# l#
289         else
290            loop (c# +# 1#)
291     _ -> loop (c# +# 1#)
292
293
294 untilEndOfChar# :: StringBuffer -> StringBuffer
295 untilEndOfChar# (StringBuffer fo l# s# c#) = 
296  loop c# 
297  where
298   loop c# =
299    case indexCharOffAddr# fo c# of
300     '\''# ->
301        case indexCharOffAddr# fo (c# -# 1#) of
302         '\\'# ->
303            case indexCharOffAddr# fo (c# -# 2#) of      
304              '\\'# -> -- end of char
305                    StringBuffer fo l# s# c#
306              _ -> loop (c# +# 1#) -- false alarm
307         _ -> StringBuffer fo l# s# c#
308     '\NUL'# ->
309         if c# >=# l# then -- hit sentinel, this doesn't look too good..
310            StringBuffer fo l# l# l#
311         else
312            loop (c# +# 1#)
313     _ -> loop (c# +# 1#)
314
315 untilChar# :: StringBuffer -> Char# -> StringBuffer
316 untilChar# (StringBuffer fo l# s# c#) x# = 
317  loop c# 
318  where
319   loop c# =
320    if indexCharOffAddr# fo c# `eqChar#` x# then
321       StringBuffer fo l# s# c#
322    else
323       loop (c# +# 1#)
324
325          -- conversion
326 lexemeToString :: StringBuffer -> String
327 lexemeToString (StringBuffer fo _ start_pos# current#) = 
328  if start_pos# ==# current# then
329     ""
330  else
331     byteArrayToString (copySubStr (A# fo) (I# start_pos#) (I# (current# -# start_pos#)))
332
333     
334 lexemeToByteArray :: StringBuffer -> _ByteArray Int
335 lexemeToByteArray (StringBuffer fo _ start_pos# current#) = 
336  if start_pos# ==# current# then
337     error "lexemeToByteArray" 
338  else
339     copySubStr (A# fo) (I# start_pos#) (I# (current# -# start_pos#))
340
341 lexemeToFastString :: StringBuffer -> FastString
342 lexemeToFastString (StringBuffer fo l# start_pos# current#) =
343  if start_pos# ==# current# then
344     mkFastCharString2 (A# fo) (I# 0#)
345  else
346     mkFastSubString (A# fo) (I# start_pos#) (I# (current# -# start_pos#))
347
348 {-
349  Create a StringBuffer from the current lexeme, and add a sentinel
350  at the end. Know What You're Doing before taking this function
351  into use..
352 -}
353 lexemeToBuffer :: StringBuffer -> StringBuffer
354 lexemeToBuffer (StringBuffer fo l# start_pos# current#) =
355  if start_pos# ==# current# then
356     StringBuffer fo 0# start_pos# current# -- an error, really. 
357  else
358     unsafeWriteBuffer (StringBuffer fo (current# -# start_pos#) start_pos# start_pos#)
359                       (current# -# 1#)
360                       '\NUL'#
361
362 \end{code}