dph-lifted-vseg-0.6.0.2: Data Parallel Haskell lifted array combinators.

Safe HaskellSafe-Infered

Data.Array.Parallel.Prelude.Base

Description

This module sets up the basic vectorisation map for vectorising the DPH Prelude.

Synopsis

Documentation

type PArr = [::]

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.

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.

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.

Minimal complete definition: either == or /=.

Methods

(==) :: a -> a -> Bool

(/=) :: a -> a -> Bool

Instances

Eq Bool 
Eq Char 
Eq Double 
Eq Float 
Eq Int 
Eq Integer 
Eq Ordering 
Eq Word 
Eq Word8 
Eq Word16 
Eq Word32 
Eq Word64 
Eq () 
Eq TypeRep 
Eq Field 
Eq SpecConstrAnnotation 
Eq Constr

Equality of constructors

Eq DataRep 
Eq ConstrRep 
Eq Fixity 
Eq MaskingState 
Eq TyCon 
Eq ByteString 
Eq ByteString 
Eq IntSet 
Eq Prec 
Eq CheckHiWay 
Eq TraceBinIFaceReading 
Eq TyThing 
Eq Arity 
Eq Fixity 
Eq Associativity 
Eq ChangeFlag 
Eq Label 
Eq LabelSet 
Eq Unique 
Eq UniqueSet 
Eq Addr 
Eq LocalTime 
Eq a => Eq [a] 
Eq a => Eq (Ratio a) 
Eq a => Eq (Down a) 
Eq a => Eq (Maybe a) 
Eq a => Eq (Vector a) 
(Unbox a, Eq a) => Eq (Vector a) 
Eq v => Eq (LabelMap v) 
Eq v => Eq (UniqueMap 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) 

class Eq a => Ord a where

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.

Methods

compare :: a -> a -> Ordering

(<) :: a -> a -> Bool

(>=) :: a -> a -> Bool

(>) :: a -> a -> Bool

(<=) :: a -> a -> Bool

max :: a -> a -> a

min :: a -> a -> a

Instances

Ord Bool 
Ord Char 
Ord Double 
Ord Float 
Ord Int 
Ord Integer 
Ord Ordering 
Ord Word 
Ord Word8 
Ord Word16 
Ord Word32 
Ord Word64 
Ord () 
Ord TypeRep 
Ord TyCon 
Ord ByteString 
Ord ByteString 
Ord IntSet 
Ord Prec 
Ord TyThing 
Ord Arity 
Ord Fixity 
Ord Associativity 
Ord ChangeFlag 
Ord Label 
Ord LabelSet 
Ord Unique 
Ord UniqueSet 
Ord Addr 
Ord LocalTime 
Ord a => Ord [a] 
Integral a => Ord (Ratio a) 
Ord a => Ord (Down a) 
Ord a => Ord (Maybe a) 
Ord a => Ord (Vector a) 
(Unbox a, Ord a) => Ord (Vector a) 
Ord v => Ord (LabelMap v) 
Ord v => Ord (UniqueMap v) 
(Storable a, Ord a) => Ord (Vector a) 
(Prim a, Ord a) => Ord (Vector a) 
(Ord a, Ord b) => Ord (Either a b) 
(Ord a, Ord b) => Ord (a, b) 
Ord a => Ord (Stream Id a) 
(Ord a, Ord b, Ord c) => Ord (a, b, c) 
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) 
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) 
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) 
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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 Strings.

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 than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 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,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Integer 
Show Ordering 
Show Word 
Show Word8 
Show Word16 
Show Word32 
Show Word64 
Show () 
Show TypeRep 
Show PError 
Show PWarning 
Show Field 
Show DataType 
Show Constr 
Show DataRep 
Show ConstrRep 
Show Fixity 
Show MaskingState 
Show TyCon 
Show IntSet 
Show Doc 
Show UPVSegd 
Show UPSSegd 
Show UPSegd 
Show ErrMsg 
Show OptimizationFuel 
Show Arity 
Show Fixity 
Show Associativity 
Show Label 
Show LabelSet 
Show Unique 
Show UniqueSet 
Show StdGen 
Show Doc 
Show LocalTime 
Show ZonedTime 
Show UTCTime 
Show Day 
Show Padding 
Show DateFormatSpec 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio a) 
Show a => Show (ParseResult a) 
Show a => Show (Maybe a) 
Show a => Show (Vector a) 
(Unboxes a, Unbox a, Show a) => Show (Vectors a) 
(Show a, Unbox a) => Show (Vector a) 
(Show a, DT a) => Show (Dist a) 
Show v => Show (LabelMap v) 
Show v => Show (UniqueMap v) 
(Show a, Storable a) => Show (Vector a) 
(Show a, Prim a) => Show (Vector a) 
Show (PDatas Double) 
Show (PDatas Int) 
Show (PDatas Word8) 
Show (PDatas ()) 
(Show (PDatas a), Show (PDatas b)) => Show (PDatas (a, b)) 
(Show (PDatas a), Show (PDatas b), Show (PDatas c)) => Show (PDatas (a, b, c)) 
(Show (PDatas a), Show (PDatas b), Show (PDatas c), Show (PDatas d)) => Show (PDatas (a, b, c, d)) 
(Show (PDatas a), Show (PDatas b), Show (PDatas c), Show (PDatas d), Show (PDatas e)) => Show (PDatas (a, b, c, d, e)) 
Show (PDatas Void) 
(Show (PDatas a), Show (PData a)) => Show (PDatas (PArray a)) 
Show (PData Double) 
Show (PData Int) 
Show (PData Word8) 
Show (PData ()) 
(Show (PData a), Show (PData b)) => Show (PData (a, b)) 
(Show (PData a), Show (PData b), Show (PData c)) => Show (PData (a, b, c)) 
(Show (PData a), Show (PData b), Show (PData c), Show (PData d)) => Show (PData (a, b, c, d)) 
(Show (PData a), Show (PData b), Show (PData c), Show (PData d), Show (PData e)) => Show (PData (a, b, c, d, e)) 
Show (PData Void) 
(Show (PDatas a), Show (PData a)) => Show (PData (PArray a)) 
(Show a, PA a) => Show (PArray a) 
(Show a, Show b) => Show (Either a b) 
(Show a, Show b) => Show (a, b) 
(Show a, Show b, Show c) => Show (a, b, c) 
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) 
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

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.