menoh-0.3.0: Haskell binding for Menoh DNN inference library

CopyrightCopyright (c) 2018 Preferred Networks Inc.
LicenseMIT (see the file LICENSE)
MaintainerMasahiro Sakai <sakai@preferred.jp>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Menoh

Contents

Description

Haskell binding for Menoh DNN inference library.

Basic usage

  1. Load computation graph from ONNX file using makeModelDataFromONNXFile.
  2. Specify input variable type/dimentions (in particular batch size) and which output variables you want to retrieve. This can be done by constructing VariableProfileTable using makeVariableProfileTable.
  3. Optimize ModelData with respect to your VariableProfileTable by using optimizeModelData.
  4. Construct a Model using makeModel or makeModelWithConfig. If you want to use custom buffers instead of internally allocated ones, You need to use more low level ModelBuilder.
  5. Load input data. This can be done conveniently using writeBuffer. There are also more low-level API such as unsafeGetBuffer and withBuffer.
  6. Run inference using run.
  7. Retrieve the result data. This can be done conveniently using readBuffer.

Note on thread safety

TL;DR: If you want to use Menoh from multiple haskell threads, you need to use threaded RTS by supplying -threaded option to GHC.

Menoh uses thread local storage (TLS) for storing error information, and the only way to use TLS safely is to use in bound threads (see Control.Concurrent).

  • In threaded RTS (i.e. rtsSupportsBoundThreads is True), this module runs computation in bound threads by using runInBoundThread. (If the calling thread is not bound, runInBoundThread create a bound thread temporarily and run the computation inside it).
  • In non-threaded RTS, this module does not use runInBoundThread and is therefore unsafe to use from multiple haskell threads. Using non-threaded RTS is allowed for the sake of convenience (e.g. running in GHCi) despite its unsafety.
Synopsis

Basic data types

type Dims = [Int] Source #

Dimensions of array

data DType Source #

Data type of array elements

Constructors

DTypeFloat

single precision floating point number

DTypeUnknown !MenohDType

types that this binding is unware of

Instances
Enum DType Source # 
Instance details

Defined in Menoh

Eq DType Source # 
Instance details

Defined in Menoh

Methods

(==) :: DType -> DType -> Bool #

(/=) :: DType -> DType -> Bool #

Ord DType Source # 
Instance details

Defined in Menoh

Methods

compare :: DType -> DType -> Ordering #

(<) :: DType -> DType -> Bool #

(<=) :: DType -> DType -> Bool #

(>) :: DType -> DType -> Bool #

(>=) :: DType -> DType -> Bool #

max :: DType -> DType -> DType #

min :: DType -> DType -> DType #

Read DType Source # 
Instance details

Defined in Menoh

Show DType Source # 
Instance details

Defined in Menoh

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

AddOutput (String, DType) Source # 
Instance details

Defined in Menoh

data Error Source #

Functions in this module can throw this exception type.

Instances
Eq Error Source # 
Instance details

Defined in Menoh

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Ord Error Source # 
Instance details

Defined in Menoh

Methods

compare :: Error -> Error -> Ordering #

(<) :: Error -> Error -> Bool #

(<=) :: Error -> Error -> Bool #

(>) :: Error -> Error -> Bool #

(>=) :: Error -> Error -> Bool #

max :: Error -> Error -> Error #

min :: Error -> Error -> Error #

Read Error Source # 
Instance details

Defined in Menoh

Show Error Source # 
Instance details

Defined in Menoh

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Exception Error Source # 
Instance details

Defined in Menoh

ModelData type

newtype ModelData Source #

ModelData contains model parameters and computation graph structure.

makeModelDataFromONNX :: MonadIO m => FilePath -> m ModelData Source #

Deprecated: use makeModelDataFromONNXFile instead

Load onnx file and make ModelData.

optimizeModelData :: MonadIO m => ModelData -> VariableProfileTable -> m () Source #

Optimize function for ModelData.

This function modify given ModelData.

Manual model data construction API

addParameterFromPtr :: MonadIO m => ModelData -> String -> DType -> Dims -> Ptr a -> m () Source #

Add a new parameter in ModelData

This API is tentative and will be changed in the future.

Duplication of parameter_name is not allowed and it throws error.

addNewNode :: MonadIO m => ModelData -> String -> m () Source #

Add a new node to ModelData

addInputNameToCurrentNode :: MonadIO m => ModelData -> String -> m () Source #

Add a new input name to latest added node in ModelData

addOutputNameToCurrentNode :: MonadIO m => ModelData -> String -> m () Source #

Add a new output name to latest added node in ModelData

