diff options
author | simonm <unknown> | 1998-02-02 17:35:59 +0000 |
---|---|---|
committer | simonm <unknown> | 1998-02-02 17:35:59 +0000 |
commit | 28139aea50376444d56f43f0914291348a51a7e7 (patch) | |
tree | 595c378188638ef16462972c1e7fcdb8409c7f16 /ghc/lib/std/Array.lhs | |
parent | 98a1ebecb6d22d793b1d9f8e1d24ecbb5a2d130f (diff) | |
download | haskell-28139aea50376444d56f43f0914291348a51a7e7.tar.gz |
[project @ 1998-02-02 17:27:26 by simonm]
Library re-organisation:
All libraries now live under ghc/lib, which has the following structure:
ghc/lib/std -- all prelude files (libHS.a)
ghc/lib/std/cbits
ghc/lib/exts -- standard Hugs/GHC extensions (libHSexts.a)
-- available with '-fglasgow-exts'
ghc/lib/posix -- POSIX library (libHSposix.a)
ghc/lib/posix/cbits -- available with '-syslib posix'
ghc/lib/misc -- used to be hslibs/ghc (libHSmisc.a)
ghc/lib/misc/cbits -- available with '-syslib misc'
ghc/lib/concurrent -- Concurrent libraries (libHSconc.a)
-- available with '-concurrent'
Also, several non-standard prelude modules had their names changed to begin
with 'Prel' to reduce namespace pollution.
Addr ==> PrelAddr (Addr interface available in 'exts')
ArrBase ==> PrelArr
CCall ==> PrelCCall (CCall interface available in 'exts')
ConcBase ==> PrelConc
GHCerr ==> PrelErr
Foreign ==> PrelForeign (Foreign interface available in 'exts')
GHC ==> PrelGHC
IOHandle ==> PrelHandle
IOBase ==> PrelIOBase
GHCmain ==> PrelMain
STBase ==> PrelST
Unsafe ==> PrelUnsafe
UnsafeST ==> PrelUnsafeST
Diffstat (limited to 'ghc/lib/std/Array.lhs')
-rw-r--r-- | ghc/lib/std/Array.lhs | 99 |
1 files changed, 99 insertions, 0 deletions
diff --git a/ghc/lib/std/Array.lhs b/ghc/lib/std/Array.lhs new file mode 100644 index 0000000000..390c481b8f --- /dev/null +++ b/ghc/lib/std/Array.lhs @@ -0,0 +1,99 @@ +% +% (c) The AQUA Project, Glasgow University, 1994-1996 +% + +\section[Array]{Module @Array@} + +\begin{code} +{-# OPTIONS -fno-implicit-prelude #-} + +module Array ( + module Ix, -- export all of Ix + Array, -- Array type is abstract + + array, listArray, (!), bounds, indices, elems, assocs, + accumArray, (//), accum, ixmap + ) where + +import Ix +import PrelList +import PrelRead +import PrelArr -- Most of the hard work is done here +import PrelBase + +infixl 9 !, // +\end{code} + + + +%********************************************************* +%* * +\subsection{Definitions of array, !, bounds} +%* * +%********************************************************* + +\begin{code} + +#ifdef USE_FOLDR_BUILD +{-# INLINE indices #-} +{-# INLINE elems #-} +{-# INLINE assocs #-} +#endif + +{-# GENERATE_SPECS listArray a{~,Int,IPr} b{} #-} +listArray :: (Ix a) => (a,a) -> [b] -> Array a b +listArray b vs = array b (zipWith (\ a b -> (a,b)) (range b) vs) + +{-# GENERATE_SPECS indices a{~,Int,IPr} b{} #-} +indices :: (Ix a) => Array a b -> [a] +indices = range . bounds + +{-# GENERATE_SPECS elems a{~,Int,IPr} b{} #-} +elems :: (Ix a) => Array a b -> [b] +elems a = [a!i | i <- indices a] + +{-# GENERATE_SPECS assocs a{~,Int,IPr} b{} #-} +assocs :: (Ix a) => Array a b -> [(a,b)] +assocs a = [(i, a!i) | i <- indices a] + +{-# GENERATE_SPECS amap a{~,Int,IPr} b{} c{} #-} +amap :: (Ix a) => (b -> c) -> Array a b -> Array a c +amap f a = array b [(i, f (a!i)) | i <- range b] + where b = bounds 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} +%* * +%********************************************************* + +\begin{code} +instance Ix a => Functor (Array a) where + map = amap + +instance (Ix a, Eq b) => Eq (Array a b) where + a == a' = assocs a == assocs a' + a /= a' = assocs a /= assocs a' + +instance (Ix a, Ord b) => Ord (Array a b) where + compare a b = compare (assocs a) (assocs b) + +instance (Ix a, Show a, Show b) => Show (Array a b) where + showsPrec p a = showParen (p > 9) ( + 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 + readsPrec p = readParen (p > 9) + (\r -> [(array b as, u) | ("array",s) <- lex r, + (b,t) <- reads s, + (as,u) <- reads t ]) + readList = readList__ (readsPrec 0) +\end{code} |