mxnet-0.1.0.0: MXNet interface in Haskell.

Copyright(c) 2016 Tao He
LicenseMIT
Maintainersighingnow@gmail.com
Safe HaskellSafe
LanguageHaskell2010

MXNet.Core.Base

Contents

Description

Interfaces in core module of MXNet.

Synopsis

Data type definitions

Type alias

type MXUInt = CUInt Source #

Handle size_t type.

MXUint type alias.

type MXFloat = CFloat Source #

MXFloat type alias.

Handlers and Creators

Callback types

data ExecutorMonitorCallback Source #

Callback: ExecutorMonitorCallback.

data CustomOpPropCreator Source #

Callback: CustomOpPropCreator.

type MXKVStoreUpdater Source #

Arguments

 = 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 #

Arguments

 = 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

mxRandomSeed :: Int -> IO Int Source #

Seed the global random number generators in mxnet.

mxNotifyShutdown :: IO Int Source #

Notify the engine about a shutdown.

mxSetProfilerConfig Source #

Arguments

:: 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.

mxSetProfilerState Source #

Arguments

:: 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

mxNDArrayCreateNone Source #

Arguments

:: IO (Int, NDArrayHandle)

The returned NDArrayHandle.

Create a NDArray handle that is not initialized.

mxNDArrayCreate Source #

Arguments

