base-4.9.0.0: Basic libraries

Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Ix

Contents

Description

The Ix class is used to map a contiguous subrange of values in type onto integers. It is used primarily for array indexing (see the array package). Ix uses row-major order.

Synopsis

The Ix class

class Ord a => Ix a where Source

The Ix class is used to map a contiguous subrange of values in a type onto integers. It is used primarily for array indexing (see the array package).

The first argument (l,u) of each of these operations is a pair specifying the lower and upper bounds of a contiguous subrange of values.

An implementation is entitled to assume the following laws about these operations:

Minimal complete definition

range, (index | unsafeIndex), inRange

Methods

range :: (a, a) -> [a] Source

The list of values in the subrange defined by a bounding pair.

index :: (a, a) -> a -> Int Source

The position of a subscript in the subrange.

inRange :: (a, a) -> a -> Bool Source

Returns True the given subscript lies in the range defined the bounding pair.

rangeSize :: (a, a) -> Int Source

The size of the subrange defined by a bounding pair.

Instances

Ix Bool 
Ix Char 
Ix Int 

Methods

range :: (Int, Int) -> [Int] Source

index :: (Int, Int) -> Int -> Int Source

unsafeIndex :: (Int, Int) -> Int -> Int

inRange :: (Int, Int) -> Int -> Bool Source

rangeSize :: (Int, Int) -> Int Source

unsafeRangeSize :: (Int, Int) -> Int

Ix Int8 
Ix Int16 
Ix Int32 
Ix Int64 
Ix Integer 
Ix Ordering 
Ix Word 
Ix Word8 
Ix Word16 
Ix Word32 
Ix Word64 
Ix () 

Methods

range :: ((), ()) -> [()] Source

index :: ((), ()) -> () -> Int Source

unsafeIndex :: ((), ()) -> () -> Int

inRange :: ((), ()) -> () -> Bool Source

rangeSize :: ((), ()) -> Int Source

unsafeRangeSize :: ((), ()) -> Int

Ix GeneralCategory 
Ix IOMode 
Ix SeekMode 
Ix Natural 
Ix Void 
Ix a => Ix (Identity a) 
(Ix a, Ix b) => Ix (a, b) 

Methods

range :: ((a, b), (a, b)) -> [(a, b)] Source

index :: ((a, b), (a, b)) -> (a, b) -> Int Source

unsafeIndex :: ((a, b), (a, b)) -> (a, b) -> Int

inRange :: ((a, b), (a, b)) -> (a, b) -> Bool Source

rangeSize :: ((a, b), (a, b)) -> Int Source

unsafeRangeSize :: ((a, b), (a, b)) -> Int

Ix (Proxy k s) 

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] Source

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int Source

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool Source

rangeSize :: (Proxy k s, Proxy k s) -> Int Source

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

(Ix a1, Ix a2, Ix a3) => Ix (a1, a2, a3) 

Methods

range :: ((a1, a2, a3), (a1, a2, a3)) -> [(a1, a2, a3)] Source

index :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Int Source

unsafeIndex :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Int

inRange :: ((a1, a2, a3), (a1, a2, a3)) -> (a1, a2, a3) -> Bool Source

rangeSize :: ((a1, a2, a3), (a1, a2, a3)) -> Int Source

unsafeRangeSize :: ((a1, a2, a3), (a1, a2, a3)) -> Int

Ix a => Ix (Const k a b) 

Methods

range :: (Const k a b, Const k a b) -> [Const k a b] Source

index :: (Const k a b, Const k a b) -> Const k a b -> Int Source

unsafeIndex :: (Const k a b, Const k a b) -> Const k a b -> Int

inRange :: (Const k a b, Const k a b) -> Const k a b -> Bool Source

rangeSize :: (Const k a b, Const k a b) -> Int Source

unsafeRangeSize :: (Const k a b, Const k a b) -> Int

(Ix a1, Ix a2, Ix a3, Ix a4) => Ix (a1, a2, a3, a4) 

Methods

range :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> [(a1, a2, a3, a4)] Source

index :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Int Source

unsafeIndex :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Int

inRange :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> (a1, a2, a3, a4) -> Bool Source

rangeSize :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> Int Source

unsafeRangeSize :: ((a1, a2, a3, a4), (a1, a2, a3, a4)) -> Int

(Ix a1, Ix a2, Ix a3, Ix a4, Ix a5) => Ix (a1, a2, a3, a4, a5) 

Methods

range :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> [(a1, a2, a3, a4, a5)] Source

index :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Int Source

unsafeIndex :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Int

inRange :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> (a1, a2, a3, a4, a5) -> Bool Source

rangeSize :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> Int Source

unsafeRangeSize :: ((a1, a2, a3, a4, a5), (a1, a2, a3, a4, a5)) -> Int

Deriving Instances of Ix

Derived instance declarations for the class Ix are only possible for enumerations (i.e. datatypes having only nullary constructors) and single-constructor datatypes, including arbitrarily large tuples, whose constituent types are instances of Ix.

  • For an enumeration, the nullary constructors are assumed to be numbered left-to-right with the indices being 0 to n-1 inclusive. This is the same numbering defined by the Enum class. For example, given the datatype:
       data Colour = Red | Orange | Yellow | Green | Blue | Indigo | Violet

we would have:

       range   (Yellow,Blue)        ==  [Yellow,Green,Blue]
       index   (Yellow,Blue) Green  ==  1
       inRange (Yellow,Blue) Red    ==  False