add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Data / Ix.hs
1 {-# LANGUAGE CPP #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.Ix
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  stable
11 -- Portability :  portable
12 --
13 -- The 'Ix' class is used to map a contiguous subrange of values in
14 -- type onto integers.  It is used primarily for array indexing
15 -- (see the array package).
16 -- 
17 -----------------------------------------------------------------------------
18 module Data.Ix
19     (
20     -- * The 'Ix' class
21         Ix
22           ( range       -- :: (Ix a) => (a,a) -> [a]
23           , index       -- :: (Ix a) => (a,a) -> a   -> Int
24           , inRange     -- :: (Ix a) => (a,a) -> a   -> Bool
25           , rangeSize   -- :: (Ix a) => (a,a) -> Int
26           )
27     -- Ix instances:
28     --
29     --  Ix Char
30     --  Ix Int
31     --  Ix Integer
32     --  Ix Bool
33     --  Ix Ordering
34     --  Ix ()
35     --  (Ix a, Ix b) => Ix (a, b)
36     --  ...
37
38     -- Implementation checked wrt. Haskell 98 lib report, 1/99.
39
40     -- * Deriving Instances of 'Ix'
41     -- | Derived instance declarations for the class 'Ix' are only possible
42     -- for enumerations (i.e. datatypes having only nullary constructors)
43     -- and single-constructor datatypes, including arbitrarily large tuples,
44     -- whose constituent types are instances of 'Ix'. 
45     -- 
46     -- * For an enumeration, the nullary constructors are assumed to be
47     -- numbered left-to-right with the indices being 0 to n-1 inclusive. This
48     -- is the same numbering defined by the 'Enum' class. For example, given
49     -- the datatype: 
50     -- 
51     -- >        data Colour = Red | Orange | Yellow | Green | Blue | Indigo | Violet
52     -- 
53     -- we would have: 
54     -- 
55     -- >        range   (Yellow,Blue)        ==  [Yellow,Green,Blue]
56     -- >        index   (Yellow,Blue) Green  ==  1
57     -- >        inRange (Yellow,Blue) Red    ==  False
58     -- 
59     -- * For single-constructor datatypes, the derived instance declarations
60     -- are as shown for tuples in Figure 1
61     -- <http://www.haskell.org/onlinelibrary/ix.html#prelude-index>.
62
63     ) where
64
65 -- import Prelude
66
67 #ifdef __GLASGOW_HASKELL__
68 import GHC.Arr
69 #endif
70
71 #ifdef __HUGS__
72 import Hugs.Prelude( Ix(..) )
73 #endif
74
75 #ifdef __NHC__
76 import Ix (Ix(..))
77 #endif
78