accelerate-blas-0.1.0.1: Numeric Linear Algebra in Accelerate

Copyright[2017] Trevor L. McDonell
LicenseBSD3
MaintainerTrevor L. McDonell <tmcdonell@cse.unsw.edu.au>
Stabilityexperimental
Portabilitynon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Data.Array.Accelerate.Numeric.Sum

Contents

Description

Functions for summing floating point numbers more accurately than the straightforward sum operation.

In the worst case, the sum function accumulates error at a rate proportional to the number of values being summed. The algorithms in this module implement different methods of compensated summation, which reduce the accumulation of numeric error so that it grows much more slowly than the number of inputs (e.g. logarithmically), or remains constant.

Synopsis

Summation type class

class (Elt a, Elt (s a)) => Summation s a where Source #

A class for the summation of floating-point numbers

Minimal complete definition

add, zero, into, from

Methods

add :: Exp (s a) -> Exp (s a) -> Exp (s a) Source #

Add a value to the sum

zero :: Exp (s a) Source #

The identity of the summation

into :: Proxy s -> Exp a -> Exp (s a) Source #

Insert a value into the summation

from :: Proxy s -> Exp (s a) -> Exp a Source #

Summarise the result of summation

Instances

Summation Kahan Double Source # 
Summation Kahan Float Source # 
Summation Kahan CDouble Source # 
Summation Kahan CFloat Source # 
Summation KB2 Double Source # 
Summation KB2 Float Source # 

Methods

add :: Exp (KB2 Float) -> Exp (KB2 Float) -> Exp (KB2 Float) Source #

zero :: Exp (KB2 Float) Source #

into :: Proxy (* -> *) KB2 -> Exp Float -> Exp (KB2 Float) Source #

from :: Proxy (* -> *) KB2 -> Exp (KB2 Float) -> Exp Float Source #

Summation KB2 CDouble Source # 
Summation KB2 CFloat Source # 
Summation KBN Double Source # 
Summation KBN Float Source # 

Methods

add :: Exp (KBN Float) -> Exp (KBN Float) -> Exp (KBN Float) Source #

zero :: Exp (KBN Float) Source #

into :: Proxy (* -> *) KBN -> Exp Float -> Exp (KBN Float) Source #

from :: Proxy (* -> *) KBN -> Exp (KBN Float) -> Exp Float Source #

Summation KBN CDouble Source # 
Summation KBN CFloat Source # 

sum :: (Summation s a, Shape sh) => Proxy s -> Acc (Array (sh :. Int) a) -> Acc (Array sh a) Source #

Sum an array using a particular compensation scheme.

>>> let xs = [1.0, 1.0e100, 1.0, -1.0e100] :: [Double]
>>> Prelude.sum xs
0.0
>>> let ys = fromList (Z:.4) [1.0, 1.0e100, 1.0, -1.0e100] :: Vector Double
>>> sum kbn (use ys)
Scalar Z [2.0]

Kahan-Babuška-Neumaier summation

data KBN a Source #

Kahan-Babuška-Neumaier summation. This is a little more computationally costly than plain Kahan summation, but is always at least as accurate.

Constructors

KBN a a 

Instances

Summation KBN Double Source # 
Summation KBN Float Source # 

Methods

add :: Exp (KBN Float) -> Exp (KBN Float) -> Exp (KBN Float) Source #

zero :: Exp (KBN Float) Source #

into :: Proxy (* -> *) KBN -> Exp Float -> Exp (KBN Float) Source #

from :: Proxy (* -> *) KBN -> Exp (KBN Float) -> Exp Float Source #

Summation KBN CDouble Source # 
Summation KBN CFloat Source # 
Elt a => IsProduct Elt (KBN a) Source # 

Associated Types

type ProdRepr (KBN a) :: *

Methods

fromProd :: proxy Elt -> KBN a -> ProdRepr (KBN a)

toProd :: proxy Elt -> ProdRepr (KBN a) -> KBN a

prod :: proxy Elt -> KBN a -> ProdR Elt (ProdRepr (KBN a))

(Lift Exp a, Elt (Plain a)) => Lift Exp (KBN a) Source # 

Associated Types

type Plain (KBN a) :: * #

Methods

lift :: KBN a -> Exp (Plain (KBN a)) #

Elt a => Unlift Exp (KBN (Exp a)) Source # 

Methods

unlift :: Exp (Plain (KBN (Exp a))) -> KBN (Exp a) #

Show a => Show (KBN a) Source # 

Methods

showsPrec :: Int -> KBN a -> ShowS #

show :: KBN a -> String #

showList :: [KBN a] -> ShowS #

Elt a => Elt (KBN a) Source # 

Methods

eltType :: KBN a -> TupleType (EltRepr (KBN a))

fromElt :: KBN a -> EltRepr (KBN a)

toElt :: EltRepr (KBN a) -> KBN a

