Copyright | (c) 2016-2017 Tao He |
---|---|
License | MIT |
Maintainer | sighingnow@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
NDArray module, provide an imperative-style programming interface.
- newtype NDArray a = NDArray {}
- waitAll :: IO ()
- makeEmptyNDArray :: forall a. DType a => [Int] -> Context -> Bool -> IO (NDArray a)
- makeNDArray :: DType a => [Int] -> Context -> Vector a -> IO (NDArray a)
- ndshape :: DType a => NDArray a -> IO (Int, [Int])
- ndsize :: DType a => NDArray a -> IO Int
- context :: DType a => NDArray a -> IO Context
- copy :: DType a => NDArray a -> IO (NDArray a)
- items :: DType a => NDArray a -> IO (Vector a)
- slice :: DType a => NDArray a -> Int -> Int -> NDArray a
- at :: DType a => NDArray a -> Int -> NDArray a
- waitToRead :: DType a => NDArray a -> IO ()
- onehotEncode :: DType a => NDArray a -> NDArray a -> IO (NDArray a)
- zeros :: DType a => [Int] -> IO (NDArray a)
- ones :: DType a => [Int] -> IO (NDArray a)
- full :: DType a => [Int] -> a -> IO (NDArray a)
- array :: DType a => [Int] -> Vector a -> IO (NDArray a)
- data PrettyWrapper = Pretty a => MkPretty {
- runPretty :: a
Documentation
NDArray type alias.
Neural NDArray Source # | |
Tensor NDArray Source # | |
(DType a, (~) * a Int8) => Eq (NDArray Int8) Source # | |
(DType a, (~) * a Int32) => Eq (NDArray Int32) Source # | |
(DType a, Floating a) => Eq (NDArray a) Source # | |
DType a => Floating (NDArray a) Source # | |
DType a => Fractional (NDArray a) Source # | |
DType a => Num (NDArray a) Source # | |
(DType a, Pretty a) => Show (NDArray a) Source # | |
Make a new empty ndarray with specified shape, context and data type.
Make a new NDArray with given shape.
Get the shape of given NDArray.
Get size of the given ndarray.
:: DType a | |
=> NDArray a | |
-> Int | The beginning index of slice. |
-> Int | The end index of slices. |
-> NDArray a |
Return a sliced ndarray that shares memory with current one.
Return a sub ndarray that shares memory with current one.
waitToRead :: DType a => NDArray a -> IO () Source #
Block until all pending writes operations on current ndarray are finished.
:: DType a | |
=> NDArray a | An ndarray containing indices of the categorical features. |
-> NDArray a | The result holder of the encoding. |
-> IO (NDArray a) | The encoding ndarray. |
One hot encoding indices into matrix out.
Create a new NDArray filled with 0, with specified shape and context.
Create a new NDArray filled with 1, with specified shape and context.
Create a new NDArray filled with given value, with specified shape and context.
Create a new NDArray that copies content from source_array.
data PrettyWrapper Source #
Wrapper for pretty print multiple dimensions matrices.
Pretty PrettyWrapper Source # | Destruct pretty |