class AttributeType value where Source #

A class of types that can be added to nodes using addAttribute.

Minimal complete definition

basicAddAttribute

Methods

basicAddAttribute :: Ptr MenohModelData -> CString -> value -> IO () Source #

Instances
AttributeType Float Source # 
Instance details

Defined in Menoh

AttributeType Int Source # 
Instance details

Defined in Menoh

AttributeType [Float] Source # 
Instance details

Defined in Menoh

AttributeType [Int] Source # 
Instance details

Defined in Menoh

addAttribute :: (AttributeType value, MonadIO m) => ModelData -> String -> value -> m () Source #

Add a new attribute to latest added node in model_data

VariableProfileTable

newtype VariableProfileTable Source #

VariableProfileTable contains information of dtype and dims of variables.

Users can access to dtype and dims via vptGetDType and vptGetDims.

makeVariableProfileTable Source #

Arguments

:: (AddOutput a, MonadIO m) 
=> [(String, DType, Dims)]

input names with dtypes and dims

-> [a]

required output informations (String or (String, DType))

-> ModelData

model data

-> m VariableProfileTable 

Convenient function for constructing VariableProfileTable.

If you need finer control, you can use VariableProfileTableBuidler.

vptGetDType :: MonadIO m => VariableProfileTable -> String -> m DType Source #

Accessor function for VariableProfileTable

Select variable name and get its DType.

vptGetDims :: MonadIO m => VariableProfileTable -> String -> m Dims Source #

Accessor function for VariableProfileTable

Select variable name and get its Dims.

Model type

newtype Model Source #

ONNX model with input/output buffers

Constructors

Model (ForeignPtr MenohModel) 

makeModel Source #

Arguments

:: MonadIO m 
=> VariableProfileTable

variable profile table

-> ModelData

model data

-> String

backend name

-> m Model 

Convenient methods for constructing a Model.

makeModelWithConfig Source #

Arguments

:: (MonadIO m, ToJSON a) 
=> VariableProfileTable

variable profile table

-> ModelData

model data

-> String

backend name

-> a

backend config

-> m Model 

Similar to makeModel but backend-specific configuration can be supplied.

run :: MonadIO m => Model -> m () Source #

Run model inference.

This function can't be called asynchronously.

getDType :: MonadIO m => Model -> String -> m DType Source #

Get DType of target variable.

getDims :: MonadIO m => Model -> String -> m Dims Source #

Get Dims of target variable.

Accessors for buffers

class ToBuffer a where Source #

Type that can be written to menoh's buffer.

Minimal complete definition

basicWriteBuffer

Methods

basicWriteBuffer :: DType -> Dims -> Ptr () -> a -> IO () Source #

Instances
ToBuffer a => ToBuffer [a] Source # 
Instance details

Defined in Menoh

Methods

basicWriteBuffer :: DType -> Dims -> Ptr () -> [a] -> IO () Source #

ToBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicWriteBuffer :: DType -> Dims -> Ptr () -> Vector Float -> IO () Source #

ToBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicWriteBuffer :: DType -> Dims -> Ptr () -> Vector Float -> IO () Source #

ToBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicWriteBuffer :: DType -> Dims -> Ptr () -> Vector Float -> IO () Source #

class FromBuffer a where Source #

Type that can be read from menoh's buffer.

Minimal complete definition

basicReadBuffer

Methods

basicReadBuffer :: DType -> Dims -> Ptr () -> IO a Source #

Instances
FromBuffer a => FromBuffer [a] Source # 
Instance details

Defined in Menoh

Methods

basicReadBuffer :: DType -> Dims -> Ptr () -> IO [a] Source #

FromBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicReadBuffer :: DType -> Dims -> Ptr () -> IO (Vector Float) Source #

FromBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicReadBuffer :: DType -> Dims -> Ptr () -> IO (Vector Float) Source #

FromBuffer (Vector Float) Source # 
Instance details

Defined in Menoh

Methods

basicReadBuffer :: DType -> Dims -> Ptr () -> IO (Vector Float) Source #

writeBuffer :: (ToBuffer a, MonadIO m) => Model -> String -> a -> m () Source #

Write values to the given model's buffer

readBuffer :: (FromBuffer a, MonadIO m) => Model -> String -> m a Source #

Read values from the given model's buffer

Low-level accessors for buffers

unsafeGetBuffer :: MonadIO m => Model -> String -> m (Ptr a) Source #

Get a buffer handle attached to target variable.

Users can get a buffer handle attached to target variable. If that buffer is allocated by users and attached to the variable by calling attachExternalBuffer, returned buffer handle is same to it.

