knead-1.0.1.1: Repa-like array processing using LLVM JIT
Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Array.Knead.Symbolic

Synopsis

Documentation

data Array sh a Source #

Instances

Instances details
C Array Source # 
Instance details

Defined in Data.Array.Knead.Symbolic.Private

Methods

lift0 :: Array sh a -> Array sh a Source #

lift1 :: (Array sha a -> Array shb b) -> Array sha a -> Array shb b Source #

lift2 :: (Array sha a -> Array shb b -> Array shc c) -> Array sha a -> Array shb b -> Array shc c Source #

class C array where Source #

This class allows to implement functions without parameters for both simple and parameterized arrays.

Methods

lift0 :: Array sh a -> array sh a Source #

lift1 :: (Array sha a -> Array shb b) -> array sha a -> array shb b Source #

lift2 :: (Array sha a -> Array shb b -> Array shc c) -> array sha a -> array shb b -> array shc c Source #

Instances

Instances details
C Array Source # 
Instance details

Defined in Data.Array.Knead.Symbolic.Private

Methods

lift0 :: Array sh a -> Array sh a Source #

lift1 :: (Array sha a -> Array shb b) -> Array sha a -> Array shb b Source #

lift2 :: (Array sha a -> Array shb b -> Array shc c) -> Array sha a -> Array shb b -> Array shc c Source #

data Exp a #

Instances

Instances details
Value Exp 
Instance details

Defined in LLVM.DSL.Expression

Methods

lift0 :: T a -> Exp a #

lift1 :: (T a -> T b) -> Exp a -> Exp b #

lift2 :: (T a -> T b -> T c) -> Exp a -> Exp b -> Exp c #

