Copyright | (c) 2016-2017 Tao He |
---|---|
License | MIT |
Maintainer | sighingnow@gmail.com |
Safe Haskell | Safe |
Language | Haskell2010 |
Interfaces in core module of NNVM.
- type NNUInt = CUInt
- type OpHandle = Ptr ()
- data SymbolHandle
- data GraphHandle
- nnAPISetLastError :: String -> IO ()
- nnGetLastError :: IO String
- nnListAllOpNames :: IO (Int, [String])
- nnGetOpHandle :: String -> IO (Int, OpHandle)
- nnListUniqueOps :: IO (Int, [OpHandle])
- nnGetOpInfo :: OpHandle -> IO (Int, String, String, NNUInt, [String], [String], [String], String)
- nnSymbolCreateAtomicSymbol :: OpHandle -> NNUInt -> [String] -> [String] -> IO (Int, SymbolHandle)
- nnSymbolCreateVariable :: String -> IO (Int, SymbolHandle)
- nnSymbolCreateGroup :: NNUInt -> [SymbolHandle] -> IO (Int, SymbolHandle)
- nnAddControlDeps :: SymbolHandle -> SymbolHandle -> IO Int
- nnSymbolFree :: SymbolHandle -> IO Int
- nnSymbolCopy :: SymbolHandle -> IO (Int, SymbolHandle)
- nnSymbolPrint :: SymbolHandle -> IO (Int, String)
- nnSymbolGetAttr :: SymbolHandle -> String -> IO (Int, String, Int)
- nnSymbolSetAttrs :: SymbolHandle -> NNUInt -> [String] -> [String] -> IO Int
- nnSymbolListAttrs :: SymbolHandle -> Int -> IO (Int, [String])
- nnSymbolListInputVariables :: SymbolHandle -> Int -> IO (Int, [SymbolHandle])
- nnSymbolListInputNames :: SymbolHandle -> Int -> IO (Int, [String])
- nnSymbolListOutputNames :: SymbolHandle -> IO (Int, [String])
- nnSymbolGetInternals :: SymbolHandle -> IO (Int, SymbolHandle)
- nnSymbolGetOutput :: SymbolHandle -> NNUInt -> IO (Int, SymbolHandle)
- nnSymbolCompose :: SymbolHandle -> String -> [String] -> [SymbolHandle] -> IO Int
- nnGraphCreate :: SymbolHandle -> IO (Int, GraphHandle)
- nnGraphFree :: GraphHandle -> IO Int
- nnGraphGetSymbol :: GraphHandle -> IO (Int, SymbolHandle)
- nnGraphSetJSONAttr :: GraphHandle -> String -> String -> IO Int
- nnGraphGetJSONAttr :: SymbolHandle -> String -> IO (Int, String, Int)
- nnGraphSetNodeEntryListAttr_ :: GraphHandle -> String -> SymbolHandle -> IO Int
- nnGraphApplyPasses :: GraphHandle -> NNUInt -> [String] -> IO (Int, GraphHandle)
Re-export data type definitions
data SymbolHandle Source #
Handle to a symbol that can be bind as operator.
Re-export functions.
nnAPISetLastError :: String -> IO () Source #
Set the last error message needed by C API.
nnGetLastError :: IO String Source #
Return str message of the last error.
nnListAllOpNames :: IO (Int, [String]) Source #
List all the available operator names, include entries.
Get operator handle given name.
nnGetOpInfo :: OpHandle -> IO (Int, String, String, NNUInt, [String], [String], [String], String) Source #
Get the detailed information about atomic symbol.
nnSymbolCreateAtomicSymbol Source #
:: OpHandle | The operator handle. |
-> NNUInt | The number of parameters. |
-> [String] | The keys to the params. |
-> [String] | The values to the params. |
-> IO (Int, SymbolHandle) |
Create an AtomicSymbol functor.
nnSymbolCreateVariable Source #
:: String | The name of the variable. |
-> IO (Int, SymbolHandle) |
Create a Variable Symbol.
:: NNUInt | Number of symbols to be grouped. |
-> [SymbolHandle] | Array of symbol handles. |
-> IO (Int, SymbolHandle) |
Create a Symbol by grouping list of symbols together.
:: SymbolHandle | The symbol to add dependency edges on. |
-> SymbolHandle | The source handles. |
-> IO Int |
Add src_dep to the handle as control dep.
nnSymbolFree :: SymbolHandle -> IO Int Source #
Free the symbol handle.
nnSymbolCopy :: SymbolHandle -> IO (Int, SymbolHandle) Source #
Copy the symbol to another handle.
nnSymbolPrint :: SymbolHandle -> IO (Int, String) Source #
Print the content of symbol, used for debug.
Get string attribute from symbol.
Set string attribute from symbol.
nnSymbolListAttrs :: SymbolHandle -> Int -> IO (Int, [String]) Source #
Get all attributes from symbol, including all descendents.
nnSymbolListInputVariables :: SymbolHandle -> Int -> IO (Int, [SymbolHandle]) Source #
List inputs variables in the symbol.
nnSymbolListInputNames :: SymbolHandle -> Int -> IO (Int, [String]) Source #
List input names in the symbol.
nnSymbolListOutputNames :: SymbolHandle -> IO (Int, [String]) Source #
List returns names in the symbol.
nnSymbolGetInternals :: SymbolHandle -> IO (Int, SymbolHandle) Source #
Get a symbol that contains all the internals.
nnSymbolGetOutput :: SymbolHandle -> NNUInt -> IO (Int, SymbolHandle) Source #
Get index-th outputs of the symbol.
:: SymbolHandle | Creator/Handler of the OP. |
-> String | |
-> [String] | |
-> [SymbolHandle] | |
-> IO Int |
Invoke a nnvm op and imperative function.
nnGraphCreate :: SymbolHandle -> IO (Int, GraphHandle) Source #
Create a graph handle from symbol.
nnGraphFree :: GraphHandle -> IO Int Source #
Free the graph handle.
:: GraphHandle | the graph handle. |
-> IO (Int, SymbolHandle) |
Get a new symbol from the graph.
nnGraphSetJSONAttr :: GraphHandle -> String -> String -> IO Int Source #
Get Set a attribute in json format.
nnGraphGetJSONAttr :: SymbolHandle -> String -> IO (Int, String, Int) Source #
Get a serialized attrirbute from graph.
nnGraphSetNodeEntryListAttr_ :: GraphHandle -> String -> SymbolHandle -> IO Int Source #
Set a attribute whose type is std::vectorNodeEntry in c++.
nnGraphApplyPasses :: GraphHandle -> NNUInt -> [String] -> IO (Int, GraphHandle) Source #
Apply passes on the src graph.