[project @ 1998-12-02 13:17:09 by simonm]
[ghc-hetmet.git] / ghc / lib / std / Array.lhs
1 %
2 % (c) The AQUA Project, Glasgow University, 1994-1996
3 %
4
5 \section[Array]{Module @Array@}
6
7 \begin{code}
8 {-# OPTIONS -fno-implicit-prelude #-}
9
10 module  Array ( 
11     module Ix,                  -- export all of Ix 
12     Array,                      -- Array type is abstract
13
14     array, listArray, (!), bounds, indices, elems, assocs, 
15     accumArray, (//), accum, ixmap
16   ) where
17
18 import Ix
19 import PrelList
20 --import PrelRead
21 import PrelArr          -- Most of the hard work is done here
22 import PrelBase
23
24 infixl 9  !, //
25 \end{code}
26
27
28
29 %*********************************************************
30 %*                                                      *
31 \subsection{Definitions of array, !, bounds}
32 %*                                                      *
33 %*********************************************************
34
35 \begin{code}
36
37 #ifdef USE_FOLDR_BUILD
38 {-# INLINE indices #-}
39 {-# INLINE elems #-}
40 {-# INLINE assocs #-}
41 #endif
42
43 {-# SPECIALISE listArray :: (Int,Int) -> [b] -> Array Int b #-}
44 listArray             :: (Ix a) => (a,a) -> [b] -> Array a b
45 listArray b vs        =  array b (zipWith (\ a b -> (a,b)) (range b) vs)
46
47 {-# SPECIALISE indices :: Array Int b -> [Int] #-}
48 indices               :: (Ix a) => Array a b -> [a]
49 indices               =  range . bounds
50
51 {-# SPECIALISE elems :: Array Int b -> [b] #-}
52 elems                 :: (Ix a) => Array a b -> [b]
53 elems a               =  [a!i | i <- indices a]
54
55 {-# SPECIALISE assocs :: Array Int b -> [(Int,b)] #-}
56 assocs                :: (Ix a) => Array a b -> [(a,b)]
57 assocs a              =  [(i, a!i) | i <- indices a]
58
59 {-# SPECIALISE amap :: (b -> c) -> Array Int b -> Array Int c #-}
60 amap                  :: (Ix a) => (b -> c) -> Array a b -> Array a c
61 amap f a              =  array b [(i, f (a!i)) | i <- range b]
62                          where b = bounds a
63
64 ixmap                 :: (Ix a, Ix b) => (a,a) -> (a -> b) -> Array b c -> Array a c
65 ixmap b f a           =  array b [(i, a ! f i) | i <- range b]
66 \end{code}
67
68
69 %*********************************************************
70 %*                                                      *
71 \subsection{Instance declarations for Array type}
72 %*                                                      *
73 %*********************************************************
74
75 \begin{code}
76 instance Ix a => Functor (Array a) where
77   map = amap
78
79 instance  (Ix a, Eq b)  => Eq (Array a b)  where
80     a == a'             =  assocs a == assocs a'
81     a /= a'             =  assocs a /= assocs a'
82
83 instance  (Ix a, Ord b) => Ord (Array a b)  where
84     compare a b = compare (assocs a) (assocs b)
85
86 instance  (Ix a, Show a, Show b) => Show (Array a b)  where
87     showsPrec p a = showParen (p > 9) (
88                     showString "array " .
89                     shows (bounds a) . showChar ' ' .
90                     shows (assocs a)                  )
91     showList = showList__ (showsPrec 0)
92
93 {-
94 instance  (Ix a, Read a, Read b) => Read (Array a b)  where
95     readsPrec p = readParen (p > 9)
96            (\r -> [(array b as, u) | ("array",s) <- lex r,
97                                      (b,t)       <- reads s,
98                                      (as,u)      <- reads t   ])
99     readList = readList__ (readsPrec 0)
100 -}
101 \end{code}