hasktorch-0.2.1.3: Haskell bindings to libtorch, supporting both typed and untyped tensors.
Safe HaskellNone
LanguageHaskell2010

Torch.Script

Synopsis

Documentation

newtype ScriptModule Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Castable ScriptModule (ForeignPtr Module) Source #
Instance details

Defined in Torch.Script

Methods

cast :: ScriptModule -> (ForeignPtr Module -> IO r) -> IO r

uncast :: ForeignPtr Module -> (ScriptModule -> IO r) -> IO r

Instance details

Defined in Torch.Script

newtype RawModule Source #

Constructors

Instances

Instances details
Castable RawModule (ForeignPtr Module) Source #
Instance details

Defined in Torch.Script

Methods

cast :: RawModule -> (ForeignPtr Module -> IO r) -> IO r

uncast :: ForeignPtr Module -> (RawModule -> IO r) -> IO r

type RawIValue = ForeignPtr IValue Source #

newtype Blob Source #

Constructors

UnsafeBlob (ForeignPtr (C10Ptr Blob))

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> Blob -> ShowS #

show :: Blob -> String #

showList :: [Blob] -> ShowS #

newtype Object Source #

Constructors

UnsafeObject (ForeignPtr (C10Ptr IVObject))

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> Object -> ShowS #

show :: Object -> String #

showList :: [Object] -> ShowS #

newtype Future Source #

Constructors

UnsafeFuture (ForeignPtr (C10Ptr IVFuture))

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> Future -> ShowS #

show :: Future -> String #

showList :: [Future] -> ShowS #

newtype Capsule Source #

Constructors

UnsafeCapsule (ForeignPtr (C10Ptr Capsule))

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> Capsule -> ShowS #

show :: Capsule -> String #

showList :: [Capsule] -> ShowS #

newtype Graph Source #

See https://github.com/pytorch/pytorch/wiki/PyTorch-IR

Constructors

UnsafeGraph (ForeignPtr (SharedPtr JitGraph))

Instances

Instances details
Castable Graph (ForeignPtr (SharedPtr JitGraph)) Source #
Instance details

Defined in Torch.Script

Methods

cast :: Graph -> (ForeignPtr (SharedPtr JitGraph) -> IO r) -> IO r

uncast :: ForeignPtr (SharedPtr JitGraph) -> (Graph -> IO r) -> IO r

data JitGraph Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Instance details

Defined in Torch.Script

Methods

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

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

data JitNode Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> JitNode -> ShowS #

show :: JitNode -> String #

showList :: [JitNode] -> ShowS #

Instance details

Defined in Torch.Script

Methods

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

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

data JitValue Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Instance details

Defined in Torch.Script

Methods

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

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

data IValue Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Methods

showsPrec :: Int -> IValue -> ShowS #

show :: IValue -> String #

showList :: [IValue] -> ShowS #

Instance details

Defined in Torch.Script

Methods

cast :: IValue -> (RawIValue -> IO r) -> IO r

uncast :: RawIValue -> (IValue -> IO r) -> IO r

Instance details

Defined in Torch.Script

Castable [IValue] [RawIValue] Source #
Instance details

Defined in Torch.Script

Methods

cast :: [IValue] -> ([RawIValue] -> IO r) -> IO r

uncast :: [RawIValue] -> ([IValue] -> IO r) -> IO r

newModule :: String -> IO RawModule Source #

saveScript :: ScriptModule -> FilePath -> IO () Source #

saveScript' :: RawModule -> FilePath -> IO () Source #

data LoadMode Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Instance details

Defined in Torch.Script

Methods

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

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

loadScript :: LoadMode -> FilePath -> IO ScriptModule Source #

Load a torchscript file

loadScript' :: FilePath -> IO RawModule Source #

registerParameter :: RawModule -> String -> Tensor -> Bool -> IO () Source #

registerModule :: RawModule -> String -> RawModule -> IO () Source #

getParameters Source #

Arguments

:: ScriptModule

module

-> [Tensor]

