Safe Haskell | None |
---|
Data.Array.Parallel.Prelude.Base
Description
This module sets up the basic vectorisation map for vectorising the DPH Prelude.
Documentation
type PArr = [::]
data Bool
data Ordering
data Word8
8-bit unsigned integer type
Instances
data Int
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Bounded Int | |
Enum Int | |
Eq Int | |
Integral Int | |
Data Int | |
Num Int | |
Ord Int | |
Real Int | |
Show Int | |
Typeable Int | |
Bits Int | |
PprPhysical Int | |
PprVirtual Int | |
Elt Int | |
Elts Int | |
IOElt Int | |
DPrim Int | |
DT Int | |
UIO Int | |
Unboxes Int | |
Unbox Int | |
Prim Int | |
Random Int | |
PR Int | |
PA Int | |
Scalar Int | |
Vector Vector Int | |
MVector MVector Int | |
Show (PDatas Int) | |
Show (PData Int) | |
PprPhysical (Array Int) | |
PprPhysical (Dist Int) | |
PprVirtual (PData Int) | |
Elt (Int, Int, Int) |
data Float
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
data Double
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
class Eq a where
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
Instances
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | |
Eq Int16 | |
Eq Int32 | |
Eq Int64 | |
Eq Integer | |
Eq Ordering | |
Eq Word | |
Eq Word8 | |
Eq Word16 | |
Eq Word32 | |
Eq Word64 | |
Eq () | |
Eq Field | |
Eq SpecConstrAnnotation | |
Eq Constr | Equality of constructors |
Eq DataRep | |
Eq ConstrRep | |
Eq Fixity | |
Eq TypeRepKey | |
Eq MaskingState | |
Eq TypeRep | |
Eq TyCon | |
Eq IntSet | |
Eq UniqueSet | |
Eq LabelSet | |
Eq Label | |
Eq CheckHiWay | |
Eq TraceBinIFaceReading | |
Eq ChangeFlag | |
Eq Addr | |
Eq LocalTime | |
Eq a => Eq [a] | |
Eq a => Eq (Ratio a) | |
Eq a => Eq (Maybe a) | |
Eq a => Eq (Complex a) | |
Eq a => Eq (Vector a) | |
(Unbox a, Eq a) => Eq (Vector a) | |
Eq v => Eq (UniqueMap v) | |
Eq v => Eq (LabelMap v) | |
(Storable a, Eq a) => Eq (Vector a) | |
(Prim a, Eq a) => Eq (Vector a) | |
(Eq a, PA a) => Eq (PArray a) | |
(Eq a, Eq b) => Eq (Either a b) | |
(Eq a, Eq b) => Eq (a, b) | |
Eq a => Eq (Stream Id a) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined
datatype whose constituent types are in Ord
. The declared order
of the constructors in the data declaration determines the ordering
in derived Ord
instances. The Ordering
datatype allows a single
comparison to determine the precise ordering of two objects.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Instances
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | |
Ord Int16 | |
Ord Int32 | |
Ord Int64 | |
Ord Integer | |
Ord Ordering | |
Ord Word | |
Ord Word8 | |
Ord Word16 | |
Ord Word32 | |
Ord Word64 | |
Ord () | |
Ord TypeRepKey | |
Ord TypeRep | |
Ord TyCon | |
Ord IntSet | |
Ord UniqueSet | |
Ord LabelSet | |
Ord Label | |
Ord ChangeFlag | |
Ord Addr | |
Ord LocalTime | |
(Eq [a], Ord a) => Ord [a] | |
(Eq (Ratio a), Integral a) => Ord (Ratio a) | |
(Eq (Maybe a), Ord a) => Ord (Maybe a) | |
(Eq (Vector a), Ord a) => Ord (Vector a) | |
(Eq (Vector a), Unbox a, Ord a) => Ord (Vector a) | |
(Eq (UniqueMap v), Ord v) => Ord (UniqueMap v) | |
(Eq (LabelMap v), Ord v) => Ord (LabelMap v) | |
(Eq (Vector a), Storable a, Ord a) => Ord (Vector a) | |
(Eq (Vector a), Prim a, Ord a) => Ord (Vector a) | |
(Eq (Either a b), Ord a, Ord b) => Ord (Either a b) | |
(Eq (a, b), Ord a, Ord b) => Ord (a, b) | |
(Eq (Stream Id a), Ord a) => Ord (Stream Id a) | |
(Eq (a, b, c), Ord a, Ord b, Ord c) => Ord (a, b, c) | |
(Eq (a, b, c, d), Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
(Eq (a, b, c, d, e), Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
(Eq (a, b, c, d, e, f), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
(Eq (a, b, c, d, e, f, g), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
(Eq (a, b, c, d, e, f, g, h), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h) | |
(Eq (a, b, c, d, e, f, g, h, i), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i) | |
(Eq (a, b, c, d, e, f, g, h, i, j), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j) | |
(Eq (a, b, c, d, e, f, g, h, i, j, k), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k) | |
(Eq (a, b, c, d, e, f, g, h, i, j, k, l), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l) | |
(Eq (a, b, c, d, e, f, g, h, i, j, k, l, m), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
(Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
(Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o), Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) |
class Show a
Conversion of values to readable String
s.
Minimal complete definition: showsPrec
or show
.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
-
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
Instances
class Num a where
Basic numeric class.
Minimal complete definition: all except negate
or (-)
Methods
(+) :: a -> a -> a
(*) :: a -> a -> a
(-) :: a -> a -> a
negate :: a -> a
Unary negation.
abs :: a -> a
Absolute value.
signum :: a -> a
Sign of a number.
The functions abs
and signum
should satisfy the law:
abs x * signum x == x
For real numbers, the signum
is either -1
(negative), 0
(zero)
or 1
(positive).
fromInteger :: Integer -> a
Conversion from an Integer
.
An integer literal represents the application of the function
fromInteger
to the appropriate value of type Integer
,
so such literals have type (
.
Num
a) => a