f276d14a62623af64a4c94d62a8b572ac90071be
[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 -- An efficient implementation of strings.
12 --
13 -----------------------------------------------------------------------------
14
15 -- Original GHC implementation by Bryan O\'Sullivan, 
16 -- rewritten to use UArray by Simon Marlow.
17
18 module Data.PackedString (
19         -- * The @PackedString@ type
20         PackedString,      -- abstract, instances: Eq, Ord, Show, Typeable
21
22          -- * Converting to and from @PackedString@s
23         packString,  -- :: String -> PackedString
24         unpackPS,    -- :: PackedString -> String
25
26         -- * I\/O with @PackedString@s  
27         hPutPS,      -- :: Handle -> PackedString -> IO ()
28         hGetPS,      -- :: Handle -> Int -> IO PackedString
29
30         -- * List-like manipulation functions
31         nilPS,       -- :: PackedString
32         consPS,      -- :: Char -> PackedString -> PackedString
33         headPS,      -- :: PackedString -> Char
34         tailPS,      -- :: PackedString -> PackedString
35         nullPS,      -- :: PackedString -> Bool
36         appendPS,    -- :: PackedString -> PackedString -> PackedString
37         lengthPS,    -- :: PackedString -> Int
38         indexPS,     -- :: PackedString -> Int -> Char
39         mapPS,       -- :: (Char -> Char) -> PackedString -> PackedString
40         filterPS,    -- :: (Char -> Bool) -> PackedString -> PackedString
41         reversePS,   -- :: PackedString -> PackedString
42         concatPS,    -- :: [PackedString] -> PackedString
43         elemPS,      -- :: Char -> PackedString -> Bool
44         substrPS,    -- :: PackedString -> Int -> Int -> PackedString
45         takePS,      -- :: Int -> PackedString -> PackedString
46         dropPS,      -- :: Int -> PackedString -> PackedString
47         splitAtPS,   -- :: Int -> PackedString -> (PackedString, PackedString)
48
49         foldlPS,     -- :: (a -> Char -> a) -> a -> PackedString -> a
50         foldrPS,     -- :: (Char -> a -> a) -> a -> PackedString -> a
51         takeWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
52         dropWhilePS, -- :: (Char -> Bool) -> PackedString -> PackedString
53         spanPS,      -- :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
54         breakPS,     -- :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
55         linesPS,     -- :: PackedString -> [PackedString]
56
57         wordsPS,     -- :: PackedString -> [PackedString]
58         splitPS,     -- :: Char -> PackedString -> [PackedString]
59         splitWithPS, -- :: (Char -> Bool) -> PackedString -> [PackedString]
60
61 --      joinPS,      -- :: PackedString -> [PackedString] -> PackedString
62
63     ) where
64
65 import Prelude
66
67 import Data.Array.Unboxed
68 import Data.Array.IO
69 import Data.Dynamic
70 import Data.Char
71
72 import System.IO
73
74 -- -----------------------------------------------------------------------------
75 -- PackedString type declaration
76
77 -- | A space-efficient representation of a 'String', which supports various
78 -- efficient operations.  A 'PackedString' contains full Unicode 'Char's.
79 newtype PackedString = PS (UArray Int Char)
80
81 instance Eq PackedString where
82    (PS x) == (PS y)  =  x == y
83
84 instance Ord PackedString where
85     compare (PS x) (PS y) = compare x y
86
87 --instance Read PackedString: ToDo
88
89 instance Show PackedString where
90     showsPrec p ps r = showsPrec p (unpackPS ps) r
91
92 #include "Dynamic.h"
93 INSTANCE_TYPEABLE0(PackedString,packedStringTc,"PackedString")
94
95 -- -----------------------------------------------------------------------------
96 -- Constructor functions
97
98 nilPS :: PackedString
99 nilPS = PS (array (0,-1) [])
100
101 consPS :: Char -> PackedString -> PackedString
102 consPS c cs = packString (c : (unpackPS cs)) -- ToDo:better
103
104 -- | Convert a 'String' into a 'PackedString'
105 packString :: String -> PackedString
106 packString str = packNChars (length str) str
107
108 packNChars :: Int -> [Char] -> PackedString
109 packNChars len str = PS (array (0,len-1) (zip [0..] str))
110
111 -- -----------------------------------------------------------------------------
112 -- Destructor functions (taking PackedStrings apart)
113
114 -- | Convert a 'PackedString' into a 'String'
115 unpackPS :: PackedString -> String
116 unpackPS (PS ps) = elems ps
117
118 -- -----------------------------------------------------------------------------
119 -- List-mimicking functions for PackedStrings
120
121 lengthPS :: PackedString -> Int
122 lengthPS (PS ps) = rangeSize (bounds ps)
123
124 indexPS :: PackedString -> Int -> Char
125 indexPS (PS ps) i = ps ! i
126
127 headPS :: PackedString -> Char
128 headPS ps
129   | nullPS ps = error "Data.PackedString.headPS: head []"
130   | otherwise  = indexPS ps 0
131
132 tailPS :: PackedString -> PackedString
133 tailPS ps
134   | len <= 0 = error "Data.PackedString.tailPS: tail []"
135   | len == 1 = nilPS
136   | otherwise  = substrPS ps 1 (len - 1)
137   where
138     len = lengthPS ps
139
140 nullPS :: PackedString -> Bool
141 nullPS (PS ps) = rangeSize (bounds ps) == 0
142
143 appendPS :: PackedString -> PackedString -> PackedString
144 appendPS xs ys
145   | nullPS xs = ys
146   | nullPS ys = xs
147   | otherwise  = concatPS [xs,ys]
148
149 mapPS :: (Char -> Char) -> PackedString -> PackedString
150 mapPS f (PS ps) = PS (amap f ps)
151
152 filterPS :: (Char -> Bool) -> PackedString -> PackedString {-or String?-}
153 filterPS pred ps = packString (filter pred (unpackPS ps))
154
155 foldlPS :: (a -> Char -> a) -> a -> PackedString -> a
156 foldlPS f b ps = foldl f b (unpackPS ps)
157
158 foldrPS :: (Char -> a -> a) -> a -> PackedString -> a
159 foldrPS f v ps = foldr f v (unpackPS ps)
160
161 takePS :: Int -> PackedString -> PackedString
162 takePS n ps = substrPS ps 0 (n-1)
163
164 dropPS  :: Int -> PackedString -> PackedString
165 dropPS n ps = substrPS ps n (lengthPS ps - 1)
166
167 splitAtPS :: Int -> PackedString -> (PackedString, PackedString)
168 splitAtPS  n ps  = (takePS n ps, dropPS n ps)
169
170 takeWhilePS :: (Char -> Bool) -> PackedString -> PackedString
171 takeWhilePS pred ps = packString (takeWhile pred (unpackPS ps))
172
173 dropWhilePS :: (Char -> Bool) -> PackedString -> PackedString
174 dropWhilePS pred ps = packString (dropWhile pred (unpackPS ps))
175
176 elemPS :: Char -> PackedString -> Bool
177 elemPS c ps = c `elem` unpackPS ps
178
179 spanPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
180 spanPS  p ps = (takeWhilePS p ps, dropWhilePS p ps)
181
182 breakPS :: (Char -> Bool) -> PackedString -> (PackedString, PackedString)
183 breakPS p ps = spanPS (not . p) ps
184
185 linesPS :: PackedString -> [PackedString]
186 linesPS ps = splitPS '\n' ps
187
188 wordsPS :: PackedString -> [PackedString]
189 wordsPS ps = splitWithPS isSpace ps
190
191 reversePS :: PackedString -> PackedString
192 reversePS ps = packString (reverse (unpackPS ps))
193
194 concatPS :: [PackedString] -> PackedString
195 concatPS pss = packString (concat (map unpackPS pss))
196
197 ------------------------------------------------------------
198 {-
199 joinPS :: PackedString -> [PackedString] -> PackedString
200 joinPS filler pss = concatPS (splice pss)
201  where
202   splice []  = []
203   splice [x] = [x]
204   splice (x:y:xs) = x:filler:splice (y:xs)
205
206 -- ToDo: the obvious generalisation
207 {-
208   Some properties that hold:
209
210   * splitPS x ls = ls'   
211       where False = any (map (x `elemPS`) ls')
212             False = any (map (nullPS) ls')
213
214     * all x's have been chopped out.
215     * no empty PackedStrings in returned list. A conseq.
216       of this is:
217            splitPS x nilPS = []
218          
219
220   * joinPS (packString [x]) (_splitPS x ls) = ls
221
222 -}
223 -}
224
225 splitPS :: Char -> PackedString -> [PackedString]
226 splitPS c = splitWithPS (== c)
227
228 splitWithPS :: (Char -> Bool) -> PackedString -> [PackedString]
229 splitWithPS pred (PS ps) =
230  splitify 0
231  where
232   len = lengthPS (PS ps)
233   
234   splitify n 
235    | n >= len = []
236    | otherwise =
237       let
238        break_pt = first_pos_that_satisfies pred ps len n
239       in
240       if break_pt == n then -- immediate match, no substring to cut out.
241          splitify (break_pt + 1)
242       else 
243          substrPS (PS ps) n (break_pt - 1) -- leave out the matching character
244          : splitify (break_pt + 1)
245
246 first_pos_that_satisfies pred ps len n = 
247    case [ m | m <- [n..len], pred (ps ! m) ] of
248         []    -> len
249         (m:_) -> m
250
251 -- -----------------------------------------------------------------------------
252 -- Local utility functions
253
254 -- The definition of @_substrPS@ is essentially:
255 -- @take (end - begin + 1) (drop begin str)@.
256
257 substrPS :: PackedString -> Int -> Int -> PackedString
258 substrPS (PS ps) begin end = packString [ ps ! i | i <- [begin..end] ]
259
260 -- -----------------------------------------------------------------------------
261 -- hPutPS
262
263 -- | Outputs a 'PackedString' to the specified 'Handle'.  
264 --
265 -- NOTE: the representation of the 'PackedString' in the file is assumed to
266 -- be in the ISO-8859-1 encoding.  In other words, only the least signficant
267 -- byte is taken from each character in the 'PackedString'.
268 hPutPS :: Handle -> PackedString -> IO ()
269 hPutPS h (PS ps) = do
270   let l = lengthPS (PS ps)
271   arr <- newArray_ (0, l-1)
272   sequence_ [ writeArray arr i (fromIntegral (ord (ps ! i))) | i <- [0..l-1] ]
273   hPutArray h arr l
274
275 -- -----------------------------------------------------------------------------
276 -- hGetPS
277
278 -- | Read a 'PackedString' directly from the specified 'Handle'.  This
279 -- is far more efficient than reading the characters into a 'String'
280 -- and then using 'packString'.  
281 --
282 -- NOTE: as with 'hPutPS', the string representation in the file is 
283 -- assumed to be ISO-8859-1.
284 hGetPS :: Handle -> Int -> IO PackedString
285 hGetPS h i = do
286   arr <- newArray_ (0, i-1)
287   l <- hGetArray h arr i
288   chars <- mapM (\i -> readArray arr i >>= return.chr.fromIntegral) [0..l-1]
289   return (packString chars)