(Transcendental a, Real a, RationalConstant a) => Floating (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

pi :: Exp a #

exp :: Exp a -> Exp a #

log :: Exp a -> Exp a #

sqrt :: Exp a -> Exp a #

(**) :: Exp a -> Exp a -> Exp a #

logBase :: Exp a -> Exp a -> Exp a #

sin :: Exp a -> Exp a #

cos :: Exp a -> Exp a #

tan :: Exp a -> Exp a #

asin :: Exp a -> Exp a #

acos :: Exp a -> Exp a #

atan :: Exp a -> Exp a #

sinh :: Exp a -> Exp a #

cosh :: Exp a -> Exp a #

tanh :: Exp a -> Exp a #

asinh :: Exp a -> Exp a #

acosh :: Exp a -> Exp a #

atanh :: Exp a -> Exp a #

log1p :: Exp a -> Exp a #

expm1 :: Exp a -> Exp a #

log1pexp :: Exp a -> Exp a #

log1mexp :: Exp a -> Exp a #

(PseudoRing a, Real a, IntegerConstant a) => Num (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

(+) :: Exp a -> Exp a -> Exp a #

(-) :: Exp a -> Exp a -> Exp a #

(*) :: Exp a -> Exp a -> Exp a #

negate :: Exp a -> Exp a #

abs :: Exp a -> Exp a #

signum :: Exp a -> Exp a #

fromInteger :: Integer -> Exp a #

(Field a, Real a, RationalConstant a) => Fractional (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

(/) :: Exp a -> Exp a -> Exp a #

recip :: Exp a -> Exp a #

fromRational :: Rational -> Exp a #

Compose (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Associated Types

type Composed (Exp a) #

Methods

compose :: Exp a -> Exp (Composed (Exp a)) #

(Real a, PseudoRing a, IntegerConstant a) => C (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

abs :: Exp a -> Exp a #

signum :: Exp a -> Exp a #

Additive a => C (Exp a)

We do not require a numeric prelude superclass, thus also LLVM only types like vectors are instances.

Instance details

Defined in LLVM.DSL.Expression

Methods

zero :: Exp a #

(+) :: Exp a -> Exp a -> Exp a #

(-) :: Exp a -> Exp a -> Exp a #

negate :: Exp a -> Exp a #

(Transcendental a, RationalConstant a) => C (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

sqrt :: Exp a -> Exp a #

root :: Integer -> Exp a -> Exp a #

(^/) :: Exp a -> Rational -> Exp a #

(Field a, RationalConstant a) => C (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

(/) :: Exp a -> Exp a -> Exp a #

recip :: Exp a -> Exp a #

fromRational' :: Rational -> Exp a #

(^-) :: Exp a -> Integer -> Exp a #

(PseudoRing a, IntegerConstant a) => C (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

(*) :: Exp a -> Exp a -> Exp a #

one :: Exp a #

fromInteger :: Integer -> Exp a #

(^) :: Exp a -> Integer -> Exp a #

(Transcendental a, RationalConstant a) => C (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

Methods

pi :: Exp a #

exp :: Exp a -> Exp a #

log :: Exp a -> Exp a #

logBase :: Exp a -> Exp a -> Exp a #

(**) :: Exp a -> Exp a -> Exp a #

sin :: Exp a -> Exp a #

cos :: Exp a -> Exp a #

tan :: Exp a -> Exp a #

asin :: Exp a -> Exp a #

acos :: Exp a -> Exp a #

atan :: Exp a -> Exp a #

sinh :: Exp a -> Exp a #

cosh :: Exp a -> Exp a #

tanh :: Exp a -> Exp a #

asinh :: Exp a -> Exp a #

acosh :: Exp a -> Exp a #

atanh :: Exp a -> Exp a #

Aggregate (Exp a) (T a) 
Instance details

Defined in LLVM.DSL.Expression

Associated Types

type MultiValuesOf (Exp a) #

type ExpressionsOf (T a) #

Methods

bundle :: Exp a -> CodeGenFunction r (T a) #

dissect :: T a -> Exp a #

(a ~ Scalar v, PseudoModule v, IntegerConstant a) => C (Exp a) (Exp v) 
Instance details

Defined in LLVM.DSL.Expression

Methods

(*>) :: Exp a -> Exp v -> Exp v #

type Composed (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

type Composed (Exp a) = a
type MultiValuesOf (Exp a) 
Instance details

Defined in LLVM.DSL.Expression

type MultiValuesOf (Exp a) = T a

fix :: Id (Array sh a) Source #

shape :: Array sh a -> Exp sh Source #

(!) :: (C sh, Index sh ~ ix) => Array sh a -> Exp ix -> Exp a Source #

the :: Scalar sh => Array sh a -> Exp a Source #

fromScalar :: Scalar sh => Exp a -> Array sh a Source #

fill :: Exp sh -> Exp a -> Array sh a Source #

gather :: (C array, C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C a) => array sh1 ix0 -> array sh0 a -> array sh1 a Source #

backpermute :: (C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C a) => Exp sh1 -> (Exp ix1 -> Exp ix0) -> Array sh0 a -> Array sh1 a Source #

backpermute2 :: (C array, C sh0, Index sh0 ~ ix0, C sh1, Index sh1 ~ ix1, C sh, Index sh ~ ix) => Exp sh -> (Exp ix -> Exp ix0) -> (Exp ix -> Exp ix1) -> (Exp a -> Exp b -> Exp c) -> array sh0 a -> array sh1 b -> array sh c Source #

id :: (C array, C sh, Index sh ~ ix) => Exp sh -> array sh ix Source #

map :: (C array, C sh) => (Exp a -> Exp b) -> array sh a -> array sh b Source #

mapWithIndex :: (C array, C sh, Index sh ~ ix) => (Exp ix -> Exp a -> Exp b) -> array sh a -> array sh b Source #

zipWith :: (C array, C sh) => (Exp a -> Exp b -> Exp c) -> array sh a -> array sh b -> array sh c Source #

zipWith3 :: (C array, C sh) => (Exp a -> Exp b -> Exp c -> Exp d) -> array sh a -> array sh b -> array sh c -> array sh d Source #

zipWith4 :: (C array, C sh) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> array sh a -> array sh b -> array sh c -> array sh d -> array sh e Source #

zip :: (C array, C sh) => array sh a -> array sh b -> array sh (a, b) Source #

zip3 :: (C array, C sh) => array sh a -> array sh b -> array sh c -> array sh (a, b, c) Source #

zip4 :: (C array, C sh) => array sh a -> array sh b -> array sh c -> array sh d -> array sh (a, b, c, d) Source #

fold1 :: (C array, C sh0, C sh1, C a) => (Exp a -> Exp a -> Exp a) -> array (sh0, sh1) a -> array sh0 a Source #

fold1All :: (C sh, C a) => (Exp a -> Exp a -> Exp a) -> Array sh a -> Exp a Source #

findAll :: (C sh, C a) => (Exp a -> Exp Bool) -> Array sh a -> Exp (Maybe a) Source #

In principle this can be implemented using fold1All but it has a short-cut semantics. All means that it scans all dimensions but it does not mean that it finds all occurrences. If you want to get the index of the found element, please decorate the array elements with their indices before calling findAll.