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