Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / GHC / Arr.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude -fno-bang-patterns #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Arr
6 -- Copyright   :  (c) The University of Glasgow, 1994-2000
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC extensions)
12 --
13 -- GHC\'s array implementation.
14 -- 
15 -----------------------------------------------------------------------------
16
17 -- #hide
18 module GHC.Arr where
19
20 import {-# SOURCE #-} GHC.Err ( error )
21 import GHC.Enum
22 import GHC.Num
23 import GHC.ST
24 import GHC.Base
25 import GHC.List
26 import GHC.Show
27
28 infixl 9  !, //
29
30 default ()
31 \end{code}
32
33
34 %*********************************************************
35 %*                                                      *
36 \subsection{The @Ix@ class}
37 %*                                                      *
38 %*********************************************************
39
40 \begin{code}
41 -- | The 'Ix' class is used to map a contiguous subrange of values in
42 -- a type onto integers.  It is used primarily for array indexing
43 -- (see "Data.Array", "Data.Array.IArray" and "Data.Array.MArray").
44 --
45 -- The first argument @(l,u)@ of each of these operations is a pair
46 -- specifying the lower and upper bounds of a contiguous subrange of values.
47 --
48 -- An implementation is entitled to assume the following laws about these
49 -- operations:
50 --
51 -- * @'inRange' (l,u) i == 'elem' i ('range' (l,u))@
52 --
53 -- * @'range' (l,u) '!!' 'index' (l,u) i == i@, when @'inRange' (l,u) i@
54 --
55 -- * @'map' ('index' (l,u)) ('range' (l,u))) == [0..'rangeSize' (l,u)-1]@
56 --
57 -- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@
58 --
59 -- Minimal complete instance: 'range', 'index' and 'inRange'.
60 --
61 class (Ord a) => Ix a where
62     -- | The list of values in the subrange defined by a bounding pair.
63     range               :: (a,a) -> [a]
64     -- | The position of a subscript in the subrange.
65     index               :: (a,a) -> a -> Int
66     -- | Like 'index', but without checking that the value is in range.
67     unsafeIndex         :: (a,a) -> a -> Int
68     -- | Returns 'True' the given subscript lies in the range defined
69     -- the bounding pair.
70     inRange             :: (a,a) -> a -> Bool
71     -- | The size of the subrange defined by a bounding pair.
72     rangeSize           :: (a,a) -> Int
73     -- | like 'rangeSize', but without checking that the upper bound is
74     -- in range.
75     unsafeRangeSize     :: (a,a) -> Int
76
77         -- Must specify one of index, unsafeIndex
78     index b i | inRange b i = unsafeIndex b i   
79               | otherwise   = error "Error in array index"
80     unsafeIndex b i = index b i
81
82     rangeSize b@(_l,h) | inRange b h = unsafeIndex b h + 1
83                        | otherwise   = 0        -- This case is only here to
84                                                 -- check for an empty range
85         -- NB: replacing (inRange b h) by (l <= h) fails for
86         --     tuples.  E.g.  (1,2) <= (2,1) but the range is empty
87
88     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
89 \end{code}
90
91 Note that the following is NOT right
92         rangeSize (l,h) | l <= h    = index b h + 1
93                         | otherwise = 0
94
95 Because it might be the case that l<h, but the range
96 is nevertheless empty.  Consider
97         ((1,2),(2,1))
98 Here l<h, but the second index ranges from 2..1 and
99 hence is empty
100
101 %*********************************************************
102 %*                                                      *
103 \subsection{Instances of @Ix@}
104 %*                                                      *
105 %*********************************************************
106
107 \begin{code}
108 -- abstract these errors from the relevant index functions so that
109 -- the guts of the function will be small enough to inline.
110
111 {-# NOINLINE indexError #-}
112 indexError :: Show a => (a,a) -> a -> String -> b
113 indexError rng i tp
114   = error (showString "Ix{" . showString tp . showString "}.index: Index " .
115            showParen True (showsPrec 0 i) .
116            showString " out of range " $
117            showParen True (showsPrec 0 rng) "")
118
119 ----------------------------------------------------------------------
120 instance  Ix Char  where
121     {-# INLINE range #-}
122     range (m,n) = [m..n]
123
124     {-# INLINE unsafeIndex #-}
125     unsafeIndex (m,_n) i = fromEnum i - fromEnum m
126
127     index b i | inRange b i =  unsafeIndex b i
128               | otherwise   =  indexError b i "Char"
129
130     inRange (m,n) i     =  m <= i && i <= n
131
132 ----------------------------------------------------------------------
133 instance  Ix Int  where
134     {-# INLINE range #-}
135         -- The INLINE stops the build in the RHS from getting inlined,
136         -- so that callers can fuse with the result of range
137     range (m,n) = [m..n]
138
139     {-# INLINE unsafeIndex #-}
140     unsafeIndex (m,_n) i = i - m
141
142     index b i | inRange b i =  unsafeIndex b i
143               | otherwise   =  indexError b i "Int"
144
145     {-# INLINE inRange #-}
146     inRange (I# m,I# n) (I# i) =  m <=# i && i <=# n
147
148 ----------------------------------------------------------------------
149 instance  Ix Integer  where
150     {-# INLINE range #-}
151     range (m,n) = [m..n]
152
153     {-# INLINE unsafeIndex #-}
154     unsafeIndex (m,_n) i   = fromInteger (i - m)
155
156     index b i | inRange b i =  unsafeIndex b i
157               | otherwise   =  indexError b i "Integer"
158
159     inRange (m,n) i     =  m <= i && i <= n
160
161 ----------------------------------------------------------------------
162 instance Ix Bool where -- as derived
163     {-# INLINE range #-}
164     range (m,n) = [m..n]
165
166     {-# INLINE unsafeIndex #-}
167     unsafeIndex (l,_) i = fromEnum i - fromEnum l
168
169     index b i | inRange b i =  unsafeIndex b i
170               | otherwise   =  indexError b i "Bool"
171
172     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
173
174 ----------------------------------------------------------------------
175 instance Ix Ordering where -- as derived
176     {-# INLINE range #-}
177     range (m,n) = [m..n]
178
179     {-# INLINE unsafeIndex #-}
180     unsafeIndex (l,_) i = fromEnum i - fromEnum l
181
182     index b i | inRange b i =  unsafeIndex b i
183               | otherwise   =  indexError b i "Ordering"
184
185     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
186
187 ----------------------------------------------------------------------
188 instance Ix () where
189     {-# INLINE range #-}
190     range   ((), ())    = [()]
191     {-# INLINE unsafeIndex #-}
192     unsafeIndex   ((), ()) () = 0
193     {-# INLINE inRange #-}
194     inRange ((), ()) () = True
195     {-# INLINE index #-}
196     index b i = unsafeIndex b i
197
198 ----------------------------------------------------------------------
199 instance (Ix a, Ix b) => Ix (a, b) where -- as derived
200     {-# SPECIALISE instance Ix (Int,Int) #-}
201
202     {-# INLINE range #-}
203     range ((l1,l2),(u1,u2)) =
204       [ (i1,i2) | i1 <- range (l1,u1), i2 <- range (l2,u2) ]
205
206     {-# INLINE unsafeIndex #-}
207     unsafeIndex ((l1,l2),(u1,u2)) (i1,i2) =
208       unsafeIndex (l1,u1) i1 * unsafeRangeSize (l2,u2) + unsafeIndex (l2,u2) i2
209
210     {-# INLINE inRange #-}
211     inRange ((l1,l2),(u1,u2)) (i1,i2) =
212       inRange (l1,u1) i1 && inRange (l2,u2) i2
213
214     -- Default method for index
215
216 ----------------------------------------------------------------------
217 instance  (Ix a1, Ix a2, Ix a3) => Ix (a1,a2,a3)  where
218     {-# SPECIALISE instance Ix (Int,Int,Int) #-}
219
220     range ((l1,l2,l3),(u1,u2,u3)) =
221         [(i1,i2,i3) | i1 <- range (l1,u1),
222                       i2 <- range (l2,u2),
223                       i3 <- range (l3,u3)]
224
225     unsafeIndex ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
226       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
227       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
228       unsafeIndex (l1,u1) i1))
229
230     inRange ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
231       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
232       inRange (l3,u3) i3
233
234     -- Default method for index
235
236 ----------------------------------------------------------------------
237 instance  (Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1,a2,a3,a4)  where
238     range ((l1,l2,l3,l4),(u1,u2,u3,u4)) =
239       [(i1,i2,i3,i4) | i1 <- range (l1,u1),
240                        i2 <- range (l2,u2),
241                        i3 <- range (l3,u3),
242                        i4 <- range (l4,u4)]
243
244     unsafeIndex ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
245       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
246       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
247       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
248       unsafeIndex (l1,u1) i1)))
249
250     inRange ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
251       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
252       inRange (l3,u3) i3 && inRange (l4,u4) i4
253
254     -- Default method for index
255
256 instance  (Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1,a2,a3,a4,a5)  where
257     range ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) =
258       [(i1,i2,i3,i4,i5) | i1 <- range (l1,u1),
259                           i2 <- range (l2,u2),
260                           i3 <- range (l3,u3),
261                           i4 <- range (l4,u4),
262                           i5 <- range (l5,u5)]
263
264     unsafeIndex ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
265       unsafeIndex (l5,u5) i5 + unsafeRangeSize (l5,u5) * (
266       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
267       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
268       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
269       unsafeIndex (l1,u1) i1))))
270
271     inRange ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
272       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
273       inRange (l3,u3) i3 && inRange (l4,u4) i4 && 
274       inRange (l5,u5) i5
275
276     -- Default method for index
277 \end{code}
278
279 %*********************************************************
280 %*                                                      *
281 \subsection{The @Array@ types}
282 %*                                                      *
283 %*********************************************************
284
285 \begin{code}
286 type IPr = (Int, Int)
287
288 -- | The type of immutable non-strict (boxed) arrays
289 -- with indices in @i@ and elements in @e@.
290 data Ix i => Array     i e = Array   !i !i (Array# e)
291
292 -- | Mutable, boxed, non-strict arrays in the 'ST' monad.  The type
293 -- arguments are as follows:
294 --
295 --  * @s@: the state variable argument for the 'ST' type
296 --
297 --  * @i@: the index type of the array (should be an instance of 'Ix')
298 --
299 --  * @e@: the element type of the array.
300 --
301 data         STArray s i e = STArray !i !i (MutableArray# s e)
302         -- No Ix context for STArray.  They are stupid,
303         -- and force an Ix context on the equality instance.
304
305 -- Just pointer equality on mutable arrays:
306 instance Eq (STArray s i e) where
307     STArray _ _ arr1# == STArray _ _ arr2# =
308         sameMutableArray# arr1# arr2#
309 \end{code}
310
311
312 %*********************************************************
313 %*                                                      *
314 \subsection{Operations on immutable arrays}
315 %*                                                      *
316 %*********************************************************
317
318 \begin{code}
319 {-# NOINLINE arrEleBottom #-}
320 arrEleBottom :: a
321 arrEleBottom = error "(Array.!): undefined array element"
322
323 -- | Construct an array with the specified bounds and containing values
324 -- for given indices within these bounds.
325 --
326 -- The array is undefined (i.e. bottom) if any index in the list is
327 -- out of bounds.  The Haskell 98 Report further specifies that if any
328 -- two associations in the list have the same index, the value at that
329 -- index is undefined (i.e. bottom).  However in GHC's implementation,
330 -- the value at such an index is the value part of the last association
331 -- with that index in the list.
332 --
333 -- Because the indices must be checked for these errors, 'array' is
334 -- strict in the bounds argument and in the indices of the association
335 -- list, but nonstrict in the values.  Thus, recurrences such as the
336 -- following are possible:
337 --
338 -- > a = array (1,100) ((1,1) : [(i, i * a!(i-1)) | i <- [2..100]])
339 --
340 -- Not every index within the bounds of the array need appear in the
341 -- association list, but the values associated with indices that do not
342 -- appear will be undefined (i.e. bottom).
343 --
344 -- If, in any dimension, the lower bound is greater than the upper bound,
345 -- then the array is legal, but empty.  Indexing an empty array always
346 -- gives an array-bounds error, but 'bounds' still yields the bounds
347 -- with which the array was constructed.
348 {-# INLINE array #-}
349 array :: Ix i
350         => (i,i)        -- ^ a pair of /bounds/, each of the index type
351                         -- of the array.  These bounds are the lowest and
352                         -- highest indices in the array, in that order.
353                         -- For example, a one-origin vector of length
354                         -- '10' has bounds '(1,10)', and a one-origin '10'
355                         -- by '10' matrix has bounds '((1,1),(10,10))'.
356         -> [(i, e)]     -- ^ a list of /associations/ of the form
357                         -- (/index/, /value/).  Typically, this list will
358                         -- be expressed as a comprehension.  An
359                         -- association '(i, x)' defines the value of
360                         -- the array at index 'i' to be 'x'.
361         -> Array i e
362 array (l,u) ies = unsafeArray (l,u) [(index (l,u) i, e) | (i, e) <- ies]
363
364 {-# INLINE unsafeArray #-}
365 unsafeArray :: Ix i => (i,i) -> [(Int, e)] -> Array i e
366 unsafeArray (l,u) ies = runST (ST $ \s1# ->
367     case rangeSize (l,u)                of { I# n# ->
368     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
369     foldr (fill marr#) (done l u marr#) ies s2# }})
370
371 {-# INLINE fill #-}
372 fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
373 fill marr# (I# i#, e) next s1# =
374     case writeArray# marr# i# e s1#     of { s2# ->
375     next s2# }
376
377 {-# INLINE done #-}
378 done :: Ix i => i -> i -> MutableArray# s e -> STRep s (Array i e)
379 done l u marr# s1# =
380     case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
381     (# s2#, Array l u arr# #) }
382
383 -- This is inefficient and I'm not sure why:
384 -- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es)
385 -- The code below is better. It still doesn't enable foldr/build
386 -- transformation on the list of elements; I guess it's impossible
387 -- using mechanisms currently available.
388
389 -- | Construct an array from a pair of bounds and a list of values in
390 -- index order.
391 {-# INLINE listArray #-}
392 listArray :: Ix i => (i,i) -> [e] -> Array i e
393 listArray (l,u) es = runST (ST $ \s1# ->
394     case rangeSize (l,u)                of { I# n# ->
395     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
396     let fillFromList i# xs s3# | i# ==# n# = s3#
397                                | otherwise = case xs of
398             []   -> s3#
399             y:ys -> case writeArray# marr# i# y s3# of { s4# ->
400                     fillFromList (i# +# 1#) ys s4# } in
401     case fillFromList 0# es s2#         of { s3# ->
402     done l u marr# s3# }}})
403
404 -- | The value at the given index in an array.
405 {-# INLINE (!) #-}
406 (!) :: Ix i => Array i e -> i -> e
407 arr@(Array l u _) ! i = unsafeAt arr (index (l,u) i)
408
409 {-# INLINE unsafeAt #-}
410 unsafeAt :: Ix i => Array i e -> Int -> e
411 unsafeAt (Array _ _ arr#) (I# i#) =
412     case indexArray# arr# i# of (# e #) -> e
413
414 -- | The bounds with which an array was constructed.
415 {-# INLINE bounds #-}
416 bounds :: Ix i => Array i e -> (i,i)
417 bounds (Array l u _) = (l,u)
418
419 -- | The list of indices of an array in ascending order.
420 {-# INLINE indices #-}
421 indices :: Ix i => Array i e -> [i]
422 indices (Array l u _) = range (l,u)
423
424 -- | The list of elements of an array in index order.
425 {-# INLINE elems #-}
426 elems :: Ix i => Array i e -> [e]
427 elems arr@(Array l u _) =
428     [unsafeAt arr i | i <- [0 .. rangeSize (l,u) - 1]]
429
430 -- | The list of associations of an array in index order.
431 {-# INLINE assocs #-}
432 assocs :: Ix i => Array i e -> [(i, e)]
433 assocs arr@(Array l u _) =
434     [(i, unsafeAt arr (unsafeIndex (l,u) i)) | i <- range (l,u)]
435
436 -- | The 'accumArray' deals with repeated indices in the association
437 -- list using an /accumulating function/ which combines the values of
438 -- associations with the same index.
439 -- For example, given a list of values of some index type, @hist@
440 -- produces a histogram of the number of occurrences of each index within
441 -- a specified range:
442 --
443 -- > hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
444 -- > hist bnds is = accumArray (+) 0 bnds [(i, 1) | i<-is, inRange bnds i]
445 --
446 -- If the accumulating function is strict, then 'accumArray' is strict in
447 -- the values, as well as the indices, in the association list.  Thus,
448 -- unlike ordinary arrays built with 'array', accumulated arrays should
449 -- not in general be recursive.
450 {-# INLINE accumArray #-}
451 accumArray :: Ix i
452         => (e -> a -> e)        -- ^ accumulating function
453         -> e                    -- ^ initial value
454         -> (i,i)                -- ^ bounds of the array
455         -> [(i, a)]             -- ^ association list
456         -> Array i e
457 accumArray f init (l,u) ies =
458     unsafeAccumArray f init (l,u) [(index (l,u) i, e) | (i, e) <- ies]
459
460 {-# INLINE unsafeAccumArray #-}
461 unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i,i) -> [(Int, a)] -> Array i e
462 unsafeAccumArray f init (l,u) ies = runST (ST $ \s1# ->
463     case rangeSize (l,u)                of { I# n# ->
464     case newArray# n# init s1#          of { (# s2#, marr# #) ->
465     foldr (adjust f marr#) (done l u marr#) ies s2# }})
466
467 {-# INLINE adjust #-}
468 adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
469 adjust f marr# (I# i#, new) next s1# =
470     case readArray# marr# i# s1#        of { (# s2#, old #) ->
471     case writeArray# marr# i# (f old new) s2# of { s3# ->
472     next s3# }}
473
474 -- | Constructs an array identical to the first argument except that it has
475 -- been updated by the associations in the right argument.
476 -- For example, if @m@ is a 1-origin, @n@ by @n@ matrix, then
477 --
478 -- > m//[((i,i), 0) | i <- [1..n]]
479 --
480 -- is the same matrix, except with the diagonal zeroed.
481 --
482 -- Repeated indices in the association list are handled as for 'array':
483 -- Haskell 98 specifies that the resulting array is undefined (i.e. bottom),
484 -- but GHC's implementation uses the last association for each index.
485 {-# INLINE (//) #-}
486 (//) :: Ix i => Array i e -> [(i, e)] -> Array i e
487 arr@(Array l u _) // ies =
488     unsafeReplace arr [(index (l,u) i, e) | (i, e) <- ies]
489
490 {-# INLINE unsafeReplace #-}
491 unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e
492 unsafeReplace arr@(Array l u _) ies = runST (do
493     STArray _ _ marr# <- thawSTArray arr
494     ST (foldr (fill marr#) (done l u marr#) ies))
495
496 -- | @'accum' f@ takes an array and an association list and accumulates
497 -- pairs from the list into the array with the accumulating function @f@.
498 -- Thus 'accumArray' can be defined using 'accum':
499 --
500 -- > accumArray f z b = accum f (array b [(i, z) | i <- range b])
501 --
502 {-# INLINE accum #-}
503 accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
504 accum f arr@(Array l u _) ies =
505     unsafeAccum f arr [(index (l,u) i, e) | (i, e) <- ies]
506
507 {-# INLINE unsafeAccum #-}
508 unsafeAccum :: Ix i => (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
509 unsafeAccum f arr@(Array l u _) ies = runST (do
510     STArray _ _ marr# <- thawSTArray arr
511     ST (foldr (adjust f marr#) (done l u marr#) ies))
512
513 {-# INLINE amap #-}
514 amap :: Ix i => (a -> b) -> Array i a -> Array i b
515 amap f arr@(Array l u _) =
516     unsafeArray (l,u) [(i, f (unsafeAt arr i)) | i <- [0 .. rangeSize (l,u) - 1]]
517
518 -- | 'ixmap' allows for transformations on array indices.
519 -- It may be thought of as providing function composition on the right
520 -- with the mapping that the original array embodies.
521 --
522 -- A similar transformation of array values may be achieved using 'fmap'
523 -- from the 'Array' instance of the 'Functor' class.
524 {-# INLINE ixmap #-}
525 ixmap :: (Ix i, Ix j) => (i,i) -> (i -> j) -> Array j e -> Array i e
526 ixmap (l,u) f arr =
527     unsafeArray (l,u) [(unsafeIndex (l,u) i, arr ! f i) | i <- range (l,u)]
528
529 {-# INLINE eqArray #-}
530 eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool
531 eqArray arr1@(Array l1 u1 _) arr2@(Array l2 u2 _) =
532     if rangeSize (l1,u1) == 0 then rangeSize (l2,u2) == 0 else
533     l1 == l2 && u1 == u2 &&
534     and [unsafeAt arr1 i == unsafeAt arr2 i | i <- [0 .. rangeSize (l1,u1) - 1]]
535
536 {-# INLINE cmpArray #-}
537 cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering
538 cmpArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
539
540 {-# INLINE cmpIntArray #-}
541 cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering
542 cmpIntArray arr1@(Array l1 u1 _) arr2@(Array l2 u2 _) =
543     if rangeSize (l1,u1) == 0 then if rangeSize (l2,u2) == 0 then EQ else LT else
544     if rangeSize (l2,u2) == 0 then GT else
545     case compare l1 l2 of
546         EQ    -> foldr cmp (compare u1 u2) [0 .. rangeSize (l1, min u1 u2) - 1]
547         other -> other
548     where
549     cmp i rest = case compare (unsafeAt arr1 i) (unsafeAt arr2 i) of
550         EQ    -> rest
551         other -> other
552
553 {-# RULES "cmpArray/Int" cmpArray = cmpIntArray #-}
554 \end{code}
555
556
557 %*********************************************************
558 %*                                                      *
559 \subsection{Array instances}
560 %*                                                      *
561 %*********************************************************
562
563 \begin{code}
564 instance Ix i => Functor (Array i) where
565     fmap = amap
566
567 instance (Ix i, Eq e) => Eq (Array i e) where
568     (==) = eqArray
569
570 instance (Ix i, Ord e) => Ord (Array i e) where
571     compare = cmpArray
572
573 instance (Ix a, Show a, Show b) => Show (Array a b) where
574     showsPrec p a =
575         showParen (p > appPrec) $
576         showString "array " .
577         showsPrec appPrec1 (bounds a) .
578         showChar ' ' .
579         showsPrec appPrec1 (assocs a)
580         -- Precedence of 'array' is the precedence of application
581
582 -- The Read instance is in GHC.Read
583 \end{code}
584
585
586 %*********************************************************
587 %*                                                      *
588 \subsection{Operations on mutable arrays}
589 %*                                                      *
590 %*********************************************************
591
592 Idle ADR question: What's the tradeoff here between flattening these
593 datatypes into @STArray ix ix (MutableArray# s elt)@ and using
594 it as is?  As I see it, the former uses slightly less heap and
595 provides faster access to the individual parts of the bounds while the
596 code used has the benefit of providing a ready-made @(lo, hi)@ pair as
597 required by many array-related functions.  Which wins? Is the
598 difference significant (probably not).
599
600 Idle AJG answer: When I looked at the outputted code (though it was 2
601 years ago) it seems like you often needed the tuple, and we build
602 it frequently. Now we've got the overloading specialiser things
603 might be different, though.
604
605 \begin{code}
606 {-# INLINE newSTArray #-}
607 newSTArray :: Ix i => (i,i) -> e -> ST s (STArray s i e)
608 newSTArray (l,u) init = ST $ \s1# ->
609     case rangeSize (l,u)                of { I# n# ->
610     case newArray# n# init s1#          of { (# s2#, marr# #) ->
611     (# s2#, STArray l u marr# #) }}
612
613 {-# INLINE boundsSTArray #-}
614 boundsSTArray :: STArray s i e -> (i,i)  
615 boundsSTArray (STArray l u _) = (l,u)
616
617 {-# INLINE readSTArray #-}
618 readSTArray :: Ix i => STArray s i e -> i -> ST s e
619 readSTArray marr@(STArray l u _) i =
620     unsafeReadSTArray marr (index (l,u) i)
621
622 {-# INLINE unsafeReadSTArray #-}
623 unsafeReadSTArray :: Ix i => STArray s i e -> Int -> ST s e
624 unsafeReadSTArray (STArray _ _ marr#) (I# i#) = ST $ \s1# ->
625     readArray# marr# i# s1#
626
627 {-# INLINE writeSTArray #-}
628 writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s () 
629 writeSTArray marr@(STArray l u _) i e =
630     unsafeWriteSTArray marr (index (l,u) i) e
631
632 {-# INLINE unsafeWriteSTArray #-}
633 unsafeWriteSTArray :: Ix i => STArray s i e -> Int -> e -> ST s () 
634 unsafeWriteSTArray (STArray _ _ marr#) (I# i#) e = ST $ \s1# ->
635     case writeArray# marr# i# e s1#     of { s2# ->
636     (# s2#, () #) }
637 \end{code}
638
639
640 %*********************************************************
641 %*                                                      *
642 \subsection{Moving between mutable and immutable}
643 %*                                                      *
644 %*********************************************************
645
646 \begin{code}
647 freezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
648 freezeSTArray (STArray l u marr#) = ST $ \s1# ->
649     case rangeSize (l,u)                of { I# n# ->
650     case newArray# n# arrEleBottom s1#  of { (# s2#, marr'# #) ->
651     let copy i# s3# | i# ==# n# = s3#
652                     | otherwise =
653             case readArray# marr# i# s3# of { (# s4#, e #) ->
654             case writeArray# marr'# i# e s4# of { s5# ->
655             copy (i# +# 1#) s5# }} in
656     case copy 0# s2#                    of { s3# ->
657     case unsafeFreezeArray# marr'# s3#  of { (# s4#, arr# #) ->
658     (# s4#, Array l u arr# #) }}}}
659
660 {-# INLINE unsafeFreezeSTArray #-}
661 unsafeFreezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
662 unsafeFreezeSTArray (STArray l u marr#) = ST $ \s1# ->
663     case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
664     (# s2#, Array l u arr# #) }
665
666 thawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
667 thawSTArray (Array l u arr#) = ST $ \s1# ->
668     case rangeSize (l,u)                of { I# n# ->
669     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
670     let copy i# s3# | i# ==# n# = s3#
671                     | otherwise =
672             case indexArray# arr# i#    of { (# e #) ->
673             case writeArray# marr# i# e s3# of { s4# ->
674             copy (i# +# 1#) s4# }} in
675     case copy 0# s2#                    of { s3# ->
676     (# s3#, STArray l u marr# #) }}}
677
678 {-# INLINE unsafeThawSTArray #-}
679 unsafeThawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
680 unsafeThawSTArray (Array l u arr#) = ST $ \s1# ->
681     case unsafeThawArray# arr# s1#      of { (# s2#, marr# #) ->
682     (# s2#, STArray l u marr# #) }
683 \end{code}