type EltRepr (KBN a) Source # 
type EltRepr (KBN a) = (((), EltRepr a), EltRepr a)
type ProdRepr (KBN a) Source # 
type ProdRepr (KBN a) = (((), a), a)
type Plain (KBN a) Source # 
type Plain (KBN a) = KBN (Plain a)

kbn :: Proxy KBN Source #

Return the result of a Kahan-Babuška-Neumaier sum.

Order-2 Kahan-Babuška summation

data KB2 a Source #

Second-order Kahan-Babuška summation. This is more computationally costly than Kahan-Babuška-Neumaier summation. Its advantage is that it can lose less precision (in admittedly obscure cases).

This method compensates for error in both the sum and the first-order compensation term, hence the use of "second order" in the name.

Constructors

KB2 a a a 

Instances

Summation KB2 Double Source # 
Summation KB2 Float Source # 

Methods

add :: Exp (KB2 Float) -> Exp (KB2 Float) -> Exp (KB2 Float) Source #

zero :: Exp (KB2 Float) Source #

into :: Proxy (* -> *) KB2 -> Exp Float -> Exp (KB2 Float) Source #

from :: Proxy (* -> *) KB2 -> Exp (KB2 Float) -> Exp Float Source #

Summation KB2 CDouble Source # 
Summation KB2 CFloat Source # 
Elt a => IsProduct Elt (KB2 a) Source # 

Associated Types

type ProdRepr (KB2 a) :: *

Methods

fromProd :: proxy Elt -> KB2 a -> ProdRepr (KB2 a)

toProd :: proxy Elt -> ProdRepr (KB2 a) -> KB2 a

prod :: proxy Elt -> KB2 a -> ProdR Elt (ProdRepr (KB2 a))

(Lift Exp a, Elt (Plain a)) => Lift Exp (KB2 a) Source # 

Associated Types

type Plain (KB2 a) :: * #

Methods

lift :: KB2 a -> Exp (Plain (KB2 a)) #

Elt a => Unlift Exp (KB2 (Exp a)) Source # 

Methods

unlift :: Exp (Plain (KB2 (Exp a))) -> KB2 (Exp a) #

Show a => Show (KB2 a) Source # 

Methods

showsPrec :: Int -> KB2 a -> ShowS #

show :: KB2 a -> String #

showList :: [KB2 a] -> ShowS #

Elt a => Elt (KB2 a) Source # 

Methods

eltType :: KB2 a -> TupleType (EltRepr (KB2 a))

fromElt :: KB2 a -> EltRepr (KB2 a)

toElt :: EltRepr (KB2 a) -> KB2 a

type EltRepr (KB2 a) Source # 
type EltRepr (KB2 a) = ((((), EltRepr a), EltRepr a), EltRepr a)
type ProdRepr (KB2 a) Source # 
type ProdRepr (KB2 a) = ((((), a), a), a)
type Plain (KB2 a) Source # 
type Plain (KB2 a) = KB2 (Plain a)

kb2 :: Proxy KB2 Source #

Return the result of a second-order Kahan-Babuška sum.

Kahan summation

data Kahan a Source #

Kahan summation. This is the least accurate of the compensated summation methods. This summation method is included only for completeness.

Constructors

Kahan a a 

Instances

Summation Kahan Double Source # 
Summation Kahan Float Source # 
Summation Kahan CDouble Source # 
Summation Kahan CFloat Source # 
Elt a => IsProduct Elt (Kahan a) Source # 

Associated Types

type ProdRepr (Kahan a) :: *

Methods

fromProd :: proxy Elt -> Kahan a -> ProdRepr (Kahan a)

toProd :: proxy Elt -> ProdRepr (Kahan a) -> Kahan a

prod :: proxy Elt -> Kahan a -> ProdR Elt (ProdRepr (Kahan a))

(Lift Exp a, Elt (Plain a)) => Lift Exp (Kahan a) Source # 

Associated Types

type Plain (Kahan a) :: * #

Methods

lift :: Kahan a -> Exp (Plain (Kahan a)) #

Elt a => Unlift Exp (Kahan (Exp a)) Source # 

Methods

unlift :: Exp (Plain (Kahan (Exp a))) -> Kahan (Exp a) #

Show a => Show (Kahan a) Source # 

Methods

showsPrec :: Int -> Kahan a -> ShowS #

show :: Kahan a -> String #

showList :: [Kahan a] -> ShowS #

Elt a => Elt (Kahan a) Source # 

Methods

eltType :: Kahan a -> TupleType (EltRepr (Kahan a))

fromElt :: Kahan a -> EltRepr (Kahan a)

toElt :: EltRepr (Kahan a) -> Kahan a

type EltRepr (Kahan a) Source # 
type EltRepr (Kahan a) = (((), EltRepr a), EltRepr a)
type ProdRepr (Kahan a) Source # 
type ProdRepr (Kahan a) = (((), a), a)
type Plain (Kahan a) Source # 
type Plain (Kahan a) = Kahan (Plain a)

kahan :: Proxy Kahan Source #

Return the result of a Kahan sum.