This function is unsafe because it does not prevent the model to be GC'ed and the returned pointer become dangling pointer.

See also withBuffer.

withBuffer :: forall m r a. (MonadIO m, MonadBaseControl IO m) => Model -> String -> (Ptr a -> m r) -> m r Source #

This function takes a function which is applied to the buffer associated to specified variable. The resulting action is then executed. The buffer is kept alive at least during the whole action, even if it is not used directly inside. Note that it is not safe to return the pointer from the action and use it after the action completes.

See also unsafeGetBuffer.

Deprecated accessors for buffers

class Storable a => HasDType a where Source #

Deprecated: use FromBuffer/ToBuffer instead

Haskell types that have associated DType type code.

Minimal complete definition

dtypeOf

Methods

dtypeOf :: Proxy a -> DType Source #

Instances
HasDType Float Source # 
Instance details

Defined in Menoh

HasDType CFloat Source # 
Instance details

Defined in Menoh

writeBufferFromVector :: forall v a m. (Vector v a, HasDType a, MonadIO m) => Model -> String -> v a -> m () Source #

Deprecated: Use ToBuffer class and writeBuffer instead

Copy whole elements of Vector into a model's buffer

writeBufferFromStorableVector :: forall a m. (HasDType a, MonadIO m) => Model -> String -> Vector a -> m () Source #

Deprecated: Use ToBuffer class and writeBuffer instead

Copy whole elements of Vector a into a model's buffer

readBufferToVector :: forall v a m. (Vector v a, HasDType a, MonadIO m) => Model -> String -> m (v a) Source #

Deprecated: Use FromBuffer class and readBuffer instead

Read whole elements of Array and return as a Vector.

readBufferToStorableVector :: forall a m. (HasDType a, MonadIO m) => Model -> String -> m (Vector a) Source #

Deprecated: Use FromBuffer class and readBuffer instead

Read whole eleemnts of Array and return as a Vector.

Misc

version :: Version Source #

Menoh version which was supplied on compilation time via CPP macro.

bindingVersion :: Version Source #

Version of this Haskell binding. (Not the version of Menoh itself)

Low-level API

Builder for VariableProfileTable

addInputProfileDims2 Source #

Arguments

:: MonadIO m 
=> VariableProfileTableBuilder 
-> String 
-> DType 
-> (Int, Int)

(num, size)

-> m () 

Deprecated: use addInputProfileDims instead

Add 2D input profile.

Input profile contains name, dtype and dims (num, size). This 2D input is conventional batched 1D inputs.

addInputProfileDims4 Source #

Arguments

:: MonadIO m 
=> VariableProfileTableBuilder 
-> String 
-> DType 
-> (Int, Int, Int, Int)

(num, channel, height, width)

-> m () 

Deprecated: use addInputProfileDims instead

Add 4D input profile

Input profile contains name, dtype and dims (num, channel, height, width). This 4D input is conventional batched image inputs. Image input is 3D (channel, height, width).

addOutputName :: MonadIO m => VariableProfileTableBuilder -> String -> m () Source #

Add output name

Output profile contains name and dtype. Its Dims and DType are calculated automatically, so that you don't need to specify explicitly.

addOutputProfile :: MonadIO m => VariableProfileTableBuilder -> String -> DType -> m () Source #

Deprecated: use addOutputName instead

Add output profile

Output profile contains name and dtype. Its Dims are calculated automatically, so that you don't need to specify explicitly.

class AddOutput a where Source #

Type class for abstracting addOutputProfile and addOutputName.

Minimal complete definition

addOutput

Instances
AddOutput String Source # 
Instance details

Defined in Menoh

AddOutput (String, DType) Source # 
Instance details

Defined in Menoh

Builder for Model

newtype ModelBuilder Source #

Helper for creating of Model.

attachExternalBuffer :: MonadIO m => ModelBuilder -> String -> Ptr a -> m () Source #

Attach a buffer which allocated by users.

Users can attach a external buffer which they allocated to target variable.

Variables attached no external buffer are attached internal buffers allocated automatically.

Users can get that internal buffer handle by calling unsafeGetBuffer etc. later.

buildModel Source #

Arguments

:: MonadIO m 
=> ModelBuilder 
-> ModelData 
-> String

backend name

-> m Model 

Factory function for Model.

buildModelWithConfig Source #

Arguments

:: (MonadIO m, ToJSON a) 
=> ModelBuilder 
-> ModelData 
-> String

backend name

-> a

backend config

-> m Model 

Similar to buildModel, but backend specific configuration can be supplied as JSON.