Copyright | [2008..2020] The Accelerate Team |
---|---|
License | BSD3 |
Maintainer | Trevor L. McDonell <trevor.mcdonell@gmail.com> |
Stability | experimental |
Portability | non-portable (GHC extensions) |
Safe Haskell | None |
Language | Haskell2010 |
Data.Array.Accelerate
Description
Data.Array.Accelerate
defines an embedded language of array computations
for high-performance computing in Haskell. Computations on multi-dimensional,
regular arrays are expressed in the form of parameterised collective
operations such as maps, reductions, and permutations. These computations are
online compiled and can be executed on a range of architectures.
- Abstract interface:
The types representing array computations are only exported abstractly; client code can generate array computations and submit them for execution, but it cannot inspect these computations. This is to allow for more flexibility for future extensions of this library.
- Stratified language:
Accelerate distinguishes the types of collective operations Acc
from the
type of scalar operations Exp
to achieve a stratified language. Collective
operations comprise many scalar computations that are executed in parallel,
but scalar computations can not contain collective operations. This
separation excludes nested, irregular data-parallelism statically; instead,
Accelerate is limited to flat data-parallelism involving only regular,
multi-dimensional arrays.
- Optimisations:
Accelerate uses a number of scalar and array optimisations, including array fusion, in order to improve the performance of programs. Fusing a program entails combining successive traversals (loops) over an array into a single traversal, which reduces memory traffic and eliminates intermediate arrays.
- Code execution:
Several backends are available which can be used to evaluate accelerate programs:
- Data.Array.Accelerate.Interpreter: simple interpreter in Haskell as a reference implementation defining the semantics of the Accelerate language
- accelerate-llvm-native: implementation supporting parallel execution on multicore CPUs (e.g. x86).
- accelerate-llvm-ptx: implementation supporting parallel execution on CUDA-capable NVIDIA GPUs.
- Examples:
- A short tutorial-style example for generating a Mandelbrot set: http://www.acceleratehs.org/examples/mandelbrot.html
The accelerate-examples package demonstrates a range of computational kernels and several complete applications:
- Implementation of the canny edge detector
- Interactive Mandelbrot set generator
- N-body simulation of gravitational attraction between large bodies
- Implementation of the PageRank algorithm
- A simple, real-time, interactive ray tracer.
- A particle based simulation of stable fluid flows
- A cellular automaton simulation
- A "password recovery" tool, for dictionary attacks on MD5 hashes.
lulesh-accelerate is an implementation of the Livermore Unstructured Lagrangian Explicit Shock Hydrodynamics (LULESH) application. LULESH is representative of typical hydrodynamics codes, although simplified and hard-coded to solve the Sedov blast problem on an unstructured hexahedron mesh.
- For more information on LULESH: https://codesign.llnl.gov/lulesh.php.
- Starting a new project:
Accelerate and its associated packages are available on both Hackage and Stackage. A project template is available to help create a new projects using the stack build tool. To create a new project using the template:
stack new PROJECT_NAME https://github.com/AccelerateHS/accelerate/raw/stable/accelerate.hsfiles
- Additional components:
- accelerate-io: Fast conversion between Accelerate arrays and other formats (e.g. Repa, Vector).
- accelerate-fft: Fast Fourier transform, with FFI bindings to optimised implementations.
- accelerate-blas: BLAS and LAPACK operations, with FFI bindings to optimised implementations.
- accelerate-bignum: Fixed-width large integer arithmetic.
- containers-accelerate: Container types for use with Accelerate.
- hashable-accelerate: Class for types which can be converted to a value.
- colour-accelerate: Colour representations in Accelerate (RGB, sRGB, HSV, and HSL).
- gloss-accelerate: Generate gloss pictures from Accelerate.
- gloss-raster-accelerate: Parallel rendering of raster images and animations.
- lens-accelerate: Lens operators for Accelerate types.
- linear-accelerate: Linear vector space types for Accelerate.
- mwc-random-accelerate: Generate Accelerate arrays filled with high-quality pseudorandom numbers.
- Contact:
Mailing list for both use and development discussion:
- Bug reports: https://github.com/AccelerateHS/accelerate/issues
- Maintainer: Trevor L. McDonell: mailto:trevor.mcdonell@gmail.com
- Tip:
Accelerate tends to stress GHC's garbage collector, so it helps to increase the default GC allocation sizes. This can be done when running an executable by specifying RTS options on the command line, for example:
./foo +RTS -A64M -n2M -RTS
You can make these settings the default by adding the following ghc-options
to your .cabal
file or similar:
ghc-options: -with-rtsopts=-n2M -with-rtsopts=-A64M
To specify RTS options you will also need to compile your program with -rtsopts
.
Synopsis
- data Acc a
- data Array sh e
- class Arrays a
- type Scalar = Array DIM0
- type Vector = Array DIM1
- type Matrix = Array DIM2
- type Segments = Vector
- class Elt a
- data Z = Z
- data tail :. head = !tail :. !head
- type DIM0 = Z
- type DIM1 = DIM0 :. Int
- type DIM2 = DIM1 :. Int
- type DIM3 = DIM2 :. Int
- type DIM4 = DIM3 :. Int
- type DIM5 = DIM4 :. Int
- type DIM6 = DIM5 :. Int
- type DIM7 = DIM6 :. Int
- type DIM8 = DIM7 :. Int
- type DIM9 = DIM8 :. Int
- class (Elt sh, Elt (Any sh), FullShape sh ~ sh, CoSliceShape sh ~ sh, SliceShape sh ~ Z) => Shape sh
- class (Elt sl, Shape (SliceShape sl), Shape (CoSliceShape sl), Shape (FullShape sl)) => Slice sl where
- type SliceShape sl :: Type
- type CoSliceShape sl :: Type
- type FullShape sl :: Type
- sliceIndex :: SliceIndex (EltR sl) (EltR (SliceShape sl)) (EltR (CoSliceShape sl)) (EltR (FullShape sl))
- data All = All
- data Any sh = Any
- (!) :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh -> Exp e
- (!!) :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int -> Exp e
- the :: Elt e => Acc (Scalar e) -> Exp e
- null :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Bool
- length :: Elt e => Acc (Vector e) -> Exp Int
- shape :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh
- size :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int
- shapeSize :: forall sh. Shape sh => Exp sh -> Exp Int
- use :: forall arrays. Arrays arrays => arrays -> Acc arrays
- unit :: forall e. Elt e => Exp e -> Acc (Scalar e)
- generate :: forall sh a. (Shape sh, Elt a) => Exp sh -> (Exp sh -> Exp a) -> Acc (Array sh a)
- fill :: (Shape sh, Elt e) => Exp sh -> Exp e -> Acc (Array sh e)
- enumFromN :: (Shape sh, Num e, FromIntegral Int e) => Exp sh -> Exp e -> Acc (Array sh e)
- enumFromStepN :: (Shape sh, Num e, FromIntegral Int e) => Exp sh -> Exp e -> Exp e -> Acc (Array sh e)
- (++) :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- concatOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) -> Acc (Array sh e)
- expand :: (Elt a, Elt b) => (Exp a -> Exp Int) -> (Exp a -> Exp Int -> Exp b) -> Acc (Vector a) -> Acc (Vector b)
- (?|) :: Arrays a => Exp Bool -> (Acc a, Acc a) -> Acc a
- acond :: Arrays a => Exp Bool -> Acc a -> Acc a -> Acc a
- awhile :: forall a. Arrays a => (Acc a -> Acc (Scalar Bool)) -> (Acc a -> Acc a) -> Acc a -> Acc a
- class IfThenElse t where
- type EltT t a :: Constraint
- ifThenElse :: EltT t a => Exp Bool -> t a -> t a -> t a
- (>->) :: forall a b c. (Arrays a, Arrays b, Arrays c) => (Acc a -> Acc b) -> (Acc b -> Acc c) -> Acc a -> Acc c
- compute :: Arrays a => Acc a -> Acc a
- indexed :: (Shape sh, Elt a) => Acc (Array sh a) -> Acc (Array sh (sh, a))
- map :: forall sh a b. (Shape sh, Elt a, Elt b) => (Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b)
- imap :: (Shape sh, Elt a, Elt b) => (Exp sh -> Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b)
- zipWith :: forall sh a b c. (Shape sh, Elt a, Elt b, Elt c) => (Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c)
- zipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d)
- zipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e)
- zipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f)
- zipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g)
- zipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h)
- zipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i)
- zipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j)
- izipWith :: (Shape sh, Elt a, Elt b, Elt c) => (Exp sh -> Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c)
- izipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d)
- izipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e)
- izipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f)
- izipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g)
- izipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h)
- izipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i)
- izipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j)
- zip :: (Shape sh, Elt a, Elt b) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh (a, b))
- zip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh (a, b, c))
- zip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh (a, b, c, d))
- zip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh (a, b, c, d, e))
- zip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh (a, b, c, d, e, f))
- zip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh (a, b, c, d, e, f, g))
- zip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh (a, b, c, d, e, f, g, h))
- zip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh (a, b, c, d, e, f, g, h, i))
- unzip :: (Shape sh, Elt a, Elt b) => Acc (Array sh (a, b)) -> (Acc (Array sh a), Acc (Array sh b))
- unzip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh (a, b, c)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c))
- unzip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh (a, b, c, d)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d))
- unzip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh (a, b, c, d, e)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e))
- unzip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh (a, b, c, d, e, f)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f))
- unzip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh (a, b, c, d, e, f, g)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g))
- unzip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh (a, b, c, d, e, f, g, h)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h))
- unzip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh (a, b, c, d, e, f, g, h, i)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h), Acc (Array sh i))
- reshape :: forall sh sh' e. (Shape sh, Shape sh', Elt e) => Exp sh -> Acc (Array sh' e) -> Acc (Array sh e)
- flatten :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Acc (Vector e)
- replicate :: forall slix e. (Slice slix, Elt e) => Exp slix -> Acc (Array (SliceShape slix) e) -> Acc (Array (FullShape slix) e)
- slice :: forall slix e. (Slice slix, Elt e) => Acc (Array (FullShape slix) e) -> Exp slix -> Acc (Array (SliceShape slix) e)
- init :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- tail :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- take :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- drop :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- slit :: (Shape sh, Elt e) => Exp Int -> Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e)
- initOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e)
- tailOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e)
- takeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e)
- dropOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e)
- slitOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e)
- permute :: forall sh sh' a. (Shape sh, Shape sh', Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array sh' a) -> (Exp sh -> Exp (Maybe sh')) -> Acc (Array sh a) -> Acc (Array sh' a)
- scatter :: Elt e => Acc (Vector Int) -> Acc (Vector e) -> Acc (Vector e) -> Acc (Vector e)
- backpermute :: forall sh sh' a. (Shape sh, Shape sh', Elt a) => Exp sh' -> (Exp sh' -> Exp sh) -> Acc (Array sh a) -> Acc (Array sh' a)
- gather :: (Shape sh, Elt e) => Acc (Array sh Int) -> Acc (Vector e) -> Acc (Array sh e)
- reverse :: Elt e => Acc (Vector e) -> Acc (Vector e)
- transpose :: Elt e => Acc (Array DIM2 e) -> Acc (Array DIM2 e)
- reverseOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e)
- transposeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e)
- filter :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int)
- compact :: forall sh e. (Shape sh, Elt e) => Acc (Array (sh :. Int) Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int)
- fold :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array sh a)
- fold1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array sh a)
- foldAll :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array sh a) -> Acc (Scalar a)
- fold1All :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array sh a) -> Acc (Scalar a)
- foldSeg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- fold1Seg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- foldSeg' :: forall sh a i. (Shape sh, Elt a, Elt i, IsIntegral i, i ~ EltR i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a)
- fold1Seg' :: forall sh a i. (Shape sh, Elt a, Elt i, IsIntegral i, i ~ EltR i) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a)
- all :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Array sh Bool)
- any :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Array sh Bool)
- and :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool)
- or :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool)
- sum :: (Shape sh, Num e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e)
- product :: (Shape sh, Num e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e)
- minimum :: (Shape sh, Ord e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e)
- maximum :: (Shape sh, Ord e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e)
- scanl :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- scanl1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- scanl' :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a, Array sh a)
- scanr :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- scanr1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- scanr' :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a, Array sh a)
- prescanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- postscanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- prescanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- postscanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a)
- scanlSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- scanl1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- scanl'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e)
- prescanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- postscanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- scanrSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- scanr1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- scanr'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e)
- prescanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- postscanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e)
- stencil :: forall sh stencil a b. (Stencil sh a stencil, Elt b) => (stencil -> Exp b) -> Boundary (Array sh a) -> Acc (Array sh a) -> Acc (Array sh b)
- stencil2 :: forall sh stencil1 stencil2 a b c. (Stencil sh a stencil1, Stencil sh b stencil2, Elt c) => (stencil1 -> stencil2 -> Exp c) -> Boundary (Array sh a) -> Acc (Array sh a) -> Boundary (Array sh b) -> Acc (Array sh b) -> Acc (Array sh c)
- class Stencil sh e stencil
- data Boundary t
- clamp :: Boundary (Array sh e)
- mirror :: Boundary (Array sh e)
- wrap :: Boundary (Array sh e)
- function :: forall sh e. (Shape sh, Elt e) => (Exp sh -> Exp e) -> Boundary (Array sh e)
- type Stencil3 a = (Exp a, Exp a, Exp a)
- type Stencil5 a = (Exp a, Exp a, Exp a, Exp a, Exp a)
- type Stencil7 a = (Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a)
- type Stencil9 a = (Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a, Exp a)
- type Stencil3x3 a = (Stencil3 a, Stencil3 a, Stencil3 a)
- type Stencil5x3 a = (Stencil5 a, Stencil5 a, Stencil5 a)
- type Stencil3x5 a = (Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a)
- type Stencil5x5 a = (Stencil5 a, Stencil5 a, Stencil5 a, Stencil5 a, Stencil5 a)
- type Stencil3x3x3 a = (Stencil3x3 a, Stencil3x3 a, Stencil3x3 a)
- type Stencil5x3x3 a = (Stencil5x3 a, Stencil5x3 a, Stencil5x3 a)
- type Stencil3x5x3 a = (Stencil3x5 a, Stencil3x5 a, Stencil3x5 a)
- type Stencil3x3x5 a = (Stencil3x3 a, Stencil3x3 a, Stencil3x3 a, Stencil3x3 a, Stencil3x3 a)
- type Stencil5x5x3 a = (Stencil5x5 a, Stencil5x5 a, Stencil5x5 a)
- type Stencil5x3x5 a = (Stencil5x3 a, Stencil5x3 a, Stencil5x3 a, Stencil5x3 a, Stencil5x3 a)
- type Stencil3x5x5 a = (Stencil3x5 a, Stencil3x5 a, Stencil3x5 a, Stencil3x5 a, Stencil3x5 a)
- type Stencil5x5x5 a = (Stencil5x5 a, Stencil5x5 a, Stencil5x5 a, Stencil5x5 a, Stencil5x5 a)
- data Exp t
- data Vec (n :: Nat) a
- type VecElt a = (Elt a, Prim a, IsSingle a, EltR a ~ a)
- class Elt a => Eq a where
- class Eq a => Ord a where
- data Ordering
- pattern LT_ :: HasCallStack => Exp Ordering
- pattern EQ_ :: HasCallStack => Exp Ordering
- pattern GT_ :: HasCallStack => Exp Ordering
- type Enum a = Enum (Exp a)
- succ :: Enum a => a -> a
- pred :: Enum a => a -> a
- type Bounded a = (Elt a, Bounded (Exp a))
- minBound :: Bounded a => a
- maxBound :: Bounded a => a
- type Num a = (Elt a, Num (Exp a))
- (+) :: Num a => a -> a -> a
- (-) :: Num a => a -> a -> a
- (*) :: Num a => a -> a -> a
- negate :: Num a => a -> a
- abs :: Num a => a -> a
- signum :: Num a => a -> a
- fromInteger :: Num a => Integer -> a
- type Integral a = (Enum a, Ord a, Num a, Integral (Exp a))
- quot :: Integral a => a -> a -> a
- rem :: Integral a => a -> a -> a
- div :: Integral a => a -> a -> a
- mod :: Integral a => a -> a -> a
- quotRem :: Integral a => a -> a -> (a, a)
- divMod :: Integral a => a -> a -> (a, a)
- class (Num a, Ord a) => Rational a where
- toRational :: (FromIntegral Int64 b, Integral b) => Exp a -> Exp (Ratio b)
- type Fractional a = (Num a, Fractional (Exp a))
- (/) :: Fractional a => a -> a -> a
- recip :: Fractional a => a -> a
- fromRational :: Fractional a => Rational -> a
- type Floating a = (Fractional a, Floating (Exp a))
- pi :: Floating a => a
- sin :: Floating a => a -> a
- cos :: Floating a => a -> a
- tan :: Floating a => a -> a
- asin :: Floating a => a -> a
- acos :: Floating a => a -> a
- atan :: Floating a => a -> a
- sinh :: Floating a => a -> a
- cosh :: Floating a => a -> a
- tanh :: Floating a => a -> a
- asinh :: Floating a => a -> a
- acosh :: Floating a => a -> a
- atanh :: Floating a => a -> a
- exp :: Floating a => a -> a
- sqrt :: Floating a => a -> a
- log :: Floating a => a -> a
- (**) :: Floating a => a -> a -> a
- logBase :: Floating a => a -> a -> a
- class (Ord a, Fractional a) => RealFrac a where
- properFraction :: (Integral b, FromIntegral Int64 b) => Exp a -> (Exp b, Exp a)
- truncate :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b
- round :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b
- ceiling :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b
- floor :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b
- div' :: (RealFrac a, FromIntegral Int64 b, Integral b) => Exp a -> Exp a -> Exp b
- mod' :: (Floating a, RealFrac a, ToFloating Int64 a) => Exp a -> Exp a -> Exp a
- divMod' :: (Floating a, RealFrac a, Integral b, FromIntegral Int64 b, ToFloating b a) => Exp a -> Exp a -> (Exp b, Exp a)
- class (RealFrac a, Floating a) => RealFloat a where
- floatRadix :: Exp a -> Exp Int64
- floatDigits :: Exp a -> Exp Int
- floatRange :: Exp a -> (Exp Int, Exp Int)
- decodeFloat :: Exp a -> (Exp Int64, Exp Int)
- encodeFloat :: Exp Int64 -> Exp Int -> Exp a
- exponent :: Exp a -> Exp Int
- significand :: Exp a -> Exp a
- scaleFloat :: Exp Int -> Exp a -> Exp a
- isNaN :: Exp a -> Exp Bool
- isInfinite :: Exp a -> Exp Bool
- isDenormalized :: Exp a -> Exp Bool
- isNegativeZero :: Exp a -> Exp Bool
- isIEEE :: Exp a -> Exp Bool
- atan2 :: Exp a -> Exp a -> Exp a
- class FromIntegral a b where
- fromIntegral :: Integral a => Exp a -> Exp b
- class ToFloating a b where
- toFloating :: (Num a, Floating b) => Exp a -> Exp b
- class Lift c e where
- class Lift c e => Unlift c e where
- lift1 :: (Unlift Exp a, Lift Exp b) => (a -> b) -> Exp (Plain a) -> Exp (Plain b)
- lift2 :: (Unlift Exp a, Unlift Exp b, Lift Exp c) => (a -> b -> c) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c)
- lift3 :: (Unlift Exp a, Unlift Exp b, Unlift Exp c, Lift Exp d) => (a -> b -> c -> d) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c) -> Exp (Plain d)
- ilift1 :: (Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1
- ilift2 :: (Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1
- ilift3 :: (Exp Int -> Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 -> Exp DIM1
- pattern Pattern :: forall b a context. IsPattern context a b => b -> context a
- pattern T2 :: IsPattern con (x0, x1) (con x0, con x1) => con x0 -> con x1 -> con (x0, x1)
- pattern T3 :: IsPattern con (x0, x1, x2) (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con (x0, x1, x2)
- pattern T4 :: IsPattern con (x0, x1, x2, x3) (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con (x0, x1, x2, x3)
- pattern T5 :: IsPattern con (x0, x1, x2, x3, x4) (con x0, con x1, con x2, con x3, con x4) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con (x0, x1, x2, x3, x4)
- pattern T6 :: IsPattern con (x0, x1, x2, x3, x4, x5) (con x0, con x1, con x2, con x3, con x4, con x5) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con (x0, x1, x2, x3, x4, x5)
- pattern T7 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6) (con x0, con x1, con x2, con x3, con x4, con x5, con x6) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con (x0, x1, x2, x3, x4, x5, x6)
- pattern T8 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con (x0, x1, x2, x3, x4, x5, x6, x7)
- pattern T9 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8)
- pattern T10 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)
- pattern T11 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)
- pattern T12 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)
- pattern T13 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)
- pattern T14 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)
- pattern T15 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)
- pattern T16 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)
- pattern Z_ :: Exp DIM0
- pattern Ix :: (Elt a, Elt b) => Exp a -> Exp b -> Exp (a :. b)
- pattern (::.) :: (Elt a, Elt b) => Exp a -> Exp b -> Exp (a :. b)
- pattern I0 :: () => Exp Z
- pattern I1 :: Elt x0 => Exp x0 -> Exp ((:.) Z x0)
- pattern I2 :: (Elt x0, Elt x1) => Exp x0 -> Exp x1 -> Exp ((:.) ((:.) Z x0) x1)
- pattern I3 :: (Elt x0, Elt x1, Elt x2) => Exp x0 -> Exp x1 -> Exp x2 -> Exp ((:.) ((:.) ((:.) Z x0) x1) x2)
- pattern I4 :: (Elt x0, Elt x1, Elt x2, Elt x3) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3)
- pattern I5 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4)
- pattern I6 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5)
- pattern I7 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6)
- pattern I8 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7)
- pattern I9 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp x8 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7) x8)
- pattern Vec2 :: Prim a => a -> a -> Vec2 a
- pattern V2 :: IsVector con vec (con x0, con x1) => con x0 -> con x1 -> con vec
- pattern Vec3 :: Prim a => a -> a -> a -> Vec3 a
- pattern V3 :: IsVector con vec (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con vec
- pattern Vec4 :: Prim a => a -> a -> a -> a -> Vec4 a
- pattern V4 :: IsVector con vec (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con vec
- pattern Vec8 :: Prim a => a -> a -> a -> a -> a -> a -> a -> a -> Vec8 a
- pattern V8 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con vec
- pattern Vec16 :: Prim a => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> Vec16 a
- pattern V16 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con vec
- mkPattern :: Name -> DecsQ
- mkPatterns :: [Name] -> DecsQ
- constant :: forall e. (HasCallStack, Elt e) => e -> Exp e
- fst :: (Elt a, Elt b) => Exp (a, b) -> Exp a
- afst :: (Arrays a, Arrays b) => Acc (a, b) -> Acc a
- snd :: (Elt a, Elt b) => Exp (a, b) -> Exp b
- asnd :: (Arrays a, Arrays b) => Acc (a, b) -> Acc b
- curry :: Lift f (f a, f b) => (f (Plain (f a), Plain (f b)) -> f c) -> f a -> f b -> f c
- uncurry :: Unlift f (f a, f b) => (f a -> f b -> f c) -> f (Plain (f a), Plain (f b)) -> f c
- (?) :: Elt t => Exp Bool -> (Exp t, Exp t) -> Exp t
- match :: Matching f => f -> f
- cond :: Elt t => Exp Bool -> Exp t -> Exp t -> Exp t
- while :: forall e. Elt e => (Exp e -> Exp Bool) -> (Exp e -> Exp e) -> Exp e -> Exp e
- iterate :: Elt a => Exp Int -> (Exp a -> Exp a) -> Exp a -> Exp a
- sfoldl :: (Shape sh, Elt a, Elt b) => (Exp a -> Exp b -> Exp a) -> Exp a -> Exp sh -> Acc (Array (sh :. Int) b) -> Exp a
- (&&) :: Exp Bool -> Exp Bool -> Exp Bool
- (||) :: Exp Bool -> Exp Bool -> Exp Bool
- not :: Exp Bool -> Exp Bool
- subtract :: Num a => Exp a -> Exp a -> Exp a
- even :: Integral a => Exp a -> Exp Bool
- odd :: Integral a => Exp a -> Exp Bool
- gcd :: Integral a => Exp a -> Exp a -> Exp a
- lcm :: Integral a => Exp a -> Exp a -> Exp a
- (^) :: forall a b. (Num a, Integral b) => Exp a -> Exp b -> Exp a
- (^^) :: (Fractional a, Integral b) => Exp a -> Exp b -> Exp a
- index0 :: Exp Z
- index1 :: Elt i => Exp i -> Exp (Z :. i)
- unindex1 :: Elt i => Exp (Z :. i) -> Exp i
- index2 :: Elt i => Exp i -> Exp i -> Exp ((Z :. i) :. i)
- unindex2 :: Elt i => Exp ((Z :. i) :. i) -> Exp (i, i)
- index3 :: Elt i => Exp i -> Exp i -> Exp i -> Exp (((Z :. i) :. i) :. i)
- unindex3 :: Elt i => Exp (((Z :. i) :. i) :. i) -> Exp (i, i, i)
- indexHead :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp a
- indexTail :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp sh
- toIndex :: forall sh. Shape sh => Exp sh -> Exp sh -> Exp Int
- fromIndex :: forall sh. Shape sh => Exp sh -> Exp Int -> Exp sh
- intersect :: forall sh. Shape sh => Exp sh -> Exp sh -> Exp sh
- ord :: Exp Char -> Exp Int
- chr :: Exp Int -> Exp Char
- boolToInt :: Exp Bool -> Exp Int
- bitcast :: (Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b), BitSizeEq (EltR a) (EltR b)) => Exp a -> Exp b
- foreignAcc :: forall as bs asm. (Arrays as, Arrays bs, Foreign asm) => asm (ArraysR as -> ArraysR bs) -> (Acc as -> Acc bs) -> Acc as -> Acc bs
- foreignExp :: forall x y asm. (Elt x, Elt y, Foreign asm) => asm (EltR x -> EltR y) -> (Exp x -> Exp y) -> Exp x -> Exp y
- arrayRank :: forall sh e. Shape sh => Array sh e -> Int
- arrayShape :: Shape sh => Array sh e -> sh
- arraySize :: Shape sh => Array sh e -> Int
- arrayReshape :: (Shape sh, Shape sh') => sh -> Array sh' e -> Array sh e
- indexArray :: (Shape sh, Elt e) => Array sh e -> sh -> e
- linearIndexArray :: Elt e => Array sh e -> Int -> e
- fromFunction :: (Shape sh, Elt e) => sh -> (sh -> e) -> Array sh e
- fromFunctionM :: forall sh e. (Shape sh, Elt e) => sh -> (sh -> IO e) -> IO (Array sh e)
- fromList :: forall sh e. (Shape sh, Elt e) => sh -> [e] -> Array sh e
- toList :: forall sh e. (Shape sh, Elt e) => Array sh e -> [e]
- (.) :: (b -> c) -> (a -> b) -> a -> c
- ($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b
- (&) :: a -> (a -> b) -> b
- error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a
- undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a
- const :: a -> b -> a
- otherwise :: Bool
- class Show a
- class Generic a
- type HasCallStack = ?callStack :: CallStack
- data Int
- data Int8
- data Int16
- data Int32
- data Int64
- data Word
- data Word8
- data Word16
- data Word32
- data Word64
- newtype Half = Half {}
- data Float
- data Double
- data Bool
- pattern True_ :: HasCallStack => Exp Bool
- pattern False_ :: HasCallStack => Exp Bool
- data Maybe a
- pattern Nothing_ :: forall a. (HasCallStack, Elt a) => Exp (Maybe a)
- pattern Just_ :: forall a. (HasCallStack, Elt a) => Exp a -> Exp (Maybe a)
- data Char
- data CFloat
- data CDouble
- data CShort
- data CUShort
- data CInt
- data CUInt
- data CLong
- data CULong
- data CLLong
- data CULLong
- data CChar
- data CSChar
- data CUChar
The Accelerate Array Language
Embedded array computations
Accelerate is an embedded language that distinguishes between vanilla arrays (e.g. in Haskell memory on the CPU) and embedded arrays (e.g. in device memory on a GPU), as well as the computations on both of these. Since Accelerate is an embedded language, programs written in Accelerate are not compiled by the Haskell compiler (GHC). Rather, each Accelerate backend is a runtime compiler which generates and executes parallel SIMD code of the target language at application runtime.
The type constructor Acc
represents embedded collective array operations.
A term of type Acc a
is an Accelerate program which, once executed, will
produce a value of type a
(an Array
or a tuple of Arrays
). Collective
operations of type Acc a
comprise many scalar expressions, wrapped in
type constructor Exp
, which will be executed in parallel. Although
collective operations comprise many scalar operations executed in parallel,
scalar operations cannot initiate new collective operations: this
stratification between scalar operations in Exp
and array operations in
Acc
helps statically exclude nested data parallelism, which is difficult
to execute efficiently on constrained hardware such as GPUs.
- A simple example
As a simple example, to compute a vector dot product we can write:
dotp :: Num a => Vector a -> Vector a -> Acc (Scalar a) dotp xs ys = let xs' = use xs ys' = use ys in fold (+) 0 ( zipWith (*) xs' ys' )
The function dotp
consumes two one-dimensional arrays (Vector
s) of
values, and produces a single (Scalar
) result as output. As the return type
is wrapped in the type Acc
, we see that it is an embedded Accelerate
computation - it will be evaluated in the object language of dynamically
generated parallel code, rather than the meta language of vanilla Haskell.
As the arguments to dotp
are plain Haskell arrays, to make these available
to Accelerate computations they must be embedded with the
use
function.
An Accelerate backend is used to evaluate the embedded computation and return
the result back to vanilla Haskell. Calling the run
function of a backend
will generate code for the target architecture, compile, and execute it. For
example, the following backends are available:
- accelerate-llvm-native: for execution on multicore CPUs
- accelerate-llvm-ptx: for execution on NVIDIA CUDA-capable GPUs
See also Exp
, which encapsulates embedded scalar computations.
- Avoiding nested parallelism
As mentioned above, embedded scalar computations of type Exp
can not
initiate further collective operations.
Suppose we wanted to extend our above dotp
function to matrix-vector
multiplication. First, let's rewrite our dotp
function to take Acc
arrays
as input (which is typically what we want):
dotp :: Num a => Acc (Vector a) -> Acc (Vector a) -> Acc (Scalar a) dotp xs ys = fold (+) 0 ( zipWith (*) xs ys )
We might then be inclined to lift our dot-product program to the following
(incorrect) matrix-vector product, by applying dotp
to each row of the
input matrix:
mvm_ndp :: Num a => Acc (Matrix a) -> Acc (Vector a) -> Acc (Vector a) mvm_ndp mat vec = let Z :. rows :. cols = unlift (shape mat) :: Z :. Exp Int :. Exp Int in generate (index1 rows) (\row -> the $ dotp vec (slice mat (lift (row :. All))))
Here, we use generate
to create a one-dimensional
vector by applying at each index a function to slice
out the corresponding row
of the matrix to pass to the dotp
function.
However, since both generate
and
slice
are data-parallel operations, and moreover that
slice
depends on the argument row
given to it by
the generate
function, this definition requires
nested data-parallelism, and is thus not permitted. The clue that this
definition is invalid is that in order to create a program which will be
accepted by the type checker, we must use the function
the
to retrieve the result of the dotp
operation,
effectively concealing that dotp
is a collective array computation in order
to match the type expected by generate
, which is that
of scalar expressions. Additionally, since we have fooled the type-checker,
this problem will only be discovered at program runtime.
In order to avoid this problem, we can make use of the fact that operations
in Accelerate are rank polymorphic. The fold
operation reduces along the innermost dimension of an array of arbitrary
rank, reducing the rank (dimensionality) of the array by one. Thus, we can
replicate
the input vector to as many rows
there
are in the input matrix, and perform the dot-product of the vector with every
row simultaneously:
mvm :: A.Num a => Acc (Matrix a) -> Acc (Vector a) -> Acc (Vector a) mvm mat vec = let Z :. rows :. cols = unlift (shape mat) :: Z :. Exp Int :. Exp Int vec' = A.replicate (lift (Z :. rows :. All)) vec in A.fold (+) 0 ( A.zipWith (*) mat vec' )
Note that the intermediate, replicated array vec'
is never actually created
in memory; it will be fused directly into the operation which consumes it. We
discuss fusion next.
- Fusion
Array computations of type Acc
will be subject to array fusion;
Accelerate will combine individual Acc
computations into a single
computation, which reduces the number of traversals over the input data and
thus improves performance. As such, it is often useful to have some intuition
on when fusion should occur.
The main idea is to first partition array operations into two categories:
- Element-wise operations, such as
map
,generate
, andbackpermute
. Each element of these operations can be computed independently of all others. - Collective operations such as
fold
,scanl
, andstencil
. To compute each output element of these operations requires reading multiple elements from the input array(s).
Element-wise operations fuse together whenever the consumer operation uses a single element of the input array. Element-wise operations can both fuse their inputs into themselves, as well be fused into later operations. Both these examples should fuse into a single loop:
If the consumer operation uses more than one element of the input array
(typically, via generate
indexing an array multiple
times), then the input array will be completely evaluated first; no fusion
occurs in this case, because fusing the first operation into the second
implies duplicating work.
On the other hand, collective operations can fuse their input arrays into themselves, but on output always evaluate to an array; collective operations will not be fused into a later step. For example:
Here the element-wise sequence (use
+ generate
+ zipWith
) will
fuse into a single operation, which then fuses into the collective
fold
operation. At this point in the program the
fold
must now be evaluated. In the final step the
map
reads in the array produced by
fold
. As there is no fusion between the
fold
and map
steps, this
program consists of two "loops"; one for the use
+ generate
+ zipWith
+ fold
step, and one for the final
map
step.
You can see how many operations will be executed in the fused program by
Show
-ing the Acc
program, or by using the debugging option -ddump-dot
to save the program as a graphviz DOT file.
As a special note, the operations unzip
and
reshape
, when applied to a real array, are executed
in constant time, so in this situation these operations will not be fused.
- Tips
- Since
Acc
represents embedded computations that will only be executed when evaluated by a backend, we can programatically generate these computations using the meta language Haskell; for example, unrolling loops or embedding input values into the generated code. - It is usually best to keep all intermediate computations in
Acc
, and onlyrun
the computation at the very end to produce the final result. This enables optimisations between intermediate results (e.g. array fusion) and, if the target architecture has a separate memory space, as is the case of GPUs, to prevent excessive data transfers.
Instances
IfThenElse Acc Source # | |
Unlift Acc () Source # | |
Lift Acc () Source # | |
Unlift Acc (Acc a) Source # | |
Lift Acc (Acc a) Source # | |
(Arrays x0, Arrays x1) => Unlift Acc (Acc x0, Acc x1) Source # | |
((Lift Acc x0, Lift Acc x1), (Arrays (Plain x0), Arrays (Plain x1))) => Lift Acc (x0, x1) Source # | |
(Shape sh, Elt e) => Lift Acc (Array sh e) Source # | |
(Arrays x0, Arrays x1, Arrays x2) => Unlift Acc (Acc x0, Acc x1, Acc x2) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2))) => Lift Acc (x0, x1, x2) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3))) => Lift Acc (x0, x1, x2, x3) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4))) => Lift Acc (x0, x1, x2, x3, x4) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5))) => Lift Acc (x0, x1, x2, x3, x4, x5) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13) Source # | |
Defined in Data.Array.Accelerate.Lift | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14) Source # | |
Defined in Data.Array.Accelerate.Lift | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13, Lift Acc x14), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13), Arrays (Plain x14))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # | |
Defined in Data.Array.Accelerate.Lift | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14, Arrays x15) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source # | |
Defined in Data.Array.Accelerate.Lift Methods unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source # | |
((Lift Acc x0, Lift Acc x1, Lift Acc x2, Lift Acc x3, Lift Acc x4, Lift Acc x5, Lift Acc x6, Lift Acc x7, Lift Acc x8, Lift Acc x9, Lift Acc x10, Lift Acc x11, Lift Acc x12, Lift Acc x13, Lift Acc x14, Lift Acc x15), (Arrays (Plain x0), Arrays (Plain x1), Arrays (Plain x2), Arrays (Plain x3), Arrays (Plain x4), Arrays (Plain x5), Arrays (Plain x6), Arrays (Plain x7), Arrays (Plain x8), Arrays (Plain x9), Arrays (Plain x10), Arrays (Plain x11), Arrays (Plain x12), Arrays (Plain x13), Arrays (Plain x14), Arrays (Plain x15))) => Lift Acc (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # | |
Defined in Data.Array.Accelerate.Lift | |
Arrays arrs => Show (Acc arrs) Source # | |
Arrays b => Afunction (Acc b) Source # | |
Defined in Data.Array.Accelerate.Trafo.Sharing Methods afunctionRepr :: AfunctionRepr (Acc b) (AfunctionR (Acc b)) (ArraysFunctionR (Acc b)) convertOpenAfun :: HasCallStack => Config -> ArrayLayout aenv aenv -> Acc b -> OpenAfun aenv (ArraysFunctionR (Acc b)) | |
Afunction (Acc a -> f) => Show (Acc a -> f) Source # | |
(Arrays a, Afunction r) => Afunction (Acc a -> r) Source # | |
Defined in Data.Array.Accelerate.Trafo.Sharing Methods afunctionRepr :: AfunctionRepr (Acc a -> r) (AfunctionR (Acc a -> r)) (ArraysFunctionR (Acc a -> r)) convertOpenAfun :: HasCallStack => Config -> ArrayLayout aenv aenv -> (Acc a -> r) -> OpenAfun aenv (ArraysFunctionR (Acc a -> r)) | |
type EltT Acc a Source # | |
Defined in Data.Array.Accelerate.Prelude | |
type AfunctionR (Acc b) Source # | |
Defined in Data.Array.Accelerate.Trafo.Sharing | |
type Plain (Acc a) Source # | |
Defined in Data.Array.Accelerate.Lift | |
type AfunctionR (Acc a -> r) Source # | |
Defined in Data.Array.Accelerate.Trafo.Sharing |
Arrays
Dense, regular, multi-dimensional arrays.
The Array
is the core computational unit of Accelerate; all programs
in Accelerate take zero or more arrays as input and produce one or more
arrays as output. The Array
type has two type parameters:
- sh: is the shape of the array, tracking the dimensionality and extent of
each dimension of the array; for example,
DIM1
for one-dimensionalVector
s,DIM2
for two-dimensional matrices, and so on. - e: represents the type of each element of the array; for example,
Int
,Float
, et cetera.
Array data is store unboxed in an unzipped struct-of-array representation.
Elements are laid out in row-major order (the right-most index of a Shape
is the fastest varying). The allowable array element types are members of the
Elt
class, which roughly consists of:
- Signed and unsigned integers (8, 16, 32, and 64-bits wide).
- Floating point numbers (single and double precision)
Char
Bool
- ()
- Shapes formed from
Z
and (:.
) - Nested tuples of all of these, currently up to 16-elements wide.
Note that Array
itself is not an allowable element type---there are no
nested arrays in Accelerate, regular arrays only!
If device and host memory are separate, arrays will be transferred to the
device when necessary (possibly asynchronously and in parallel with other
tasks) and cached on the device if sufficient memory is available. Arrays are
made available to embedded language computations via
use
.
Section "Getting data in" lists functions for getting data into and out of
the Array
type.
Instances
(Shape sh, Elt e) => Lift Acc (Array sh e) Source # | |
Elt e => IsList (Array DIM1 e) Source # | |
(Shape sh, Elt e, Eq sh, Eq e) => Eq (Array sh e) Source # | |
(Shape sh, Elt e, Show e) => Show (Array sh e) Source # | |
(Shape sh, Elt e) => NFData (Array sh e) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array | |
(Shape sh, Elt e) => Arrays (Array sh e) Source # | |
type Item (Vector e) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array | |
type Plain (Array sh e) Source # | |
Defined in Data.Array.Accelerate.Lift |
The Arrays
class characterises the types which can appear in collective
Accelerate computations of type Acc
.
Arrays
consists of nested tuples of individual Array
s, currently up
to 16-elements wide. Accelerate computations can thereby return multiple
results.
Instances
Arrays () Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR () | |
(Arrays x0, Arrays x1) => Arrays (x0, x1) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1) | |
(Shape sh, Elt e) => Arrays (Array sh e) Source # | |
(Arrays x0, Arrays x1, Arrays x2) => Arrays (x0, x1, x2) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3) => Arrays (x0, x1, x2, x3) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4) => Arrays (x0, x1, x2, x3, x4) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5) => Arrays (x0, x1, x2, x3, x4, x5) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6) => Arrays (x0, x1, x2, x3, x4, x5, x6) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14, Arrays x15) => Arrays (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array Associated Types type ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Methods arraysR :: ArraysR (ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) toArr :: ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) fromArr :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> ArraysR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) |
type Segments = Vector Source #
Segment descriptor (vector of segment lengths)
To represent nested one-dimensional arrays, we use a flat array of data values in conjunction with a segment descriptor, which stores the lengths of the sub-arrays.
Array elements
The Elt
class characterises the allowable array element types, and
hence the types which can appear in scalar Accelerate expressions of
type Exp
.
Accelerate arrays consist of simple atomic types as well as nested tuples thereof, stored efficiently in memory as consecutive unpacked elements without pointers. It roughly consists of:
- Signed and unsigned integers (8, 16, 32, and 64-bits wide)
- Floating point numbers (half, single, and double precision)
Char
Bool
- ()
- Shapes formed from
Z
and (:.
) - Nested tuples of all of these, currently up to 16-elements wide
Adding new instances for Elt
consists of explaining to Accelerate how
to map between your data type and a (tuple of) primitive values. For
examples see:
- Data.Array.Accelerate.Data.Complex
- Data.Array.Accelerate.Data.Monoid
- linear-accelerate
- colour-accelerate
For simple types it is possible to derive Elt
automatically, for
example:
data Point = Point Int Float deriving (Generic, Elt)
data Option a = None | Just a deriving (Generic, Elt)
See the function match
for details on how to use
sum types in embedded code.
Instances
Elt Bool Source # | |
Elt Char Source # | |
Elt Double Source # | |
Elt Float Source # | |
Elt Int Source # | |
Elt Int8 Source # | |
Elt Int16 Source # | |
Elt Int32 Source # | |
Elt Int64 Source # | |
Elt Ordering Source # | |
Elt Word Source # | |
Elt Word8 Source # | |
Elt Word16 Source # | |
Elt Word32 Source # | |
Elt Word64 Source # | |
Elt () Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR () | |
Elt CChar Source # | |
Elt CSChar Source # | |
Elt CUChar Source # | |
Elt CShort Source # | |
Elt CUShort Source # | |
Elt CInt Source # | |
Elt CUInt Source # | |
Elt CLong Source # | |
Elt CULong Source # | |
Elt CLLong Source # | |
Elt CULLong Source # | |
Elt CFloat Source # | |
Elt CDouble Source # | |
Elt Half Source # | |
Elt All Source # | |
Elt Z Source # | |
Elt a => Elt (Maybe a) Source # | |
Elt a => Elt (Ratio a) Source # | |
Elt a => Elt (Complex a) Source # | |
Elt a => Elt (Min a) Source # | |
Elt a => Elt (Max a) Source # | |
Elt a => Elt (Sum a) Source # | |
Elt a => Elt (Product a) Source # | |
Shape sh => Elt (Any (sh :. Int)) Source # | |
Elt (Any Z) Source # | |
(Elt a, Elt b) => Elt (Either a b) Source # | |
(Elt x0, Elt x1) => Elt (x0, x1) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1) | |
(KnownNat n, VecElt a) => Elt (Vec n a) Source # | |
(Elt t, Elt h) => Elt (t :. h) Source # | |
(Elt x0, Elt x1, Elt x2) => Elt (x0, x1, x2) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2) | |
(Elt x0, Elt x1, Elt x2, Elt x3) => Elt (x0, x1, x2, x3) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Elt (x0, x1, x2, x3, x4) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Elt (x0, x1, x2, x3, x4, x5) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Elt (x0, x1, x2, x3, x4, x5, x6) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Elt (x0, x1, x2, x3, x4, x5, x6, x7) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14, Elt x15) => Elt (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # | |
Defined in Data.Array.Accelerate.Sugar.Elt Associated Types type EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Methods eltR :: TypeR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15)) tagsR :: [TagR (EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15))] fromElt :: (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) toElt :: EltR (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) |
Array shapes & indices
Operations in Accelerate take the form of collective operations over arrays
of the type
. Much like the
repa library, arrays in Accelerate
are parameterised by a type sh which determines the dimensionality of the
array and the type of each index, as well as the type of each element of the
array e.Array
sh e
Shape types, and multidimensional array indices, are built like lists
(technically; a heterogeneous snoc-list) using Z
and (:.
):
data Z = Z data tail :. head = tail :. head
Here, the constructor Z
corresponds to a shape with zero dimension (or
a Scalar
array, with one element) and is used to mark the end of the list.
The constructor (:.
) adds additional dimensions to the shape on the
right. For example:
Z :. Int
is the type of the shape of a one-dimensional array (Vector
) indexed by an
Int
, while:
Z :. Int :. Int
is the type of the shape of a two-dimensional array (a matrix) indexed by an
Int
in each dimension.
This style is used to construct both the type and value of the shape. For example, to define the shape of a vector of ten elements:
sh :: Z :. Int sh = Z :. 10
Note that the right-most index is the innermost dimension. This is the fastest-varying index, and corresponds to the elements of the array which are adjacent in memory.
Rank-0 index
Constructors
Z |
Instances
data tail :. head infixl 3 Source #
Increase an index rank by one dimension. The :.
operator is used to
construct both values and types.
Constructors
!tail :. !head infixl 3 |
Instances
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Elt e, Elt (Plain ix), Unlift Exp ix) => Unlift Exp (ix :. Exp e) Source # | |
(Elt e, Elt ix) => Unlift Exp (Exp ix :. Exp e) Source # | |
(Elt e, Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. Exp e) Source # | |
(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. All) Source # | |
(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. Int) Source # | |
Shape sh => Elt (Any (sh :. Int)) Source # | |
Elt e => IsList (Array DIM1 e) Source # | |
(Eq tail, Eq head) => Eq (tail :. head) Source # | |
(Show sh, Show sz) => Show (sh :. sz) Source # | |
Generic (tail :. head) Source # | |
(Elt t, Elt h) => Elt (t :. h) Source # | |
Slice sl => Slice (sl :. Int) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (sl :. Int)) (EltR (SliceShape (sl :. Int))) (EltR (CoSliceShape (sl :. Int))) (EltR (FullShape (sl :. Int))) Source # | |
Slice sl => Slice (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source # | |
Shape sh => Shape (sh :. Int) Source # | |
Eq sh => Eq (sh :. Int) Source # | |
Ord sh => Ord (sh :. Int) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (>) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (<=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (>=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # min :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source # max :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source # compare :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Ordering Source # | |
(Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row6, row5, row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row8, Stencil (sh :. Int) a row7, Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row8, row7, row6, row5, row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart Associated Types type StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0) Methods stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)) stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)) -> (row8, row7, row6, row5, row4, row3, row2, row1, row0) | |
type Item (Vector e) Source # | |
Defined in Data.Array.Accelerate.Sugar.Array | |
type Rep (tail :. head) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape type Rep (tail :. head) = D1 ('MetaData ":." "Data.Array.Accelerate.Sugar.Shape" "accelerate-1.3.0.0-JUAol0vo0mBEBEK4xLffPu" 'False) (C1 ('MetaCons ":." ('InfixI 'LeftAssociative 3) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 tail) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 head))) | |
type SliceShape (sl :. Int) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type SliceShape (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type CoSliceShape (sl :. Int) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type CoSliceShape (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type FullShape (sl :. Int) Source # | |
type FullShape (sl :. All) Source # | |
type Plain (ix :. Exp e) Source # | |
type Plain (ix :. All) Source # | |
type Plain (ix :. Int) Source # | |
class (Elt sh, Elt (Any sh), FullShape sh ~ sh, CoSliceShape sh ~ sh, SliceShape sh ~ Z) => Shape sh Source #
Shapes and indices of multi-dimensional arrays
Minimal complete definition
shapeR, sliceAnyIndex, sliceNoneIndex
class (Elt sl, Shape (SliceShape sl), Shape (CoSliceShape sl), Shape (FullShape sl)) => Slice sl where Source #
Slices, aka generalised indices, as n-tuples and mappings of slice indices to slices, co-slices, and slice dimensions
Methods
sliceIndex :: SliceIndex (EltR sl) (EltR (SliceShape sl)) (EltR (CoSliceShape sl)) (EltR (FullShape sl)) Source #
Instances
Slice Z Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR Z) (EltR (SliceShape Z)) (EltR (CoSliceShape Z)) (EltR (FullShape Z)) Source # | |
Shape sh => Slice (Any sh) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (Any sh)) (EltR (SliceShape (Any sh))) (EltR (CoSliceShape (Any sh))) (EltR (FullShape (Any sh))) Source # | |
Slice sl => Slice (sl :. Int) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (sl :. Int)) (EltR (SliceShape (sl :. Int))) (EltR (CoSliceShape (sl :. Int))) (EltR (FullShape (sl :. Int))) Source # | |
Slice sl => Slice (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source # |
Marker for entire dimensions in slice
and
replicate
descriptors.
Occurrences of All
indicate the dimensions into which the array's existing
extent will be placed unchanged.
Constructors
All |
Instances
Eq All Source # | |
Show All Source # | |
Generic All Source # | |
Elt All Source # | |
(Elt (Plain ix), Lift Exp ix) => Lift Exp (ix :. All) Source # | |
Slice sl => Slice (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (sl :. All)) (EltR (SliceShape (sl :. All))) (EltR (CoSliceShape (sl :. All))) (EltR (FullShape (sl :. All))) Source # | |
type Rep All Source # | |
type SliceShape (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type CoSliceShape (sl :. All) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type FullShape (sl :. All) Source # | |
type Plain (ix :. All) Source # | |
Marker for arbitrary dimensions in slice
and replicate
descriptors.
Any
can be used in the leftmost position of a slice instead of Z
,
indicating that any dimensionality is admissible in that position.
Constructors
Any |
Instances
(Shape sh, Elt (Any sh)) => Lift Exp (Any sh) Source # | |
Eq (Any sh) Source # | |
Show (Any sh) Source # | |
Generic (Any sh) Source # | |
Shape sh => Elt (Any (sh :. Int)) Source # | |
Elt (Any Z) Source # | |
Shape sh => Slice (Any sh) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape Methods sliceIndex :: SliceIndex (EltR (Any sh)) (EltR (SliceShape (Any sh))) (EltR (CoSliceShape (Any sh))) (EltR (FullShape (Any sh))) Source # | |
type Rep (Any sh) Source # | |
type SliceShape (Any sh) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type CoSliceShape (Any sh) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type FullShape (Any sh) Source # | |
Defined in Data.Array.Accelerate.Sugar.Shape | |
type Plain (Any sh) Source # | |
Defined in Data.Array.Accelerate.Lift |
Array access
Element indexing
(!) :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh -> Exp e infixl 9 Source #
Multidimensional array indexing. Extract the value from an array at the specified zero-based index.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
runExp $ use mat ! constant (Z:.1:.2)
12
(!!) :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int -> Exp e infixl 9 Source #
Extract the value from an array at the specified linear index. Multidimensional arrays in Accelerate are stored in row-major order with zero-based indexing.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
runExp $ use mat !! 12
12
the :: Elt e => Acc (Scalar e) -> Exp e Source #
Extract the element of a singleton array.
the xs == xs ! Z
Shape information
shape :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Exp sh Source #
Extract the shape (extent) of an array.
size :: (Shape sh, Elt e) => Acc (Array sh e) -> Exp Int Source #
The number of elements in the array
shapeSize :: forall sh. Shape sh => Exp sh -> Exp Int Source #
The number of elements that would be held by an array of the given shape.
Construction
Introduction
use :: forall arrays. Arrays arrays => arrays -> Acc arrays Source #
Make an array from vanilla Haskell available for processing within embedded Accelerate computations.
Depending upon which backend is used to eventually execute array
computations, use
may entail data transfer (e.g. to a GPU).
use
is overloaded so that it can accept tuples of Arrays
:
>>>
let vec = fromList (Z:.10) [0..] :: Vector Int
>>>
vec
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let vec' = use vec :: Acc (Vector Int)
>>>
let mat' = use mat :: Acc (Matrix Int)
>>>
let tup = use (vec, mat) :: Acc (Vector Int, Matrix Int)
unit :: forall e. Elt e => Exp e -> Acc (Scalar e) Source #
Construct a singleton (one element) array from a scalar value (or tuple of scalar values).
Initialisation
generate :: forall sh a. (Shape sh, Elt a) => Exp sh -> (Exp sh -> Exp a) -> Acc (Array sh a) Source #
Construct a new array by applying a function to each index.
For example, the following will generate a one-dimensional array
(Vector
) of three floating point numbers:
>>>
run $ generate (I1 3) (\_ -> 1.2) :: Vector Float
Vector (Z :. 3) [1.2,1.2,1.2]
Or equivalently:
>>>
run $ fill (constant (Z :. 3)) 1.2 :: Vector Float
Vector (Z :. 3) [1.2,1.2,1.2]
The following will create a vector with the elements [1..10]
:
>>>
run $ generate (I1 10) (\(I1 i) -> i + 1) :: Vector Int
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]
- NOTE:
Using generate
, it is possible to introduce nested data parallelism, which
will cause the program to fail.
If the index given by the scalar function is then used to dispatch further
parallel work, whose result is returned into Exp
terms by array indexing
operations such as (!
) or the
, the program
will fail with the error:
./Data/Array/Accelerate/Trafo/Sharing.hs:447 (convertSharingExp): inconsistent valuation @ shared 'Exp' tree ...
.
fill :: (Shape sh, Elt e) => Exp sh -> Exp e -> Acc (Array sh e) Source #
Create an array where all elements are the same value.
>>>
run $ fill (constant (Z:.10)) 0 :: Vector Float
Vector (Z :. 10) [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0]
Enumeration
enumFromN :: (Shape sh, Num e, FromIntegral Int e) => Exp sh -> Exp e -> Acc (Array sh e) Source #
Create an array of the given shape containing the values x
, x+1
, etc.
(in row-major order).
>>>
run $ enumFromN (constant (Z:.5:.10)) 0 :: Matrix Int
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
Arguments
:: (Shape sh, Num e, FromIntegral Int e) | |
=> Exp sh | |
-> Exp e | x: start |
-> Exp e | y: step |
-> Acc (Array sh e) |
Create an array of the given shape containing the values x
, x+y
,
x+y+y
etc. (in row-major order).
>>>
run $ enumFromStepN (constant (Z:.5:.10)) 0 0.5 :: Matrix Float
Matrix (Z :. 5 :. 10) [ 0.0, 0.5, 1.0, 1.5, 2.0, 2.5, 3.0, 3.5, 4.0, 4.5, 5.0, 5.5, 6.0, 6.5, 7.0, 7.5, 8.0, 8.5, 9.0, 9.5, 10.0, 10.5, 11.0, 11.5, 12.0, 12.5, 13.0, 13.5, 14.0, 14.5, 15.0, 15.5, 16.0, 16.5, 17.0, 17.5, 18.0, 18.5, 19.0, 19.5, 20.0, 20.5, 21.0, 21.5, 22.0, 22.5, 23.0, 23.5, 24.0, 24.5]
Concatenation
(++) :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) infixr 5 Source #
Concatenate innermost component of two arrays. The extent of the lower dimensional component is the intersection of the two arrays.
>>>
let m1 = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
m1
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let m2 = fromList (Z:.10:.3) [0..] :: Matrix Int
>>>
m2
Matrix (Z :. 10 :. 3) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29]
>>>
run $ use m1 ++ use m2
Matrix (Z :. 5 :. 13) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 3, 4, 5, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 6, 7, 8, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 9, 10, 11, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 12, 13, 14]
concatOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of (++)
where the argument Lens'
specifies which
dimension to concatenate along.
Appropriate lenses are available from lens-accelerate.
>>>
let m1 = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
m1
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let m2 = fromList (Z:.10:.5) [0..] :: Matrix Int
>>>
m2
Matrix (Z :. 10 :. 5) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ concatOn _1 (use m1) (use m2)
Matrix (Z :. 5 :. 15) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 5, 6, 7, 8, 9, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 10, 11, 12, 13, 14, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 15, 16, 17, 18, 19, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 20, 21, 22, 23, 24]
>>>
run $ concatOn _2 (use m1) (use m2)
Matrix (Z :. 15 :. 5) [ 0, 1, 2, 3, 4, 10, 11, 12, 13, 14, 20, 21, 22, 23, 24, 30, 31, 32, 33, 34, 40, 41, 42, 43, 44, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
Expansion
expand :: (Elt a, Elt b) => (Exp a -> Exp Int) -> (Exp a -> Exp Int -> Exp b) -> Acc (Vector a) -> Acc (Vector b) Source #
A recipe for generating flattened implementations of some kinds of irregular nested parallelism. Given two functions that:
- for each source element, determine how many target elements it expands into; and
- computes a particular target element based on a source element and the target element index associated with the source
The following example implements the Sieve of Eratosthenes,
a contraction style algorithm which first computes all primes less than
sqrt n, then uses this intermediate result to sieve away all numbers
in the range [sqrt n .. n]. The expand
function is used to calculate
and flatten the sieves. For each prime p and upper limit c2,
function sz computes the number of contributions in the sieve. Then,
for each prime p and sieve index i, the function get computes the
sieve contribution. The final step produces all the new primes in the
interval [c1 .. c2].
>>>
:{
primes :: Exp Int -> Acc (Vector Int) primes n = afst loop where c0 = unit 2 a0 = use $ fromList (Z:.0) [] limit = truncate (sqrt (fromIntegral (n+1) :: Exp Float)) loop = awhile (\(T2 _ c) -> map (< n+1) c) (\(T2 old c) -> let c1 = the c c2 = c1 < limit ? ( c1*c1, n+1 ) -- sieves = let sz p = (c2 - p) `quot` p get p i = (2+i)*p in map (subtract c1) (expand sz get old) -- new = let m = c2-c1 put i = let s = sieves ! i in s >= 0 && s < m ? (Just_ (I1 s), Nothing_) in afst $ filter (> 0) $ permute const (enumFromN (I1 m) c1) put $ fill (shape sieves) 0 in T2 (old ++ new) (unit c2)) (T2 a0 c0) :}
>>>
run $ primes 100
Vector (Z :. 25) [2,3,5,7,11,13,17,19,23,29,31,37,41,43,47,53,59,61,67,71,73,79,83,89,97]
Inspired by the paper Data-Parallel Flattening by Expansion by Martin Elsman, Troels Henriksen, and Niels Gustav Westphal Serup, ARRAY'19.
Since: 1.3.0.0
Composition
Flow control
An array-level if-then-else construct.
Enabling the RebindableSyntax
extension will allow you to use the standard
if-then-else syntax instead.
class IfThenElse t where Source #
For use with -XRebindableSyntax
, this class provides ifThenElse
lifted
to both scalar and array types.
Associated Types
type EltT t a :: Constraint Source #
Instances
Controlling execution
(>->) :: forall a b c. (Arrays a, Arrays b, Arrays c) => (Acc a -> Acc b) -> (Acc b -> Acc c) -> Acc a -> Acc c infixl 1 Source #
Pipelining of two array computations. The first argument will be fully evaluated before being passed to the second computation. This can be used to prevent the argument being fused into the function, for example.
Denotationally, we have
(acc1 >-> acc2) arrs = let tmp = acc1 arrs in tmp `seq` acc2 tmp
For an example use of this operation see the compute
function.
compute :: Arrays a => Acc a -> Acc a Source #
Force an array expression to be evaluated, preventing it from fusing with
other operations. Forcing operations to be computed to memory, rather than
being fused into their consuming function, can sometimes improve performance.
For example, computing a matrix transpose
could provide better memory
locality for the subsequent operation. Preventing fusion to split large
operations into several simpler steps could also help by reducing register
pressure.
Preventing fusion also means that the individual operations are available to be executed concurrently with other kernels. In particular, consider using this if you have a series of operations that are compute bound rather than memory bound.
Here is the synthetic example:
loop :: Exp Int -> Exp Int loop ticks = let clockRate = 900000 -- kHz in while (\i -> i < clockRate * ticks) (+1) 0 test :: Acc (Vector Int) test = zip3 (compute $ map loop (use $ fromList (Z:.1) [10])) (compute $ map loop (use $ fromList (Z:.1) [10])) (compute $ map loop (use $ fromList (Z:.1) [10]))
Without the use of compute
, the operations are fused together and the three
long-running loops are executed sequentially in a single kernel. Instead, the
individual operations can now be executed concurrently, potentially reducing
overall runtime.
Element-wise operations
Indexing
indexed :: (Shape sh, Elt a) => Acc (Array sh a) -> Acc (Array sh (sh, a)) Source #
Pair each element with its index
>>>
let xs = fromList (Z:.5) [0..] :: Vector Float
>>>
run $ indexed (use xs)
Vector (Z :. 5) [(Z :. 0,0.0),(Z :. 1,1.0),(Z :. 2,2.0),(Z :. 3,3.0),(Z :. 4,4.0)]
>>>
let mat = fromList (Z:.3:.4) [0..] :: Matrix Float
>>>
run $ indexed (use mat)
Matrix (Z :. 3 :. 4) [ (Z :. 0 :. 0,0.0), (Z :. 0 :. 1,1.0), (Z :. 0 :. 2,2.0), (Z :. 0 :. 3,3.0), (Z :. 1 :. 0,4.0), (Z :. 1 :. 1,5.0), (Z :. 1 :. 2,6.0), (Z :. 1 :. 3,7.0), (Z :. 2 :. 0,8.0), (Z :. 2 :. 1,9.0), (Z :. 2 :. 2,10.0), (Z :. 2 :. 3,11.0)]
Mapping
map :: forall sh a b. (Shape sh, Elt a, Elt b) => (Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b) Source #
Apply the given function element-wise to an array. Denotationally we have:
map f [x1, x2, ... xn] = [f x1, f x2, ... f xn]
>>>
let xs = fromList (Z:.10) [0..] :: Vector Int
>>>
xs
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
>>>
run $ map (+1) (use xs)
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]
imap :: (Shape sh, Elt a, Elt b) => (Exp sh -> Exp a -> Exp b) -> Acc (Array sh a) -> Acc (Array sh b) Source #
Apply a function to every element of an array and its index
Zipping
zipWith :: forall sh a b c. (Shape sh, Elt a, Elt b, Elt c) => (Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) Source #
Apply the given binary function element-wise to the two arrays. The extent of the resulting array is the intersection of the extents of the two source arrays.
>>>
let xs = fromList (Z:.3:.5) [0..] :: Matrix Int
>>>
xs
Matrix (Z :. 3 :. 5) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14]
>>>
let ys = fromList (Z:.5:.10) [1..] :: Matrix Int
>>>
ys
Matrix (Z :. 5 :. 10) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 50]
>>>
run $ zipWith (+) (use xs) (use ys)
Matrix (Z :. 3 :. 5) [ 1, 3, 5, 7, 9, 16, 18, 20, 22, 24, 31, 33, 35, 37, 39]
zipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) Source #
Zip three arrays with the given function, analogous to zipWith
.
zipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) Source #
Zip four arrays with the given function, analogous to zipWith
.
zipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) Source #
Zip five arrays with the given function, analogous to zipWith
.
zipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) Source #
Zip six arrays with the given function, analogous to zipWith
.
zipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) Source #
Zip seven arrays with the given function, analogous to zipWith
.
zipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) Source #
Zip eight arrays with the given function, analogous to zipWith
.
zipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j) Source #
Zip nine arrays with the given function, analogous to zipWith
.
izipWith :: (Shape sh, Elt a, Elt b, Elt c) => (Exp sh -> Exp a -> Exp b -> Exp c) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) Source #
Zip two arrays with a function that also takes the element index
izipWith3 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) Source #
Zip three arrays with a function that also takes the element index,
analogous to izipWith
.
izipWith4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) Source #
Zip four arrays with the given function that also takes the element index,
analogous to zipWith
.
izipWith5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) Source #
Zip five arrays with the given function that also takes the element index,
analogous to zipWith
.
izipWith6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) Source #
Zip six arrays with the given function that also takes the element index,
analogous to zipWith
.
izipWith7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) Source #
Zip seven arrays with the given function that also takes the element
index, analogous to zipWith
.
izipWith8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) Source #
Zip eight arrays with the given function that also takes the element
index, analogous to zipWith
.
izipWith9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i, Elt j) => (Exp sh -> Exp a -> Exp b -> Exp c -> Exp d -> Exp e -> Exp f -> Exp g -> Exp h -> Exp i -> Exp j) -> Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh j) Source #
Zip nine arrays with the given function that also takes the element index,
analogous to zipWith
.
zip :: (Shape sh, Elt a, Elt b) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh (a, b)) Source #
Combine the elements of two arrays pairwise. The shape of the result is the intersection of the two argument shapes.
>>>
let m1 = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
let m2 = fromList (Z:.10:.5) [0..] :: Matrix Float
>>>
run $ zip (use m1) (use m2)
Matrix (Z :. 5 :. 5) [ (0,0.0), (1,1.0), (2,2.0), (3,3.0), (4,4.0), (10,5.0), (11,6.0), (12,7.0), (13,8.0), (14,9.0), (20,10.0), (21,11.0), (22,12.0), (23,13.0), (24,14.0), (30,15.0), (31,16.0), (32,17.0), (33,18.0), (34,19.0), (40,20.0), (41,21.0), (42,22.0), (43,23.0), (44,24.0)]
zip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh (a, b, c)) Source #
Take three arrays and return an array of triples, analogous to zip.
zip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh (a, b, c, d)) Source #
Take four arrays and return an array of quadruples, analogous to zip.
zip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh (a, b, c, d, e)) Source #
Take five arrays and return an array of five-tuples, analogous to zip.
zip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh (a, b, c, d, e, f)) Source #
Take six arrays and return an array of six-tuples, analogous to zip.
zip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh (a, b, c, d, e, f, g)) Source #
Take seven arrays and return an array of seven-tuples, analogous to zip.
zip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh (a, b, c, d, e, f, g, h)) Source #
Take seven arrays and return an array of seven-tuples, analogous to zip.
zip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh a) -> Acc (Array sh b) -> Acc (Array sh c) -> Acc (Array sh d) -> Acc (Array sh e) -> Acc (Array sh f) -> Acc (Array sh g) -> Acc (Array sh h) -> Acc (Array sh i) -> Acc (Array sh (a, b, c, d, e, f, g, h, i)) Source #
Take seven arrays and return an array of seven-tuples, analogous to zip.
Unzipping
unzip :: (Shape sh, Elt a, Elt b) => Acc (Array sh (a, b)) -> (Acc (Array sh a), Acc (Array sh b)) Source #
unzip3 :: (Shape sh, Elt a, Elt b, Elt c) => Acc (Array sh (a, b, c)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c)) Source #
Take an array of triples and return three arrays, analogous to unzip
.
unzip4 :: (Shape sh, Elt a, Elt b, Elt c, Elt d) => Acc (Array sh (a, b, c, d)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d)) Source #
Take an array of quadruples and return four arrays, analogous to unzip
.
unzip5 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e) => Acc (Array sh (a, b, c, d, e)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e)) Source #
Take an array of 5-tuples and return five arrays, analogous to unzip
.
unzip6 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f) => Acc (Array sh (a, b, c, d, e, f)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f)) Source #
Take an array of 6-tuples and return six arrays, analogous to unzip
.
unzip7 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g) => Acc (Array sh (a, b, c, d, e, f, g)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g)) Source #
Take an array of 7-tuples and return seven arrays, analogous to unzip
.
unzip8 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h) => Acc (Array sh (a, b, c, d, e, f, g, h)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h)) Source #
Take an array of 8-tuples and return eight arrays, analogous to unzip
.
unzip9 :: (Shape sh, Elt a, Elt b, Elt c, Elt d, Elt e, Elt f, Elt g, Elt h, Elt i) => Acc (Array sh (a, b, c, d, e, f, g, h, i)) -> (Acc (Array sh a), Acc (Array sh b), Acc (Array sh c), Acc (Array sh d), Acc (Array sh e), Acc (Array sh f), Acc (Array sh g), Acc (Array sh h), Acc (Array sh i)) Source #
Take an array of 9-tuples and return nine arrays, analogous to unzip
.
Modifying Arrays
Shape manipulation
reshape :: forall sh sh' e. (Shape sh, Shape sh', Elt e) => Exp sh -> Acc (Array sh' e) -> Acc (Array sh e) Source #
Change the shape of an array without altering its contents. The size
of
the source and result arrays must be identical.
precondition: shapeSize sh == shapeSize sh'
If the argument array is manifest in memory, reshape
is a no-op. If the
argument is to be fused into a subsequent operation, reshape
corresponds to
an index transformation in the fused code.
flatten :: forall sh e. (Shape sh, Elt e) => Acc (Array sh e) -> Acc (Vector e) Source #
Flatten the given array of arbitrary dimension into a one-dimensional
vector. As with reshape
, this operation performs no work.
Replication
replicate :: forall slix e. (Slice slix, Elt e) => Exp slix -> Acc (Array (SliceShape slix) e) -> Acc (Array (FullShape slix) e) Source #
Replicate an array across one or more dimensions as specified by the generalised array index provided as the first argument.
For example, given the following vector:
>>>
let vec = fromList (Z:.10) [0..] :: Vector Int
>>>
vec
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
...we can replicate these elements to form a two-dimensional array either by replicating those elements as new rows:
>>>
run $ replicate (constant (Z :. (4::Int) :. All)) (use vec)
Matrix (Z :. 4 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9]
...or as columns:
>>>
run $ replicate (lift (Z :. All :. (4::Int))) (use vec)
Matrix (Z :. 10 :. 4) [ 0, 0, 0, 0, 1, 1, 1, 1, 2, 2, 2, 2, 3, 3, 3, 3, 4, 4, 4, 4, 5, 5, 5, 5, 6, 6, 6, 6, 7, 7, 7, 7, 8, 8, 8, 8, 9, 9, 9, 9]
Replication along more than one dimension is also possible. Here we replicate twice across the first dimension and three times across the third dimension:
>>>
run $ replicate (constant (Z :. (2::Int) :. All :. (3::Int))) (use vec)
Array (Z :. 2 :. 10 :. 3) [0,0,0,1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6,7,7,7,8,8,8,9,9,9,0,0,0,1,1,1,2,2,2,3,3,3,4,4,4,5,5,5,6,6,6,7,7,7,8,8,8,9,9,9]
The marker Any
can be used in the slice specification to match against some
arbitrary dimension. For example, here Any
matches against whatever shape
type variable sh
takes.
>>>
:{
let rep0 :: (Shape sh, Elt e) => Exp Int -> Acc (Array sh e) -> Acc (Array (sh :. Int) e) rep0 n a = replicate (lift (Any :. n)) a :}
>>>
let x = unit 42 :: Acc (Scalar Int)
>>>
run $ rep0 10 x
Vector (Z :. 10) [42,42,42,42,42,42,42,42,42,42]
>>>
run $ rep0 5 (use vec)
Matrix (Z :. 10 :. 5) [ 0, 0, 0, 0, 0, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 3, 3, 3, 3, 3, 4, 4, 4, 4, 4, 5, 5, 5, 5, 5, 6, 6, 6, 6, 6, 7, 7, 7, 7, 7, 8, 8, 8, 8, 8, 9, 9, 9, 9, 9]
Of course, Any
and All
can be used together.
>>>
:{
let rep1 :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int :. Int) e) rep1 n a = replicate (lift (Any :. n :. All)) a :}
>>>
run $ rep1 5 (use vec)
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9]
Extracting sub-arrays
slice :: forall slix e. (Slice slix, Elt e) => Acc (Array (FullShape slix) e) -> Exp slix -> Acc (Array (SliceShape slix) e) Source #
Index an array with a generalised array index, supplied as the second
argument. The result is a new array (possibly a singleton) containing the
selected dimensions (All
s) in their entirety.
slice
is the opposite of replicate
, and can be used to cut out entire
dimensions. For example, for the two dimensional array mat
:
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
...will can select a specific row to yield a one dimensional result by fixing
the row index (2) while allowing the column index to vary (via All
):
>>>
run $ slice (use mat) (constant (Z :. (2::Int) :. All))
Vector (Z :. 10) [20,21,22,23,24,25,26,27,28,29]
A fully specified index (with no All
s) returns a single element (zero
dimensional array).
>>>
run $ slice (use mat) (constant (Z :. 4 :. 2 :: DIM2))
Scalar Z [42]
The marker Any
can be used in the slice specification to match against some
arbitrary (lower) dimension. Here Any
matches whatever shape type variable
sh
takes:
>>>
:{
let sl0 :: (Shape sh, Elt e) => Acc (Array (sh:.Int) e) -> Exp Int -> Acc (Array sh e) sl0 a n = slice a (lift (Any :. n)) :}
>>>
let vec = fromList (Z:.10) [0..] :: Vector Int
>>>
run $ sl0 (use vec) 4
Scalar Z [4]
>>>
run $ sl0 (use mat) 4
Vector (Z :. 5) [4,14,24,34,44]
Of course, Any
and All
can be used together.
>>>
:{
let sl1 :: (Shape sh, Elt e) => Acc (Array (sh:.Int:.Int) e) -> Exp Int -> Acc (Array (sh:.Int) e) sl1 a n = slice a (lift (Any :. n :. All)) :}
>>>
run $ sl1 (use mat) 4
Vector (Z :. 10) [40,41,42,43,44,45,46,47,48,49]
>>>
let cube = fromList (Z:.3:.4:.5) [0..] :: Array DIM3 Int
>>>
cube
Array (Z :. 3 :. 4 :. 5) [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59]
>>>
run $ sl1 (use cube) 2
Matrix (Z :. 3 :. 5) [ 10, 11, 12, 13, 14, 30, 31, 32, 33, 34, 50, 51, 52, 53, 54]
init :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #
Yield all but the elements in the last index of the innermost dimension.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ init (use mat)
Matrix (Z :. 5 :. 9) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 10, 11, 12, 13, 14, 15, 16, 17, 18, 20, 21, 22, 23, 24, 25, 26, 27, 28, 30, 31, 32, 33, 34, 35, 36, 37, 38, 40, 41, 42, 43, 44, 45, 46, 47, 48]
tail :: (Shape sh, Elt e) => Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #
Yield all but the first element along the innermost dimension of an array. The innermost dimension must not be empty.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ tail (use mat)
Matrix (Z :. 5 :. 9) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 11, 12, 13, 14, 15, 16, 17, 18, 19, 21, 22, 23, 24, 25, 26, 27, 28, 29, 31, 32, 33, 34, 35, 36, 37, 38, 39, 41, 42, 43, 44, 45, 46, 47, 48, 49]
take :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #
Yield the first n
elements in the innermost dimension of the array (plus
all lower dimensional elements).
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ take 5 (use mat)
Matrix (Z :. 5 :. 5) [ 0, 1, 2, 3, 4, 10, 11, 12, 13, 14, 20, 21, 22, 23, 24, 30, 31, 32, 33, 34, 40, 41, 42, 43, 44]
drop :: (Shape sh, Elt e) => Exp Int -> Acc (Array (sh :. Int) e) -> Acc (Array (sh :. Int) e) Source #
Yield all but the first n
elements along the innermost dimension of the
array (plus all lower dimensional elements).
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ drop 7 (use mat)
Matrix (Z :. 5 :. 3) [ 7, 8, 9, 17, 18, 19, 27, 28, 29, 37, 38, 39, 47, 48, 49]
Arguments
:: (Shape sh, Elt e) | |
=> Exp Int | starting index |
-> Exp Int | length |
-> Acc (Array (sh :. Int) e) | |
-> Acc (Array (sh :. Int) e) |
Yield a slit (slice) of the innermost indices of an array. Denotationally, we have:
slit i n = take n . drop i
initOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of init
where the argument Lens'
specifies which
dimension to operate over.
Appropriate lenses are available from lens-accelerate.
Since: 1.2.0.0
tailOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of tail
where the argument Lens'
specifies which
dimension to operate over.
Appropriate lenses are available from lens-accelerate.
Since: 1.2.0.0
takeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of take
where the argument Lens'
specifies which
dimension to operate over.
Appropriate lenses are available from lens-accelerate.
Since: 1.2.0.0
dropOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Exp Int -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of drop
where the argument Lens'
specifies which
dimension to operate over.
Appropriate lenses are available from lens-accelerate.
Since: 1.2.0.0
Arguments
:: (Shape sh, Elt e) | |
=> Lens' (Exp sh) (Exp Int) | |
-> Exp Int | starting index |
-> Exp Int | length |
-> Acc (Array sh e) | |
-> Acc (Array sh e) |
Generalised version of drop
where the argument Lens'
specifies which
dimension to operate over.
Appropriate lenses are available from lens-accelerate.
Since: 1.2.0.0
Permutations
Forward permutation (scatter)
Arguments
:: forall sh sh' a. (Shape sh, Shape sh', Elt a) | |
=> (Exp a -> Exp a -> Exp a) | combination function |
-> Acc (Array sh' a) | array of default values |
-> (Exp sh -> Exp (Maybe sh')) | index permutation function |
-> Acc (Array sh a) | array of source values to be permuted |
-> Acc (Array sh' a) |
Generalised forward permutation operation (array scatter).
Forward permutation specified by a function mapping indices from the source array to indices in the result array. The result array is initialised with the given defaults and any further values that are permuted into the result array are added to the current value using the given combination function.
The combination function must be associative and commutative.
Elements for which the permutation function returns Nothing
are
dropped.
The combination function is given the new value being permuted as its first argument, and the current value of the array as its second.
For example, we can use permute
to compute the occurrence count (histogram)
for an array of values in the range [0,10)
:
>>>
:{
let histogram :: Acc (Vector Int) -> Acc (Vector Int) histogram xs = let zeros = fill (constant (Z:.10)) 0 ones = fill (shape xs) 1 in permute (+) zeros (\ix -> Just_ (I1 (xs!ix))) ones :}
>>>
let xs = fromList (Z :. 20) [0,0,1,2,1,1,2,4,8,3,4,9,8,3,2,5,5,3,1,2] :: Vector Int
>>>
run $ histogram (use xs)
Vector (Z :. 10) [2,4,4,3,2,2,0,0,2,1]
As a second example, note that the dimensionality of the source and
destination arrays can differ. In this way, we can use permute
to create an
identity matrix by overwriting elements along the diagonal:
>>>
:{
let identity :: Num a => Exp Int -> Acc (Matrix a) identity n = let zeros = fill (I2 n n) 0 ones = fill (I1 n) 1 in permute const zeros (\(I1 i) -> Just_ (I2 i i)) ones :}
>>>
run $ identity 5 :: Matrix Int
Matrix (Z :. 5 :. 5) [ 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 1]
- Note:
Regarding array fusion:
- The
permute
operation will always be evaluated; it can not be fused into a later step. - Since the index permutation function might not cover all positions in the output array (the function is not surjective), the array of default values must be evaluated. However, other operations may fuse into this.
- The array of source values can fuse into the permutation operation.
- If the array of default values is only used once, it will be updated
in-place. This behaviour can be disabled this with
-fno-inplace
.
Regarding the defaults array:
If you are sure that the default values are not necessary---they are not used
by the combination function and every element will be overwritten---a default
array created by fill
ing with the value
undef
will give you a new uninitialised array.
Regarding the combination function:
The function const
can be used to replace elements of the defaults
array with the new values. If the permutation function maps multiple
values to the same location in the results array (the function is not
injective) then this operation is non-deterministic.
Since Accelerate uses an unzipped struct-of-array representation, where the individual components of product types (for example, pairs) are stored in separate arrays, storing values of product type requires multiple store instructions.
Accelerate prior to version 1.3.0.0 performs this operation atomically,
to ensure that the stored values are always consistent (each component
of the product type is written by the same thread). Later versions relax
this restriction, but this behaviour can be disabled with
-fno-fast-permute-const
.
Arguments
:: Elt e | |
=> Acc (Vector Int) | destination indices to scatter into |
-> Acc (Vector e) | default values |
-> Acc (Vector e) | source values |
-> Acc (Vector e) |
Overwrite elements of the destination by scattering the values of the source array according to the given index mapping.
Note that if the destination index appears more than once in the mapping the result is undefined.
>>>
let to = fromList (Z :. 6) [1,3,7,2,5,8] :: Vector Int
>>>
let input = fromList (Z :. 7) [1,9,6,4,4,2,5] :: Vector Int
>>>
run $ scatter (use to) (fill (constant (Z:.10)) 0) (use input)
Vector (Z :. 10) [0,1,4,9,0,4,0,6,2,0]
Backward permutation (gather)
Arguments
:: forall sh sh' a. (Shape sh, Shape sh', Elt a) | |
=> Exp sh' | shape of the result array |
-> (Exp sh' -> Exp sh) | index permutation function |
-> Acc (Array sh a) | source array |
-> Acc (Array sh' a) |
Generalised backward permutation operation (array gather).
Backward permutation specified by a function mapping indices in the destination array to indices in the source array. Elements of the output array are thus generated by reading from the corresponding index in the source array.
For example, backpermute can be used to
transpose
a matrix; at every index Z:.y:.x
in the result array, we get the value at that index by reading from the
source array at index Z:.x:.y
:
>>>
:{
let swap :: Exp DIM2 -> Exp DIM2 swap = lift1 f where f :: Z :. Exp Int :. Exp Int -> Z :. Exp Int :. Exp Int f (Z:.y:.x) = Z :. x :. y :}
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let mat' = use mat
>>>
run $ backpermute (swap (shape mat')) swap mat'
Matrix (Z :. 10 :. 5) [ 0, 10, 20, 30, 40, 1, 11, 21, 31, 41, 2, 12, 22, 32, 42, 3, 13, 23, 33, 43, 4, 14, 24, 34, 44, 5, 15, 25, 35, 45, 6, 16, 26, 36, 46, 7, 17, 27, 37, 47, 8, 18, 28, 38, 48, 9, 19, 29, 39, 49]
Arguments
:: (Shape sh, Elt e) | |
=> Acc (Array sh Int) | index of source at each index to gather |
-> Acc (Vector e) | source values |
-> Acc (Array sh e) |
Gather elements from a source array by reading values at the given indices.
>>>
let input = fromList (Z:.9) [1,9,6,4,4,2,0,1,2] :: Vector Int
>>>
let from = fromList (Z:.6) [1,3,7,2,5,3] :: Vector Int
>>>
run $ gather (use from) (use input)
Vector (Z :. 6) [9,4,1,6,2,4]
Specialised permutations
transpose :: Elt e => Acc (Array DIM2 e) -> Acc (Array DIM2 e) Source #
Transpose the rows and columns of a matrix.
reverseOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of reverse
where the argument Lens'
specifies which
dimension to reverse.
Appropriate lenses are available from lens-accelerate.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ reverseOn _1 (use mat)
Matrix (Z :. 5 :. 10) [ 9, 8, 7, 6, 5, 4, 3, 2, 1, 0, 19, 18, 17, 16, 15, 14, 13, 12, 11, 10, 29, 28, 27, 26, 25, 24, 23, 22, 21, 20, 39, 38, 37, 36, 35, 34, 33, 32, 31, 30, 49, 48, 47, 46, 45, 44, 43, 42, 41, 40]
>>>
run $ reverseOn _2 (use mat)
Matrix (Z :. 5 :. 10) [ 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 0, 1, 2, 3, 4, 5, 6, 7, 8, 9]
Since: 1.2.0.0
transposeOn :: (Shape sh, Elt e) => Lens' (Exp sh) (Exp Int) -> Lens' (Exp sh) (Exp Int) -> Acc (Array sh e) -> Acc (Array sh e) Source #
Generalised version of transpose
where the argument Lens'
s specify
which two dimensions to transpose.
Appropriate lenses are available from lens-accelerate.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ transposeOn _1 _2 (use mat)
Matrix (Z :. 10 :. 5) [ 0, 10, 20, 30, 40, 1, 11, 21, 31, 41, 2, 12, 22, 32, 42, 3, 13, 23, 33, 43, 4, 14, 24, 34, 44, 5, 15, 25, 35, 45, 6, 16, 26, 36, 46, 7, 17, 27, 37, 47, 8, 18, 28, 38, 48, 9, 19, 29, 39, 49]
>>>
let box = fromList (Z:.2:.3:.5) [0..] :: Array DIM3 Int
>>>
box
Array (Z :. 2 :. 3 :. 5) [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29]
>>>
run $ transposeOn _1 _2 (use box)
Array (Z :. 2 :. 5 :. 3) [0,5,10,1,6,11,2,7,12,3,8,13,4,9,14,15,20,25,16,21,26,17,22,27,18,23,28,19,24,29]
>>>
run $ transposeOn _2 _3 (use box)
Array (Z :. 3 :. 2 :. 5) [0,1,2,3,4,15,16,17,18,19,5,6,7,8,9,20,21,22,23,24,10,11,12,13,14,25,26,27,28,29]
>>>
run $ transposeOn _1 _3 (use box)
Array (Z :. 5 :. 3 :. 2) [0,15,5,20,10,25,1,16,6,21,11,26,2,17,7,22,12,27,3,18,8,23,13,28,4,19,9,24,14,29]
Since: 1.2.0.0
Filtering
filter :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int) Source #
Drop elements that do not satisfy the predicate. Returns the elements which pass the predicate, together with a segment descriptor indicating how many elements along each outer dimension were valid.
>>>
let vec = fromList (Z :. 10) [1..10] :: Vector Int
>>>
vec
Vector (Z :. 10) [1,2,3,4,5,6,7,8,9,10]
>>>
run $ filter even (use vec)
(Vector (Z :. 5) [2,4,6,8,10],Scalar Z [5])
>>>
let mat = fromList (Z :. 4 :. 10) [1,2,3,4,5,6,7,8,9,10,1,1,1,1,1,2,2,2,2,2,2,4,6,8,10,12,14,16,18,20,1,3,5,7,9,11,13,15,17,19] :: Matrix Int
>>>
mat
Matrix (Z :. 4 :. 10) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 1, 3, 5, 7, 9, 11, 13, 15, 17, 19]
>>>
run $ filter odd (use mat)
(Vector (Z :. 20) [1,3,5,7,9,1,1,1,1,1,1,3,5,7,9,11,13,15,17,19],Vector (Z :. 4) [5,5,0,10])
compact :: forall sh e. (Shape sh, Elt e) => Acc (Array (sh :. Int) Bool) -> Acc (Array (sh :. Int) e) -> Acc (Vector e, Array sh Int) Source #
As filter
, but with separate arrays for the data elements and the
flags indicating which elements of that array should be kept.
Folding
fold :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array sh a) Source #
Reduction of the innermost dimension of an array of arbitrary rank.
The shape of the result obeys the property:
shape (fold f z xs) == indexTail (shape xs)
The first argument needs to be an associative function to enable an efficient parallel implementation. The initial element does not need to be an identity element of the combination function.
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ fold (+) 42 (use mat)
Vector (Z :. 5) [87,187,287,387,487]
Reductions with non-commutative operators are supported. For example, the following computes the maximum segment sum problem along each innermost dimension of the array.
https://en.wikipedia.org/wiki/Maximum_subarray_problem
>>>
:{
let maximumSegmentSum :: forall sh e. (Shape sh, Num e, Ord e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e) maximumSegmentSum = map (\(T4 x _ _ _) -> x) . fold1 f . map g where f :: (Num a, Ord a) => Exp (a,a,a,a) -> Exp (a,a,a,a) -> Exp (a,a,a,a) f x y = let T4 mssx misx mcsx tsx = x T4 mssy misy mcsy tsy = y in T4 (mssx `max` (mssy `max` (mcsx+misy))) (misx `max` (tsx+misy)) (mcsy `max` (mcsx+tsy)) (tsx+tsy) -- g :: (Num a, Ord a) => Exp a -> Exp (a,a,a,a) g x = let y = max x 0 in T4 y y y x :}
>>>
let vec = fromList (Z:.10) [-2,1,-3,4,-1,2,1,-5,4,0] :: Vector Int
>>>
run $ maximumSegmentSum (use vec)
Scalar Z [6]
See also Fold
, which can be a useful way to
compute multiple results from a single reduction.
fold1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array sh a) Source #
Variant of fold
that requires the innermost dimension of the array to be
non-empty and doesn't need an default value.
The shape of the result obeys the property:
shape (fold f z xs) == indexTail (shape xs)
The first argument needs to be an associative function to enable an efficient parallel implementation, but does not need to be commutative.
foldAll :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array sh a) -> Acc (Scalar a) Source #
Reduction of an array of arbitrary rank to a single scalar value. The first argument needs to be an associative function to enable efficient parallel implementation. The initial element does not need to be an identity element.
>>>
let vec = fromList (Z:.10) [0..] :: Vector Float
>>>
run $ foldAll (+) 42 (use vec)
Scalar Z [87.0]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Float
>>>
run $ foldAll (+) 0 (use mat)
Scalar Z [1225.0]
fold1All :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array sh a) -> Acc (Scalar a) Source #
Variant of foldAll
that requires the reduced array to be non-empty and
does not need a default value. The first argument must be an associative
function.
Segmented reductions
foldSeg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented reduction along the innermost dimension of an array. The segment descriptor specifies the lengths of the logical sub-arrays, each of which is reduced independently. The innermost dimension must contain at least as many elements as required by the segment descriptor (sum thereof).
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ foldSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 4) [ 0, 10, 0, 18, 10, 50, 0, 48, 20, 90, 0, 78, 30, 130, 0, 108, 40, 170, 0, 138]
fold1Seg :: forall sh e i. (Shape sh, Elt e, Elt i, i ~ EltR i, IsIntegral i) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Variant of foldSeg
that requires all segments of the reduced array
to be non-empty, and does not need a default value. The segment
descriptor species the length of each of the logical sub-arrays.
foldSeg' :: forall sh a i. (Shape sh, Elt a, Elt i, IsIntegral i, i ~ EltR i) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) Source #
Segmented reduction along the innermost dimension of an array. The segment descriptor specifies the starting index (offset) along the innermost dimension to the beginning of each logical sub-array.
The value in the output array at index i is the reduction of values between the indices of the segment descriptor at index i and (i+1).
We have that:
foldSeg f z xs seg == foldSeg' f z xs (scanl (+) 0 seg)
Since: 1.3.0.0
fold1Seg' :: forall sh a i. (Shape sh, Elt a, Elt i, IsIntegral i, i ~ EltR i) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Segments i) -> Acc (Array (sh :. Int) a) Source #
Variant of foldSeg'
that requires all segments of the reduced
array to be non-empty, and doesn't need a default value. The segment
descriptor specifies the offset to the beginning of each of the logical
sub-arrays.
Since: 1.3.0.0
Specialised reductions
all :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Array sh Bool) Source #
Check if all elements along the innermost dimension satisfy a predicate.
>>>
let mat = fromList (Z :. 4 :. 10) [1,2,3,4,5,6,7,8,9,10,1,1,1,1,1,2,2,2,2,2,2,4,6,8,10,12,14,16,18,20,1,3,5,7,9,11,13,15,17,19] :: Matrix Int
>>>
mat
Matrix (Z :. 4 :. 10) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 1, 3, 5, 7, 9, 11, 13, 15, 17, 19]
>>>
run $ all even (use mat)
Vector (Z :. 4) [False,False,True,False]
any :: (Shape sh, Elt e) => (Exp e -> Exp Bool) -> Acc (Array (sh :. Int) e) -> Acc (Array sh Bool) Source #
Check if any element along the innermost dimension satisfies the predicate.
>>>
let mat = fromList (Z :. 4 :. 10) [1,2,3,4,5,6,7,8,9,10,1,1,1,1,1,2,2,2,2,2,2,4,6,8,10,12,14,16,18,20,1,3,5,7,9,11,13,15,17,19] :: Matrix Int
>>>
mat
Matrix (Z :. 4 :. 10) [ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 1, 1, 1, 1, 1, 2, 2, 2, 2, 2, 2, 4, 6, 8, 10, 12, 14, 16, 18, 20, 1, 3, 5, 7, 9, 11, 13, 15, 17, 19]
>>>
run $ any even (use mat)
Vector (Z :. 4) [True,True,True,False]
and :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool) Source #
Check if all elements along the innermost dimension are True
.
or :: Shape sh => Acc (Array (sh :. Int) Bool) -> Acc (Array sh Bool) Source #
Check if any element along the innermost dimension is True
.
sum :: (Shape sh, Num e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e) Source #
Compute the sum of elements along the innermost dimension of the array. To
find the sum of the entire array, flatten
it first.
>>>
let mat = fromList (Z:.2:.5) [0..] :: Matrix Int
>>>
run $ sum (use mat)
Vector (Z :. 2) [10,35]
product :: (Shape sh, Num e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e) Source #
Compute the product of the elements along the innermost dimension of the
array. To find the product of the entire array, flatten
it first.
>>>
let mat = fromList (Z:.2:.5) [0..] :: Matrix Int
>>>
run $ product (use mat)
Vector (Z :. 2) [0,15120]
minimum :: (Shape sh, Ord e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e) Source #
Yield the minimum element along the innermost dimension of the array. To
find find the minimum element of the entire array, flatten
it first.
The array must not be empty. See also fold1
.
>>>
let mat = fromList (Z :. 3 :. 4) [1,4,3,8, 0,2,8,4, 7,9,8,8] :: Matrix Int
>>>
mat
Matrix (Z :. 3 :. 4) [ 1, 4, 3, 8, 0, 2, 8, 4, 7, 9, 8, 8]
>>>
run $ minimum (use mat)
Vector (Z :. 3) [1,0,7]
maximum :: (Shape sh, Ord e) => Acc (Array (sh :. Int) e) -> Acc (Array sh e) Source #
Yield the maximum element along the innermost dimension of the array. To
find the maximum element of the entire array, flatten
it first.
The array must not be empty. See also fold1
.
>>>
let mat = fromList (Z :. 3 :. 4) [1,4,3,8, 0,2,8,4, 7,9,8,8] :: Matrix Int
>>>
mat
Matrix (Z :. 3 :. 4) [ 1, 4, 3, 8, 0, 2, 8, 4, 7, 9, 8, 8]
>>>
run $ maximum (use mat)
Vector (Z :. 3) [8,8,9]
Scans (prefix sums)
scanl :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Data.List style left-to-right scan along the innermost dimension of an arbitrary rank array. The first argument needs to be an associative function to enable efficient parallel implementation. The initial value (second argument) may be arbitrary.
>>>
let vec = fromList (Z :. 10) [0..] :: Vector Int
>>>
run $ scanl (+) 10 (use vec)
Vector (Z :. 11) [10,10,11,13,16,20,25,31,38,46,55]
>>>
let mat = fromList (Z :. 4 :. 10) [0..] :: Matrix Int
>>>
run $ scanl (+) 0 (use mat)
Matrix (Z :. 4 :. 11) [ 0, 0, 1, 3, 6, 10, 15, 21, 28, 36, 45, 0, 10, 21, 33, 46, 60, 75, 91, 108, 126, 145, 0, 20, 41, 63, 86, 110, 135, 161, 188, 216, 245, 0, 30, 61, 93, 126, 160, 195, 231, 268, 306, 345]
scanl1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Data.List style left-to-right scan along the innermost dimension without an initial value (aka inclusive scan). The innermost dimension of the array must not be empty. The first argument must be an associative function.
>>>
let mat = fromList (Z:.4:.10) [0..] :: Matrix Int
>>>
run $ scanl1 (+) (use mat)
Matrix (Z :. 4 :. 10) [ 0, 1, 3, 6, 10, 15, 21, 28, 36, 45, 10, 21, 33, 46, 60, 75, 91, 108, 126, 145, 20, 41, 63, 86, 110, 135, 161, 188, 216, 245, 30, 61, 93, 126, 160, 195, 231, 268, 306, 345]
scanl' :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a, Array sh a) Source #
Variant of scanl
, where the last element (final reduction result) along
each dimension is returned separately. Denotationally we have:
scanl' f e arr = (init res, unit (res!len)) where len = shape arr res = scanl f e arr
>>>
let vec = fromList (Z:.10) [0..] :: Vector Int
>>>
let (res,sum) = run $ scanl' (+) 0 (use vec)
>>>
res
Vector (Z :. 10) [0,0,1,3,6,10,15,21,28,36]>>>
sum
Scalar Z [45]
>>>
let mat = fromList (Z:.4:.10) [0..] :: Matrix Int
>>>
let (res,sums) = run $ scanl' (+) 0 (use mat)
>>>
res
Matrix (Z :. 4 :. 10) [ 0, 0, 1, 3, 6, 10, 15, 21, 28, 36, 0, 10, 21, 33, 46, 60, 75, 91, 108, 126, 0, 20, 41, 63, 86, 110, 135, 161, 188, 216, 0, 30, 61, 93, 126, 160, 195, 231, 268, 306]>>>
sums
Vector (Z :. 4) [45,145,245,345]
scanr :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Right-to-left variant of scanl
.
scanr1 :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Right-to-left variant of scanl1
.
scanr' :: forall sh a. (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a, Array sh a) Source #
Right-to-left variant of scanl'
.
prescanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Left-to-right pre-scan (aka exclusive scan). As for scan
, the first
argument must be an associative function. Denotationally, we have:
prescanl f e = afst . scanl' f e
>>>
let vec = fromList (Z:.10) [1..10] :: Vector Int
>>>
run $ prescanl (+) 0 (use vec)
Vector (Z :. 10) [0,1,3,6,10,15,21,28,36,45]
postscanl :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Left-to-right post-scan, a variant of scanl1
with an initial value. As
with scanl1
, the array must not be empty. Denotationally, we have:
postscanl f e = map (e `f`) . scanl1 f
>>>
let vec = fromList (Z:.10) [1..10] :: Vector Int
>>>
run $ postscanl (+) 42 (use vec)
Vector (Z :. 10) [43,45,48,52,57,63,70,78,87,97]
prescanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Right-to-left pre-scan (aka exclusive scan). As for scan
, the first
argument must be an associative function. Denotationally, we have:
prescanr f e = afst . scanr' f e
postscanr :: (Shape sh, Elt a) => (Exp a -> Exp a -> Exp a) -> Exp a -> Acc (Array (sh :. Int) a) -> Acc (Array (sh :. Int) a) Source #
Right-to-left postscan, a variant of scanr1
with an initial value.
Denotationally, we have:
postscanr f e = map (e `f`) . scanr1 f
Segmented scans
scanlSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of scanl
along the innermost dimension of an array. The
innermost dimension must have at least as many elements as the sum of the
segment descriptor.
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ scanlSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12) [ 0, 0, 0, 1, 3, 6, 10, 0, 0, 5, 11, 18, 0, 10, 0, 11, 23, 36, 50, 0, 0, 15, 31, 48, 0, 20, 0, 21, 43, 66, 90, 0, 0, 25, 51, 78, 0, 30, 0, 31, 63, 96, 130, 0, 0, 35, 71, 108, 0, 40, 0, 41, 83, 126, 170, 0, 0, 45, 91, 138]
scanl1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of scanl1
along the innermost dimension.
As with scanl1
, the total number of elements considered, in this case given
by the sum
of segment descriptor, must not be zero. The input vector must
contain at least this many elements.
Zero length segments are allowed, and the behaviour is as if those entries were not present in the segment descriptor; that is:
scanl1Seg f xs [n,0,0] == scanl1Seg f xs [n] where n /= 0
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ scanl1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8) [ 0, 1, 3, 6, 10, 5, 11, 18, 10, 11, 23, 36, 50, 15, 31, 48, 20, 21, 43, 66, 90, 25, 51, 78, 30, 31, 63, 96, 130, 35, 71, 108, 40, 41, 83, 126, 170, 45, 91, 138]
scanl'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e) Source #
Segmented version of scanl'
along the innermost dimension of an array. The
innermost dimension must have at least as many elements as the sum of the
segment descriptor.
The first element of the resulting tuple is a vector of scanned values. The second element is a vector of segment scan totals and has the same size as the segment vector.
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let (res,sums) = run $ scanl'Seg (+) 0 (use mat) (use seg)
>>>
res
Matrix (Z :. 5 :. 8) [ 0, 0, 1, 3, 6, 0, 5, 11, 0, 0, 11, 23, 36, 0, 15, 31, 0, 0, 21, 43, 66, 0, 25, 51, 0, 0, 31, 63, 96, 0, 35, 71, 0, 0, 41, 83, 126, 0, 45, 91]>>>
sums
Matrix (Z :. 5 :. 4) [ 0, 10, 0, 18, 10, 50, 0, 48, 20, 90, 0, 78, 30, 130, 0, 108, 40, 170, 0, 138]
prescanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of prescanl
.
postscanlSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of postscanl
.
scanrSeg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of scanr
along the innermost dimension of an array. The
innermost dimension must have at least as many elements as the sum of the
segment descriptor.
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ scanrSeg (+) 0 (use mat) (use seg)
Matrix (Z :. 5 :. 12) [ 2, 0, 18, 15, 11, 6, 0, 0, 24, 17, 9, 0, 12, 0, 58, 45, 31, 16, 0, 0, 54, 37, 19, 0, 22, 0, 98, 75, 51, 26, 0, 0, 84, 57, 29, 0, 32, 0, 138, 105, 71, 36, 0, 0, 114, 77, 39, 0, 42, 0, 178, 135, 91, 46, 0, 0, 144, 97, 49, 0]
scanr1Seg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of scanr1
.
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
run $ scanr1Seg (+) (use mat) (use seg)
Matrix (Z :. 5 :. 8) [ 0, 10, 9, 7, 4, 18, 13, 7, 10, 50, 39, 27, 14, 48, 33, 17, 20, 90, 69, 47, 24, 78, 53, 27, 30, 130, 99, 67, 34, 108, 73, 37, 40, 170, 129, 87, 44, 138, 93, 47]
scanr'Seg :: forall sh e i. (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e, Array (sh :. Int) e) Source #
Segmented version of scanr'
.
>>>
let seg = fromList (Z:.4) [1,4,0,3] :: Segments Int
>>>
seg
Vector (Z :. 4) [1,4,0,3]
>>>
let mat = fromList (Z:.5:.10) [0..] :: Matrix Int
>>>
mat
Matrix (Z :. 5 :. 10) [ 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49]
>>>
let (res,sums) = run $ scanr'Seg (+) 0 (use mat) (use seg)
>>>
res
Matrix (Z :. 5 :. 8) [ 0, 15, 11, 6, 0, 17, 9, 0, 0, 45, 31, 16, 0, 37, 19, 0, 0, 75, 51, 26, 0, 57, 29, 0, 0, 105, 71, 36, 0, 77, 39, 0, 0, 135, 91, 46, 0, 97, 49, 0]>>>
sums
Matrix (Z :. 5 :. 4) [ 2, 18, 0, 24, 12, 58, 0, 54, 22, 98, 0, 84, 32, 138, 0, 114, 42, 178, 0, 144]
prescanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of prescanr
.
postscanrSeg :: (Shape sh, Slice sh, Elt e, Integral i, Bits i, FromIntegral i Int) => (Exp e -> Exp e -> Exp e) -> Exp e -> Acc (Array (sh :. Int) e) -> Acc (Segments i) -> Acc (Array (sh :. Int) e) Source #
Segmented version of postscanr
.
Stencils
Arguments
:: forall sh stencil a b. (Stencil sh a stencil, Elt b) | |
=> (stencil -> Exp b) | stencil function |
-> Boundary (Array sh a) | boundary condition |
-> Acc (Array sh a) | source array |
-> Acc (Array sh b) | destination array |
Map a stencil over an array. In contrast to map
, the domain of a stencil
function is an entire neighbourhood of each array element. Neighbourhoods
are sub-arrays centred around a focal point. They are not necessarily
rectangular, but they are symmetric and have an extent of at least three
along each axis. Due to the symmetry requirement the extent is necessarily
odd. The focal point is the array position that is determined by the stencil.
For those array positions where the neighbourhood extends past the boundaries of the source array, a boundary condition determines the contents of the out-of-bounds neighbourhood positions.
Stencil neighbourhoods are specified via nested tuples, where the nesting depth is equal to the dimensionality of the array. For example, a 3x1 stencil for a one-dimensional array:
s31 :: Stencil3 a -> Exp a s31 (l,c,r) = ...
...where c
is the focal point of the stencil, and l
and r
represent the
elements to the left and right of the focal point, respectively. Similarly,
a 3x3 stencil for a two-dimensional array:
s33 :: Stencil3x3 a -> Exp a s33 ((_,t,_) ,(l,c,r) ,(_,b,_)) = ...
...where c
is again the focal point and t
, b
, l
and r
are the
elements to the top, bottom, left, and right of the focal point, respectively
(the diagonal elements have been elided).
For example, the following computes a 5x5 Gaussian blur as a separable 2-pass operation.
type Stencil5x1 a = (Stencil3 a, Stencil5 a, Stencil3 a) type Stencil1x5 a = (Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a, Stencil3 a) convolve5x1 :: Num a => [Exp a] -> Stencil5x1 a -> Exp a convolve5x1 kernel (_, (a,b,c,d,e), _) = Prelude.sum $ Prelude.zipWith (*) kernel [a,b,c,d,e] convolve1x5 :: Num a => [Exp a] -> Stencil1x5 a -> Exp a convolve1x5 kernel ((_,a,_), (_,b,_), (_,c,_), (_,d,_), (_,e,_)) = Prelude.sum $ Prelude.zipWith (*) kernel [a,b,c,d,e] gaussian = [0.06136,0.24477,0.38774,0.24477,0.06136] blur :: Num a => Acc (Matrix a) -> Acc (Matrix a) blur = stencil (convolve5x1 gaussian) clamp . stencil (convolve1x5 gaussian) clamp
- Note:
Since accelerate-1.3.0.0, we allow the source array to fuse into the stencil operation. However, since a stencil computation (typically) requires multiple values from the source array, this means that the work of the fused operation will be duplicated for each element in the stencil pattern.
For example, suppose we write:
blur . map f
The operation f
will be fused into each element of the first Gaussian blur
kernel, resulting in a stencil equivalent to:
f_and_convolve1x5 :: Num a => (Exp a -> Exp b) -> [Exp b] -> Stencil1x5 a -> Exp b f_and_convolve1x5 f kernel ((_,a,_), (_,b,_), (_,c,_), (_,d,_), (_,e,_)) = Prelude.sum $ Prelude.zipWith (*) kernel [f a, f b, f c, f d, f e]
This duplication is often beneficial, however you may choose to instead force
the array to be evaluated first, preventing fusion, using the
compute
operation. Benchmarking should reveal
which approach is best for your application.
Arguments
:: forall sh stencil1 stencil2 a b c. (Stencil sh a stencil1, Stencil sh b stencil2, Elt c) | |
=> (stencil1 -> stencil2 -> Exp c) | binary stencil function |
-> Boundary (Array sh a) | boundary condition #1 |
-> Acc (Array sh a) | source array #1 |
-> Boundary (Array sh b) | boundary condition #2 |
-> Acc (Array sh b) | source array #2 |
-> Acc (Array sh c) | destination array |
Map a binary stencil of an array. The extent of the resulting array is the
intersection of the extents of the two source arrays. This is the stencil
equivalent of zipWith
.
Stencil specification
class Stencil sh e stencil Source #
Minimal complete definition
stencilR, stencilPrj
Instances
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e) Source # | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
Elt e => Stencil DIM1 e (Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e, Exp e) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row6, row5, row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart | |
(Stencil (sh :. Int) a row8, Stencil (sh :. Int) a row7, Stencil (sh :. Int) a row6, Stencil (sh :. Int) a row5, Stencil (sh :. Int) a row4, Stencil (sh :. Int) a row3, Stencil (sh :. Int) a row2, Stencil (sh :. Int) a row1, Stencil (sh :. Int) a row0) => Stencil ((sh :. Int) :. Int) a (row8, row7, row6, row5, row4, row3, row2, row1, row0) Source # | |
Defined in Data.Array.Accelerate.Smart Associated Types type StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0) Methods stencilR :: StencilR (EltR ((sh :. Int) :. Int)) (EltR a) (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)) stencilPrj :: SmartExp (StencilR ((sh :. Int) :. Int) (row8, row7, row6, row5, row4, row3, row2, row1, row0)) -> (row8, row7, row6, row5, row4, row3, row2, row1, row0) |
clamp :: Boundary (Array sh e) Source #
Boundary condition where elements of the stencil which would be out-of-bounds are instead clamped to the edges of the array.
In the following 3x3 stencil, the out-of-bounds element b
will instead
return the value at position c
:
+------------+ |a | b|cd | |e | +------------+
mirror :: Boundary (Array sh e) Source #
Stencil boundary condition where coordinates beyond the array extent are instead mirrored
In the following 5x3 stencil, the out-of-bounds element c
will instead
return the value at position d
, and similarly the element at b
will
return the value at e
:
+------------+ |a | bc|def | |g | +------------+
wrap :: Boundary (Array sh e) Source #
Stencil boundary condition where coordinates beyond the array extent instead wrap around the array (circular boundary conditions).
In the following 3x3 stencil, the out of bounds elements will be read as in the pattern on the right.
a bc +------------+ +------------+ d|ef | |ef d| g|hi | -> |hi g| | | |bc a| +------------+ +------------+
function :: forall sh e. (Shape sh, Elt e) => (Exp sh -> Exp e) -> Boundary (Array sh e) Source #
Stencil boundary condition where the given function is applied to any outlying coordinates.
The function is passed the out-of-bounds index, so you can use it to specify different boundary conditions at each side. For example, the following would clamp out-of-bounds elements in the y-direction to zero, while having circular boundary conditions in the x-direction.
ring :: Acc (Matrix Float) -> Acc (Matrix Float) ring xs = stencil f boundary xs where boundary :: Boundary (Matrix Float) boundary = function $ \(unlift -> Z :. y :. x) -> if y < 0 || y >= height then 0 else if x < 0 then xs ! index2 y (width+x) else xs ! index2 y (x-width) f :: Stencil3x3 Float -> Exp Float f = ... Z :. height :. width = unlift (shape xs)
Common stencil patterns
type Stencil3x3x3 a = (Stencil3x3 a, Stencil3x3 a, Stencil3x3 a) Source #
type Stencil5x3x3 a = (Stencil5x3 a, Stencil5x3 a, Stencil5x3 a) Source #
type Stencil3x5x3 a = (Stencil3x5 a, Stencil3x5 a, Stencil3x5 a) Source #
type Stencil3x3x5 a = (Stencil3x3 a, Stencil3x3 a, Stencil3x3 a, Stencil3x3 a, Stencil3x3 a) Source #
type Stencil5x5x3 a = (Stencil5x5 a, Stencil5x5 a, Stencil5x5 a) Source #
type Stencil5x3x5 a = (Stencil5x3 a, Stencil5x3 a, Stencil5x3 a, Stencil5x3 a, Stencil5x3 a) Source #
type Stencil3x5x5 a = (Stencil3x5 a, Stencil3x5 a, Stencil3x5 a, Stencil3x5 a, Stencil3x5 a) Source #
type Stencil5x5x5 a = (Stencil5x5 a, Stencil5x5 a, Stencil5x5 a, Stencil5x5 a, Stencil5x5 a) Source #
The Accelerate Expression Language
Scalar data types
The type Exp
represents embedded scalar expressions. The collective
operations of Accelerate Acc
consist of many scalar expressions executed in
data-parallel.
Note that scalar expressions can not initiate new collective operations: doing so introduces nested data parallelism, which is difficult to execute efficiently on constrained hardware such as GPUs, and is thus currently unsupported.
Instances
SIMD vectors
Type classes
Basic type classes
class Elt a => Eq a where Source #
The Eq
class defines equality ==
and inequality /=
for scalar
Accelerate expressions.
For convenience, we include Elt
as a superclass.
Instances
Eq Bool Source # | |
Eq Char Source # | |
Eq Double Source # | |
Eq Float Source # | |
Eq Int Source # | |
Eq Int8 Source # | |
Eq Int16 Source # | |
Eq Int32 Source # | |
Eq Int64 Source # | |
Eq Ordering Source # | |
Eq Word Source # | |
Eq Word8 Source # | |
Eq Word16 Source # | |
Eq Word32 Source # | |
Eq Word64 Source # | |
Eq () Source # | |
Eq CChar Source # | |
Eq CSChar Source # | |
Eq CUChar Source # | |
Eq CShort Source # | |
Eq CUShort Source # | |
Eq CInt Source # | |
Eq CUInt Source # | |
Eq CLong Source # | |
Eq CULong Source # | |
Eq CLLong Source # | |
Eq CULLong Source # | |
Eq CFloat Source # | |
Eq CDouble Source # | |
Eq Half Source # | |
Eq Z Source # | |
Eq a => Eq (Maybe a) Source # | |
Integral a => Eq (Ratio a) Source # | |
Eq a => Eq (Complex a) Source # | |
Eq a => Eq (Min a) Source # | |
Eq a => Eq (Max a) Source # | |
Eq a => Eq (Sum a) Source # | |
Eq a => Eq (Product a) Source # | |
(Eq a, Eq b) => Eq (Either a b) Source # | |
(Eq x0, Eq x1) => Eq (x0, x1) Source # | |
Eq sh => Eq (sh :. Int) Source # | |
(Eq x0, Eq x1, Eq x2) => Eq (x0, x1, x2) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3) => Eq (x0, x1, x2, x3) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4) => Eq (x0, x1, x2, x3, x4) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5) => Eq (x0, x1, x2, x3, x4, x5) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6) => Eq (x0, x1, x2, x3, x4, x5, x6) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7) => Eq (x0, x1, x2, x3, x4, x5, x6, x7) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10, Eq x11) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10, Eq x11, Eq x12) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq Methods (==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # (/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10, Eq x11, Eq x12, Eq x13) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq Methods (==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # (/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10, Eq x11, Eq x12, Eq x13, Eq x14) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq Methods (==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # (/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # | |
(Eq x0, Eq x1, Eq x2, Eq x3, Eq x4, Eq x5, Eq x6, Eq x7, Eq x8, Eq x9, Eq x10, Eq x11, Eq x12, Eq x13, Eq x14, Eq x15) => Eq (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # | |
Defined in Data.Array.Accelerate.Classes.Eq Methods (==) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # (/=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # |
class Eq a => Ord a where Source #
The Ord
class for totally ordered datatypes
Methods
(<) :: Exp a -> Exp a -> Exp Bool infix 4 Source #
(>) :: Exp a -> Exp a -> Exp Bool infix 4 Source #
(<=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #
(>=) :: Exp a -> Exp a -> Exp Bool infix 4 Source #
min :: Exp a -> Exp a -> Exp a Source #
Instances
Ord Char Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord Double Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Double -> Exp Double -> Exp Bool Source # (>) :: Exp Double -> Exp Double -> Exp Bool Source # (<=) :: Exp Double -> Exp Double -> Exp Bool Source # (>=) :: Exp Double -> Exp Double -> Exp Bool Source # min :: Exp Double -> Exp Double -> Exp Double Source # max :: Exp Double -> Exp Double -> Exp Double Source # compare :: Exp Double -> Exp Double -> Exp Ordering Source # | |
Ord Float Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Float -> Exp Float -> Exp Bool Source # (>) :: Exp Float -> Exp Float -> Exp Bool Source # (<=) :: Exp Float -> Exp Float -> Exp Bool Source # (>=) :: Exp Float -> Exp Float -> Exp Bool Source # min :: Exp Float -> Exp Float -> Exp Float Source # | |
Ord Int Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord Int8 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord Int16 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Int16 -> Exp Int16 -> Exp Bool Source # (>) :: Exp Int16 -> Exp Int16 -> Exp Bool Source # (<=) :: Exp Int16 -> Exp Int16 -> Exp Bool Source # (>=) :: Exp Int16 -> Exp Int16 -> Exp Bool Source # min :: Exp Int16 -> Exp Int16 -> Exp Int16 Source # | |
Ord Int32 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Int32 -> Exp Int32 -> Exp Bool Source # (>) :: Exp Int32 -> Exp Int32 -> Exp Bool Source # (<=) :: Exp Int32 -> Exp Int32 -> Exp Bool Source # (>=) :: Exp Int32 -> Exp Int32 -> Exp Bool Source # min :: Exp Int32 -> Exp Int32 -> Exp Int32 Source # | |
Ord Int64 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Int64 -> Exp Int64 -> Exp Bool Source # (>) :: Exp Int64 -> Exp Int64 -> Exp Bool Source # (<=) :: Exp Int64 -> Exp Int64 -> Exp Bool Source # (>=) :: Exp Int64 -> Exp Int64 -> Exp Bool Source # min :: Exp Int64 -> Exp Int64 -> Exp Int64 Source # | |
Ord Ordering Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Ordering -> Exp Ordering -> Exp Bool Source # (>) :: Exp Ordering -> Exp Ordering -> Exp Bool Source # (<=) :: Exp Ordering -> Exp Ordering -> Exp Bool Source # (>=) :: Exp Ordering -> Exp Ordering -> Exp Bool Source # min :: Exp Ordering -> Exp Ordering -> Exp Ordering Source # max :: Exp Ordering -> Exp Ordering -> Exp Ordering Source # compare :: Exp Ordering -> Exp Ordering -> Exp Ordering Source # | |
Ord Word Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord Word8 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Word8 -> Exp Word8 -> Exp Bool Source # (>) :: Exp Word8 -> Exp Word8 -> Exp Bool Source # (<=) :: Exp Word8 -> Exp Word8 -> Exp Bool Source # (>=) :: Exp Word8 -> Exp Word8 -> Exp Bool Source # min :: Exp Word8 -> Exp Word8 -> Exp Word8 Source # | |
Ord Word16 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Word16 -> Exp Word16 -> Exp Bool Source # (>) :: Exp Word16 -> Exp Word16 -> Exp Bool Source # (<=) :: Exp Word16 -> Exp Word16 -> Exp Bool Source # (>=) :: Exp Word16 -> Exp Word16 -> Exp Bool Source # min :: Exp Word16 -> Exp Word16 -> Exp Word16 Source # max :: Exp Word16 -> Exp Word16 -> Exp Word16 Source # compare :: Exp Word16 -> Exp Word16 -> Exp Ordering Source # | |
Ord Word32 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Word32 -> Exp Word32 -> Exp Bool Source # (>) :: Exp Word32 -> Exp Word32 -> Exp Bool Source # (<=) :: Exp Word32 -> Exp Word32 -> Exp Bool Source # (>=) :: Exp Word32 -> Exp Word32 -> Exp Bool Source # min :: Exp Word32 -> Exp Word32 -> Exp Word32 Source # max :: Exp Word32 -> Exp Word32 -> Exp Word32 Source # compare :: Exp Word32 -> Exp Word32 -> Exp Ordering Source # | |
Ord Word64 Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp Word64 -> Exp Word64 -> Exp Bool Source # (>) :: Exp Word64 -> Exp Word64 -> Exp Bool Source # (<=) :: Exp Word64 -> Exp Word64 -> Exp Bool Source # (>=) :: Exp Word64 -> Exp Word64 -> Exp Bool Source # min :: Exp Word64 -> Exp Word64 -> Exp Word64 Source # max :: Exp Word64 -> Exp Word64 -> Exp Word64 Source # compare :: Exp Word64 -> Exp Word64 -> Exp Ordering Source # | |
Ord () Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord CChar Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CChar -> Exp CChar -> Exp Bool Source # (>) :: Exp CChar -> Exp CChar -> Exp Bool Source # (<=) :: Exp CChar -> Exp CChar -> Exp Bool Source # (>=) :: Exp CChar -> Exp CChar -> Exp Bool Source # min :: Exp CChar -> Exp CChar -> Exp CChar Source # | |
Ord CSChar Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CSChar -> Exp CSChar -> Exp Bool Source # (>) :: Exp CSChar -> Exp CSChar -> Exp Bool Source # (<=) :: Exp CSChar -> Exp CSChar -> Exp Bool Source # (>=) :: Exp CSChar -> Exp CSChar -> Exp Bool Source # min :: Exp CSChar -> Exp CSChar -> Exp CSChar Source # max :: Exp CSChar -> Exp CSChar -> Exp CSChar Source # compare :: Exp CSChar -> Exp CSChar -> Exp Ordering Source # | |
Ord CUChar Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CUChar -> Exp CUChar -> Exp Bool Source # (>) :: Exp CUChar -> Exp CUChar -> Exp Bool Source # (<=) :: Exp CUChar -> Exp CUChar -> Exp Bool Source # (>=) :: Exp CUChar -> Exp CUChar -> Exp Bool Source # min :: Exp CUChar -> Exp CUChar -> Exp CUChar Source # max :: Exp CUChar -> Exp CUChar -> Exp CUChar Source # compare :: Exp CUChar -> Exp CUChar -> Exp Ordering Source # | |
Ord CShort Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CShort -> Exp CShort -> Exp Bool Source # (>) :: Exp CShort -> Exp CShort -> Exp Bool Source # (<=) :: Exp CShort -> Exp CShort -> Exp Bool Source # (>=) :: Exp CShort -> Exp CShort -> Exp Bool Source # min :: Exp CShort -> Exp CShort -> Exp CShort Source # max :: Exp CShort -> Exp CShort -> Exp CShort Source # compare :: Exp CShort -> Exp CShort -> Exp Ordering Source # | |
Ord CUShort Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CUShort -> Exp CUShort -> Exp Bool Source # (>) :: Exp CUShort -> Exp CUShort -> Exp Bool Source # (<=) :: Exp CUShort -> Exp CUShort -> Exp Bool Source # (>=) :: Exp CUShort -> Exp CUShort -> Exp Bool Source # min :: Exp CUShort -> Exp CUShort -> Exp CUShort Source # max :: Exp CUShort -> Exp CUShort -> Exp CUShort Source # compare :: Exp CUShort -> Exp CUShort -> Exp Ordering Source # | |
Ord CInt Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord CUInt Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CUInt -> Exp CUInt -> Exp Bool Source # (>) :: Exp CUInt -> Exp CUInt -> Exp Bool Source # (<=) :: Exp CUInt -> Exp CUInt -> Exp Bool Source # (>=) :: Exp CUInt -> Exp CUInt -> Exp Bool Source # min :: Exp CUInt -> Exp CUInt -> Exp CUInt Source # | |
Ord CLong Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CLong -> Exp CLong -> Exp Bool Source # (>) :: Exp CLong -> Exp CLong -> Exp Bool Source # (<=) :: Exp CLong -> Exp CLong -> Exp Bool Source # (>=) :: Exp CLong -> Exp CLong -> Exp Bool Source # min :: Exp CLong -> Exp CLong -> Exp CLong Source # | |
Ord CULong Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CULong -> Exp CULong -> Exp Bool Source # (>) :: Exp CULong -> Exp CULong -> Exp Bool Source # (<=) :: Exp CULong -> Exp CULong -> Exp Bool Source # (>=) :: Exp CULong -> Exp CULong -> Exp Bool Source # min :: Exp CULong -> Exp CULong -> Exp CULong Source # max :: Exp CULong -> Exp CULong -> Exp CULong Source # compare :: Exp CULong -> Exp CULong -> Exp Ordering Source # | |
Ord CLLong Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CLLong -> Exp CLLong -> Exp Bool Source # (>) :: Exp CLLong -> Exp CLLong -> Exp Bool Source # (<=) :: Exp CLLong -> Exp CLLong -> Exp Bool Source # (>=) :: Exp CLLong -> Exp CLLong -> Exp Bool Source # min :: Exp CLLong -> Exp CLLong -> Exp CLLong Source # max :: Exp CLLong -> Exp CLLong -> Exp CLLong Source # compare :: Exp CLLong -> Exp CLLong -> Exp Ordering Source # | |
Ord CULLong Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CULLong -> Exp CULLong -> Exp Bool Source # (>) :: Exp CULLong -> Exp CULLong -> Exp Bool Source # (<=) :: Exp CULLong -> Exp CULLong -> Exp Bool Source # (>=) :: Exp CULLong -> Exp CULLong -> Exp Bool Source # min :: Exp CULLong -> Exp CULLong -> Exp CULLong Source # max :: Exp CULLong -> Exp CULLong -> Exp CULLong Source # compare :: Exp CULLong -> Exp CULLong -> Exp Ordering Source # | |
Ord CFloat Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CFloat -> Exp CFloat -> Exp Bool Source # (>) :: Exp CFloat -> Exp CFloat -> Exp Bool Source # (<=) :: Exp CFloat -> Exp CFloat -> Exp Bool Source # (>=) :: Exp CFloat -> Exp CFloat -> Exp Bool Source # min :: Exp CFloat -> Exp CFloat -> Exp CFloat Source # max :: Exp CFloat -> Exp CFloat -> Exp CFloat Source # compare :: Exp CFloat -> Exp CFloat -> Exp Ordering Source # | |
Ord CDouble Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp CDouble -> Exp CDouble -> Exp Bool Source # (>) :: Exp CDouble -> Exp CDouble -> Exp Bool Source # (<=) :: Exp CDouble -> Exp CDouble -> Exp Bool Source # (>=) :: Exp CDouble -> Exp CDouble -> Exp Bool Source # min :: Exp CDouble -> Exp CDouble -> Exp CDouble Source # max :: Exp CDouble -> Exp CDouble -> Exp CDouble Source # compare :: Exp CDouble -> Exp CDouble -> Exp Ordering Source # | |
Ord Half Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord Z Source # | |
Defined in Data.Array.Accelerate.Classes.Ord | |
Ord a => Ord (Maybe a) Source # | |
Defined in Data.Array.Accelerate.Data.Maybe Methods (<) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (<=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (>=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # min :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source # max :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source # compare :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Ordering Source # | |
Integral a => Ord (Ratio a) Source # | |
Defined in Data.Array.Accelerate.Data.Ratio Methods (<) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source # (>) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source # (<=) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source # (>=) :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Bool Source # min :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) Source # max :: Exp (Ratio a) -> Exp (Ratio a) -> Exp (Ratio a) Source # compare :: Exp (Ratio a) -> Exp (Ratio a) -> Exp Ordering Source # | |
Ord a => Ord (Min a) Source # | |
Defined in Data.Array.Accelerate.Data.Semigroup Methods (<) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source # (>) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source # (<=) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source # (>=) :: Exp (Min a) -> Exp (Min a) -> Exp Bool Source # min :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) Source # max :: Exp (Min a) -> Exp (Min a) -> Exp (Min a) Source # compare :: Exp (Min a) -> Exp (Min a) -> Exp Ordering Source # | |
Ord a => Ord (Max a) Source # | |
Defined in Data.Array.Accelerate.Data.Semigroup Methods (<) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source # (>) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source # (<=) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source # (>=) :: Exp (Max a) -> Exp (Max a) -> Exp Bool Source # min :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) Source # max :: Exp (Max a) -> Exp (Max a) -> Exp (Max a) Source # compare :: Exp (Max a) -> Exp (Max a) -> Exp Ordering Source # | |
Ord a => Ord (Sum a) Source # | |
Defined in Data.Array.Accelerate.Data.Monoid Methods (<) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source # (>) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source # (<=) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source # (>=) :: Exp (Sum a) -> Exp (Sum a) -> Exp Bool Source # min :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) Source # max :: Exp (Sum a) -> Exp (Sum a) -> Exp (Sum a) Source # compare :: Exp (Sum a) -> Exp (Sum a) -> Exp Ordering Source # | |
Ord a => Ord (Product a) Source # | |
Defined in Data.Array.Accelerate.Data.Monoid Methods (<) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source # (>) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source # (<=) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source # (>=) :: Exp (Product a) -> Exp (Product a) -> Exp Bool Source # min :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) Source # max :: Exp (Product a) -> Exp (Product a) -> Exp (Product a) Source # compare :: Exp (Product a) -> Exp (Product a) -> Exp Ordering Source # | |
(Ord a, Ord b) => Ord (Either a b) Source # | |
Defined in Data.Array.Accelerate.Data.Either Methods (<) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (<=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # (>=) :: Exp (Either a b) -> Exp (Either a b) -> Exp Bool Source # min :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # max :: Exp (Either a b) -> Exp (Either a b) -> Exp (Either a b) Source # compare :: Exp (Either a b) -> Exp (Either a b) -> Exp Ordering Source # | |
(Ord x0, Ord x1) => Ord (x0, x1) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source # (>) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source # (<=) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source # (>=) :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Bool Source # min :: Exp (x0, x1) -> Exp (x0, x1) -> Exp (x0, x1) Source # max :: Exp (x0, x1) -> Exp (x0, x1) -> Exp (x0, x1) Source # compare :: Exp (x0, x1) -> Exp (x0, x1) -> Exp Ordering Source # | |
Ord sh => Ord (sh :. Int) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (>) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (<=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # (>=) :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Bool Source # min :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source # max :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp (sh :. Int) Source # compare :: Exp (sh :. Int) -> Exp (sh :. Int) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2) => Ord (x0, x1, x2) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source # (>) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Bool Source # min :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp (x0, x1, x2) Source # max :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp (x0, x1, x2) Source # compare :: Exp (x0, x1, x2) -> Exp (x0, x1, x2) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3) => Ord (x0, x1, x2, x3) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) Source # max :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) Source # compare :: Exp (x0, x1, x2, x3) -> Exp (x0, x1, x2, x3) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4) => Ord (x0, x1, x2, x3, x4) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) Source # max :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) Source # compare :: Exp (x0, x1, x2, x3, x4) -> Exp (x0, x1, x2, x3, x4) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5) => Ord (x0, x1, x2, x3, x4, x5) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) Source # max :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) Source # compare :: Exp (x0, x1, x2, x3, x4, x5) -> Exp (x0, x1, x2, x3, x4, x5) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6) => Ord (x0, x1, x2, x3, x4, x5, x6) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp (x0, x1, x2, x3, x4, x5, x6) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7) => Ord (x0, x1, x2, x3, x4, x5, x6, x7) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10, Ord x11) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10, Ord x11, Ord x12) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10, Ord x11, Ord x12, Ord x13) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10, Ord x11, Ord x12, Ord x13, Ord x14) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) -> Exp Ordering Source # | |
(Ord x0, Ord x1, Ord x2, Ord x3, Ord x4, Ord x5, Ord x6, Ord x7, Ord x8, Ord x9, Ord x10, Ord x11, Ord x12, Ord x13, Ord x14, Ord x15) => Ord (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # | |
Defined in Data.Array.Accelerate.Classes.Ord Methods (<) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # (>) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # (<=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # (>=) :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Bool Source # min :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # max :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source # compare :: Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) -> Exp Ordering Source # |
Instances
type Bounded a = (Elt a, Bounded (Exp a)) Source #
Name the upper and lower limits of a type. Types which are not totally ordered may still have upper and lower bounds.
Numeric type classes
type Num a = (Elt a, Num (Exp a)) Source #
Conversion from an Integer
.
An integer literal represents the application of the function fromInteger
to the appropriate value of type Integer
. We export this specialised
version where the return type is fixed to an Exp
term in order to improve
type checking in Accelerate modules when RebindableSyntax
is enabled.
fromInteger :: Num a => Integer -> Exp a fromInteger = P.fromInteger
Basic numeric class
fromInteger :: Num a => 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
type Integral a = (Enum a, Ord a, Num a, Integral (Exp a)) Source #
Integral numbers, supporting integral division
rem :: Integral a => a -> a -> a infixl 7 #
integer remainder, satisfying
(x `quot` y)*y + (x `rem` y) == x
mod :: Integral a => a -> a -> a infixl 7 #
integer modulus, satisfying
(x `div` y)*y + (x `mod` y) == x
class (Num a, Ord a) => Rational a where Source #
Numbers which can be expressed as the quotient of two integers.
Accelerate does not have an arbitrary precision Integer type, however
fixed-length large integers are provide by the accelerate-bignum
package.
Methods
toRational :: (FromIntegral Int64 b, Integral b) => Exp a -> Exp (Ratio b) Source #
Convert a number to the quotient of two integers
Instances
type Fractional a = (Num a, Fractional (Exp a)) Source #
Conversion from a Rational
.
A floating point literal representations the application of the function
fromRational
to a value of type Rational
. We export this specialised
version where the return type is fixed to an Exp
term in order to improve
type checking in Accelerate modules when RebindableSyntax
is enabled.
fromRational :: Fractional a => Rational -> Exp a fromRational = P.fromRational
Fractional numbers, supporting real division
(/) :: Fractional a => a -> a -> a infixl 7 #
Fractional division.
recip :: Fractional a => a -> a #
Reciprocal fraction.
fromRational :: Fractional a => Rational -> a #
Conversion from a Rational
(that is
).
A floating literal stands for an application of Ratio
Integer
fromRational
to a value of type Rational
, so such literals have type
(
.Fractional
a) => a
type Floating a = (Fractional a, Floating (Exp a)) Source #
Trigonometric and hyperbolic functions and related functions
class (Ord a, Fractional a) => RealFrac a where Source #
Extracting components of fractions.
Minimal complete definition
Methods
properFraction :: (Integral b, FromIntegral Int64 b) => Exp a -> (Exp b, Exp a) Source #
The function properFraction
takes a real fractional number x
and
returns a pair (n,f)
such that x = n+f
, and:
n
is an integral number with the same sign asx
; andf
is a fraction with the same type and sign asx
, and with absolute value less than1
.
The default definitions of the ceiling
, floor
, truncate
and round
functions are in terms of properFraction
.
truncate :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #
truncate x
returns the integer nearest x
between zero and x
round :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #
returns the nearest integer to round
xx
; the even integer if x
is equidistant between two integers
ceiling :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #
returns the least integer not less than ceiling
xx
floor :: (Integral b, FromIntegral Int64 b) => Exp a -> Exp b Source #
returns the greatest integer not greater than floor
xx
Instances
divMod' :: (Floating a, RealFrac a, Integral b, FromIntegral Int64 b, ToFloating b a) => Exp a -> Exp a -> (Exp b, Exp a) Source #
class (RealFrac a, Floating a) => RealFloat a where Source #
Efficient, machine-independent access to the components of a floating-point number
Minimal complete definition
decodeFloat, isNaN, isInfinite, isDenormalized, isNegativeZero, atan2
Methods
floatRadix :: Exp a -> Exp Int64 Source #
The radix of the representation (often 2) (constant)
floatDigits :: Exp a -> Exp Int Source #
The number of digits of floatRadix
in the significand (constant)
floatRange :: Exp a -> (Exp Int, Exp Int) Source #
The lowest and highest values the exponent may assume (constant)
decodeFloat :: Exp a -> (Exp Int64, Exp Int) Source #
Return the significand and an appropriately scaled exponent. If
(m,n) =
then decodeFloat
xx = m*b^^n
, where b
is the
floating-point radix (floatRadix
). Furthermore, either m
and n
are
both zero, or b^(d-1) <=
, where abs
m < b^dd =
.floatDigits
x
encodeFloat :: Exp Int64 -> Exp Int -> Exp a Source #
Inverse of decodeFloat
default encodeFloat :: (FromIntegral Int a, FromIntegral Int64 a) => Exp Int64 -> Exp Int -> Exp a Source #
exponent :: Exp a -> Exp Int Source #
Corresponds to the second component of decodeFloat
significand :: Exp a -> Exp a Source #
Corresponds to the first component of decodeFloat
scaleFloat :: Exp Int -> Exp a -> Exp a Source #
Multiply a floating point number by an integer power of the radix
isNaN :: Exp a -> Exp Bool Source #
True
if the argument is an IEEE "not-a-number" (NaN) value
isInfinite :: Exp a -> Exp Bool Source #
True
if the argument is an IEEE infinity or negative-infinity
isDenormalized :: Exp a -> Exp Bool Source #
True
if the argument is too small to be represented in normalized
format
isNegativeZero :: Exp a -> Exp Bool Source #
True
if the argument is an IEEE negative zero
isIEEE :: Exp a -> Exp Bool Source #
True
if the argument is an IEEE floating point number
Instances
Numeric conversion classes
class FromIntegral a b where Source #
Accelerate lacks a most-general lossless Integer
type, which the
standard fromIntegral
function uses as an intermediate value when
coercing from integral types. Instead, we use this class to capture a direct
coercion between two types.
Instances
class ToFloating a b where Source #
Accelerate lacks an arbitrary-precision Rational
type, which the
standard realToFrac
uses as an intermediate value when coercing
to floating-point types. Instead, we use this class to capture a direct
coercion between two types.
Methods
toFloating :: (Num a, Floating b) => Exp a -> Exp b Source #
General coercion to floating types
Instances
Lifting and Unlifting
A value of type Int
is a plain Haskell value (unlifted), whereas an Exp
Int
is a lifted value, that is, an integer lifted into the domain of
embedded expressions (an abstract syntax tree in disguise). Both Acc
and
Exp
are surface types into which values may be lifted. Lifting plain
array and scalar surface types is equivalent to use
and constant
respectively.
In general an Exp Int
cannot be unlifted into an Int
, because the actual
number will not be available until a later stage of execution (e.g. during
GPU execution, when run
is called). Similarly an Acc array
can not be
unlifted to a vanilla array
; you should instead run
the expression with
a specific backend to evaluate it.
Lifting and unlifting are also used to pack and unpack an expression into and out of constructors such as tuples, respectively. Those expressions, at runtime, will become tuple dereferences. For example:
>>>
let sh = constant (Z :. 4 :. 10) :: Exp DIM2
>>>
let Z :. x :. y = unlift sh :: Z :. Exp Int :. Exp Int
>>>
let t = lift (x,y) :: Exp (Int, Int)
>>>
let xs = use $ fromList (Z:.10) [0..] :: Acc (Vector Int)
>>>
let ys = use $ fromList (Z:.3:.4) [0..] :: Acc (Matrix Int)
>>>
let r = (xs,ys) :: (Acc (Vector Int), Acc (Matrix Int))
>>>
let r' = lift r :: Acc (Vector Int, Matrix Int)
- Note:
Use of lift
and unlift
is probably the most common source of type errors
when using Accelerate. GHC is not very good at determining the type the
[un]lifted expression should have, so it is often necessary to add an
explicit type signature.
For example, in the following GHC will complain that it can not determine the
type of y
, even though we might expect that to be obvious (or for it to not
care):
fst :: (Elt a, Elt b) => Exp (a,b) -> Exp a fst t = let (x,y) = unlift t in x
The fix is to instead add an explicit type signature. Note that this requires
the ScopedTypeVariables
extension and to bring the type variables a
and
b
into scope with forall
:
fst :: forall a b. (Elt a, Elt b) => Exp (a,b) -> Exp a fst t = let (x,y) = unlift t :: (Exp a, Exp b) in x
For an alternative, see section Pattern synonyms.
The class of types e
which can be lifted into c
.
Associated Types
An associated-type (i.e. a type-level function) that strips all
instances of surface type constructors c
from the input type e
.
For example, the tuple types (Exp Int, Int)
and (Int, Exp
Int)
have the same "Plain" representation. That is, the
following type equality holds:
Plain (Exp Int, Int) ~ (Int,Int) ~ Plain (Int, Exp Int)
Methods
Instances
class Lift c e => Unlift c e where Source #
A limited subset of types which can be lifted, can also be unlifted.
Methods
unlift :: c (Plain e) -> e Source #
Unlift the outermost constructor through the surface type. This is only possible if the constructor is fully determined by its type - i.e., it is a singleton.
Instances
Unlift Exp () Source # | |
Unlift Exp Z Source # | |
Unlift Acc () Source # | |
Elt a => Unlift Exp (Complex (Exp a)) Source # | |
Elt a => Unlift Exp (Min (Exp a)) Source # | |
Elt a => Unlift Exp (Max (Exp a)) Source # | |
Elt a => Unlift Exp (Sum (Exp a)) Source # | |
Elt a => Unlift Exp (Product (Exp a)) Source # | |
Unlift Exp (Exp e) Source # | |
Unlift Acc (Acc a) Source # | |
(Elt x0, Elt x1) => Unlift Exp (Exp x0, Exp x1) Source # | |
(Elt e, Elt (Plain ix), Unlift Exp ix) => Unlift Exp (ix :. Exp e) Source # | |
(Elt e, Elt ix) => Unlift Exp (Exp ix :. Exp e) Source # | |
(Arrays x0, Arrays x1) => Unlift Acc (Acc x0, Acc x1) Source # | |
(Elt x0, Elt x1, Elt x2) => Unlift Exp (Exp x0, Exp x1, Exp x2) Source # | |
(Arrays x0, Arrays x1, Arrays x2) => Unlift Acc (Acc x0, Acc x1, Acc x2) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12) Source # | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13) Source # | |
Defined in Data.Array.Accelerate.Lift | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13) Source # | |
Defined in Data.Array.Accelerate.Lift | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14) Source # | |
Defined in Data.Array.Accelerate.Lift | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14) Source # | |
Defined in Data.Array.Accelerate.Lift | |
(Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8, Elt x9, Elt x10, Elt x11, Elt x12, Elt x13, Elt x14, Elt x15) => Unlift Exp (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15) Source # | |
Defined in Data.Array.Accelerate.Lift Methods unlift :: Exp (Plain (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15)) -> (Exp x0, Exp x1, Exp x2, Exp x3, Exp x4, Exp x5, Exp x6, Exp x7, Exp x8, Exp x9, Exp x10, Exp x11, Exp x12, Exp x13, Exp x14, Exp x15) Source # | |
(Arrays x0, Arrays x1, Arrays x2, Arrays x3, Arrays x4, Arrays x5, Arrays x6, Arrays x7, Arrays x8, Arrays x9, Arrays x10, Arrays x11, Arrays x12, Arrays x13, Arrays x14, Arrays x15) => Unlift Acc (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source # | |
Defined in Data.Array.Accelerate.Lift Methods unlift :: Acc (Plain (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15)) -> (Acc x0, Acc x1, Acc x2, Acc x3, Acc x4, Acc x5, Acc x6, Acc x7, Acc x8, Acc x9, Acc x10, Acc x11, Acc x12, Acc x13, Acc x14, Acc x15) Source # |
lift1 :: (Unlift Exp a, Lift Exp b) => (a -> b) -> Exp (Plain a) -> Exp (Plain b) Source #
Lift a unary function into Exp
.
lift2 :: (Unlift Exp a, Unlift Exp b, Lift Exp c) => (a -> b -> c) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c) Source #
Lift a binary function into Exp
.
lift3 :: (Unlift Exp a, Unlift Exp b, Unlift Exp c, Lift Exp d) => (a -> b -> c -> d) -> Exp (Plain a) -> Exp (Plain b) -> Exp (Plain c) -> Exp (Plain d) Source #
Lift a ternary function into Exp
.
ilift1 :: (Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 Source #
Lift a unary function to a computation over rank-1 indices.
ilift2 :: (Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 Source #
Lift a binary function to a computation over rank-1 indices.
ilift3 :: (Exp Int -> Exp Int -> Exp Int -> Exp Int) -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 -> Exp DIM1 Source #
Lift a ternary function to a computation over rank-1 indices.
Pattern synonyms
Pattern synonyms can be used as an alternative to lift
and unlift
for
constructing and accessing data types isomorphic to simple product (tuple)
types.
In contrast to lift
and unlift
however, pattern synonyms do not require
these data types to be fully polymorphic.
For example, let's say we have regular Haskell data type representing a point in two-dimensional space:
data Point = Point_ Float Float deriving (Generic, Elt)
Here we derive instance an instance of the Elt
class (via Generic
),
so that this data type can be used within scalar Accelerate expressions
In order to access the individual fields of the data constructor from within an Accelerate expression, we define the following pattern synonym:
pattern Point :: Exp Float -> Exp Float -> Exp Point pattern Point x y = Pattern (x,y)
Notice how we named the constructor of our original datatype with a trailing underscore, so that we can use the undecorated name for the pattern synonym; these must have unique names.
In essence, the Pattern
pattern is really telling GHC how to treat our Point
type as a regular pair for use in Accelerate code. The pattern can then be
used on both the left and right hand side of an expression:
addPoint :: Exp Point -> Exp Point -> Exp Point addPoint (Point x1 y1) (Point x2 y2) = Point (x1+x2) (y1+y2)
Similarly, we can define pattern synonyms for values in Acc
. We can also
use record syntax to generate field accessors, if we desire:
data SparseVector a = SparseVector_ (Vector Int) (Vector a) deriving (Generic, Arrays) pattern SparseVector :: Elt a => Acc (Vector Int) -> Acc (Vector a) -> Acc (SparseVector a) pattern SparseVector { indices, values } = Pattern (indices, values)
For convenience, we have defined several pattern synonyms for regular tuples,
T2
(for pairs), T3
(for triples), and so on up to T16
. These are
occasionally more convenient to use than lift
and unlift
together with
the regular tuple syntax.
Since: 1.3.0.0
pattern Pattern :: forall b a context. IsPattern context a b => b -> context a Source #
A pattern synonym for working with (product) data types. You can declare your own pattern synonyms based off of this.
pattern T3 :: IsPattern con (x0, x1, x2) (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con (x0, x1, x2) Source #
pattern T4 :: IsPattern con (x0, x1, x2, x3) (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con (x0, x1, x2, x3) Source #
pattern T5 :: IsPattern con (x0, x1, x2, x3, x4) (con x0, con x1, con x2, con x3, con x4) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con (x0, x1, x2, x3, x4) Source #
pattern T6 :: IsPattern con (x0, x1, x2, x3, x4, x5) (con x0, con x1, con x2, con x3, con x4, con x5) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con (x0, x1, x2, x3, x4, x5) Source #
pattern T7 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6) (con x0, con x1, con x2, con x3, con x4, con x5, con x6) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con (x0, x1, x2, x3, x4, x5, x6) Source #
pattern T8 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con (x0, x1, x2, x3, x4, x5, x6, x7) Source #
pattern T9 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8) Source #
pattern T10 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9) Source #
pattern T11 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10) Source #
pattern T12 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11) Source #
pattern T13 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12) Source #
pattern T14 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13) Source #
pattern T15 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14) Source #
pattern T16 :: IsPattern con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con (x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15) Source #
pattern I3 :: (Elt x0, Elt x1, Elt x2) => Exp x0 -> Exp x1 -> Exp x2 -> Exp ((:.) ((:.) ((:.) Z x0) x1) x2) Source #
pattern I4 :: (Elt x0, Elt x1, Elt x2, Elt x3) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) Source #
pattern I5 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) Source #
pattern I6 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) Source #
pattern I7 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) Source #
pattern I8 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7) Source #
pattern I9 :: (Elt x0, Elt x1, Elt x2, Elt x3, Elt x4, Elt x5, Elt x6, Elt x7, Elt x8) => Exp x0 -> Exp x1 -> Exp x2 -> Exp x3 -> Exp x4 -> Exp x5 -> Exp x6 -> Exp x7 -> Exp x8 -> Exp ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) ((:.) Z x0) x1) x2) x3) x4) x5) x6) x7) x8) Source #
pattern V3 :: IsVector con vec (con x0, con x1, con x2) => con x0 -> con x1 -> con x2 -> con vec Source #
pattern V4 :: IsVector con vec (con x0, con x1, con x2, con x3) => con x0 -> con x1 -> con x2 -> con x3 -> con vec Source #
pattern V8 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con vec Source #
pattern Vec16 :: Prim a => a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> a -> Vec16 a Source #
pattern V16 :: IsVector con vec (con x0, con x1, con x2, con x3, con x4, con x5, con x6, con x7, con x8, con x9, con x10, con x11, con x12, con x13, con x14, con x15) => con x0 -> con x1 -> con x2 -> con x3 -> con x4 -> con x5 -> con x6 -> con x7 -> con x8 -> con x9 -> con x10 -> con x11 -> con x12 -> con x13 -> con x14 -> con x15 -> con vec Source #
Specialised pattern synonyms for tuples, which may be more convenient to
use than lift
and
unlift
. For example, to construct a pair:
let a = 4 :: Exp Int let b = 2 :: Exp Float let c = T2 a b -- :: Exp (Int, Float); equivalent to 'lift (a,b)'
Similarly they can be used to destruct values:
let T2 x y = c -- x :: Exp Int, y :: Exp Float; equivalent to 'let (x,y) = unlift c'
These pattern synonyms can be used for both Exp
and Acc
terms.
Similarly, we have patterns for constructing and destructing indices of a given dimensionality:
let ix = Ix 2 3 -- :: Exp DIM2 let I2 y x = ix -- y :: Exp Int, x :: Exp Int
mkPattern :: Name -> DecsQ Source #
Generate pattern synonyms for the given simple (Haskell'98) sum or product data type.
Constructor and record selectors are renamed to add a trailing
underscore if it does not exist, or to remove it if it does. For infix
constructors, the name is prepended with a colon :
. For example:
data Point = Point { xcoord_ :: Float, ycoord_ :: Float } deriving (Generic, Elt)
Will create the pattern synonym:
Point_ :: Exp Float -> Exp Float -> Exp Point
together with the selector functions
xcoord :: Exp Point -> Exp Float ycoord :: Exp Point -> Exp Float
Scalar operations
Introduction
constant :: forall e. (HasCallStack, Elt e) => e -> Exp e Source #
Scalar expression inlet: make a Haskell value available for processing in an Accelerate scalar expression.
Note that this embeds the value directly into the expression. Depending on the backend used to execute the computation, this might not always be desirable. For example, a backend that does external code generation may embed this constant directly into the generated code, which means new code will need to be generated and compiled every time the value changes. In such cases, consider instead lifting scalar values into (singleton) arrays so that they can be passed as an input to the computation and thus the value can change without the need to generate fresh code.
Tuples
afst :: (Arrays a, Arrays b) => Acc (a, b) -> Acc a Source #
Extract the first component of an array pair.
asnd :: (Arrays a, Arrays b) => Acc (a, b) -> Acc b Source #
Extract the second component of an array pair
curry :: Lift f (f a, f b) => (f (Plain (f a), Plain (f b)) -> f c) -> f a -> f b -> f c Source #
Converts an uncurried function to a curried function.
uncurry :: Unlift f (f a, f b) => (f a -> f b -> f c) -> f (Plain (f a), Plain (f b)) -> f c Source #
Converts a curried function to a function on pairs.
Flow control
match :: Matching f => f -> f Source #
The match
operation is the core operation which enables embedded
pattern matching. It is applied to an n-ary scalar function, and
generates the necessary case-statements in the embedded code for each
argument. For example, given the function:
example1 :: Exp (Maybe Bool) -> Exp Int example1 Nothing_ = 0 example1 (Just_ False_) = 1 example1 (Just_ True_) = 2
In order to use this function it must be applied to the match
operator:
match example1
Using the infix-flip operator (&
), we can also write
case statements inline. For example, instead of this:
example2 x = case f x of Nothing_ -> ... -- error: embedded pattern synonym... Just_ y -> ... -- ...used outside of 'match' context
This can be written instead as:
example3 x = f x & match \case Nothing_ -> ... Just_ y -> ...
And utilising the LambdaCase
and BlockArguments
syntactic extensions.
The Template Haskell splice mkPattern
(or
mkPatterns
) can be used to generate the pattern
synonyms for a given Haskell'98 sum or product data type. For example:
data Option a = None | Some a deriving (Generic, Elt) mkPattern ''Option
Which can then be used such as:
isNone :: Elt a => Exp (Option a) -> Exp Bool isNone = match \case None_ -> True_ Some_{} -> False_
Since: 1.3.0.0
A scalar-level if-then-else construct.
Enabling the RebindableSyntax
extension will allow you to use the standard
if-then-else syntax instead.
Arguments
:: forall e. Elt e | |
=> (Exp e -> Exp Bool) | keep evaluating while this returns |
-> (Exp e -> Exp e) | function to apply |
-> Exp e | initial value |
-> Exp e |
While construct. Continue to apply the given function, starting with the
initial value, until the test function evaluates to False
.
iterate :: Elt a => Exp Int -> (Exp a -> Exp a) -> Exp a -> Exp a Source #
Repeatedly apply a function a fixed number of times
Scalar reduction
sfoldl :: (Shape sh, Elt a, Elt b) => (Exp a -> Exp b -> Exp a) -> Exp a -> Exp sh -> Acc (Array (sh :. Int) b) -> Exp a Source #
Reduce along an innermost slice of an array sequentially, by applying a binary operator to a starting value and the array from left to right.
Logical operations
(&&) :: Exp Bool -> Exp Bool -> Exp Bool infixr 3 Source #
Conjunction: True if both arguments are true. This is a short-circuit operator, so the second argument will be evaluated only if the first is true.
(||) :: Exp Bool -> Exp Bool -> Exp Bool infixr 2 Source #
Disjunction: True if either argument is true. This is a short-circuit operator, so the second argument will be evaluated only if the first is false.
Numeric operations
gcd :: Integral a => Exp a -> Exp a -> Exp a Source #
is the non-negative factor of both gcd
x yx
and y
of which every
common factor of both x
and y
is also a factor; for example:
gcd 4 2 = 2 gcd (-4) 6 = 2 gcd 0 4 = 4 gcd 0 0 = 0
That is, the common divisor that is "greatest" in the divisibility preordering.
lcm :: Integral a => Exp a -> Exp a -> Exp a Source #
is the smallest positive integer that both lcm
x yx
and y
divide.
(^) :: forall a b. (Num a, Integral b) => Exp a -> Exp b -> Exp a infixr 8 Source #
Raise a number to a non-negative integral power
(^^) :: (Fractional a, Integral b) => Exp a -> Exp b -> Exp a infixr 8 Source #
Raise a number to an integral power
Shape manipulation
index1 :: Elt i => Exp i -> Exp (Z :. i) Source #
Turn an Int
expression into a rank-1 indexing expression.
unindex1 :: Elt i => Exp (Z :. i) -> Exp i Source #
Turn a rank-1 indexing expression into an Int
expression.
index2 :: Elt i => Exp i -> Exp i -> Exp ((Z :. i) :. i) Source #
Creates a rank-2 index from two Exp Int`s
unindex2 :: Elt i => Exp ((Z :. i) :. i) -> Exp (i, i) Source #
Destructs a rank-2 index to an Exp tuple of two Int`s.
index3 :: Elt i => Exp i -> Exp i -> Exp i -> Exp (((Z :. i) :. i) :. i) Source #
Create a rank-3 index from three Exp Int`s
unindex3 :: Elt i => Exp (((Z :. i) :. i) :. i) -> Exp (i, i, i) Source #
Destruct a rank-3 index into an Exp tuple of Int`s
indexHead :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp a Source #
Get the innermost dimension of a shape.
The innermost dimension (right-most component of the shape) is the index of the array which varies most rapidly, and corresponds to elements of the array which are adjacent in memory.
Another way to think of this is, for example when writing nested loops over an array in C, this index corresponds to the index iterated over by the innermost nested loop.
indexTail :: (Elt sh, Elt a) => Exp (sh :. a) -> Exp sh Source #
Get all but the innermost element of a shape
Map a multi-dimensional index into a linear, row-major representation of an array.
Conversions
bitcast :: (Elt a, Elt b, IsScalar (EltR a), IsScalar (EltR b), BitSizeEq (EltR a) (EltR b)) => Exp a -> Exp b Source #
Reinterpret a value as another type. The two representations must have the same bit size.
Foreign Function Interface (FFI)
foreignAcc :: forall as bs asm. (Arrays as, Arrays bs, Foreign asm) => asm (ArraysR as -> ArraysR bs) -> (Acc as -> Acc bs) -> Acc as -> Acc bs Source #
Call a foreign array function.
The form the first argument takes is dependent on the backend being targeted. Note that the foreign function only has access to the input array(s) passed in as its argument.
In case the operation is being executed on a backend which does not support this foreign implementation, the fallback implementation is used instead, which itself could be a foreign implementation for a (presumably) different backend, or an implementation in pure Accelerate. In this way, multiple foreign implementations can be supplied, and will be tested for suitability against the target backend in sequence.
For an example see the accelerate-fft package.
foreignExp :: forall x y asm. (Elt x, Elt y, Foreign asm) => asm (EltR x -> EltR y) -> (Exp x -> Exp y) -> Exp x -> Exp y Source #
Call a foreign scalar expression.
The form of the first argument is dependent on the backend being targeted. Note that the foreign function only has access to the input element(s) passed in as its first argument.
As with foreignAcc
, the fallback implementation itself may be a (sequence
of) foreign implementation(s) for a different backend(s), or implemented
purely in Accelerate.
Plain arrays
Operations
arrayRank :: forall sh e. Shape sh => Array sh e -> Int Source #
Rank of an array (as a plain Haskell value)
arrayShape :: Shape sh => Array sh e -> sh Source #
Shape of an array (as a plain Haskell value)
arraySize :: Shape sh => Array sh e -> Int Source #
Total number of elements in an array (as a plain Haskell value)
arrayReshape :: (Shape sh, Shape sh') => sh -> Array sh' e -> Array sh e Source #
Change the shape of an array without altering its contents. The arraySize
of the source and result arrays must be identical.
indexArray :: (Shape sh, Elt e) => Array sh e -> sh -> e Source #
Array indexing in plain Haskell code.
linearIndexArray :: Elt e => Array sh e -> Int -> e Source #
Linear array indexing in plain Haskell code.
Getting data in
We often need to generate or read data into an Array
so that it can be used
in Accelerate. The base accelerate
library includes basic conversions
routines, but for additional functionality see the
accelerate-io package,
which includes conversions between:
Function
fromFunction :: (Shape sh, Elt e) => sh -> (sh -> e) -> Array sh e Source #
Create an array from its representation function, applied at each index of the array
fromFunctionM :: forall sh e. (Shape sh, Elt e) => sh -> (sh -> IO e) -> IO (Array sh e) Source #
Create an array using a monadic function applied at each index
Since: 1.2.0.0
Lists
fromList :: forall sh e. (Shape sh, Elt e) => sh -> [e] -> Array sh e Source #
Convert elements of a list into an Accelerate Array
This will generate a new multidimensional Array
of the specified shape and
extent by consuming elements from the list and adding them to the array in
row-major order.
>>>
fromList (Z:.10) [0..] :: Vector Int
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
Note that we pull elements off the list lazily, so infinite lists are accepted:
>>>
fromList (Z:.5:.10) (repeat 0) :: Matrix Float
Matrix (Z :. 5 :. 10) [ 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0]
You can also make use of the OverloadedLists
extension to produce
one-dimensional vectors from a finite list.
>>>
[0..9] :: Vector Int
Vector (Z :. 10) [0,1,2,3,4,5,6,7,8,9]
Note that this requires first traversing the list to determine its length, and then traversing it a second time to collect the elements into the array, thus forcing the spine of the list to be manifest on the heap.
toList :: forall sh e. (Shape sh, Elt e) => Array sh e -> [e] Source #
Convert an accelerated Array
to a list in row-major order
Useful re-exports
($) :: forall (r :: RuntimeRep) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
Note that (
is levity-polymorphic in its result type, so that
$
)foo
where $
Truefoo :: Bool -> Int#
is well-typed.
error :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => [Char] -> a #
error
stops execution and displays an error message.
undefined :: forall (r :: RuntimeRep) (a :: TYPE r). HasCallStack => a #
const x
is a unary function which evaluates to x
for all inputs.
>>>
const 42 "hello"
42
>>>
map (const 42) [0..3]
[42,42,42,42]
Conversion of values to readable String
s.
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
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack
is an
implementation detail and should not be considered part of the
CallStack
API, we may decide to change the implementation in the
future.
Since: base-4.9.0.0
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
8-bit signed integer type
Instances
16-bit signed integer type
Instances
32-bit signed integer type
Instances
64-bit signed integer type
Instances
Instances
8-bit unsigned integer type
Instances
16-bit unsigned integer type
Instances
32-bit unsigned integer type
Instances
64-bit unsigned integer type
Instances
Instances
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.
Instances
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
Instances
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
Monad Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
MonadFix Maybe | Since: base-2.1 |
Defined in Control.Monad.Fix | |
MonadFail Maybe | Since: base-4.9.0.0 |
Defined in Control.Monad.Fail | |
Applicative Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable Methods fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldMap' :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Traversable Maybe | Since: base-2.1 |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
Alternative Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
MonadFailure Maybe | |
MonadThrow Maybe | |
Defined in Control.Monad.Catch | |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 Maybe | |
Defined in Data.Hashable.Class | |
Functor Maybe Source # | |
MonadBaseControl Maybe Maybe | |
FunctorWithIndex () Maybe | |
Defined in Control.Lens.Indexed | |
FoldableWithIndex () Maybe | |
TraversableWithIndex () Maybe | |
Defined in Control.Lens.Indexed Methods itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) # itraversed :: IndexedTraversal () (Maybe a) (Maybe b) a b # | |
Lift a => Lift (Maybe a :: Type) | |
(Lift Exp a, Elt (Plain a)) => Lift Exp (Maybe a) Source # | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Generic (Maybe a) | Since: base-4.6.0.0 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
(Semigroup (Exp a), Elt a) => Semigroup (Exp (Maybe a)) Source # | |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
(Monoid (Exp a), Elt a) => Monoid (Exp (Maybe a)) Source # | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Hashable a => Hashable (Maybe a) | |
Defined in Data.Hashable.Class | |
Ixed (Maybe a) | |
Defined in Control.Lens.At | |
At (Maybe a) | |
AsEmpty (Maybe a) | |
Defined in Control.Lens.Empty | |
Pretty a => Pretty (Maybe a) | Ignore
|
Defined in Data.Text.Prettyprint.Doc.Internal | |
Pretty a => Pretty (Maybe a) | |
Defined in Text.PrettyPrint.Annotated.WL | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics Associated Types type DemoteRep (Maybe a) | |
Elt a => Elt (Maybe a) Source # | |
Eq a => Eq (Maybe a) Source # | |
Ord a => Ord (Maybe a) Source # | |
Defined in Data.Array.Accelerate.Data.Maybe Methods (<) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (>) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (<=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # (>=) :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Bool Source # min :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source # max :: Exp (Maybe a) -> Exp (Maybe a) -> Exp (Maybe a) Source # compare :: Exp (Maybe a) -> Exp (Maybe a) -> Exp Ordering Source # | |
Generic1 Maybe | Since: base-4.6.0.0 |
SingI ('Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Each (Maybe a) (Maybe b) a b |
|
SingI a2 => SingI ('Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
type Failure Maybe | |
Defined in Basement.Monad | |
type StM Maybe a | |
Defined in Control.Monad.Trans.Control | |
type Rep (Maybe a) | |
Defined in GHC.Generics | |
type Index (Maybe a) | |
Defined in Control.Lens.At | |
type IxValue (Maybe a) | |
Defined in Control.Lens.At | |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
data Sing (b :: Maybe a) | |
type Plain (Maybe a) Source # | |
Defined in Data.Array.Accelerate.Data.Maybe | |
type Rep1 Maybe | |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and
chr
).
Instances
Haskell type representing the C float
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C double
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C short
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned short
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C int
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned int
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C long long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned long long
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C char
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C signed char
type.
(The concrete types of Foreign.C.Types are platform-specific.)
Instances
Haskell type representing the C unsigned char
type.
(The concrete types of Foreign.C.Types are platform-specific.)