:: [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.

mxNDArrayCreateEx Source #

Arguments

:: [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 #

Arguments

:: 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 #

Arguments

:: NDArrayHandle

The NDArray handle.

-> IO (Int, CSize, Ptr CChar) 

Save the NDArray into raw bytes.

mxNDArraySave Source #

Arguments

:: 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.

mxNDArrayLoad Source #

Arguments

:: 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 #

Arguments

:: 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 #

Arguments

:: 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.

mxNDArraySlice Source #

Arguments

:: 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.

mxNDArrayAt Source #

Arguments

:: NDArrayHandle

The handle to the NDArray.

-> MXUInt

The index.

-> IO (Int, NDArrayHandle)

The NDArrayHandle of output NDArray.

Index the NDArray along axis 0.

mxNDArrayReshape Source #

Arguments

:: 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.

mxNDArrayGetShape Source #

Arguments

:: NDArrayHandle 
-> IO (Int, MXUInt, [MXUInt])

The output dimension and it's shape.

mxNDArrayGetData Source #

Arguments

:: NDArrayHandle

The NDArray handle.

-> IO (Int, Ptr MXFloat)

Pointer holder to get pointer of data.

Get the content of the data in NDArray.

mxNDArrayGetDType Source #

Arguments

:: NDArrayHandle

The NDArray handle.

-> IO (Int, Int)

The type of data in this NDArray handle.

Get the type of the data in NDArray

mxNDArrayGetContext Source #

Arguments

:: NDArrayHandle

The NDArray handle.

-> IO (Int, Int, Int)

The device type and device id.

Get the context of the NDArray.

Functions on NDArray

mxListFunctions Source #

Arguments

:: IO (Int, MXUInt, [FunctionHandle])

The output function handle array.

List all the available functions handles.

mxGetFunction Source #

Arguments

:: String

The name of the function.

-> IO (Int, FunctionHandle)

The corresponding function handle.

Get the function handle by name.

mxFuncGetInfo Source #

Arguments

:: 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.

mxFuncDescribe Source #

Arguments

:: 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.

mxFuncInvoke Source #

Arguments

:: 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.

mxFuncInvokeEx Source #

Arguments

:: 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 #

Arguments

:: IO (Int, MXUInt, [AtomicSymbolCreator])

The number of atomic symbol creators and the atomic symbol creators list.

List all the available AtomicSymbolCreator.

mxSymbolGetAtomicSymbolName Source #

Arguments

:: AtomicSymbolCreator 
-> IO (Int, String)

Name of the target atomic symbol.

Get the name of an atomic symbol.

mxSymbolGetAtomicSymbolInfo Source #

Arguments

:: 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 #

Arguments

:: 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 #

Arguments

:: String

Name of the variable.

-> IO (Int, SymbolHandle)

The created variable symbol.

Create a Variable Symbol.

mxSymbolCreateGroup Source #

Arguments

:: 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 #

Arguments

:: String

The file name

-> IO (Int, SymbolHandle) 

Load a symbol from a json file.

mxSymbolCreateFromJSON Source #

Arguments

:: String

The json string.

-> IO (Int, SymbolHandle) 

Load a symbol from a json string.

mxSymbolSaveToFile Source #

Arguments

:: SymbolHandle

The symbol to save.

-> String

The target file name.

-> IO Int 

Save a symbol into a json file.

mxSymbolSaveToJSON Source #

Arguments

:: 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.

mxSymbolPrint Source #

Arguments

:: SymbolHandle

The symbol handle to print.

-> IO (Int, String) 

Print the content of symbol, used for debug.

mxSymbolGetName Source #

Arguments

:: SymbolHandle 
-> IO (Int, String, Int)

The name of the symbol and whether the call is successful.

Get string name from symbol

mxSymbolGetAttr Source #

Arguments

:: 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.

mxSymbolSetAttr Source #

Arguments

:: 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.

mxSymbolListAttr Source #

Arguments

:: SymbolHandle 
-> IO (Int, MXUInt, [String])

The number of attributes and attributes list.

Get all attributes from symbol, including all descendents.

mxSymbolListAttrShallow Source #

Arguments

:: SymbolHandle 
-> IO (Int, MXUInt, [String])

The number of attributes and attributes list.

Get all attributes from symbol, excluding descendents.

mxSymbolListArguments Source #

Arguments

:: SymbolHandle 
-> IO (Int, MXUInt, [String])

The number of arguments and list of arguments' names.

List arguments in the symbol.

mxSymbolListOutputs Source #

Arguments

:: SymbolHandle 
-> IO (Int, MXUInt, [String])

The number of outputs and list of outputs' names.

List returns in the symbol.

mxSymbolGetInternals Source #

Arguments

:: SymbolHandle 
-> IO (Int, SymbolHandle)

The output symbol whose outputs are all the internals.

Get a symbol that contains all the internals.

mxSymbolGetOutput Source #

Arguments

:: 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 #

Arguments

:: SymbolHandle 
-> IO (Int, MXUInt, [String])

The output size and the output string array.

List auxiliary states in the symbol.

mxSymbolCompose Source #

Arguments

:: 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.

mxSymbolGrad Source #

Arguments

:: 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.

mxSymbolInferShape Source #

Arguments

:: 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 #

Arguments

:: 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.

mxSymbolInferType Source #

Arguments

:: 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

mxExecutorFree Source #

Arguments

:: ExecutorHandle

The executor handle.

-> IO Int 

Delete the executor.

mxExecutorPrint Source #

Arguments

:: ExecutorHandle

The executor handle.

-> IO (Int, String) 

Print the content of execution plan, used for debug.

mxExecutorForward Source #

Arguments

:: ExecutorHandle

The executor handle.

-> Int

int value to indicate whether the forward pass is for evaluation.

-> IO Int 

Executor forward method.

mxExecutorBackward Source #

Arguments

:: ExecutorHandle

The executor handle.

-> MXUInt

Length.

-> [NDArrayHandle]

NDArray handle for heads' gradient.

-> IO Int 

Excecutor run backward.

mxExecutorOutputs Source #

Arguments

:: ExecutorHandle

The executor handle.

-> IO (Int, [NDArrayHandle])

The handles for outputs.

Get executor's head NDArray.

mxExecutorBind Source #

Arguments

:: 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.

mxExecutorBindX Source #

Arguments

:: 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.

mxExecutorBindEX Source #

Arguments

:: 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 #

Arguments

:: ExecutorHandle

The executor handle.

-> ExecutorMonitorCallback 
-> Ptr () 
-> IO Int 

Set a call back to notify the completion of operation.

IO Interface

mxListDataIters Source #

Arguments

:: IO (Int, [DataIterCreator])

The output iterator entries.

List all the available iterator entries.

mxDataIterCreateIter Source #

Arguments

:: 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 #

Arguments

:: 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.

mxDataIterFree Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO Int 

Get the detailed information about data iterator.

Free the handle to the IO module.

mxDataIterNext Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO (Int, Int) 

Move iterator to next position.

mxDataIterBeforeFirst Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO Int 

Call iterator.Reset.

mxDataIterGetData Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO (Int, NDArrayHandle) 

Get the handle to the NDArray of underlying data.

mxDataIterGetIndex Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO (Int, [CULong])

Output indices of the array.

Get the image index by array.

mxDataIterGetPadNum Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO (Int, Int) 

Get the padding number in current data batch.

mxDataIterGetLabel Source #

Arguments

:: DataIterHandle

The handle pointer to the data iterator.

-> IO (Int, NDArrayHandle) 

Get the handle to the NDArray of underlying label.

Basic KVStore interface

mxInitPSEnv Source #

Arguments

:: MXUInt

Number of variables to initialize.

-> [String]

Environment keys.

-> [String]

Environment values.

-> IO Int 

Initialized ps-lite environment variables.

mxKVStoreCreate Source #

Arguments

:: String

The type of KVStore.

-> IO (Int, KVStoreHandle) 

Create a kvstore.

mxKVStoreFree Source #

Arguments

:: KVStoreHandle

Handle to the kvstore.

-> IO Int 

Delete a KVStore handle.

mxKVStoreInit Source #

Arguments

:: 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.

mxKVStorePush Source #

Arguments

:: 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.

mxKVStorePull Source #

Arguments

:: 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.

mxKVStoreGetType Source #

Arguments

:: KVStoreHandle

Handle to the KVStore.

-> IO (Int, String) 

Get the type of the kvstore.

Advanced KVStore for multi-machines

mxKVStoreGetRank Source #

Arguments

:: KVStoreHandle

Handle to the KVStore.

-> IO (Int, Int) 

The rank of this node in its group, which is in [0, GroupSize).

mxKVStoreGetGroupSize Source #

Arguments

:: 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`.

mxKVStoreIsWorkerNode :: IO (Int, Int) Source #

Return whether or not this process is a worker node.

mxKVStoreIsServerNode :: IO (Int, Int) Source #

Return whether or not this process is a server node.

mxKVStoreIsSchedulerNode :: IO (Int, Int) Source #

Return whether or not this process is a scheduler node.

mxKVStoreBarrier Source #

Arguments

:: KVStoreHandle

Handle to the KVStore.

-> IO Int 

Global barrier among all worker machines.

mxKVStoreSetBarrierBeforeExit Source #

Arguments

:: 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 #

Arguments

:: 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 #

Arguments

:: 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 dead

-> IO (Int, Int) 

Get the number of ps dead node(s) specified by {node_id}.

mxRecordIOWriterCreate Source #

Arguments

:: String

Path to file.

-> IO (Int, RecordIOHandle) 

Create a RecordIO writer object.

mxRecordIOWriterFree Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> IO Int 

Delete a RecordIO writer object.

mxRecordIOWriterWriteRecord Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> Ptr CChar

Buffer to write.

-> CSize

Size of buffer.

-> IO Int 

Write a record to a RecordIO object.

mxRecordIOWriterTell Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> Ptr CSize

Handle to output position.

-> IO Int 

Get the current writer pointer position.

mxRecordIOReaderCreate Source #

Arguments

:: String

Path to file.

-> IO (Int, RecordIOHandle) 

Create a RecordIO reader object.

mxRecordIOReaderFree Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> IO Int 

Delete a RecordIO reader object.

mxRecordIOReaderReadRecord Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> Ptr (Ptr CChar)

Pointer to return buffer.

-> IO (Int, CSize) 

Write a record to a RecordIO object.

mxRecordIOReaderSeek Source #

Arguments

:: RecordIOHandle

Handle to RecordIO object.

-> CSize

Target position.

-> IO Int 

Set the current reader pointer position.

mxRtcCreate Source #

Arguments

:: 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.

mxRtcPush Source #

Arguments

:: 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.

mxRtcFree :: RtcHandle -> IO Int Source #

Delete a MXRtc object.