Remove datatype contexts from base
[ghc-base.git] / GHC / Arr.lhs
1 \begin{code}
2 {-# LANGUAGE NoImplicitPrelude, NoBangPatterns, MagicHash, UnboxedTuples #-}
3 {-# OPTIONS_GHC -funbox-strict-fields #-}
4 {-# OPTIONS_HADDOCK hide #-}
5
6 -----------------------------------------------------------------------------
7 -- |
8 -- Module      :  GHC.Arr
9 -- Copyright   :  (c) The University of Glasgow, 1994-2000
10 -- License     :  see libraries/base/LICENSE
11 -- 
12 -- Maintainer  :  cvs-ghc@haskell.org
13 -- Stability   :  internal
14 -- Portability :  non-portable (GHC extensions)
15 --
16 -- GHC\'s array implementation.
17 -- 
18 -----------------------------------------------------------------------------
19
20 -- #hide
21 module GHC.Arr where
22
23 import GHC.Enum
24 import GHC.Num
25 import GHC.ST
26 import GHC.Base
27 import GHC.List
28 import GHC.Show
29
30 infixl 9  !, //
31
32 default ()
33 \end{code}
34
35
36 %*********************************************************
37 %*                                                      *
38 \subsection{The @Ix@ class}
39 %*                                                      *
40 %*********************************************************
41
42 \begin{code}
43 -- | The 'Ix' class is used to map a contiguous subrange of values in
44 -- a type onto integers.  It is used primarily for array indexing
45 -- (see the array package).
46 --
47 -- The first argument @(l,u)@ of each of these operations is a pair
48 -- specifying the lower and upper bounds of a contiguous subrange of values.
49 --
50 -- An implementation is entitled to assume the following laws about these
51 -- operations:
52 --
53 -- * @'inRange' (l,u) i == 'elem' i ('range' (l,u))@ @ @
54 --
55 -- * @'range' (l,u) '!!' 'index' (l,u) i == i@, when @'inRange' (l,u) i@
56 --
57 -- * @'map' ('index' (l,u)) ('range' (l,u))) == [0..'rangeSize' (l,u)-1]@ @ @
58 --
59 -- * @'rangeSize' (l,u) == 'length' ('range' (l,u))@ @ @
60 --
61 -- Minimal complete instance: 'range', 'index' and 'inRange'.
62 --
63 class (Ord a) => Ix a where
64     -- | The list of values in the subrange defined by a bounding pair.
65     range               :: (a,a) -> [a]
66     -- | The position of a subscript in the subrange.
67     index               :: (a,a) -> a -> Int
68     -- | Like 'index', but without checking that the value is in range.
69     unsafeIndex         :: (a,a) -> a -> Int
70     -- | Returns 'True' the given subscript lies in the range defined
71     -- the bounding pair.
72     inRange             :: (a,a) -> a -> Bool
73     -- | The size of the subrange defined by a bounding pair.
74     rangeSize           :: (a,a) -> Int
75     -- | like 'rangeSize', but without checking that the upper bound is
76     -- in range.
77     unsafeRangeSize     :: (a,a) -> Int
78
79         -- Must specify one of index, unsafeIndex
80
81         -- 'index' is typically over-ridden in instances, with essentially
82         -- the same code, but using indexError instead of hopelessIndexError
83         -- Reason: we have 'Show' at the instances
84     {-# INLINE index #-}  -- See Note [Inlining index]
85     index b i | inRange b i = unsafeIndex b i   
86               | otherwise   = hopelessIndexError
87
88     unsafeIndex b i = index b i
89
90     rangeSize b@(_l,h) | inRange b h = unsafeIndex b h + 1
91                        | otherwise   = 0        -- This case is only here to
92                                                 -- check for an empty range
93         -- NB: replacing (inRange b h) by (l <= h) fails for
94         --     tuples.  E.g.  (1,2) <= (2,1) but the range is empty
95
96     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
97 \end{code}
98
99 Note that the following is NOT right
100         rangeSize (l,h) | l <= h    = index b h + 1
101                         | otherwise = 0
102
103 Because it might be the case that l<h, but the range
104 is nevertheless empty.  Consider
105         ((1,2),(2,1))
106 Here l<h, but the second index ranges from 2..1 and
107 hence is empty
108
109 %*********************************************************
110 %*                                                      *
111 \subsection{Instances of @Ix@}
112 %*                                                      *
113 %*********************************************************
114
115 Note [Inlining index]
116 ~~~~~~~~~~~~~~~~~~~~~
117 We inline the 'index' operation, 
118
119  * Partly because it generates much faster code 
120    (although bigger); see Trac #1216
121
122  * Partly because it exposes the bounds checks to the simplifier which
123    might help a big.
124
125 If you make a per-instance index method, you may consider inlining it.
126
127 Note [Double bounds-checking of index values]
128 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
129 When you index an array, a!x, there are two possible bounds checks we might make:
130
131   (A) Check that (inRange (bounds a) x) holds.  
132
133       (A) is checked in the method for 'index'
134
135   (B) Check that (index (bounds a) x) lies in the range 0..n, 
136       where n is the size of the underlying array
137
138       (B) is checked in the top-level function (!), in safeIndex.
139
140 Of course it *should* be the case that (A) holds iff (B) holds, but that 
141 is a property of the particular instances of index, bounds, and inRange,
142 so GHC cannot guarantee it.
143
144  * If you do (A) and not (B), then you might get a seg-fault, 
145    by indexing at some bizarre location.  Trac #1610
146
147  * If you do (B) but not (A), you may get no complaint when you index
148    an array out of its semantic bounds.  Trac #2120
149
150 At various times we have had (A) and not (B), or (B) and not (A); both
151 led to complaints.  So now we implement *both* checks (Trac #2669).
152
153 For 1-d, 2-d, and 3-d arrays of Int we have specialised instances to avoid this.
154
155 Note [Out-of-bounds error messages]
156 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
157 The default method for 'index' generates hoplelessIndexError, because
158 Ix doesn't have Show as a superclass.  For particular base types we
159 can do better, so we override the default method for index.
160
161 \begin{code}
162 -- Abstract these errors from the relevant index functions so that
163 -- the guts of the function will be small enough to inline.
164
165 {-# NOINLINE indexError #-}
166 indexError :: Show a => (a,a) -> a -> String -> b
167 indexError rng i tp
168   = error (showString "Ix{" . showString tp . showString "}.index: Index " .
169            showParen True (showsPrec 0 i) .
170            showString " out of range " $
171            showParen True (showsPrec 0 rng) "")
172
173 hopelessIndexError :: Int -- Try to use 'indexError' instead!
174 hopelessIndexError = error "Error in array index"
175
176 ----------------------------------------------------------------------
177 instance  Ix Char  where
178     {-# INLINE range #-}
179     range (m,n) = [m..n]
180
181     {-# INLINE unsafeIndex #-}
182     unsafeIndex (m,_n) i = fromEnum i - fromEnum m
183
184     {-# INLINE index #-}  -- See Note [Out-of-bounds error messages]
185                           -- and Note [Inlining index]
186     index b i | inRange b i =  unsafeIndex b i
187               | otherwise   =  indexError b i "Char"
188
189     inRange (m,n) i     =  m <= i && i <= n
190
191 ----------------------------------------------------------------------
192 instance  Ix Int  where
193     {-# INLINE range #-}
194         -- The INLINE stops the build in the RHS from getting inlined,
195         -- so that callers can fuse with the result of range
196     range (m,n) = [m..n]
197
198     {-# INLINE unsafeIndex #-}
199     unsafeIndex (m,_n) i = i - m
200
201     {-# INLINE index #-}  -- See Note [Out-of-bounds error messages]
202                           -- and Note [Inlining index]
203     index b i | inRange b i =  unsafeIndex b i
204               | otherwise   =  indexError b i "Int"
205
206     {-# INLINE inRange #-}
207     inRange (I# m,I# n) (I# i) =  m <=# i && i <=# n
208
209 ----------------------------------------------------------------------
210 instance  Ix Integer  where
211     {-# INLINE range #-}
212     range (m,n) = [m..n]
213
214     {-# INLINE unsafeIndex #-}
215     unsafeIndex (m,_n) i   = fromInteger (i - m)
216
217     {-# INLINE index #-}  -- See Note [Out-of-bounds error messages]
218                           -- and Note [Inlining index]
219     index b i | inRange b i =  unsafeIndex b i
220               | otherwise   =  indexError b i "Integer"
221
222     inRange (m,n) i     =  m <= i && i <= n
223
224 ----------------------------------------------------------------------
225 instance Ix Bool where -- as derived
226     {-# INLINE range #-}
227     range (m,n) = [m..n]
228
229     {-# INLINE unsafeIndex #-}
230     unsafeIndex (l,_) i = fromEnum i - fromEnum l
231
232     {-# INLINE index #-}  -- See Note [Out-of-bounds error messages]
233                           -- and Note [Inlining index]
234     index b i | inRange b i =  unsafeIndex b i
235               | otherwise   =  indexError b i "Bool"
236
237     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
238
239 ----------------------------------------------------------------------
240 instance Ix Ordering where -- as derived
241     {-# INLINE range #-}
242     range (m,n) = [m..n]
243
244     {-# INLINE unsafeIndex #-}
245     unsafeIndex (l,_) i = fromEnum i - fromEnum l
246
247     {-# INLINE index #-}  -- See Note [Out-of-bounds error messages]
248                           -- and Note [Inlining index]
249     index b i | inRange b i =  unsafeIndex b i
250               | otherwise   =  indexError b i "Ordering"
251
252     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
253
254 ----------------------------------------------------------------------
255 instance Ix () where
256     {-# INLINE range #-}
257     range   ((), ())    = [()]
258     {-# INLINE unsafeIndex #-}
259     unsafeIndex   ((), ()) () = 0
260     {-# INLINE inRange #-}
261     inRange ((), ()) () = True
262
263     {-# INLINE index #-}  -- See Note [Inlining index]
264     index b i = unsafeIndex b i
265
266 ----------------------------------------------------------------------
267 instance (Ix a, Ix b) => Ix (a, b) where -- as derived
268     {-# SPECIALISE instance Ix (Int,Int) #-}
269
270     {-# INLINE range #-}
271     range ((l1,l2),(u1,u2)) =
272       [ (i1,i2) | i1 <- range (l1,u1), i2 <- range (l2,u2) ]
273
274     {-# INLINE unsafeIndex #-}
275     unsafeIndex ((l1,l2),(u1,u2)) (i1,i2) =
276       unsafeIndex (l1,u1) i1 * unsafeRangeSize (l2,u2) + unsafeIndex (l2,u2) i2
277
278     {-# INLINE inRange #-}
279     inRange ((l1,l2),(u1,u2)) (i1,i2) =
280       inRange (l1,u1) i1 && inRange (l2,u2) i2
281
282     -- Default method for index
283
284 ----------------------------------------------------------------------
285 instance  (Ix a1, Ix a2, Ix a3) => Ix (a1,a2,a3)  where
286     {-# SPECIALISE instance Ix (Int,Int,Int) #-}
287
288     range ((l1,l2,l3),(u1,u2,u3)) =
289         [(i1,i2,i3) | i1 <- range (l1,u1),
290                       i2 <- range (l2,u2),
291                       i3 <- range (l3,u3)]
292
293     unsafeIndex ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
294       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
295       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
296       unsafeIndex (l1,u1) i1))
297
298     inRange ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
299       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
300       inRange (l3,u3) i3
301
302     -- Default method for index
303
304 ----------------------------------------------------------------------
305 instance  (Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1,a2,a3,a4)  where
306     range ((l1,l2,l3,l4),(u1,u2,u3,u4)) =
307       [(i1,i2,i3,i4) | i1 <- range (l1,u1),
308                        i2 <- range (l2,u2),
309                        i3 <- range (l3,u3),
310                        i4 <- range (l4,u4)]
311
312     unsafeIndex ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
313       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
314       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
315       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
316       unsafeIndex (l1,u1) i1)))
317
318     inRange ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
319       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
320       inRange (l3,u3) i3 && inRange (l4,u4) i4
321
322     -- Default method for index
323
324 instance  (Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1,a2,a3,a4,a5)  where
325     range ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) =
326       [(i1,i2,i3,i4,i5) | i1 <- range (l1,u1),
327                           i2 <- range (l2,u2),
328                           i3 <- range (l3,u3),
329                           i4 <- range (l4,u4),
330                           i5 <- range (l5,u5)]
331
332     unsafeIndex ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
333       unsafeIndex (l5,u5) i5 + unsafeRangeSize (l5,u5) * (
334       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
335       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
336       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
337       unsafeIndex (l1,u1) i1))))
338
339     inRange ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
340       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
341       inRange (l3,u3) i3 && inRange (l4,u4) i4 && 
342       inRange (l5,u5) i5
343
344     -- Default method for index
345 \end{code}
346
347 %*********************************************************
348 %*                                                      *
349 \subsection{The @Array@ types}
350 %*                                                      *
351 %*********************************************************
352
353 \begin{code}
354 type IPr = (Int, Int)
355
356 -- | The type of immutable non-strict (boxed) arrays
357 -- with indices in @i@ and elements in @e@.
358 data 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 non-strict 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 -- NB: put the \s after the "=" so that 'fill' 
461 --     inlines when applied to three args 
462 fill marr# (I# i#, e) next 
463  = \s1# -> case writeArray# marr# i# e s1# of 
464              s2# -> next s2# 
465
466 {-# INLINE done #-}
467 done :: Ix i => i -> i -> Int -> MutableArray# s e -> STRep s (Array i e)
468 -- See NB on 'fill'
469 done l u n marr# 
470   = \s1# -> case unsafeFreezeArray# marr# s1# of
471               (# s2#, arr# #) -> (# s2#, Array l u n arr# #)
472
473 -- This is inefficient and I'm not sure why:
474 -- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es)
475 -- The code below is better. It still doesn't enable foldr/build
476 -- transformation on the list of elements; I guess it's impossible
477 -- using mechanisms currently available.
478
479 -- | Construct an array from a pair of bounds and a list of values in
480 -- index order.
481 {-# INLINE listArray #-}
482 listArray :: Ix i => (i,i) -> [e] -> Array i e
483 listArray (l,u) es = runST (ST $ \s1# ->
484     case safeRangeSize (l,u)            of { n@(I# n#) ->
485     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
486     let fillFromList i# xs s3# | i# ==# n# = s3#
487                                | otherwise = case xs of
488             []   -> s3#
489             y:ys -> case writeArray# marr# i# y s3# of { s4# ->
490                     fillFromList (i# +# 1#) ys s4# } in
491     case fillFromList 0# es s2#         of { s3# ->
492     done l u n marr# s3# }}})
493
494 -- | The value at the given index in an array.
495 {-# INLINE (!) #-}
496 (!) :: Ix i => Array i e -> i -> e
497 arr@(Array l u n _) ! i = unsafeAt arr $ safeIndex (l,u) n i
498
499 {-# INLINE safeRangeSize #-}
500 safeRangeSize :: Ix i => (i, i) -> Int
501 safeRangeSize (l,u) = let r = rangeSize (l, u)
502                       in if r < 0 then negRange
503                                   else r
504
505 -- Don't inline this error message everywhere!!
506 negRange :: Int   -- Uninformative, but Ix does not provide Show
507 negRange = error "Negative range size"
508
509 {-# INLINE[1] safeIndex #-}
510 -- See Note [Double bounds-checking of index values]
511 -- Inline *after* (!) so the rules can fire
512 safeIndex :: Ix i => (i, i) -> Int -> i -> Int
513 safeIndex (l,u) n i = let i' = index (l,u) i
514                       in if (0 <= i') && (i' < n)
515                          then i'
516                          else badSafeIndex i' n
517
518 -- See Note [Double bounds-checking of index values]
519 {-# RULES
520 "safeIndex/I"       safeIndex = lessSafeIndex :: (Int,Int) -> Int -> Int -> Int
521 "safeIndex/(I,I)"   safeIndex = lessSafeIndex :: ((Int,Int),(Int,Int)) -> Int -> (Int,Int) -> Int
522 "safeIndex/(I,I,I)" safeIndex = lessSafeIndex :: ((Int,Int,Int),(Int,Int,Int)) -> Int -> (Int,Int,Int) -> Int
523   #-}
524
525 lessSafeIndex :: Ix i => (i, i) -> Int -> i -> Int
526 -- See Note [Double bounds-checking of index values]
527 -- Do only (A), the semantic check
528 lessSafeIndex (l,u) _ i = index (l,u) i  
529
530 -- Don't inline this long error message everywhere!!
531 badSafeIndex :: Int -> Int -> Int
532 badSafeIndex i' n = error ("Error in array index; " ++ show i' ++
533                         " not in range [0.." ++ show n ++ ")")
534
535 {-# INLINE unsafeAt #-}
536 unsafeAt :: Ix i => Array i e -> Int -> e
537 unsafeAt (Array _ _ _ arr#) (I# i#) =
538     case indexArray# arr# i# of (# e #) -> e
539
540 -- | The bounds with which an array was constructed.
541 {-# INLINE bounds #-}
542 bounds :: Ix i => Array i e -> (i,i)
543 bounds (Array l u _ _) = (l,u)
544
545 -- | The number of elements in the array.
546 {-# INLINE numElements #-}
547 numElements :: Ix i => Array i e -> Int
548 numElements (Array _ _ n _) = n
549
550 -- | The list of indices of an array in ascending order.
551 {-# INLINE indices #-}
552 indices :: Ix i => Array i e -> [i]
553 indices (Array l u _ _) = range (l,u)
554
555 -- | The list of elements of an array in index order.
556 {-# INLINE elems #-}
557 elems :: Ix i => Array i e -> [e]
558 elems arr@(Array _ _ n _) =
559     [unsafeAt arr i | i <- [0 .. n - 1]]
560
561 -- | The list of associations of an array in index order.
562 {-# INLINE assocs #-}
563 assocs :: Ix i => Array i e -> [(i, e)]
564 assocs arr@(Array l u _ _) =
565     [(i, arr ! i) | i <- range (l,u)]
566
567 -- | The 'accumArray' function deals with repeated indices in the association
568 -- list using an /accumulating function/ which combines the values of
569 -- associations with the same index.
570 -- For example, given a list of values of some index type, @hist@
571 -- produces a histogram of the number of occurrences of each index within
572 -- a specified range:
573 --
574 -- > hist :: (Ix a, Num b) => (a,a) -> [a] -> Array a b
575 -- > hist bnds is = accumArray (+) 0 bnds [(i, 1) | i<-is, inRange bnds i]
576 --
577 -- If the accumulating function is strict, then 'accumArray' is strict in
578 -- the values, as well as the indices, in the association list.  Thus,
579 -- unlike ordinary arrays built with 'array', accumulated arrays should
580 -- not in general be recursive.
581 {-# INLINE accumArray #-}
582 accumArray :: Ix i
583         => (e -> a -> e)        -- ^ accumulating function
584         -> e                    -- ^ initial value
585         -> (i,i)                -- ^ bounds of the array
586         -> [(i, a)]             -- ^ association list
587         -> Array i e
588 accumArray f initial (l,u) ies =
589     let n = safeRangeSize (l,u)
590     in unsafeAccumArray' f initial (l,u) n
591                          [(safeIndex (l,u) n i, e) | (i, e) <- ies]
592
593 {-# INLINE unsafeAccumArray #-}
594 unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i,i) -> [(Int, a)] -> Array i e
595 unsafeAccumArray f initial b ies = unsafeAccumArray' f initial b (rangeSize b) ies
596
597 {-# INLINE unsafeAccumArray' #-}
598 unsafeAccumArray' :: Ix i => (e -> a -> e) -> e -> (i,i) -> Int -> [(Int, a)] -> Array i e
599 unsafeAccumArray' f initial (l,u) n@(I# n#) ies = runST (ST $ \s1# ->
600     case newArray# n# initial s1#          of { (# s2#, marr# #) ->
601     foldr (adjust f marr#) (done l u n marr#) ies s2# })
602
603 {-# INLINE adjust #-}
604 adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
605 -- See NB on 'fill'
606 adjust f marr# (I# i#, new) next
607   = \s1# -> case readArray# marr# i# s1# of
608                 (# s2#, old #) ->
609                     case writeArray# marr# i# (f old new) s2# of
610                         s3# -> next s3#
611
612 -- | Constructs an array identical to the first argument except that it has
613 -- been updated by the associations in the right argument.
614 -- For example, if @m@ is a 1-origin, @n@ by @n@ matrix, then
615 --
616 -- > m//[((i,i), 0) | i <- [1..n]]
617 --
618 -- is the same matrix, except with the diagonal zeroed.
619 --
620 -- Repeated indices in the association list are handled as for 'array':
621 -- Haskell 98 specifies that the resulting array is undefined (i.e. bottom),
622 -- but GHC's implementation uses the last association for each index.
623 {-# INLINE (//) #-}
624 (//) :: Ix i => Array i e -> [(i, e)] -> Array i e
625 arr@(Array l u n _) // ies =
626     unsafeReplace arr [(safeIndex (l,u) n i, e) | (i, e) <- ies]
627
628 {-# INLINE unsafeReplace #-}
629 unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e
630 unsafeReplace arr ies = runST (do
631     STArray l u n marr# <- thawSTArray arr
632     ST (foldr (fill marr#) (done l u n marr#) ies))
633
634 -- | @'accum' f@ takes an array and an association list and accumulates
635 -- pairs from the list into the array with the accumulating function @f@.
636 -- Thus 'accumArray' can be defined using 'accum':
637 --
638 -- > accumArray f z b = accum f (array b [(i, z) | i <- range b])
639 --
640 {-# INLINE accum #-}
641 accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
642 accum f arr@(Array l u n _) ies =
643     unsafeAccum f arr [(safeIndex (l,u) n i, e) | (i, e) <- ies]
644
645 {-# INLINE unsafeAccum #-}
646 unsafeAccum :: Ix i => (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
647 unsafeAccum f arr ies = runST (do
648     STArray l u n marr# <- thawSTArray arr
649     ST (foldr (adjust f marr#) (done l u n marr#) ies))
650
651 {-# INLINE amap #-}
652 amap :: Ix i => (a -> b) -> Array i a -> Array i b
653 amap f arr@(Array l u n _) =
654     unsafeArray' (l,u) n [(i, f (unsafeAt arr i)) | i <- [0 .. n - 1]]
655
656 -- | 'ixmap' allows for transformations on array indices.
657 -- It may be thought of as providing function composition on the right
658 -- with the mapping that the original array embodies.
659 --
660 -- A similar transformation of array values may be achieved using 'fmap'
661 -- from the 'Array' instance of the 'Functor' class.
662 {-# INLINE ixmap #-}
663 ixmap :: (Ix i, Ix j) => (i,i) -> (i -> j) -> Array j e -> Array i e
664 ixmap (l,u) f arr =
665     array (l,u) [(i, arr ! f i) | i <- range (l,u)]
666
667 {-# INLINE eqArray #-}
668 eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool
669 eqArray arr1@(Array l1 u1 n1 _) arr2@(Array l2 u2 n2 _) =
670     if n1 == 0 then n2 == 0 else
671     l1 == l2 && u1 == u2 &&
672     and [unsafeAt arr1 i == unsafeAt arr2 i | i <- [0 .. n1 - 1]]
673
674 {-# INLINE cmpArray #-}
675 cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering
676 cmpArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
677
678 {-# INLINE cmpIntArray #-}
679 cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering
680 cmpIntArray arr1@(Array l1 u1 n1 _) arr2@(Array l2 u2 n2 _) =
681     if n1 == 0 then
682         if n2 == 0 then EQ else LT
683     else if n2 == 0 then GT
684     else case compare l1 l2 of
685              EQ    -> foldr cmp (compare u1 u2) [0 .. (n1 `min` n2) - 1]
686              other -> other
687   where
688     cmp i rest = case compare (unsafeAt arr1 i) (unsafeAt arr2 i) of
689         EQ    -> rest
690         other -> other
691
692 {-# RULES "cmpArray/Int" cmpArray = cmpIntArray #-}
693 \end{code}
694
695
696 %*********************************************************
697 %*                                                      *
698 \subsection{Array instances}
699 %*                                                      *
700 %*********************************************************
701
702 \begin{code}
703 instance Ix i => Functor (Array i) where
704     fmap = amap
705
706 instance (Ix i, Eq e) => Eq (Array i e) where
707     (==) = eqArray
708
709 instance (Ix i, Ord e) => Ord (Array i e) where
710     compare = cmpArray
711
712 instance (Ix a, Show a, Show b) => Show (Array a b) where
713     showsPrec p a =
714         showParen (p > appPrec) $
715         showString "array " .
716         showsPrec appPrec1 (bounds a) .
717         showChar ' ' .
718         showsPrec appPrec1 (assocs a)
719         -- Precedence of 'array' is the precedence of application
720
721 -- The Read instance is in GHC.Read
722 \end{code}
723
724
725 %*********************************************************
726 %*                                                      *
727 \subsection{Operations on mutable arrays}
728 %*                                                      *
729 %*********************************************************
730
731 Idle ADR question: What's the tradeoff here between flattening these
732 datatypes into @STArray ix ix (MutableArray# s elt)@ and using
733 it as is?  As I see it, the former uses slightly less heap and
734 provides faster access to the individual parts of the bounds while the
735 code used has the benefit of providing a ready-made @(lo, hi)@ pair as
736 required by many array-related functions.  Which wins? Is the
737 difference significant (probably not).
738
739 Idle AJG answer: When I looked at the outputted code (though it was 2
740 years ago) it seems like you often needed the tuple, and we build
741 it frequently. Now we've got the overloading specialiser things
742 might be different, though.
743
744 \begin{code}
745 {-# INLINE newSTArray #-}
746 newSTArray :: Ix i => (i,i) -> e -> ST s (STArray s i e)
747 newSTArray (l,u) initial = ST $ \s1# ->
748     case safeRangeSize (l,u)            of { n@(I# n#) ->
749     case newArray# n# initial s1#       of { (# s2#, marr# #) ->
750     (# s2#, STArray l u n marr# #) }}
751
752 {-# INLINE boundsSTArray #-}
753 boundsSTArray :: STArray s i e -> (i,i)  
754 boundsSTArray (STArray l u _ _) = (l,u)
755
756 {-# INLINE numElementsSTArray #-}
757 numElementsSTArray :: STArray s i e -> Int
758 numElementsSTArray (STArray _ _ n _) = n
759
760 {-# INLINE readSTArray #-}
761 readSTArray :: Ix i => STArray s i e -> i -> ST s e
762 readSTArray marr@(STArray l u n _) i =
763     unsafeReadSTArray marr (safeIndex (l,u) n i)
764
765 {-# INLINE unsafeReadSTArray #-}
766 unsafeReadSTArray :: Ix i => STArray s i e -> Int -> ST s e
767 unsafeReadSTArray (STArray _ _ _ marr#) (I# i#)
768     = ST $ \s1# -> readArray# marr# i# s1#
769
770 {-# INLINE writeSTArray #-}
771 writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s () 
772 writeSTArray marr@(STArray l u n _) i e =
773     unsafeWriteSTArray marr (safeIndex (l,u) n i) e
774
775 {-# INLINE unsafeWriteSTArray #-}
776 unsafeWriteSTArray :: Ix i => STArray s i e -> Int -> e -> ST s () 
777 unsafeWriteSTArray (STArray _ _ _ marr#) (I# i#) e = ST $ \s1# ->
778     case writeArray# marr# i# e s1# of
779         s2# -> (# s2#, () #)
780 \end{code}
781
782
783 %*********************************************************
784 %*                                                      *
785 \subsection{Moving between mutable and immutable}
786 %*                                                      *
787 %*********************************************************
788
789 \begin{code}
790 freezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
791 freezeSTArray (STArray l u n@(I# n#) marr#) = ST $ \s1# ->
792     case newArray# n# arrEleBottom s1#  of { (# s2#, marr'# #) ->
793     let copy i# s3# | i# ==# n# = s3#
794                     | otherwise =
795             case readArray# marr# i# s3# of { (# s4#, e #) ->
796             case writeArray# marr'# i# e s4# of { s5# ->
797             copy (i# +# 1#) s5# }} in
798     case copy 0# s2#                    of { s3# ->
799     case unsafeFreezeArray# marr'# s3#  of { (# s4#, arr# #) ->
800     (# s4#, Array l u n arr# #) }}}
801
802 {-# INLINE unsafeFreezeSTArray #-}
803 unsafeFreezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
804 unsafeFreezeSTArray (STArray l u n marr#) = ST $ \s1# ->
805     case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
806     (# s2#, Array l u n arr# #) }
807
808 thawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
809 thawSTArray (Array l u n@(I# n#) arr#) = ST $ \s1# ->
810     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
811     let copy i# s3# | i# ==# n# = s3#
812                     | otherwise =
813             case indexArray# arr# i#    of { (# e #) ->
814             case writeArray# marr# i# e s3# of { s4# ->
815             copy (i# +# 1#) s4# }} in
816     case copy 0# s2#                    of { s3# ->
817     (# s3#, STArray l u n marr# #) }}
818
819 {-# INLINE unsafeThawSTArray #-}
820 unsafeThawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
821 unsafeThawSTArray (Array l u n arr#) = ST $ \s1# ->
822     case unsafeThawArray# arr# s1#      of { (# s2#, marr# #) ->
823     (# s2#, STArray l u n marr# #) }
824 \end{code}