Copyright | (c) 2016 Tao He |
---|---|
License | MIT |
Maintainer | sighingnow@gmail.com |
Safe Haskell | Safe |
Language | Haskell2010 |
Interfaces in core module of MXNet.
- type MXUInt = CUInt
- type MXFloat = CFloat
- data NDArrayHandle
- data FunctionHandle
- data AtomicSymbolCreator
- data SymbolHandle
- data AtomicSymbolHandle
- data ExecutorHandle
- data DataIterCreator
- data DataIterHandle
- data KVStoreHandle
- data RecordIOHandle
- data RtcHandle
- data ExecutorMonitorCallback
- data CustomOpPropCreator
- type MXKVStoreUpdater = Int -> NDArrayHandle -> NDArrayHandle -> Ptr () -> IO Int
- type MXKVStoreServerController = Int -> Ptr CChar -> Ptr () -> IO Int
- mxGetLastError :: IO String
- mxRandomSeed :: Int -> IO Int
- mxNotifyShutdown :: IO Int
- mxSetProfilerConfig :: Int -> String -> IO Int
- mxSetProfilerState :: Int -> IO Int
- mxDumpProfile :: IO Int
- mxNDArrayCreateNone :: IO (Int, NDArrayHandle)
- mxNDArrayCreate :: [MXUInt] -> MXUInt -> Int -> Int -> Int -> IO (Int, NDArrayHandle)
- mxNDArrayCreateEx :: [MXUInt] -> MXUInt -> Int -> Int -> Int -> Int -> IO (Int, NDArrayHandle)
- mxNDArrayLoadFromRawBytes :: Ptr () -> CSize -> IO (Int, NDArrayHandle)
- mxNDArraySaveRawBytes :: NDArrayHandle -> IO (Int, CSize, Ptr CChar)
- mxNDArraySave :: String -> MXUInt -> [NDArrayHandle] -> [String] -> IO Int
- mxNDArrayLoad :: String -> IO (Int, MXUInt, [NDArrayHandle], MXUInt, [String])
- mxNDArraySyncCopyFromCPU :: NDArrayHandle -> Ptr () -> CSize -> IO Int
- mxNDArraySyncCopyToCPU :: NDArrayHandle -> Ptr () -> CSize -> IO Int
- mxNDArrayWaitToRead :: NDArrayHandle -> IO Int
- mxNDArrayWaitToWrite :: NDArrayHandle -> IO Int
- mxNDArrayWaitAll :: IO Int
- mxNDArrayFree :: NDArrayHandle -> IO Int
- mxNDArraySlice :: NDArrayHandle -> MXUInt -> MXUInt -> IO (Int, NDArrayHandle)
- mxNDArrayAt :: NDArrayHandle -> MXUInt -> IO (Int, NDArrayHandle)
- mxNDArrayReshape :: NDArrayHandle -> Int -> [Int] -> IO (Int, NDArrayHandle)
- mxNDArrayGetShape :: NDArrayHandle -> IO (Int, MXUInt, [MXUInt])
- mxNDArrayGetData :: NDArrayHandle -> IO (Int, Ptr MXFloat)
- mxNDArrayGetDType :: NDArrayHandle -> IO (Int, Int)
- mxNDArrayGetContext :: NDArrayHandle -> IO (Int, Int, Int)
- mxListFunctions :: IO (Int, MXUInt, [FunctionHandle])
- mxGetFunction :: String -> IO (Int, FunctionHandle)
- mxFuncGetInfo :: FunctionHandle -> IO (Int, String, String, MXUInt, [String], [String], [String], String)
- mxFuncDescribe :: FunctionHandle -> IO (Int, MXUInt, MXUInt, MXUInt, Int)
- mxFuncInvoke :: FunctionHandle -> [NDArrayHandle] -> [MXFloat] -> [NDArrayHandle] -> IO Int
- mxFuncInvokeEx :: FunctionHandle -> [NDArrayHandle] -> [MXFloat] -> [NDArrayHandle] -> Int -> [String] -> [String] -> IO Int
- mxImperativeInvoke :: a
- mxSymbolListAtomicSymbolCreators :: IO (Int, MXUInt, [AtomicSymbolCreator])
- mxSymbolGetAtomicSymbolName :: AtomicSymbolCreator -> IO (Int, String)
- mxSymbolGetAtomicSymbolInfo :: AtomicSymbolCreator -> [String] -> IO (Int, String, String, MXUInt, [String], [String], [String], String)
- mxSymbolCreateAtomicSymbol :: AtomicSymbolCreator -> MXUInt -> [String] -> [String] -> IO (Int, SymbolHandle)
- mxSymbolCreateVariable :: String -> IO (Int, SymbolHandle)
- mxSymbolCreateGroup :: MXUInt -> [SymbolHandle] -> IO (Int, SymbolHandle)
- mxSymbolCreateFromFile :: String -> IO (Int, SymbolHandle)
- mxSymbolCreateFromJSON :: String -> IO (Int, SymbolHandle)
- mxSymbolSaveToFile :: SymbolHandle -> String -> IO Int
- mxSymbolSaveToJSON :: SymbolHandle -> IO (Int, String)
- mxSymbolFree :: SymbolHandle -> IO Int
- mxSymbolCopy :: SymbolHandle -> IO (Int, SymbolHandle)
- mxSymbolPrint :: SymbolHandle -> IO (Int, String)
- mxSymbolGetName :: SymbolHandle -> IO (Int, String, Int)
- mxSymbolGetAttr :: SymbolHandle -> String -> IO (Int, String, Int)
- mxSymbolSetAttr :: SymbolHandle -> String -> String -> IO Int
- mxSymbolListAttr :: SymbolHandle -> IO (Int, MXUInt, [String])
- mxSymbolListAttrShallow :: SymbolHandle -> IO (Int, MXUInt, [String])
- mxSymbolListArguments :: SymbolHandle -> IO (Int, MXUInt, [String])
- mxSymbolListOutputs :: SymbolHandle -> IO (Int, MXUInt, [String])
- mxSymbolGetInternals :: SymbolHandle -> IO (Int, SymbolHandle)
- mxSymbolGetOutput :: SymbolHandle -> MXUInt -> IO (Int, SymbolHandle)
- mxSymbolListAuxiliaryStates :: SymbolHandle -> IO (Int, MXUInt, [String])
- mxSymbolCompose :: SymbolHandle -> String -> MXUInt -> [String] -> [SymbolHandle] -> IO Int
- mxSymbolGrad :: SymbolHandle -> MXUInt -> [String] -> IO (Int, SymbolHandle)
- mxSymbolInferShape :: SymbolHandle -> MXUInt -> [String] -> Ptr MXUInt -> Ptr MXUInt -> IO (Int, (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), Int)
- mxSymbolInferShapePartial :: SymbolHandle -> MXUInt -> [String] -> Ptr MXUInt -> Ptr MXUInt -> IO (Int, (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), Int)
- mxSymbolInferType :: SymbolHandle -> MXUInt -> [String] -> Ptr CInt -> IO (Int, MXUInt, MXUInt, MXUInt, Int)
- mxExecutorFree :: ExecutorHandle -> IO Int
- mxExecutorPrint :: ExecutorHandle -> IO (Int, String)
- mxExecutorForward :: ExecutorHandle -> Int -> IO Int
- mxExecutorBackward :: ExecutorHandle -> MXUInt -> [NDArrayHandle] -> IO Int
- mxExecutorOutputs :: ExecutorHandle -> IO (Int, [NDArrayHandle])
- mxExecutorBind :: SymbolHandle -> Int -> Int -> MXUInt -> [NDArrayHandle] -> [NDArrayHandle] -> [MXUInt] -> MXUInt -> [NDArrayHandle] -> IO (Int, ExecutorHandle)
- mxExecutorBindX :: SymbolHandle -> Int -> Int -> MXUInt -> [String] -> [Int] -> [Int] -> MXUInt -> [NDArrayHandle] -> [NDArrayHandle] -> [MXUInt] -> MXUInt -> [NDArrayHandle] -> IO (Int, ExecutorHandle)
- mxExecutorBindEX :: SymbolHandle -> Int -> Int -> MXUInt -> [String] -> [Int] -> [Int] -> MXUInt -> [NDArrayHandle] -> [NDArrayHandle] -> [MXUInt] -> MXUInt -> [NDArrayHandle] -> ExecutorHandle -> IO (Int, ExecutorHandle)
- mxExecutorSetMonitorCallback :: ExecutorHandle -> ExecutorMonitorCallback -> Ptr () -> IO Int
- mxListDataIters :: IO (Int, [DataIterCreator])
- mxDataIterCreateIter :: DataIterCreator -> MXUInt -> [String] -> [String] -> IO (Int, DataIterHandle)
- mxDataIterGetIterInfo :: DataIterCreator -> IO (Int, String, String, MXUInt, [String], [String], [String])
- mxDataIterFree :: DataIterHandle -> IO Int
- mxDataIterNext :: DataIterHandle -> IO (Int, Int)
- mxDataIterBeforeFirst :: DataIterHandle -> IO Int
- mxDataIterGetData :: DataIterHandle -> IO (Int, NDArrayHandle)
- mxDataIterGetIndex :: DataIterHandle -> IO (Int, [CULong])
- mxDataIterGetPadNum :: DataIterHandle -> IO (Int, Int)
- mxDataIterGetLabel :: DataIterHandle -> IO (Int, NDArrayHandle)
- mxInitPSEnv :: MXUInt -> [String] -> [String] -> IO Int
- mxKVStoreCreate :: String -> IO (Int, KVStoreHandle)
- mxKVStoreFree :: KVStoreHandle -> IO Int
- mxKVStoreInit :: KVStoreHandle -> MXUInt -> [Int] -> [NDArrayHandle] -> IO Int
- mxKVStorePush :: KVStoreHandle -> MXUInt -> [Int] -> [NDArrayHandle] -> Int -> IO Int
- mxKVStorePull :: KVStoreHandle -> MXUInt -> [Int] -> [NDArrayHandle] -> Int -> IO Int
- mxKVStoreSetUpdater :: a
- mxKVStoreGetType :: KVStoreHandle -> IO (Int, String)
- mxKVStoreGetRank :: KVStoreHandle -> IO (Int, Int)
- mxKVStoreGetGroupSize :: KVStoreHandle -> IO (Int, Int)
- mxKVStoreIsWorkerNode :: IO (Int, Int)
- mxKVStoreIsServerNode :: IO (Int, Int)
- mxKVStoreIsSchedulerNode :: IO (Int, Int)
- mxKVStoreBarrier :: KVStoreHandle -> IO Int
- mxKVStoreSetBarrierBeforeExit :: KVStoreHandle -> Int -> IO Int
- mxKVStoreRunServer :: a
- mxKVStoreSendCommmandToServers :: KVStoreHandle -> Int -> String -> IO Int
- mxKVStoreGetNumDeadNode :: KVStoreHandle -> Int -> Int -> IO (Int, Int)
- mxRecordIOWriterCreate :: String -> IO (Int, RecordIOHandle)
- mxRecordIOWriterFree :: RecordIOHandle -> IO Int
- mxRecordIOWriterWriteRecord :: RecordIOHandle -> Ptr CChar -> CSize -> IO Int
- mxRecordIOWriterTell :: RecordIOHandle -> Ptr CSize -> IO Int
- mxRecordIOReaderCreate :: String -> IO (Int, RecordIOHandle)
- mxRecordIOReaderFree :: RecordIOHandle -> IO Int
- mxRecordIOReaderReadRecord :: RecordIOHandle -> Ptr (Ptr CChar) -> IO (Int, CSize)
- mxRecordIOReaderSeek :: RecordIOHandle -> CSize -> IO Int
- mxRtcCreate :: String -> MXUInt -> MXUInt -> [String] -> [String] -> [NDArrayHandle] -> [NDArrayHandle] -> Ptr CChar -> IO (Int, RtcHandle)
- mxRtcPush :: RtcHandle -> MXUInt -> MXUInt -> [NDArrayHandle] -> [NDArrayHandle] -> MXUInt -> MXUInt -> MXUInt -> MXUInt -> MXUInt -> MXUInt -> IO Int
- mxRtcFree :: RtcHandle -> IO Int
- mxCustomOpRegister :: String -> CustomOpPropCreator -> IO Int
Data type definitions
Type alias
Handlers and Creators
data FunctionHandle Source #
Handle to a mxnet narray function that changes NDArray.
data AtomicSymbolCreator Source #
Handle to a function that takes param and creates symbol.
data SymbolHandle Source #
Handle to a symbol that can be bind as operator.
data ExecutorHandle Source #
Storable ExecutorHandle Source # | Handle to an Executor. |
Callback types
data ExecutorMonitorCallback Source #
Callback: ExecutorMonitorCallback.
data CustomOpPropCreator Source #
Callback: CustomOpPropCreator.
type MXKVStoreUpdater Source #
= Int | The key. |
-> NDArrayHandle | The pushed value on the key. |
-> NDArrayHandle | The value stored on local on the key. |
-> Ptr () | The additional handle to the updater. |
-> IO Int |
Callback: MXKVStoreUpdater, user-defined updater for the kvstore.
type MXKVStoreServerController Source #
= Int | The head of the command. |
-> Ptr CChar | The body of the command. |
-> Ptr () | Helper handle for implementing controller. |
-> IO Int |
Callback: MXKVStoreServerController, the prototype of a server controller.
Error handling.
mxGetLastError :: IO String Source #
Handle size_t type.
Get the string message of last error.
Global State setups
mxNotifyShutdown :: IO Int Source #
Notify the engine about a shutdown.
:: Int | Mode, indicate the working mode of profiler, record anly symbolic operator when mode == 0, record all operator when mode == 1. |
-> String | Filename, where to save trace file. |
-> IO Int |
Set up configuration of profiler.
:: Int | State, indicate the working state of profiler, profiler not running when state == 0, profiler running when state == 1. |
-> IO Int |
Set up state of profiler.
mxDumpProfile :: IO Int Source #
Save profile and stop profiler.
NDArray creation and deletion
:: IO (Int, NDArrayHandle) | The returned NDArrayHandle. |
Create a NDArray handle that is not initialized.
:: [MXUInt] | The shape of NDArray. |
-> MXUInt | The dimension of the shape. |
-> Int | Device type, specify device we want to take. |
-> Int | The device id of the specific device. |
-> Int | Whether to delay allocation until. |
-> IO (Int, NDArrayHandle) | The returing handle. |
Create a NDArray with specified shape.
:: [MXUInt] | |
-> MXUInt | |
-> Int | Device type, specify device we want to take. |
-> Int | The device id of the specific device. |
-> Int | Whether to delay allocation until. |
-> Int | Data type of created array. |
-> IO (Int, NDArrayHandle) | The returing handle. |
Create a NDArray with specified shape and data type.
mxNDArrayLoadFromRawBytes Source #
:: Ptr () | The head of the raw bytes. |
-> CSize | Size of the raw bytes. |
-> IO (Int, NDArrayHandle) |
Create a NDArray handle that is loaded from raw bytes.
mxNDArraySaveRawBytes Source #
Save the NDArray into raw bytes.
:: String | Name of the file. |
-> MXUInt | Number of arguments to save. |
-> [NDArrayHandle] | the array of NDArrayHandles to be saved. |
-> [String] | names of the NDArrays to save. |
-> IO Int |
Save list of narray into the file.
:: String | Name of the file. |
-> IO (Int, MXUInt, [NDArrayHandle], MXUInt, [String]) | The size of ndarray handles, ndarray handles the number of names and the returned names. |
Load list of narray from the file.
mxNDArraySyncCopyFromCPU Source #
:: NDArrayHandle | The NDArrayHandle. |
-> Ptr () | The raw data source to copy from. |
-> CSize | The memory size want to copy from. |
-> IO Int |
Perform a synchronize copy from a continugous CPU memory region. This is useful to copy data from existing memory region that are not wrapped by NDArray (thus dependency not being tracked).
mxNDArraySyncCopyToCPU Source #
:: NDArrayHandle | The NDArrayHandle. |
-> Ptr () | The raw data source to copy into. |
-> CSize | The memory size want to copy into. |
-> IO Int |
Perform a synchronize copy to a continugous CPU memory region.
mxNDArrayWaitToRead :: NDArrayHandle -> IO Int Source #
Wait until all the pending writes with respect NDArray are finished.
mxNDArrayWaitToWrite :: NDArrayHandle -> IO Int Source #
Wait until all the pending read/write with respect NDArray are finished.
mxNDArrayWaitAll :: IO Int Source #
Wait until all delayed operations in the system is completed.
mxNDArrayFree :: NDArrayHandle -> IO Int Source #
Free the narray handle.
:: NDArrayHandle | The handle to the NDArray. |
-> MXUInt | The beginning index of slice. |
-> MXUInt | The ending index of slice. |
-> IO (Int, NDArrayHandle) | The NDArrayHandle of sliced NDArray. |
Slice the NDArray along axis 0.
:: NDArrayHandle | The handle to the NDArray. |
-> MXUInt | The index. |
-> IO (Int, NDArrayHandle) | The NDArrayHandle of output NDArray. |
Index the NDArray along axis 0.
:: NDArrayHandle | The handle to the NDArray. |
-> Int | Number of dimensions of new shape. |
-> [Int] | New sizes of every dimension. |
-> IO (Int, NDArrayHandle) | The new shape data and the NDArrayHandle of reshaped NDArray. |
Reshape the NDArray.
:: NDArrayHandle | |
-> IO (Int, MXUInt, [MXUInt]) | The output dimension and it's shape. |
:: NDArrayHandle | The NDArray handle. |
-> IO (Int, Ptr MXFloat) | Pointer holder to get pointer of data. |
Get the content of the data in NDArray.
:: NDArrayHandle | The NDArray handle. |
-> IO (Int, Int) | The type of data in this NDArray handle. |
Get the type of the data in NDArray
:: NDArrayHandle | The NDArray handle. |
-> IO (Int, Int, Int) | The device type and device id. |
Get the context of the NDArray.
Functions on NDArray
:: IO (Int, MXUInt, [FunctionHandle]) | The output function handle array. |
List all the available functions handles.
:: String | The name of the function. |
-> IO (Int, FunctionHandle) | The corresponding function handle. |
Get the function handle by name.
:: FunctionHandle | The target function handle. |
-> IO (Int, String, String, MXUInt, [String], [String], [String], String) | The name of returned function, it's description, the number of it's arguments, argument name, type and descriptions, as well as the return type of this function. |
Get the information of the function handle.
:: FunctionHandle | |
-> IO (Int, MXUInt, MXUInt, MXUInt, Int) | The number of NDArrays, scalar variables and mutable NDArrays to be passed in, and the type mask of this function. |
Get the argument requirements of the function.
:: FunctionHandle | The function to invoke. |
-> [NDArrayHandle] | The normal NDArrays arguments. |
-> [MXFloat] | The scalar arguments. |
-> [NDArrayHandle] | The mutable NDArrays arguments. |
-> IO Int |
Invoke a function, the array size of passed in arguments must match the values in the
fun
function.
:: FunctionHandle | The function to invoke. |
-> [NDArrayHandle] | The normal NDArrays arguments. |
-> [MXFloat] | The scalar arguments. |
-> [NDArrayHandle] | The mutable NDArrays arguments. |
-> Int | Number of keyword parameters. |
-> [String] | Keys for keyword parameters. |
-> [String] | Values for keyword parameters. |
-> IO Int |
Invoke a function, the array size of passed in arguments must match the values in the
fun
function.
mxImperativeInvoke :: a Source #
Invoke a nnvm op and imperative function. FIXME
Symbolic configuration generation
mxSymbolListAtomicSymbolCreators Source #
:: IO (Int, MXUInt, [AtomicSymbolCreator]) | The number of atomic symbol creators and the atomic symbol creators list. |
List all the available AtomicSymbolCreator
.
mxSymbolGetAtomicSymbolName Source #
:: AtomicSymbolCreator | |
-> IO (Int, String) | Name of the target atomic symbol. |
Get the name of an atomic symbol.
mxSymbolGetAtomicSymbolInfo Source #
:: AtomicSymbolCreator | |
-> [String] | TODO document for this argument. The keyword arguments for specifying variable number of arguments. |
-> IO (Int, String, String, MXUInt, [String], [String], [String], String) | Return the name and description of the symbol, the name, type and description of it's arguments, as well as the return type of this symbol. |
Get the detailed information about atomic symbol.
mxSymbolCreateAtomicSymbol Source #
:: AtomicSymbolCreator | The atomic symbol creator. |
-> MXUInt | The number of parameters. |
-> [String] | The keys of the parameters. |
-> [String] | The values of the parameters. |
-> IO (Int, SymbolHandle) | The created symbol. |
Create an AtomicSymbol.
mxSymbolCreateVariable Source #
:: String | Name of the variable. |
-> IO (Int, SymbolHandle) | The created variable symbol. |
Create a Variable Symbol.
:: MXUInt | Number of symbols to be grouped. |
-> [SymbolHandle] | |
-> IO (Int, SymbolHandle) | The created symbol group. |
Create a Symbol by grouping list of symbols together.
mxSymbolCreateFromFile Source #
:: String | The file name |
-> IO (Int, SymbolHandle) |
Load a symbol from a json file.
mxSymbolCreateFromJSON Source #
:: String | The json string. |
-> IO (Int, SymbolHandle) |
Load a symbol from a json string.
:: SymbolHandle | The symbol to save. |
-> String | The target file name. |
-> IO Int |
Save a symbol into a json file.
:: SymbolHandle | The symbol to save. |
-> IO (Int, String) | The result json string. |
Save a symbol into a json string.
mxSymbolFree :: SymbolHandle -> IO Int Source #
Free the symbol handle.
mxSymbolCopy :: SymbolHandle -> IO (Int, SymbolHandle) Source #
Copy the symbol to another handle.
:: SymbolHandle | The symbol handle to print. |
-> IO (Int, String) |
Print the content of symbol, used for debug.
:: SymbolHandle | |
-> IO (Int, String, Int) | The name of the symbol and whether the call is successful. |
Get string name from symbol
:: SymbolHandle | The source symbol. |
-> String | The key of this attribute. |
-> IO (Int, String, Int) | The value of this attribute and whether the call is successful. |
Get string attribute from symbol.
:: SymbolHandle | The source symbol. |
-> String | The name of the attribute. |
-> String | The value of the attribute. |
-> IO Int |
Set string attribute from symbol. Setting attribute to a symbol can affect the semantics (mutable/immutable) of symbolic graph.
:: SymbolHandle | |
-> IO (Int, MXUInt, [String]) | The number of attributes and attributes list. |
Get all attributes from symbol, including all descendents.
mxSymbolListAttrShallow Source #
:: SymbolHandle | |
-> IO (Int, MXUInt, [String]) | The number of attributes and attributes list. |
Get all attributes from symbol, excluding descendents.
mxSymbolListArguments Source #
:: SymbolHandle | |
-> IO (Int, MXUInt, [String]) | The number of arguments and list of arguments' names. |
List arguments in the symbol.
:: SymbolHandle | |
-> IO (Int, MXUInt, [String]) | The number of outputs and list of outputs' names. |
List returns in the symbol.
:: SymbolHandle | |
-> IO (Int, SymbolHandle) | The output symbol whose outputs are all the internals. |
Get a symbol that contains all the internals.
:: SymbolHandle | The symbol. |
-> MXUInt | Index of the output. |
-> IO (Int, SymbolHandle) | The output symbol whose outputs are the index-th symbol. |
Get index-th outputs of the symbol.
mxSymbolListAuxiliaryStates Source #
:: SymbolHandle | |
-> IO (Int, MXUInt, [String]) | The output size and the output string array. |
List auxiliary states in the symbol.
:: SymbolHandle | The symbol to apply. |
-> String | Name of the symbol. |
-> MXUInt | Number of arguments. |
-> [String] | Key of keyword arguments, optional. |
-> [SymbolHandle] | Arguments. |
-> IO Int |
Compose the symbol on other symbols.
:: SymbolHandle | The symbol to get gradient. |
-> MXUInt | Number of arguments to get gradient. |
-> [String] | Names of the arguments to get gradient. |
-> IO (Int, SymbolHandle) | Return the symbol that has gradient. |
Get the gradient graph of the symbol.
:: SymbolHandle | Symbol handle. |
-> MXUInt | Number of input arguments. |
-> [String] | Number of input arguments. |
-> Ptr MXUInt | Keys of keyword arguments, optional. |
-> Ptr MXUInt | The head pointer of the rows in CSR |
-> IO (Int, (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), Int) | Return the in, out and auxiliary shape size, ndim and data (array of pointers to head of the input shape), and whether infer shape completes or more information is needed. |
Infer shape of unknown input shapes given the known one.
mxSymbolInferShapePartial Source #
:: SymbolHandle | Symbol handle. |
-> MXUInt | Number of input arguments. |
-> [String] | Number of input arguments. |
-> Ptr MXUInt | Keys of keyword arguments, optional. |
-> Ptr MXUInt | The head pointer of the rows in CSR |
-> IO (Int, (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), (MXUInt, [MXUInt], [Ptr MXUInt]), Int) | Return the in, out and auxiliary array's shape size, ndim and data (array of pointers to head of the input shape), and whether infer shape completes or more information is needed. |
Partially infer shape of unknown input shapes given the known one.
:: SymbolHandle | Symbol handle. |
-> MXUInt | Number of input arguments. |
-> [String] | Key of keyword arguments, optional. |
-> Ptr CInt | The content of the CSR. |
-> IO (Int, MXUInt, MXUInt, MXUInt, Int) | Return the size and an array of pointers to head the input, output and auxiliary type, as well as whether infer type completes or more information is needed. |
Infer type of unknown input types given the known one.
Executor interface
:: ExecutorHandle | The executor handle. |
-> IO (Int, String) |
Print the content of execution plan, used for debug.
:: ExecutorHandle | The executor handle. |
-> Int | int value to indicate whether the forward pass is for evaluation. |
-> IO Int |
Executor forward method.
:: ExecutorHandle | The executor handle. |
-> MXUInt | Length. |
-> [NDArrayHandle] | NDArray handle for heads' gradient. |
-> IO Int |
Excecutor run backward.
:: ExecutorHandle | The executor handle. |
-> IO (Int, [NDArrayHandle]) | The handles for outputs. |
Get executor's head NDArray.
:: SymbolHandle | The symbol handle. |
-> Int | Device type. |
-> Int | Device id. |
-> MXUInt | Length of arrays in arguments. |
-> [NDArrayHandle] | In array. |
-> [NDArrayHandle] | Grads handle array. |
-> [MXUInt] | Grad req array. |
-> MXUInt | Length of auxiliary states. |
-> [NDArrayHandle] | Auxiliary states array. |
-> IO (Int, ExecutorHandle) |
Generate Executor from symbol.
:: SymbolHandle | The symbol handle. |
-> Int | Device type of default context. |
-> Int | Device id of default context. |
-> MXUInt | Size of group2ctx map. |
-> [String] | Keys of group2ctx map. |
-> [Int] | Device type of group2ctx map. |
-> [Int] | Device id of group2ctx map. |
-> MXUInt | Length of arrays in arguments. |
-> [NDArrayHandle] | In array. |
-> [NDArrayHandle] | Grads handle array. |
-> [MXUInt] | Grad req array. |
-> MXUInt | Length of auxiliary states. |
-> [NDArrayHandle] | Auxiliary states array. |
-> IO (Int, ExecutorHandle) |
Generate Executor from symbol. This is advanced function, allow specify group2ctx map. The user can annotate "ctx_group" attribute to name each group.
:: SymbolHandle | The symbol handle. |
-> Int | Device type of default context. |
-> Int | Device id of default context. |
-> MXUInt | Size of group2ctx map. |
-> [String] | Keys of group2ctx map. |
-> [Int] | Device type of group2ctx map. |
-> [Int] | Device id of group2ctx map. |
-> MXUInt | Length of arrays in arguments. |
-> [NDArrayHandle] | In array. |
-> [NDArrayHandle] | Grads handle array. |
-> [MXUInt] | Grad req array. |
-> MXUInt | Length of auxiliary states. |
-> [NDArrayHandle] | Auxiliary states array. |
-> ExecutorHandle | Input executor handle for memory sharing. |
-> IO (Int, ExecutorHandle) |
Generate Executor from symbol. This is advanced function, allow specify group2ctx map. The user can annotate "ctx_group" attribute to name each group.
mxExecutorSetMonitorCallback Source #
:: ExecutorHandle | The executor handle. |
-> ExecutorMonitorCallback | |
-> Ptr () | |
-> IO Int |
Set a call back to notify the completion of operation.
IO Interface
:: IO (Int, [DataIterCreator]) | The output iterator entries. |
List all the available iterator entries.
:: DataIterCreator | The handle pointer to the data iterator. |
-> MXUInt | Size of arrays in arguments. |
-> [String] | Parameter keys. |
-> [String] | Parameter values. |
-> IO (Int, DataIterHandle) |
Init an iterator, init with parameters the array size of passed in arguments.
mxDataIterGetIterInfo Source #
:: DataIterCreator | The handle pointer to the data iterator. |
-> IO (Int, String, String, MXUInt, [String], [String], [String]) | Return the name and description of the data iter creator, the name, type and description of it's arguments, as well as the return type of this symbol. |
Get the detailed information about data iterator.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO Int |
Get the detailed information about data iterator.
Free the handle to the IO module.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO (Int, Int) |
Move iterator to next position.
mxDataIterBeforeFirst Source #
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO Int |
Call iterator.Reset.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO (Int, NDArrayHandle) |
Get the handle to the NDArray of underlying data.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO (Int, [CULong]) | Output indices of the array. |
Get the image index by array.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO (Int, Int) |
Get the padding number in current data batch.
:: DataIterHandle | The handle pointer to the data iterator. |
-> IO (Int, NDArrayHandle) |
Get the handle to the NDArray of underlying label.
Basic KVStore interface
:: MXUInt | Number of variables to initialize. |
-> [String] | Environment keys. |
-> [String] | Environment values. |
-> IO Int |
Initialized ps-lite environment variables.
:: KVStoreHandle | Handle to the kvstore. |
-> MXUInt | The number of key-value pairs. |
-> [Int] | The list of keys. |
-> [NDArrayHandle] | The list of values. |
-> IO Int |
Init a list of (key,value) pairs in kvstore.
:: KVStoreHandle | Handle to the kvstore. |
-> MXUInt | The number of key-value pairs. |
-> [Int] | The list of keys. |
-> [NDArrayHandle] | The list of values. |
-> Int | The priority of the action. |
-> IO Int |
Push a list of (key,value) pairs to kvstore.
:: KVStoreHandle | Handle to the kvstore. |
-> MXUInt | The number of key-value pairs. |
-> [Int] | The list of keys. |
-> [NDArrayHandle] | The list of values. |
-> Int | The priority of the action. |
-> IO Int |
FIXME Pull a list of (key, value) pairs from the kvstore.
mxKVStoreSetUpdater :: a Source #
FIXME Register an push updater.
:: KVStoreHandle | Handle to the KVStore. |
-> IO (Int, String) |
Get the type of the kvstore.
Advanced KVStore for multi-machines
:: KVStoreHandle | Handle to the KVStore. |
-> IO (Int, Int) |
The rank of this node in its group, which is in [0, GroupSize).
mxKVStoreGetGroupSize Source #
:: KVStoreHandle | Handle to the KVStore. |
-> IO (Int, Int) |
The number of nodes in this group, which is
- number of workers if if `IsWorkerNode() == true`,
- number of servers if if `IsServerNode() == true`,
- 1 if `IsSchedulerNode() == true`.
mxKVStoreIsSchedulerNode :: IO (Int, Int) Source #
Return whether or not this process is a scheduler node.
:: KVStoreHandle | Handle to the KVStore. |
-> IO Int |
Global barrier among all worker machines.
mxKVStoreSetBarrierBeforeExit Source #
:: KVStoreHandle | Handle to the KVStore. |
-> Int | Whether to do barrier when kvstore finalize |
-> IO Int |
Whether to do barrier when finalize.
mxKVStoreRunServer :: a Source #
FIXME Run as server (or scheduler).
mxKVStoreSendCommmandToServers Source #
:: KVStoreHandle | Handle to the KVStore. |
-> Int | The head of the command. |
-> String | The body of the command. |
-> IO Int |
Send a command to all server nodes.
mxKVStoreGetNumDeadNode Source #
:: KVStoreHandle | Handle to the kvstore. |
-> Int | node id, can be a node group or a single node. kScheduler = 1, kServerGroup = 2, kWorkerGroup = 4 |
-> Int | A node fails to send heartbeart in {timeout_sec} seconds will be presumed as |
-> IO (Int, Int) |
Get the number of ps dead node(s) specified by {node_id}.
mxRecordIOWriterCreate Source #
:: String | Path to file. |
-> IO (Int, RecordIOHandle) |
Create a RecordIO writer object.
:: RecordIOHandle | Handle to RecordIO object. |
-> IO Int |
Delete a RecordIO writer object.
mxRecordIOWriterWriteRecord Source #
:: RecordIOHandle | Handle to RecordIO object. |
-> Ptr CChar | Buffer to write. |
-> CSize | Size of buffer. |
-> IO Int |
Write a record to a RecordIO object.
:: RecordIOHandle | Handle to RecordIO object. |
-> Ptr CSize | Handle to output position. |
-> IO Int |
Get the current writer pointer position.
mxRecordIOReaderCreate Source #
:: String | Path to file. |
-> IO (Int, RecordIOHandle) |
Create a RecordIO reader object.
:: RecordIOHandle | Handle to RecordIO object. |
-> IO Int |
Delete a RecordIO reader object.
mxRecordIOReaderReadRecord Source #
:: RecordIOHandle | Handle to RecordIO object. |
-> Ptr (Ptr CChar) | Pointer to return buffer. |
-> IO (Int, CSize) |
Write a record to a RecordIO object.
:: RecordIOHandle | Handle to RecordIO object. |
-> CSize | Target position. |
-> IO Int |
Set the current reader pointer position.
:: String | Name. |
-> MXUInt | Number of inputs. |
-> MXUInt | Number of outputs. |
-> [String] | Input names. |
-> [String] | Output names. |
-> [NDArrayHandle] | Inputs. |
-> [NDArrayHandle] | Outputs. |
-> Ptr CChar | Kernel. |
-> IO (Int, RtcHandle) |
Create a MXRtc object.
:: RtcHandle | Handle. |
-> MXUInt | Number of inputs. |
-> MXUInt | Number of outputs. |
-> [NDArrayHandle] | Inputs. |
-> [NDArrayHandle] | Outputs. |
-> MXUInt | Grid dim x |
-> MXUInt | Grid dim y |
-> MXUInt | Grid dim z |
-> MXUInt | Block dim x |
-> MXUInt | Block dim y |
-> MXUInt | Block dim z |
-> IO Int |
Run cuda kernel.
:: String | op type. |
-> CustomOpPropCreator | |
-> IO Int |