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