menoh-0.1.1: 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 makeModelDataFromONNX.
  1. Specify input variable type/dimentions (in particular batch size) and which output variables you want to retrieve. These information is represented as VariableProfileTable. Simple way to construct VariableProfileTable is to use makeVariableProfileTable.
  2. Optimize ModelData with respect to your VariableProfileTable by using optimizeModelData.
  3. 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.
  4. Load input data. This can be done conveniently using writeBufferFromVector or writeBufferFromStorableVector. There are also more low-level API such as unsafeGetBuffer and withBuffer.
  5. Run inference using run.
  6. Retrieve the result data. This can be done conveniently using readBufferToVector or readBufferToStorableVector.

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

class Storable a => HasDType a where Source #

Haskell types that have associated DType type code.

Minimal complete definition

dtypeOf

Methods

dtypeOf :: Proxy a -> DType Source #

ModelData type

newtype ModelData Source #

ModelData contains model parameters and computation graph structure.

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

Load onnx file and make ModelData.

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

Optimize function for ModelData.

This function modify given ModelData.

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.

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.

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

Copy whole elements of Vector into a model's buffer

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

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 #

Read whole elements of Array and return as a Vector.

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

Read whole eleemnts of Array and return as a Vector Float.

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

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

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

input names with dtypes and dims

-> [(String, DType)]

required output name list with dtypes

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

Builder for VariableProfileTable

addInputProfileDims2 Source #

Arguments

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

(num, size)

-> m () 

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 () 

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

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

Add output profile

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

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.