[project @ 2002-04-26 12:58:45 by simonmar]
[ghc-base.git] / GHC / Arr.lhs
1 \begin{code}
2 {-# OPTIONS -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.Arr
6 -- Copyright   :  (c) The University of Glasgow, 1994-2000
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC extensions)
12 --
13 -- GHC\'s array implementation.
14 -- 
15 -----------------------------------------------------------------------------
16
17 module GHC.Arr where
18
19 import {-# SOURCE #-} GHC.Err ( error )
20 import GHC.Enum
21 import GHC.Num
22 import GHC.ST
23 import GHC.Base
24 import GHC.List
25 import GHC.Show
26
27 infixl 9  !, //
28
29 default ()
30 \end{code}
31
32
33 %*********************************************************
34 %*                                                      *
35 \subsection{The @Ix@ class}
36 %*                                                      *
37 %*********************************************************
38
39 \begin{code}
40 class (Ord a) => Ix a where
41     range               :: (a,a) -> [a]
42     index, unsafeIndex  :: (a,a) -> a -> Int
43     inRange             :: (a,a) -> a -> Bool
44     rangeSize           :: (a,a) -> Int
45     unsafeRangeSize     :: (a,a) -> Int
46
47         -- Must specify one of index, unsafeIndex
48     index b i | inRange b i = unsafeIndex b i
49               | otherwise   = error "Error in array index"
50     unsafeIndex b i = index b i
51
52         -- As long as you don't override the default rangeSize, 
53         -- you can specify unsafeRangeSize as follows, to speed up
54         -- some operations:
55         --
56         --    unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
57         --
58     rangeSize b@(_l,h) | inRange b h = unsafeIndex b h + 1
59                        | otherwise   = 0
60     unsafeRangeSize b = rangeSize b
61 \end{code}
62
63 Note that the following is NOT right
64         rangeSize (l,h) | l <= h    = index b h + 1
65                         | otherwise = 0
66
67 Because it might be the case that l<h, but the range
68 is nevertheless empty.  Consider
69         ((1,2),(2,1))
70 Here l<h, but the second index ranges from 2..1 and
71 hence is empty
72
73 %*********************************************************
74 %*                                                      *
75 \subsection{Instances of @Ix@}
76 %*                                                      *
77 %*********************************************************
78
79 \begin{code}
80 -- abstract these errors from the relevant index functions so that
81 -- the guts of the function will be small enough to inline.
82
83 {-# NOINLINE indexError #-}
84 indexError :: Show a => (a,a) -> a -> String -> b
85 indexError rng i tp
86   = error (showString "Ix{" . showString tp . showString "}.index: Index " .
87            showParen True (showsPrec 0 i) .
88            showString " out of range " $
89            showParen True (showsPrec 0 rng) "")
90
91 ----------------------------------------------------------------------
92 instance  Ix Char  where
93     {-# INLINE range #-}
94     range (m,n) = [m..n]
95
96     {-# INLINE unsafeIndex #-}
97     unsafeIndex (m,_n) i = fromEnum i - fromEnum m
98
99     index b i | inRange b i =  unsafeIndex b i
100               | otherwise   =  indexError b i "Char"
101
102     inRange (m,n) i     =  m <= i && i <= n
103
104     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
105
106 ----------------------------------------------------------------------
107 instance  Ix Int  where
108     {-# INLINE range #-}
109         -- The INLINE stops the build in the RHS from getting inlined,
110         -- so that callers can fuse with the result of range
111     range (m,n) = [m..n]
112
113     {-# INLINE unsafeIndex #-}
114     unsafeIndex (m,_n) i = i - m
115
116     index b i | inRange b i =  unsafeIndex b i
117               | otherwise   =  indexError b i "Int"
118
119     {-# INLINE inRange #-}
120     inRange (I# m,I# n) (I# i) =  m <=# i && i <=# n
121
122     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
123
124 ----------------------------------------------------------------------
125 instance  Ix Integer  where
126     {-# INLINE range #-}
127     range (m,n) = [m..n]
128
129     {-# INLINE unsafeIndex #-}
130     unsafeIndex (m,_n) i   = fromInteger (i - m)
131
132     index b i | inRange b i =  unsafeIndex b i
133               | otherwise   =  indexError b i "Integer"
134
135     inRange (m,n) i     =  m <= i && i <= n
136
137     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
138
139 ----------------------------------------------------------------------
140 instance Ix Bool where -- as derived
141     {-# INLINE range #-}
142     range (m,n) = [m..n]
143
144     {-# INLINE unsafeIndex #-}
145     unsafeIndex (l,_) i = fromEnum i - fromEnum l
146
147     index b i | inRange b i =  unsafeIndex b i
148               | otherwise   =  indexError b i "Bool"
149
150     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
151
152     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
153
154 ----------------------------------------------------------------------
155 instance Ix Ordering where -- as derived
156     {-# INLINE range #-}
157     range (m,n) = [m..n]
158
159     {-# INLINE unsafeIndex #-}
160     unsafeIndex (l,_) i = fromEnum i - fromEnum l
161
162     index b i | inRange b i =  unsafeIndex b i
163               | otherwise   =  indexError b i "Ordering"
164
165     inRange (l,u) i = fromEnum i >= fromEnum l && fromEnum i <= fromEnum u
166
167     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
168
169 ----------------------------------------------------------------------
170 instance Ix () where
171     {-# INLINE range #-}
172     range   ((), ())    = [()]
173     {-# INLINE unsafeIndex #-}
174     unsafeIndex   ((), ()) () = 0
175     {-# INLINE inRange #-}
176     inRange ((), ()) () = True
177     {-# INLINE index #-}
178     index b i = unsafeIndex b i
179
180     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
181
182 ----------------------------------------------------------------------
183 instance (Ix a, Ix b) => Ix (a, b) where -- as derived
184     {-# SPECIALISE instance Ix (Int,Int) #-}
185
186     {- INLINE range #-}
187     range ((l1,l2),(u1,u2)) =
188       [ (i1,i2) | i1 <- range (l1,u1), i2 <- range (l2,u2) ]
189
190     {- INLINE unsafeIndex #-}
191     unsafeIndex ((l1,l2),(u1,u2)) (i1,i2) =
192       unsafeIndex (l1,u1) i1 * unsafeRangeSize (l2,u2) + unsafeIndex (l2,u2) i2
193
194     {- INLINE inRange #-}
195     inRange ((l1,l2),(u1,u2)) (i1,i2) =
196       inRange (l1,u1) i1 && inRange (l2,u2) i2
197
198     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
199
200     -- Default method for index
201
202 ----------------------------------------------------------------------
203 instance  (Ix a1, Ix a2, Ix a3) => Ix (a1,a2,a3)  where
204     {-# SPECIALISE instance Ix (Int,Int,Int) #-}
205
206     range ((l1,l2,l3),(u1,u2,u3)) =
207         [(i1,i2,i3) | i1 <- range (l1,u1),
208                       i2 <- range (l2,u2),
209                       i3 <- range (l3,u3)]
210
211     unsafeIndex ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
212       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
213       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
214       unsafeIndex (l1,u1) i1))
215
216     inRange ((l1,l2,l3),(u1,u2,u3)) (i1,i2,i3) =
217       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
218       inRange (l3,u3) i3
219
220     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
221
222     -- Default method for index
223
224 ----------------------------------------------------------------------
225 instance  (Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1,a2,a3,a4)  where
226     range ((l1,l2,l3,l4),(u1,u2,u3,u4)) =
227       [(i1,i2,i3,i4) | i1 <- range (l1,u1),
228                        i2 <- range (l2,u2),
229                        i3 <- range (l3,u3),
230                        i4 <- range (l4,u4)]
231
232     unsafeIndex ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
233       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
234       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
235       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
236       unsafeIndex (l1,u1) i1)))
237
238     inRange ((l1,l2,l3,l4),(u1,u2,u3,u4)) (i1,i2,i3,i4) =
239       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
240       inRange (l3,u3) i3 && inRange (l4,u4) i4
241
242     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
243
244     -- Default method for index
245
246 instance  (Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1,a2,a3,a4,a5)  where
247     range ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) =
248       [(i1,i2,i3,i4,i5) | i1 <- range (l1,u1),
249                           i2 <- range (l2,u2),
250                           i3 <- range (l3,u3),
251                           i4 <- range (l4,u4),
252                           i5 <- range (l5,u5)]
253
254     unsafeIndex ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
255       unsafeIndex (l5,u5) i5 + unsafeRangeSize (l5,u5) * (
256       unsafeIndex (l4,u4) i4 + unsafeRangeSize (l4,u4) * (
257       unsafeIndex (l3,u3) i3 + unsafeRangeSize (l3,u3) * (
258       unsafeIndex (l2,u2) i2 + unsafeRangeSize (l2,u2) * (
259       unsafeIndex (l1,u1) i1))))
260
261     inRange ((l1,l2,l3,l4,l5),(u1,u2,u3,u4,u5)) (i1,i2,i3,i4,i5) =
262       inRange (l1,u1) i1 && inRange (l2,u2) i2 &&
263       inRange (l3,u3) i3 && inRange (l4,u4) i4 && 
264       inRange (l5,u5) i5
265
266     unsafeRangeSize b@(_l,h) = unsafeIndex b h + 1
267
268     -- Default method for index
269 \end{code}
270
271 %*********************************************************
272 %*                                                      *
273 \subsection{The @Array@ types}
274 %*                                                      *
275 %*********************************************************
276
277 \begin{code}
278 type IPr = (Int, Int)
279
280 data Ix i => Array     i e = Array   !i !i (Array# e)
281 data         STArray s i e = STArray !i !i (MutableArray# s e)
282         -- No Ix context for STArray.  They are stupid,
283         -- and force an Ix context on the equality instance.
284
285 -- Just pointer equality on mutable arrays:
286 instance Eq (STArray s i e) where
287     STArray _ _ arr1# == STArray _ _ arr2# =
288         sameMutableArray# arr1# arr2#
289 \end{code}
290
291
292 %*********************************************************
293 %*                                                      *
294 \subsection{Operations on immutable arrays}
295 %*                                                      *
296 %*********************************************************
297
298 \begin{code}
299 {-# NOINLINE arrEleBottom #-}
300 arrEleBottom :: a
301 arrEleBottom = error "(Array.!): undefined array element"
302
303 {-# INLINE array #-}
304 array :: Ix i => (i,i) -> [(i, e)] -> Array i e
305 array (l,u) ies = unsafeArray (l,u) [(index (l,u) i, e) | (i, e) <- ies]
306
307 {-# INLINE unsafeArray #-}
308 unsafeArray :: Ix i => (i,i) -> [(Int, e)] -> Array i e
309 unsafeArray (l,u) ies = runST (ST $ \s1# ->
310     case rangeSize (l,u)                of { I# n# ->
311     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
312     foldr (fill marr#) (done l u marr#) ies s2# }})
313
314 {-# INLINE fill #-}
315 fill :: MutableArray# s e -> (Int, e) -> STRep s a -> STRep s a
316 fill marr# (I# i#, e) next s1# =
317     case writeArray# marr# i# e s1#     of { s2# ->
318     next s2# }
319
320 {-# INLINE done #-}
321 done :: Ix i => i -> i -> MutableArray# s e -> STRep s (Array i e)
322 done l u marr# s1# =
323     case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
324     (# s2#, Array l u arr# #) }
325
326 -- This is inefficient and I'm not sure why:
327 -- listArray (l,u) es = unsafeArray (l,u) (zip [0 .. rangeSize (l,u) - 1] es)
328 -- The code below is better. It still doesn't enable foldr/build
329 -- transformation on the list of elements; I guess it's impossible
330 -- using mechanisms currently available.
331
332 {-# INLINE listArray #-}
333 listArray :: Ix i => (i,i) -> [e] -> Array i e
334 listArray (l,u) es = runST (ST $ \s1# ->
335     case rangeSize (l,u)                of { I# n# ->
336     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
337     let fillFromList i# xs s3# | i# ==# n# = s3#
338                                | otherwise = case xs of
339             []   -> s3#
340             y:ys -> case writeArray# marr# i# y s3# of { s4# ->
341                     fillFromList (i# +# 1#) ys s4# } in
342     case fillFromList 0# es s2#         of { s3# ->
343     done l u marr# s3# }}})
344
345 {-# INLINE (!) #-}
346 (!) :: Ix i => Array i e -> i -> e
347 arr@(Array l u _) ! i = unsafeAt arr (index (l,u) i)
348
349 {-# INLINE unsafeAt #-}
350 unsafeAt :: Ix i => Array i e -> Int -> e
351 unsafeAt (Array _ _ arr#) (I# i#) =
352     case indexArray# arr# i# of (# e #) -> e
353
354 {-# INLINE bounds #-}
355 bounds :: Ix i => Array i e -> (i,i)
356 bounds (Array l u _) = (l,u)
357
358 {-# INLINE indices #-}
359 indices :: Ix i => Array i e -> [i]
360 indices (Array l u _) = range (l,u)
361
362 {-# INLINE elems #-}
363 elems :: Ix i => Array i e -> [e]
364 elems arr@(Array l u _) =
365     [unsafeAt arr i | i <- [0 .. rangeSize (l,u) - 1]]
366
367 {-# INLINE assocs #-}
368 assocs :: Ix i => Array i e -> [(i, e)]
369 assocs arr@(Array l u _) =
370     [(i, unsafeAt arr (unsafeIndex (l,u) i)) | i <- range (l,u)]
371
372 {-# INLINE accumArray #-}
373 accumArray :: Ix i => (e -> a -> e) -> e -> (i,i) -> [(i, a)] -> Array i e
374 accumArray f init (l,u) ies =
375     unsafeAccumArray f init (l,u) [(index (l,u) i, e) | (i, e) <- ies]
376
377 {-# INLINE unsafeAccumArray #-}
378 unsafeAccumArray :: Ix i => (e -> a -> e) -> e -> (i,i) -> [(Int, a)] -> Array i e
379 unsafeAccumArray f init (l,u) ies = runST (ST $ \s1# ->
380     case rangeSize (l,u)                of { I# n# ->
381     case newArray# n# init s1#          of { (# s2#, marr# #) ->
382     foldr (adjust f marr#) (done l u marr#) ies s2# }})
383
384 {-# INLINE adjust #-}
385 adjust :: (e -> a -> e) -> MutableArray# s e -> (Int, a) -> STRep s b -> STRep s b
386 adjust f marr# (I# i#, new) next s1# =
387     case readArray# marr# i# s1#        of { (# s2#, old #) ->
388     case writeArray# marr# i# (f old new) s2# of { s3# ->
389     next s3# }}
390
391 {-# INLINE (//) #-}
392 (//) :: Ix i => Array i e -> [(i, e)] -> Array i e
393 arr@(Array l u _) // ies =
394     unsafeReplace arr [(index (l,u) i, e) | (i, e) <- ies]
395
396 {-# INLINE unsafeReplace #-}
397 unsafeReplace :: Ix i => Array i e -> [(Int, e)] -> Array i e
398 unsafeReplace arr@(Array l u _) ies = runST (do
399     STArray _ _ marr# <- thawSTArray arr
400     ST (foldr (fill marr#) (done l u marr#) ies))
401
402 {-# INLINE accum #-}
403 accum :: Ix i => (e -> a -> e) -> Array i e -> [(i, a)] -> Array i e
404 accum f arr@(Array l u _) ies =
405     unsafeAccum f arr [(index (l,u) i, e) | (i, e) <- ies]
406
407 {-# INLINE unsafeAccum #-}
408 unsafeAccum :: Ix i => (e -> a -> e) -> Array i e -> [(Int, a)] -> Array i e
409 unsafeAccum f arr@(Array l u _) ies = runST (do
410     STArray _ _ marr# <- thawSTArray arr
411     ST (foldr (adjust f marr#) (done l u marr#) ies))
412
413 {-# INLINE amap #-}
414 amap :: Ix i => (a -> b) -> Array i a -> Array i b
415 amap f arr@(Array l u _) =
416     unsafeArray (l,u) [(i, f (unsafeAt arr i)) | i <- [0 .. rangeSize (l,u) - 1]]
417
418 {-# INLINE ixmap #-}
419 ixmap :: (Ix i, Ix j) => (i,i) -> (i -> j) -> Array j e -> Array i e
420 ixmap (l,u) f arr =
421     unsafeArray (l,u) [(unsafeIndex (l,u) i, arr ! f i) | i <- range (l,u)]
422
423 {-# INLINE eqArray #-}
424 eqArray :: (Ix i, Eq e) => Array i e -> Array i e -> Bool
425 eqArray arr1@(Array l1 u1 _) arr2@(Array l2 u2 _) =
426     if rangeSize (l1,u1) == 0 then rangeSize (l2,u2) == 0 else
427     l1 == l2 && u1 == u2 &&
428     and [unsafeAt arr1 i == unsafeAt arr2 i | i <- [0 .. rangeSize (l1,u1) - 1]]
429
430 {-# INLINE cmpArray #-}
431 cmpArray :: (Ix i, Ord e) => Array i e -> Array i e -> Ordering
432 cmpArray arr1 arr2 = compare (assocs arr1) (assocs arr2)
433
434 {-# INLINE cmpIntArray #-}
435 cmpIntArray :: Ord e => Array Int e -> Array Int e -> Ordering
436 cmpIntArray arr1@(Array l1 u1 _) arr2@(Array l2 u2 _) =
437     if rangeSize (l1,u1) == 0 then if rangeSize (l2,u2) == 0 then EQ else LT else
438     if rangeSize (l2,u2) == 0 then GT else
439     case compare l1 l2 of
440         EQ    -> foldr cmp (compare u1 u2) [0 .. rangeSize (l1, min u1 u2) - 1]
441         other -> other
442     where
443     cmp i rest = case compare (unsafeAt arr1 i) (unsafeAt arr2 i) of
444         EQ    -> rest
445         other -> other
446
447 {-# RULES "cmpArray/Int" cmpArray = cmpIntArray #-}
448 \end{code}
449
450
451 %*********************************************************
452 %*                                                      *
453 \subsection{Array instances}
454 %*                                                      *
455 %*********************************************************
456
457 \begin{code}
458 instance Ix i => Functor (Array i) where
459     fmap = amap
460
461 instance (Ix i, Eq e) => Eq (Array i e) where
462     (==) = eqArray
463
464 instance (Ix i, Ord e) => Ord (Array i e) where
465     compare = cmpArray
466
467 instance (Ix a, Show a, Show b) => Show (Array a b) where
468     showsPrec p a =
469         showParen (p > 9) $
470         showString "array " .
471         shows (bounds a) .
472         showChar ' ' .
473         shows (assocs a)
474
475 {-
476 instance  (Ix a, Read a, Read b) => Read (Array a b)  where
477     readsPrec p = readParen (p > 9)
478            (\r -> [(array b as, u) | ("array",s) <- lex r,
479                                      (b,t)       <- reads s,
480                                      (as,u)      <- reads t   ])
481 -}
482 \end{code}
483
484
485 %*********************************************************
486 %*                                                      *
487 \subsection{Operations on mutable arrays}
488 %*                                                      *
489 %*********************************************************
490
491 Idle ADR question: What's the tradeoff here between flattening these
492 datatypes into @STArray ix ix (MutableArray# s elt)@ and using
493 it as is?  As I see it, the former uses slightly less heap and
494 provides faster access to the individual parts of the bounds while the
495 code used has the benefit of providing a ready-made @(lo, hi)@ pair as
496 required by many array-related functions.  Which wins? Is the
497 difference significant (probably not).
498
499 Idle AJG answer: When I looked at the outputted code (though it was 2
500 years ago) it seems like you often needed the tuple, and we build
501 it frequently. Now we've got the overloading specialiser things
502 might be different, though.
503
504 \begin{code}
505 {-# INLINE newSTArray #-}
506 newSTArray :: Ix i => (i,i) -> e -> ST s (STArray s i e)
507 newSTArray (l,u) init = ST $ \s1# ->
508     case rangeSize (l,u)                of { I# n# ->
509     case newArray# n# init s1#          of { (# s2#, marr# #) ->
510     (# s2#, STArray l u marr# #) }}
511
512 {-# INLINE boundsSTArray #-}
513 boundsSTArray :: STArray s i e -> (i,i)  
514 boundsSTArray (STArray l u _) = (l,u)
515
516 {-# INLINE readSTArray #-}
517 readSTArray :: Ix i => STArray s i e -> i -> ST s e
518 readSTArray marr@(STArray l u _) i =
519     unsafeReadSTArray marr (index (l,u) i)
520
521 {-# INLINE unsafeReadSTArray #-}
522 unsafeReadSTArray :: Ix i => STArray s i e -> Int -> ST s e
523 unsafeReadSTArray (STArray _ _ marr#) (I# i#) = ST $ \s1# ->
524     readArray# marr# i# s1#
525
526 {-# INLINE writeSTArray #-}
527 writeSTArray :: Ix i => STArray s i e -> i -> e -> ST s () 
528 writeSTArray marr@(STArray l u _) i e =
529     unsafeWriteSTArray marr (index (l,u) i) e
530
531 {-# INLINE unsafeWriteSTArray #-}
532 unsafeWriteSTArray :: Ix i => STArray s i e -> Int -> e -> ST s () 
533 unsafeWriteSTArray (STArray _ _ marr#) (I# i#) e = ST $ \s1# ->
534     case writeArray# marr# i# e s1#     of { s2# ->
535     (# s2#, () #) }
536 \end{code}
537
538
539 %*********************************************************
540 %*                                                      *
541 \subsection{Moving between mutable and immutable}
542 %*                                                      *
543 %*********************************************************
544
545 \begin{code}
546 freezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
547 freezeSTArray (STArray l u marr#) = ST $ \s1# ->
548     case rangeSize (l,u)                of { I# n# ->
549     case newArray# n# arrEleBottom s1#  of { (# s2#, marr'# #) ->
550     let copy i# s3# | i# ==# n# = s3#
551                     | otherwise =
552             case readArray# marr# i# s3# of { (# s4#, e #) ->
553             case writeArray# marr'# i# e s4# of { s5# ->
554             copy (i# +# 1#) s5# }} in
555     case copy 0# s2#                    of { s3# ->
556     case unsafeFreezeArray# marr'# s3#  of { (# s4#, arr# #) ->
557     (# s4#, Array l u arr# #) }}}}
558
559 {-# INLINE unsafeFreezeSTArray #-}
560 unsafeFreezeSTArray :: Ix i => STArray s i e -> ST s (Array i e)
561 unsafeFreezeSTArray (STArray l u marr#) = ST $ \s1# ->
562     case unsafeFreezeArray# marr# s1#   of { (# s2#, arr# #) ->
563     (# s2#, Array l u arr# #) }
564
565 thawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
566 thawSTArray (Array l u arr#) = ST $ \s1# ->
567     case rangeSize (l,u)                of { I# n# ->
568     case newArray# n# arrEleBottom s1#  of { (# s2#, marr# #) ->
569     let copy i# s3# | i# ==# n# = s3#
570                     | otherwise =
571             case indexArray# arr# i#    of { (# e #) ->
572             case writeArray# marr# i# e s3# of { s4# ->
573             copy (i# +# 1#) s4# }} in
574     case copy 0# s2#                    of { s3# ->
575     (# s3#, STArray l u marr# #) }}}
576
577 {-# INLINE unsafeThawSTArray #-}
578 unsafeThawSTArray :: Ix i => Array i e -> ST s (STArray s i e)
579 unsafeThawSTArray (Array l u arr#) = ST $ \s1# ->
580     case unsafeThawArray# arr# s1#      of { (# s2#, marr# #) ->
581     (# s2#, STArray l u marr# #) }
582 \end{code}