Copyright | (c) 2016 Tao He |
---|---|
License | MIT |
Maintainer | sighingnow@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
Interfaces in core module of MXNet.
- mxGetLastError :: IO String
- mxListAllOpNames :: IO (Int, [String])
- data NDArray a
- 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
- at :: DType a => NDArray a -> Int -> NDArray a
- items :: DType a => NDArray a -> IO (Vector a)
- slice :: DType a => NDArray a -> Int -> 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 Symbol a
- variable :: DType a => String -> IO (Symbol a)
- getName :: DType a => Symbol a -> IO String
- getAttr :: DType a => Symbol a -> String -> IO (Maybe String)
- setAttr :: DType a => Symbol a -> String -> String -> IO ()
- infershape :: DType a => Symbol a -> [String] -> IO ([[Int]], [[Int]], [[Int]])
- grad :: DType a => Symbol a -> [String] -> IO (Symbol a)
- bind :: DType a => Symbol a -> Context -> HashMap String (NDArray a) -> IO (Executor a)
- bind' :: DType a => Symbol a -> Context -> [NDArray a] -> IO (Executor a)
- listInputs :: DType a => Symbol a -> IO [String]
- listOutputs :: DType a => Symbol a -> IO [String]
- listAuxiliaries :: DType a => Symbol a -> IO [String]
- data Executor a
- makeExecutor :: DType a => ExecutorHandle -> IO (Executor a)
- forward :: DType a => Executor a -> Bool -> IO ()
- backward :: DType a => Executor a -> IO ()
- getOutputs :: DType a => Executor a -> IO [NDArray a]
- module MXNet.Core.Base.DType
- module MXNet.Core.Base.HMap
Necessary raw functions
mxGetLastError :: IO String Source #
Handle size_t type.
Get the string message of last error.
mxListAllOpNames :: IO (Int, [String]) Source #
List all the available operator names, include entries.
NDArray
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.
Return a sub ndarray that shares memory with current one.
:: 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.
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.
Symbol
Type alias for variable.
Make a new symbolic variable with given name.
getAttr :: DType a => Symbol a -> String -> IO (Maybe String) Source #
Get specified attribute of symbol.
setAttr :: DType a => Symbol a -> String -> String -> IO () Source #
Set specified attribute of symbol.
infershape :: DType a => Symbol a -> [String] -> IO ([[Int]], [[Int]], [[Int]]) Source #
Infer the shape of the given symbol, return the in, out and auxiliary shape size.
grad :: DType a => Symbol a -> [String] -> IO (Symbol a) Source #
Get the autodiff of current symbol. This function can only be used if current symbol is a loss function.
bind :: DType a => Symbol a -> Context -> HashMap String (NDArray a) -> IO (Executor a) Source #
Bind with explicit argument mapping (name -- value mapping).
bind' :: DType a => Symbol a -> Context -> [NDArray a] -> IO (Executor a) Source #
Bind without explicit argument mapping (name -- value mapping).
Executor
makeExecutor :: DType a => ExecutorHandle -> IO (Executor a) Source #
Make an executor using the given handler.
:: DType a | |
=> Executor a | The executor handle. |
-> Bool | Whether this forward is for evaluation purpose. |
-> IO () |
Executor forward method.
DType
module MXNet.Core.Base.DType
Heterogeneous Dictionary.
module MXNet.Core.Base.HMap