Safe Haskell | None |
---|---|
Language | Haskell98 |
- data U
- class (Vector Vector a, MVector MVector a) => Unbox a
- computeUnboxedS :: (Shape sh, Load r1 sh e, Unbox e) => Array r1 sh e -> Array U sh e
- computeUnboxedP :: (Shape sh, Load r1 sh e, Monad m, Unbox e) => Array r1 sh e -> m (Array U sh e)
- fromListUnboxed :: (Shape sh, Unbox a) => sh -> [a] -> Array U sh a
- fromUnboxed :: (Shape sh, Unbox e) => sh -> Vector e -> Array U sh e
- toUnboxed :: Unbox e => Array U sh e -> Vector e
- zip :: (Shape sh, Unbox a, Unbox b) => Array U sh a -> Array U sh b -> Array U sh (a, b)
- zip3 :: (Shape sh, Unbox a, Unbox b, Unbox c) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh (a, b, c)
- zip4 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh (a, b, c, d)
- zip5 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh e -> Array U sh (a, b, c, d, e)
- zip6 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh e -> Array U sh f -> Array U sh (a, b, c, d, e, f)
- unzip :: (Unbox a, Unbox b) => Array U sh (a, b) -> (Array U sh a, Array U sh b)
- unzip3 :: (Unbox a, Unbox b, Unbox c) => Array U sh (a, b, c) -> (Array U sh a, Array U sh b, Array U sh c)
- unzip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => Array U sh (a, b, c, d) -> (Array U sh a, Array U sh b, Array U sh c, Array U sh d)
- unzip5 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Array U sh (a, b, c, d, e) -> (Array U sh a, Array U sh b, Array U sh c, Array U sh d, Array U sh e)
- unzip6 :: (Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Array U sh (a, b, c, d, e, f) -> (Array U sh a, Array U sh b, Array U sh c, Array U sh d, Array U sh e, Array U sh f)
Documentation
Unboxed arrays are represented as unboxed vectors.
The implementation uses Data.Vector.Unboxed
which is based on type
families and picks an efficient, specialised representation for every
element type. In particular, unboxed vectors of pairs are represented
as pairs of unboxed vectors.
This is the most efficient representation for numerical data.
Unbox a => Source U a Source | Read elements from an unboxed vector array. |
Unbox e => Target U e Source | Filling of unboxed vector arrays. |
Unbox a => Structured U a b Source | |
(Read sh, Read e, Unbox e) => Read (Array U sh e) Source | |
(Show sh, Show e, Unbox e) => Show (Array U sh e) Source | |
data MVec U = UMVec (IOVector e) Source | |
type TR U = D Source | |
data Array U sh a = AUnboxed !sh !(Vector a) Source |
class (Vector Vector a, MVector MVector a) => Unbox a
Unbox Bool | |
Unbox Char | |
Unbox Double | |
Unbox Float | |
Unbox Int | |
Unbox Int8 | |
Unbox Int16 | |
Unbox Int32 | |
Unbox Int64 | |
Unbox Word | |
Unbox Word8 | |
Unbox Word16 | |
Unbox Word32 | |
Unbox Word64 | |
Unbox () | |
(RealFloat a, Unbox a) => Unbox (Complex a) | |
(Unbox a, Unbox b) => Unbox (a, b) | |
(Unbox a, Unbox b, Unbox c) => Unbox (a, b, c) | |
(Unbox a, Unbox b, Unbox c, Unbox d) => Unbox (a, b, c, d) | |
(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Unbox (a, b, c, d, e) | |
(Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Unbox (a, b, c, d, e, f) |
computeUnboxedS :: (Shape sh, Load r1 sh e, Unbox e) => Array r1 sh e -> Array U sh e Source
Sequential computation of array elements..
- This is an alias for
computeS
with a more specific type.
computeUnboxedP :: (Shape sh, Load r1 sh e, Monad m, Unbox e) => Array r1 sh e -> m (Array U sh e) Source
Parallel computation of array elements.
- This is an alias for
computeP
with a more specific type.
fromListUnboxed :: (Shape sh, Unbox a) => sh -> [a] -> Array U sh a Source
O(n). Convert a list to an unboxed vector array.
- This is an alias for
fromList
with a more specific type.
fromUnboxed :: (Shape sh, Unbox e) => sh -> Vector e -> Array U sh e Source
O(1). Wrap an unboxed vector as an array.
toUnboxed :: Unbox e => Array U sh e -> Vector e Source
O(1). Unpack an unboxed vector from an array.
zip :: (Shape sh, Unbox a, Unbox b) => Array U sh a -> Array U sh b -> Array U sh (a, b) Source
O(1). Zip some unboxed arrays.
The shapes must be identical else error
.
zip3 :: (Shape sh, Unbox a, Unbox b, Unbox c) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh (a, b, c) Source
O(1). Zip some unboxed arrays.
The shapes must be identical else error
.
zip4 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh (a, b, c, d) Source
O(1). Zip some unboxed arrays.
The shapes must be identical else error
.
zip5 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh e -> Array U sh (a, b, c, d, e) Source
O(1). Zip some unboxed arrays.
The shapes must be identical else error
.
zip6 :: (Shape sh, Unbox a, Unbox b, Unbox c, Unbox d, Unbox e, Unbox f) => Array U sh a -> Array U sh b -> Array U sh c -> Array U sh d -> Array U sh e -> Array U sh f -> Array U sh (a, b, c, d, e, f) Source
O(1). Zip some unboxed arrays.
The shapes must be identical else error
.
unzip :: (Unbox a, Unbox b) => Array U sh (a, b) -> (Array U sh a, Array U sh b) Source
O(1). Unzip an unboxed array.
unzip3 :: (Unbox a, Unbox b, Unbox c) => Array U sh (a, b, c) -> (Array U sh a, Array U sh b, Array U sh c) Source
O(1). Unzip an unboxed array.
unzip4 :: (Unbox a, Unbox b, Unbox c, Unbox d) => Array U sh (a, b, c, d) -> (Array U sh a, Array U sh b, Array U sh c, Array U sh d) Source
O(1). Unzip an unboxed array.