e00840114ea379f9e098f1b30f86347c461fbfd5
[ghc-base.git] / Data / PackedString.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.PackedString
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- This API is deprecated.  You might be able to use "Data.ByteString"
12 -- or "Data.ByteString.Char8", provided you don't need full Unicode support.
13 -- The long term aim is to provide a Unicode layer on "Data.ByteString",
14 -- and then to provide a replacement for this "Data.PackedString" API based on
15 -- that.
16 --
17 -----------------------------------------------------------------------------
18
19 -- Original GHC implementation by Bryan O\'Sullivan, 
20 -- rewritten to use UArray by Simon Marlow.
21
22 module Data.PackedString 
23   {-# DEPRECATED "use Data.ByteString, Data.ByteString.Char8, or plain String." #-}
24   (
25         -- * The @PackedString@ type
26         PackedString,      -- abstract, instances: Eq, Ord, Show, Typeable
27
28          -- * Converting to and from @PackedString@s
29         packString,  -- :: String -> PackedString
30         unpackPS,    -- :: PackedString -> String
31
32 #ifndef __NHC__
33         -- * I\/O with @PackedString@s  
34         hPutPS,      -- :: Handle -> PackedString -> IO ()
35         hGetPS,      -- :: Handle -> Int -> IO PackedString
36 #endif
37
38         -- * List-like manipulation functions
39         nilPS,       -- :: PackedString
40         consPS,      -- :: Char -> PackedString -> PackedString
41         headPS,      -- :: PackedString -> Char
42         tailPS,      -- :: PackedString -> PackedString
43         nullPS,      -- :: PackedString -> Bool
44         appendPS,    -- :: PackedString -> PackedString -> PackedString
45         lengthPS,    -- :: PackedString -> Int
46         indexPS,     -- :: PackedString -> Int -> Char
47         mapPS,       -- :: (Char -> Char) -> PackedString -> PackedString
48         filterPS,    -- :: (Char -> Bool) -> PackedString -> PackedString
49         reversePS,   -- :: PackedString -> PackedString
50         concatPS,    -- :: [PackedString] -> PackedString
51         elemPS,      -- :: Char -> PackedString -> Bool
52         substrPS,    -- :: PackedString -> Int -> Int -> PackedString
53         takePS,      -- :: Int -> PackedString -> PackedString
54         dropPS,      -- :: Int -> PackedString -> PackedString
55         splitAtPS,   -- :: Int -> PackedString -> (PackedString, PackedString)
56
57         foldlPS,     -- :: (a -> Char -> a) -> a -> PackedString -> a
58         foldrPS,     -- :: (Char -> a -> a) -> a -> PackedString -> a
59         takeWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
60         dropWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
61         spanPS,      -- :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
62         breakPS,     -- :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
63         linesPS,     -- :: PackedString -> [PackedString]
64         unlinesPS,   -- :: [PackedString] -> PackedString
65         wordsPS,     -- :: PackedString -> [PackedString]
66         unwordsPS,   -- :: [PackedString] -> PackedString
67         splitPS,     -- :: Char -> PackedString -> [PackedString]
68         splitWithPS, -- :: (Char -> Bool) -> PackedString -> [PackedString]
69
70         joinPS,      -- :: PackedString -> [PackedString] -> PackedString
71
72     ) where
73
74 import Prelude
75
76 #ifndef __NHC__
77
78 import Data.Array.Unboxed
79 import Data.Array.IO
80 import Data.Typeable
81 import Data.Char
82 #ifdef __GLASGOW_HASKELL__
83 import Data.Generics
84 #endif
85
86 import System.IO
87
88 -- -----------------------------------------------------------------------------
89 -- PackedString type declaration
90
91 -- | A space-efficient representation of a 'String', which supports various
92 -- efficient operations.  A 'PackedString' contains full Unicode 'Char's.
93 newtype PackedString = PS (UArray Int Char)
94
95 -- ToDo: we could support "slices", i.e. include offset and length fields into
96 -- the string, so that operations like take/drop could be O(1).  Perhaps making
97 -- a slice should be conditional on the ratio of the slice/string size to
98 -- limit memory leaks.
99
100 instance Eq PackedString where
101    (PS x) == (PS y)  =  x == y
102
103 instance Ord PackedString where
104     compare (PS x) (PS y) = compare x y
105
106 --instance Read PackedString: ToDo
107
108 instance Show PackedString where
109     showsPrec p ps r = showsPrec p (unpackPS ps) r
110
111 #include "Typeable.h"
112 INSTANCE_TYPEABLE0(PackedString,packedStringTc,"PackedString")
113
114 -- -----------------------------------------------------------------------------
115 -- Constructor functions
116
117 -- | The 'nilPS' value is the empty string.
118 nilPS :: PackedString
119 nilPS = PS (array (0,-1) [])
120
121 -- | The 'consPS' function prepends the given character to the
122 -- given string.
123 consPS :: Char -> PackedString -> PackedString
124 consPS c cs = packString (c : (unpackPS cs)) -- ToDo:better
125
126 -- | Convert a 'String' into a 'PackedString'
127 packString :: String -> PackedString
128 packString str = packNChars (length str) str
129
130 -- | The 'packNChars' function creates a 'PackedString' out of the
131 -- first @len@ elements of the given 'String'.
132 packNChars :: Int -> [Char] -> PackedString
133 packNChars len str = PS (listArray (0,len-1) str)
134
135 -- -----------------------------------------------------------------------------
136 -- Destructor functions (taking PackedStrings apart)
137
138 -- | Convert a 'PackedString' into a 'String'
139 unpackPS :: PackedString -> String
140 unpackPS (PS ps) = elems ps
141
142 -- -----------------------------------------------------------------------------
143 -- List-mimicking functions for PackedStrings
144
145 -- | The 'lengthPS' function returns the length of the input list.  Analogous to 'length'.
146 lengthPS :: PackedString -> Int
147 lengthPS (PS ps) = rangeSize (bounds ps)
148
149 -- | The 'indexPS' function returns the character in the string at the given position.
150 indexPS :: PackedString -> Int -> Char
151 indexPS (PS ps) i = ps ! i
152
153 -- | The 'headPS' function returns the first element of a 'PackedString' or throws an
154 -- error if the string is empty.
155 headPS :: PackedString -> Char
156 headPS ps
157   | nullPS ps = error "Data.PackedString.headPS: head []"
158   | otherwise  = indexPS ps 0
159
160 -- | The 'tailPS' function returns the tail of a 'PackedString' or throws an error
161 -- if the string is empty.
162 tailPS :: PackedString -> PackedString
163 tailPS ps
164   | len <= 0 = error "Data.PackedString.tailPS: tail []"
165   | len == 1 = nilPS
166   | otherwise  = substrPS ps 1 (len - 1)
167   where
168     len = lengthPS ps
169
170 -- | The 'nullPS' function returns True iff the argument is null.
171 nullPS :: PackedString -> Bool
172 nullPS (PS ps) = rangeSize (bounds ps) == 0
173
174 -- | The 'appendPS' function appends the second string onto the first.
175 appendPS :: PackedString -> PackedString -> PackedString
176 appendPS xs ys
177   | nullPS xs = ys
178   | nullPS ys = xs
179   | otherwise  = concatPS [xs,ys]
180
181 -- | The 'mapPS' function applies a function to each character in the string.
182 mapPS :: (Char -> Char) -> PackedString -> PackedString
183 mapPS f (PS ps) = PS (amap f ps)
184
185 -- | The 'filterPS' function filters out the appropriate substring.
186 filterPS :: (Char -> Bool) -> PackedString -> PackedString {-or String?-}
187 filterPS pred ps = packString (filter pred (unpackPS ps))
188
189 -- | The 'foldlPS' function behaves like 'foldl' on 'PackedString's.
190 foldlPS :: (a -> Char -> a) -> a -> PackedString -> a
191 foldlPS f b ps = foldl f b (unpackPS ps)
192
193 -- | The 'foldrPS' function behaves like 'foldr' on 'PackedString's.
194 foldrPS :: (Char -> a -> a) -> a -> PackedString -> a
195 foldrPS f v ps = foldr f v (unpackPS ps)
196
197 -- | The 'takePS' function takes the first @n@ characters of a 'PackedString'.
198 takePS :: Int -> PackedString -> PackedString
199 takePS n ps = substrPS ps 0 (n-1)
200
201 -- | The 'dropPS' function drops the first @n@ characters of a 'PackedString'.
202 dropPS  :: Int -> PackedString -> PackedString
203 dropPS n ps = substrPS ps n (lengthPS ps - 1)
204
205 -- | The 'splitWithPS' function splits a 'PackedString' at a given index.
206 splitAtPS :: Int -> PackedString -> (PackedString, PackedString)
207 splitAtPS  n ps  = (takePS n ps, dropPS n ps)
208
209 -- | The 'takeWhilePS' function is analogous to the 'takeWhile' function.
210 takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
211 takeWhilePS pred ps = packString (takeWhile pred (unpackPS ps))
212
213 -- | The 'dropWhilePS' function is analogous to the 'dropWhile' function.
214 dropWhilePS :: (Char -> Bool) -> PackedString -> PackedString
215 dropWhilePS pred ps = packString (dropWhile pred (unpackPS ps))
216
217 -- | The 'elemPS' function returns True iff the given element is in the string.
218 elemPS :: Char -> PackedString -> Bool
219 elemPS c ps = c `elem` unpackPS ps
220
221 -- | The 'spanPS' function returns a pair containing the result of
222 -- running both 'takeWhilePS' and 'dropWhilePS'.
223 spanPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
224 spanPS  p ps = (takeWhilePS p ps, dropWhilePS p ps)
225
226 -- | The 'breakPS' function breaks a string at the first position which
227 -- satisfies the predicate.
228 breakPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
229 breakPS p ps = spanPS (not . p) ps
230
231 -- | The 'linesPS' function splits the input on line-breaks.
232 linesPS :: PackedString -> [PackedString]
233 linesPS ps = splitPS '\n' ps
234
235 -- | The 'unlinesPS' function concatenates the input list after
236 -- interspersing newlines.
237 unlinesPS :: [PackedString] -> PackedString
238 unlinesPS = joinPS (packString "\n")
239
240 -- | The 'wordsPS' function is analogous to the 'words' function.
241 wordsPS :: PackedString -> [PackedString]
242 wordsPS ps = filter (not.nullPS) (splitWithPS isSpace ps)
243
244 -- | The 'unwordsPS' function is analogous to the 'unwords' function.
245 unwordsPS :: [PackedString] -> PackedString
246 unwordsPS = joinPS (packString " ")
247
248 -- | The 'reversePS' function reverses the string.
249 reversePS :: PackedString -> PackedString
250 reversePS ps = packString (reverse (unpackPS ps))
251
252 -- | The 'concatPS' function concatenates a list of 'PackedString's.
253 concatPS :: [PackedString] -> PackedString
254 concatPS pss = packString (concat (map unpackPS pss))
255
256 ------------------------------------------------------------
257
258 -- | The 'joinPS' function takes a 'PackedString' and a list of 'PackedString's
259 -- and concatenates the list after interspersing the first argument between
260 -- each element of the list.
261 joinPS :: PackedString -> [PackedString] -> PackedString
262 joinPS filler pss = concatPS (splice pss)
263  where
264   splice []  = []
265   splice [x] = [x]
266   splice (x:y:xs) = x:filler:splice (y:xs)
267
268 -- ToDo: the obvious generalisation
269 {-
270   Some properties that hold:
271
272   * splitPS x ls = ls'   
273       where False = any (map (x `elemPS`) ls')
274
275   * joinPS (packString [x]) (splitPS x ls) = ls
276 -}
277
278 -- | The 'splitPS' function splits the input string on each occurrence of the given 'Char'.
279 splitPS :: Char -> PackedString -> [PackedString]
280 splitPS c = splitWithPS (== c)
281
282 -- | The 'splitWithPS' function takes a character predicate and splits the input string
283 -- at each character which satisfies the predicate.
284 splitWithPS :: (Char -> Bool) -> PackedString -> [PackedString]
285 splitWithPS pred (PS ps) =
286  splitify 0
287  where
288   len = lengthPS (PS ps)
289   
290   splitify n 
291    | n >= len = []
292    | otherwise =
293       let
294        break_pt = first_pos_that_satisfies pred ps len n
295       in
296       if break_pt == n then -- immediate match, empty substring
297          nilPS
298          : splitify (break_pt + 1)
299       else 
300          substrPS (PS ps) n (break_pt - 1) -- leave out the matching character
301          : splitify (break_pt + 1)
302
303 first_pos_that_satisfies pred ps len n = 
304    case [ m | m <- [n..len-1], pred (ps ! m) ] of
305         []    -> len
306         (m:_) -> m
307
308 -- -----------------------------------------------------------------------------
309 -- Local utility functions
310
311 -- The definition of @_substrPS@ is essentially:
312 -- @take (end - begin + 1) (drop begin str)@.
313
314 -- | The 'substrPS' function takes a 'PackedString' and two indices
315 -- and returns the substring of the input string between (and including)
316 -- these indices.
317 substrPS :: PackedString -> Int -> Int -> PackedString
318 substrPS (PS ps) begin end = packString [ ps ! i | i <- [begin..end] ]
319
320 -- -----------------------------------------------------------------------------
321 -- hPutPS
322
323 -- | Outputs a 'PackedString' to the specified 'Handle'.
324 --
325 -- NOTE: the representation of the 'PackedString' in the file is assumed to
326 -- be in the ISO-8859-1 encoding.  In other words, only the least significant
327 -- byte is taken from each character in the 'PackedString'.
328 hPutPS :: Handle -> PackedString -> IO ()
329 hPutPS h (PS ps) = do
330   let l = lengthPS (PS ps)
331   arr <- newArray_ (0, l-1)
332   sequence_ [ writeArray arr i (fromIntegral (ord (ps ! i))) | i <- [0..l-1] ]
333   hPutArray h arr l
334
335 -- -----------------------------------------------------------------------------
336 -- hGetPS
337
338 -- | Read a 'PackedString' directly from the specified 'Handle'.
339 -- This is far more efficient than reading the characters into a 'String'
340 -- and then using 'packString'.  
341 --
342 -- NOTE: as with 'hPutPS', the string representation in the file is 
343 -- assumed to be ISO-8859-1.
344 hGetPS :: Handle -> Int -> IO PackedString
345 hGetPS h i = do
346   arr <- newArray_ (0, i-1)
347   l <- hGetArray h arr i
348   chars <- mapM (\i -> readArray arr i >>= return.chr.fromIntegral) [0..l-1]
349   return (packNChars l chars)
350
351 #else   /* __NHC__ */
352
353 --import Prelude hiding (append, break, concat, cons, drop, dropWhile,
354 --                       filter, foldl, foldr, head, length, lines, map,
355 --                       nil, null, reverse, span, splitAt, subst, tail,
356 --                       take, takeWhile, unlines, unwords, words)
357 -- also hiding: Ix(..), Functor(..)
358 import qualified NHC.PackedString
359 import NHC.PackedString (PackedString,packString,unpackPS)
360 import List (intersperse)
361
362
363 nilPS       :: PackedString
364 consPS      :: Char -> PackedString -> PackedString
365 headPS      :: PackedString -> Char
366 tailPS      :: PackedString -> PackedString
367 nullPS      :: PackedString -> Bool
368 appendPS    :: PackedString -> PackedString -> PackedString
369 lengthPS    :: PackedString -> Int
370 indexPS     :: PackedString -> Int -> Char
371 mapPS       :: (Char -> Char) -> PackedString -> PackedString
372 filterPS    :: (Char -> Bool) -> PackedString -> PackedString
373 reversePS   :: PackedString -> PackedString
374 concatPS    :: [PackedString] -> PackedString
375 elemPS      :: Char -> PackedString -> Bool
376 substrPS    :: PackedString -> Int -> Int -> PackedString
377 takePS      :: Int -> PackedString -> PackedString
378 dropPS      :: Int -> PackedString -> PackedString
379 splitAtPS   :: Int -> PackedString -> (PackedString, PackedString)
380
381 foldlPS     :: (a -> Char -> a) -> a -> PackedString -> a
382 foldrPS     :: (Char -> a -> a) -> a -> PackedString -> a
383 takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
384 dropWhilePS :: (Char -> Bool) -> PackedString -> PackedString
385 spanPS      :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
386 breakPS     :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
387 linesPS     :: PackedString -> [PackedString]
388 unlinesPS   :: [PackedString] -> PackedString
389
390 wordsPS     :: PackedString -> [PackedString]
391 unwordsPS   :: [PackedString] -> PackedString
392 splitPS     :: Char -> PackedString -> [PackedString]
393 splitWithPS :: (Char -> Bool) -> PackedString -> [PackedString]
394 joinPS      :: PackedString -> [PackedString] -> PackedString
395
396 nilPS       = NHC.PackedString.nil
397 consPS      = NHC.PackedString.cons
398 headPS      = NHC.PackedString.head
399 tailPS      = NHC.PackedString.tail
400 nullPS      = NHC.PackedString.null
401 appendPS    = NHC.PackedString.append
402 lengthPS    = NHC.PackedString.length
403 indexPS p i = (unpackPS p) !! i
404 mapPS       = NHC.PackedString.map
405 filterPS    = NHC.PackedString.filter
406 reversePS   = NHC.PackedString.reverse
407 concatPS    = NHC.PackedString.concat
408 elemPS c p  = c `elem` unpackPS p
409 substrPS    = NHC.PackedString.substr
410 takePS      = NHC.PackedString.take
411 dropPS      = NHC.PackedString.drop
412 splitAtPS   = NHC.PackedString.splitAt
413
414 foldlPS     = NHC.PackedString.foldl
415 foldrPS     = NHC.PackedString.foldr
416 takeWhilePS = NHC.PackedString.takeWhile
417 dropWhilePS = NHC.PackedString.dropWhile
418 spanPS      = NHC.PackedString.span
419 breakPS     = NHC.PackedString.break
420 linesPS     = NHC.PackedString.lines
421 unlinesPS   = NHC.PackedString.unlines
422
423 wordsPS     = NHC.PackedString.words
424 unwordsPS   = NHC.PackedString.unwords
425 splitPS c   = splitWithPS (==c)
426 splitWithPS p =
427     map packString . split' p [] . unpackPS
428   where
429     split' :: (Char->Bool) -> String -> String -> [String]
430     split' pred []  []     = []
431     split' pred acc []     = [reverse acc]
432     split' pred acc (x:xs) | pred x    = reverse acc: split' pred [] xs
433                            | otherwise = split' pred (x:acc) xs
434
435 joinPS sep  = concatPS . intersperse sep
436
437 #endif
438
439 #ifdef __GLASGOW_HASKELL__
440 instance Data PackedString where
441      gunfold k z c = error "gunfold"
442      toConstr (PS _) = con_PS
443      dataTypeOf _ = ty_PackedString
444
445 con_PS = mkConstr ty_PackedString "PS" [] Prefix
446 ty_PackedString   = mkDataType "Data.PackedString.PackedString" [con_PS]
447 #endif