diff options
author | simonmar <unknown> | 2002-02-12 15:17:36 +0000 |
---|---|---|
committer | simonmar <unknown> | 2002-02-12 15:17:36 +0000 |
commit | 2cc5b907318f97e19b28b2ad8ed9ff8c1f401dcc (patch) | |
tree | 2fefe09bc63464ac3a28ea37b61eefc5e506685a /ghc/lib/std/Array.lhs | |
parent | 239e9471e104fd88ec93bf42623c3a68a496657a (diff) | |
download | haskell-2cc5b907318f97e19b28b2ad8ed9ff8c1f401dcc.tar.gz |
[project @ 2002-02-12 15:17:13 by simonmar]
Switch over to the new hierarchical libraries
---------------------------------------------
This commit reorganises our libraries to use the new hierarchical
module namespace extension.
The basic story is this:
- fptools/libraries contains the new hierarchical libraries.
Everything in here is "clean", i.e. most deprecated stuff has
been removed.
- fptools/libraries/base is the new base package
(replacing "std") and contains roughly what was previously
in std, lang, and concurrent, minus deprecated stuff.
Things that are *not allowed* in libraries/base include:
Addr, ForeignObj, ByteArray, MutableByteArray,
_casm_, _ccall_, ``'', PrimIO
For ByteArrays and MutableByteArrays we use UArray and
STUArray/IOUArray respectively now.
Modules previously called PrelFoo are now under
fptools/libraries/GHC. eg. PrelBase is now GHC.Base.
- fptools/libraries/haskell98 provides the Haskell 98 std.
libraries (Char, IO, Numeric etc.) as a package. This
package is enabled by default.
- fptools/libraries/network is a rearranged version of
the existing net package (the old package net is still
available; see below).
- Other packages will migrate to fptools/libraries in
due course.
NB. you need to checkout fptools/libraries as well as
fptools/hslibs now. The nightly build scripts will need to be
tweaked.
- fptools/hslibs still contains (almost) the same stuff as before.
Where libraries have moved into the new hierarchy, the hslibs
version contains a "stub" that just re-exports the new version.
The idea is that code will gradually migrate from fptools/hslibs
into fptools/libraries as it gets cleaned up, and in a version or
two we can remove the old packages altogether.
- I've taken the opportunity to make some changes to the build
system, ripping out the old hslibs Makefile stuff from
mk/target.mk; the new package building Makefile code is in
mk/package.mk (auto-included from mk/target.mk).
The main improvement is that packages now register themselves at
make boot time using ghc-pkg, and the monolithic package.conf
in ghc/driver is gone.
I've updated the standard packages but haven't tested win32,
graphics, xlib, object-io, or OpenGL yet. The Makefiles in
these packages may need some further tweaks, and they'll need
pkg.conf.in files added.
- Unfortunately all this rearrangement meant I had to bump the
interface-file version and create a bunch of .hi-boot-6 files :-(
Diffstat (limited to 'ghc/lib/std/Array.lhs')
-rw-r--r-- | ghc/lib/std/Array.lhs | 148 |
1 files changed, 0 insertions, 148 deletions
diff --git a/ghc/lib/std/Array.lhs b/ghc/lib/std/Array.lhs deleted file mode 100644 index cfeb648ea3..0000000000 --- a/ghc/lib/std/Array.lhs +++ /dev/null @@ -1,148 +0,0 @@ -% ----------------------------------------------------------------------------- -% $Id: Array.lhs,v 1.16 2001/04/14 22:27:00 qrczak Exp $ -% -% (c) The University of Glasgow, 1994-2000 -% -\section[Array]{Module @Array@} - -\begin{code} -{-# OPTIONS -fno-implicit-prelude #-} - -module Array - - ( - module Ix -- export all of Ix - , Array -- Array type is abstract - - , array -- :: (Ix a) => (a,a) -> [(a,b)] -> Array a b - , listArray -- :: (Ix a) => (a,a) -> [b] -> Array a b - , (!) -- :: (Ix a) => Array a b -> a -> b - , bounds -- :: (Ix a) => Array a b -> (a,a) - , indices -- :: (Ix a) => Array a b -> [a] - , elems -- :: (Ix a) => Array a b -> [b] - , assocs -- :: (Ix a) => Array a b -> [(a,b)] - , accumArray -- :: (Ix a) => (b -> c -> b) -> b -> (a,a) -> [(a,c)] -> Array a b - , (//) -- :: (Ix a) => Array a b -> [(a,b)] -> Array a b - , accum -- :: (Ix a) => (b -> c -> b) -> Array a b -> [(a,c)] -> Array a b - , ixmap -- :: (Ix a, Ix b) => (a,a) -> (a -> b) -> Array b c -> Array a b - - -- Array instances: - -- - -- Ix a => Functor (Array a) - -- (Ix a, Eq b) => Eq (Array a b) - -- (Ix a, Ord b) => Ord (Array a b) - -- (Ix a, Show a, Show b) => Show (Array a b) - -- (Ix a, Read a, Read b) => Read (Array a b) - -- - - -- Implementation checked wrt. Haskell 98 lib report, 1/99. - - ) where -\end{code} - -#ifndef __HUGS__ - -\begin{code} - ------------ GHC -------------------- -import Ix -import PrelArr -- Most of the hard work is done here - ------------ End of GHC -------------------- -\end{code} - -#else - -\begin{code} - ------------ HUGS (rest of file) -------------------- -import PrelPrim ( PrimArray - , runST - , primNewArray - , primWriteArray - , primReadArray - , primUnsafeFreezeArray - , primIndexArray - ) -import Ix -import List( (\\) ) - -infixl 9 !, // -\end{code} - - -%********************************************************* -%* * -\subsection{The Array type} -%* * -%********************************************************* - - -\begin{code} -data Array ix elt = Array (ix,ix) (PrimArray elt) - -array :: Ix a => (a,a) -> [(a,b)] -> Array a b -array ixs@(ix_start, ix_end) ivs = runST (do - { mut_arr <- primNewArray (rangeSize ixs) arrEleBottom - ; mapM_ (\ (i,v) -> primWriteArray mut_arr (index ixs i) v) ivs - ; arr <- primUnsafeFreezeArray mut_arr - ; return (Array ixs arr) - } - ) - where - arrEleBottom = error "(Array.!): undefined array element" - -listArray :: Ix a => (a,a) -> [b] -> Array a b -listArray b vs = array b (zipWith (\ a b -> (a,b)) (range b) vs) - -(!) :: Ix a => Array a b -> a -> b -(Array bounds arr) ! i = primIndexArray arr (index bounds i) - -bounds :: Ix a => Array a b -> (a,a) -bounds (Array b _) = b - -indices :: Ix a => Array a b -> [a] -indices = range . bounds - -elems :: Ix a => Array a b -> [b] -elems a = [a!i | i <- indices a] - -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) - ([(i,a!i) | i <- indices a \\ [i | (i,_) <- us]] - ++ us) - -accum :: Ix a => (b -> c -> b) -> Array a b -> [(a,c)] -> Array a b -accum f = foldl (\a (i,v) -> a // [(i,f (a!i) v)]) - -accumArray :: Ix a => (b -> c -> b) -> b -> (a,a) -> [(a,c)] -> Array a b -accumArray f z b = accum f (array b [(i,z) | i <- range b]) - -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] - - -instance (Ix a) => Functor (Array a) where - fmap f a = array (bounds a) [(i, f(a!i)) | i <- indices a] - -instance (Ix a, Eq b) => Eq (Array a b) where - a == a' = assocs a == assocs a' - -instance (Ix a, Ord b) => Ord (Array a b) where - a <= a' = assocs a <= assocs a' - - -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) ) - -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 ]) - -\end{code} -#endif |