output

getParametersIO Source #

Arguments

:: RawModule

module

-> IO [Tensor]

output

setParameters :: RawModule -> [Tensor] -> IO () Source #

updateParameters :: LoadMode -> ScriptModule -> [Tensor] -> ScriptModule Source #

getNamedParameters Source #

Arguments

:: ScriptModule

module

-> [(String, Tensor)]

output

getNamedBuffers Source #

Arguments

:: ScriptModule

module

-> [(String, Tensor)]

output

getNamedAttributes Source #

Arguments

:: ScriptModule

module

-> [(String, IValue)]

output

Load all attributes including training flags This function returns IVObject type as Tensor type. To get Tensor type, use get getNamedParameters and getNamedBuffers.

getNamedModules Source #

Arguments

:: ScriptModule

module

-> [(String, ScriptModule)]

output

getNamedChildren Source #

Arguments

:: ScriptModule

module

-> [(String, ScriptModule)]

output

toScriptModule :: RawModule -> IO ScriptModule Source #

toRawModule :: ScriptModule -> IO RawModule Source #

cloneRawModule :: RawModule -> IO RawModule Source #

data RuntimeMode Source #

Constructors

Instances

Instances details
Instance details

Defined in Torch.Script

Instance details

Defined in Torch.Script

setRuntimeMode :: RawModule -> RuntimeMode -> IO () Source #

define :: RawModule -> String -> IO () Source #

dumpToStr Source #

Arguments

:: ScriptModule

module

-> Bool

print_method_bodies

-> Bool

print_attr_values

-> Bool

print_param_values

-> IO String

ouput

dumpToStr' :: ScriptModule -> IO String Source #

runMethod Source #

Arguments

:: ScriptModule

module

-> String

func

-> [IValue]

inputs

-> IValue

output

runMethod1 Source #

Arguments

:: ScriptModule

module

-> String

func

-> IValue

inputs

-> IValue

output

trace Source #

Arguments

:: String

moduleName

-> String

functionName

-> ([Tensor] -> IO [Tensor])

function

-> [Tensor]

inputs

-> IO RawModule

output

traceWithParameters Source #

Arguments

=> String

module name

-> (f -> [Tensor] -> IO [Tensor])

traced function

-> f

initial parameters

-> [Tensor]

example inputs

-> IO RawModule

torchscript module

This function generates torchscript-module from Parameterized-instance of hasktorch. Usage is below. -- >> let example_inputs = asTensor (4::Float) -- >> init_parameters <- sample MonoSpec -- >> mutableTorchscript <- traceWithParameters MyModule -- (parameters [example_inputs'] -> return [(traced_function parameters example_inputs')]) -- init_parameters -- [example_inputs] -- >> immutableTorchscript <- toScriptModule mutableTorchscript -- >> save immutableTorchscript "torchscript file"

traceAsGraph Source #

Arguments

:: ([Tensor] -> IO [Tensor])

function

-> [Tensor]

inputs

-> IO Graph

output

printGraph :: Graph -> IO String Source #

printOnnx :: Graph -> IO String Source #

Output onnx file from graph. (really experimental implementation) printOnnx uses export_onnx function of libtorch. It outputs following error, because prim::Constant symbol using torchscript does not exist. -- Exception: ONNX export failed: Couldn't export operator prim::Constant -- Defined at: -- Graph we tried to export: -- graph(%0 : Float(), -- %1 : Float()): -- %2 : int = prim::Constant[value=1]() -- %3 : Float() = aten::add(%0, %1, %2) -- return (%3) -- ; type: std::runtime_error On the other hand, torch.onnx.export of python works. onnx's symbol map is in python code. https://github.com/pytorch/pytorch/blob/master/torch/onnx/symbolic_opset9.py

If you need onnx-file, at first make torchscript by trace , then convert torchscript into onnx by python-code.

graphToJitGraph :: Graph -> IO JitGraph Source #

AltStyle によって変換されたページ (->オリジナル) /