[project @ 2001-03-25 09:57:24 by qrczak]
authorqrczak <unknown>
Sun, 25 Mar 2001 09:57:26 +0000 (09:57 +0000)
committerqrczak <unknown>
Sun, 25 Mar 2001 09:57:26 +0000 (09:57 +0000)
Promote (//) from a function to IArray method with an inefficient
default definition. This completely compatible change allows efficient
implementations of (//) for particular types.

Explicitly define efficient (//) for Array and UArray.

Use unsafeFreeze* instead of freeze* in (//), accum and accumArray
for Array and IArray.

Remove showList in instance Show Array (the default definition does
the job).

Add Eq, Ord and Show instances for UArray. (Would be simpler if types
in instance contexts were not required to be type variables. I didn't
use -fallow-undecidable-instances but defined instances for individual
element types separately.)

Add unsafe{Freeze,Thaw}/{STArray,IOArray,IOUArray} rules.

Fix thaw/IOUArray rule (nobody uses IOUArrays in the ST monad!).

ghc/lib/std/PrelArr.lhs
ghc/lib/std/PrelStable.lhs

index 7cfb6bd..11c6001 100644 (file)
@@ -1,5 +1,5 @@
 % -----------------------------------------------------------------------------
-% $Id: PrelArr.lhs,v 1.25 2000/08/31 19:57:42 simonpj Exp $
+% $Id: PrelArr.lhs,v 1.26 2001/03/25 09:57:24 qrczak Exp $
 %
 % (c) The University of Glasgow, 1994-2000
 %
@@ -389,16 +389,12 @@ old_array // ivs
        -- copy the old array:
        arr <- thawSTArray old_array
        -- now write the new elements into the new array:
-       fill_it_in arr ivs
-       freezeSTArray arr
+       foldr (fill_one_in arr) (unsafeFreezeSTArray arr) ivs
     )
 
-fill_it_in :: Ix ix => STArray s ix elt -> [(ix, elt)] -> ST s ()
-{-# INLINE fill_it_in #-}
-fill_it_in arr lst = foldr (fill_one_in arr) (return ()) lst
-        -- **** STRICT **** (but that's OK...)
-
-fill_one_in arr (i, v) rst = writeSTArray arr i v >> rst
+{-# INLINE fill_one_in #-}
+fill_one_in :: Ix ix => STArray s ix e -> (ix, e) -> ST s a -> ST s a
+fill_one_in arr (i, v) next = writeSTArray arr i v >> next
 
 zap_with_f :: Ix ix => (elt -> elt2 -> elt) -> STArray s ix elt -> [(ix,elt2)] -> ST s ()
 -- zap_with_f: reads an elem out first, then uses "f" on that and the new value
@@ -420,7 +416,7 @@ accum f old_array ivs
        arr <- thawSTArray old_array
        -- now zap the elements in question with "f":
        zap_with_f f arr ivs
-       freezeSTArray arr
+       unsafeFreezeSTArray arr
     )
 
 
@@ -430,7 +426,7 @@ accumArray f zero ixs ivs
   = runST (do
        arr <- newSTArray ixs zero
        zap_with_f f arr ivs
-       freezeSTArray arr
+       unsafeFreezeSTArray arr
     )
 \end{code}
 
@@ -458,7 +454,6 @@ instance  (Ix a, Show a, Show b) => Show (Array a b)  where
                    showString "array " .
                    shows (bounds a) . showChar ' ' .
                    shows (assocs a)                  )
-    showList = showList__ (showsPrec 0)
 
 {-
 instance  (Ix a, Read a, Read b) => Read (Array a b)  where
@@ -466,7 +461,6 @@ instance  (Ix a, Read a, Read b) => Read (Array a b)  where
           (\r -> [(array b as, u) | ("array",s) <- lex r,
                                     (b,t)       <- reads s,
                                     (as,u)      <- reads t   ])
-    readList = readList__ (readsPrec 0)
 -}
 \end{code}
 
index dfa87a0..2d6f8ae 100644 (file)
@@ -1,5 +1,5 @@
 % -----------------------------------------------------------------------------
-% $Id: PrelStable.lhs,v 1.8 2000/11/07 10:42:57 simonmar Exp $
+% $Id: PrelStable.lhs,v 1.9 2001/03/25 09:57:26 qrczak Exp $
 %
 % (c) The GHC Team, 1992-2000
 %
@@ -22,20 +22,19 @@ import PrelIOBase
 -----------------------------------------------------------------------------
 -- Stable Pointers
 
-data StablePtr  a = StablePtr  (StablePtr#  a)
+data StablePtr a = StablePtr (StablePtr# a)
 
 instance CCallable   (StablePtr a)
 instance CReturnable (StablePtr a)
 
 newStablePtr   :: a -> IO (StablePtr a)
-deRefStablePtr :: StablePtr a -> IO a
-foreign import unsafe freeStablePtr :: StablePtr a -> IO ()
-
 newStablePtr a = IO $ \ s ->
     case makeStablePtr# a s of (# s', sp #) -> (# s', StablePtr sp #)
 
+deRefStablePtr :: StablePtr a -> IO a
 deRefStablePtr (StablePtr sp) = IO $ \s -> deRefStablePtr# sp s
 
+foreign import unsafe freeStablePtr :: StablePtr a -> IO ()
 
 instance Eq (StablePtr a) where 
     (StablePtr sp1) == (StablePtr sp2) =