| Copyright | Copyright (c) 2018 Preferred Networks Inc. |
|---|---|
| License | MIT (see the file LICENSE) |
| Maintainer | Masahiro Sakai <sakai@preferred.jp> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Menoh
Contents
Description
Haskell binding for Menoh DNN inference library.
Basic usage
- Load computation graph from ONNX file using
makeModelDataFromONNX.
- 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 constructVariableProfileTableis to usemakeVariableProfileTable. - Optimize
ModelDatawith respect to yourVariableProfileTableby usingoptimizeModelData. - Construct a
ModelusingmakeModelormakeModelWithConfig. If you want to use custom buffers instead of internally allocated ones, You need to use more low levelModelBuilder. - Load input data. This can be done conveniently using
writeBufferFromVectororwriteBufferFromStorableVector. There are also more low-level API such asunsafeGetBufferandwithBuffer. - Run inference using
run. - Retrieve the result data. This can be done conveniently using
readBufferToVectororreadBufferToStorableVector.
- type Dims = [Int]
- data DType
- class Storable a => HasDType a where
- data Error
- = ErrorStdError String
- | ErrorUnknownError String
- | ErrorInvalidFilename String
- | ErrorONNXParseError String
- | ErrorInvalidDType String
- | ErrorInvalidAttributeType String
- | ErrorUnsupportedOperatorAttribute String
- | ErrorDimensionMismatch String
- | ErrorVariableNotFound String
- | ErrorIndexOutOfRange String
- | ErrorJSONParseError String
- | ErrorInvalidBackendName String
- | ErrorUnsupportedOperator String
- | ErrorFailedToConfigureOperator String
- | ErrorBackendError String
- | ErrorSameNamedVariableAlreadyExist String
- newtype ModelData = ModelData (ForeignPtr MenohModelData)
- makeModelDataFromONNX :: MonadIO m => FilePath -> m ModelData
- optimizeModelData :: MonadIO m => ModelData -> VariableProfileTable -> m ()
- newtype Model = Model (ForeignPtr MenohModel)
- makeModel :: MonadIO m => VariableProfileTable -> ModelData -> String -> m Model
- makeModelWithConfig :: (MonadIO m, ToJSON a) => VariableProfileTable -> ModelData -> String -> a -> m Model
- run :: MonadIO m => Model -> m ()
- getDType :: MonadIO m => Model -> String -> m DType
- getDims :: MonadIO m => Model -> String -> m Dims
- unsafeGetBuffer :: MonadIO m => Model -> String -> m (Ptr a)
- withBuffer :: forall m r a. (MonadIO m, MonadBaseControl IO m) => Model -> String -> (Ptr a -> m r) -> m r
- writeBufferFromVector :: forall v a m. (Vector v a, HasDType a, MonadIO m) => Model -> String -> v a -> m ()
- writeBufferFromStorableVector :: forall a m. (HasDType a, MonadIO m) => Model -> String -> Vector a -> m ()
- readBufferToVector :: forall v a m. (Vector v a, HasDType a, MonadIO m) => Model -> String -> m (v a)
- readBufferToStorableVector :: forall a m. (HasDType a, MonadIO m) => Model -> String -> m (Vector a)
- version :: Version
- bindingVersion :: Version
- newtype VariableProfileTable = VariableProfileTable (ForeignPtr MenohVariableProfileTable)
- makeVariableProfileTable :: MonadIO m => [(String, DType, Dims)] -> [(String, DType)] -> ModelData -> m VariableProfileTable
- vptGetDType :: MonadIO m => VariableProfileTable -> String -> m DType
- vptGetDims :: MonadIO m => VariableProfileTable -> String -> m Dims
- newtype VariableProfileTableBuilder = VariableProfileTableBuilder (ForeignPtr MenohVariableProfileTableBuilder)
- makeVariableProfileTableBuilder :: MonadIO m => m VariableProfileTableBuilder
- addInputProfileDims2 :: MonadIO m => VariableProfileTableBuilder -> String -> DType -> (Int, Int) -> m ()
- addInputProfileDims4 :: MonadIO m => VariableProfileTableBuilder -> String -> DType -> (Int, Int, Int, Int) -> m ()
- addOutputProfile :: MonadIO m => VariableProfileTableBuilder -> String -> DType -> m ()
- buildVariableProfileTable :: MonadIO m => VariableProfileTableBuilder -> ModelData -> m VariableProfileTable
- newtype ModelBuilder = ModelBuilder (ForeignPtr MenohModelBuilder)
- makeModelBuilder :: MonadIO m => VariableProfileTable -> m ModelBuilder
- attachExternalBuffer :: MonadIO m => ModelBuilder -> String -> Ptr a -> m ()
- buildModel :: MonadIO m => ModelBuilder -> ModelData -> String -> m Model
- buildModelWithConfig :: (MonadIO m, ToJSON a) => ModelBuilder -> ModelData -> String -> a -> m Model
Basic data types
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
Functions in this module can throw this exception type.
Constructors
ModelData type
ModelData contains model parameters and computation graph structure.
Constructors
| ModelData (ForeignPtr MenohModelData) |
makeModelDataFromONNX :: MonadIO m => FilePath -> m ModelData Source #
Load onnx file and make ModelData.
optimizeModelData :: MonadIO m => ModelData -> VariableProfileTable -> m () Source #
Model type
Arguments
| :: MonadIO m | |
| => VariableProfileTable | variable profile table |
| -> ModelData | model data |
| -> String | backend name |
| -> m Model |
Convenient methods for constructing a Model.
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.
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 into a model's bufferVector a
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 #
Misc
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.
Constructors
| VariableProfileTable (ForeignPtr MenohVariableProfileTable) |
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
newtype VariableProfileTableBuilder Source #
Builder for creation of VariableProfileTable.
makeVariableProfileTableBuilder :: MonadIO m => m VariableProfileTableBuilder Source #
Factory function for VariableProfileTableBuilder.
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.
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.
buildVariableProfileTable :: MonadIO m => VariableProfileTableBuilder -> ModelData -> m VariableProfileTable Source #
Factory function for VariableProfileTable
Builder for Model
newtype ModelBuilder Source #
Helper for creating of Model.
Constructors
| ModelBuilder (ForeignPtr MenohModelBuilder) |
makeModelBuilder :: MonadIO m => VariableProfileTable -> m ModelBuilder Source #
Factory function for ModelBuilder
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.
Arguments
| :: MonadIO m | |
| => ModelBuilder | |
| -> ModelData | |
| -> String | backend name |
| -> m Model |
Factory function for Model.
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.