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