[project @ 2001-05-18 16:54:04 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / Array.lhs
index 2576f7c..cfeb648 100644 (file)
@@ -1,7 +1,8 @@
+% -----------------------------------------------------------------------------
+% $Id: Array.lhs,v 1.16 2001/04/14 22:27:00 qrczak Exp $
 %
-% (c) The AQUA Project, Glasgow University, 1994-1999
+% (c) The University of Glasgow, 1994-2000
 %
-
 \section[Array]{Module @Array@}
 
 \begin{code}
@@ -37,14 +38,21 @@ module  Array
     -- Implementation checked wrt. Haskell 98 lib report, 1/99.
 
     ) where
+\end{code}
 
 #ifndef __HUGS__
+
+\begin{code}
+       ------------ GHC --------------------
 import Ix
-import PrelList
-import PrelShow
 import PrelArr         -- Most of the hard work is done here
-import PrelBase
+       ------------ End of GHC --------------------
+\end{code}
+
 #else
+
+\begin{code}
+       ------------ HUGS (rest of file) --------------------
 import PrelPrim ( PrimArray
                , runST
                , primNewArray
@@ -55,44 +63,18 @@ import PrelPrim ( PrimArray
                )
 import Ix
 import List( (\\) )
-#endif
 
 infixl 9  !, //
 \end{code}
 
-#ifndef __HUGS__
-
 
 %*********************************************************
 %*                                                     *
-\subsection{Definitions of array, !, bounds}
+\subsection{The Array type}
 %*                                                     *
 %*********************************************************
 
-\begin{code}
-
 
-{-# SPECIALISE listArray :: (Int,Int) -> [b] -> Array Int b #-}
-listArray            :: (Ix a) => (a,a) -> [b] -> Array a b
-listArray b vs       =  array b (zip (range b) vs)
-
-{-# INLINE elems #-}
-elems                :: (Ix a) => Array a b -> [b]
-elems a               =  [a!i | i <- indices a]
-
-ixmap                :: (Ix a, Ix b) => (a,a) -> (a -> b) -> Array b c -> Array a c
-ixmap b f a           =  array b [(i, a ! f i) | i <- range b]
-\end{code}
-
-
-%*********************************************************
-%*                                                     *
-\subsection{Instance declarations for Array type}
-%*                                                     *
-%*********************************************************
-
-
-#else
 \begin{code}
 data Array ix elt = Array (ix,ix) (PrimArray elt)
 
@@ -126,7 +108,7 @@ assocs                :: Ix a => Array a b -> [(a,b)]
 assocs a          =  [(i, a!i) | i <- indices a]
 
 (//)              :: Ix a => Array a b -> [(a,b)] -> Array a b
-a // us           =  array (bounds a)
+(//) a us           =  array (bounds a)
                         ([(i,a!i) | i <- indices a \\ [i | (i,_) <- us]]
                          ++ us)