{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
module Torch.Internal.Managed.Type.IValue where
import Foreign.C.String
import Foreign.C.Types
import Foreign
import Torch.Internal.Type
import Torch.Internal.Class
import Torch.Internal.Cast
import Torch.Internal.Objects
import qualified Torch.Internal.Unmanaged.Type.IValue as Unmanaged
import Torch.Internal.Unmanaged.Type.IValue (IValueLike)
instance IValueLike Double (ForeignPtr IValue) where
toIValue :: Double -> IO (ForeignPtr IValue)
toIValue Double
x = (CDouble -> IO (Ptr IValue)) -> Double -> IO (ForeignPtr IValue)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (CDouble -> IO (Ptr IValue)
forall a b. IValueLike a b => a -> IO b
Unmanaged.toIValue :: CDouble -> IO (Ptr IValue)) Double
x
fromIValue :: ForeignPtr IValue -> IO Double
fromIValue ForeignPtr IValue
x = (Ptr IValue -> IO CDouble) -> ForeignPtr IValue -> IO Double
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Ptr IValue -> IO CDouble
forall a b. IValueLike a b => b -> IO a
Unmanaged.fromIValue :: Ptr IValue -> IO CDouble) ForeignPtr IValue
x
instance IValueLike Int64 (ForeignPtr IValue) where
toIValue :: Int64 -> IO (ForeignPtr IValue)
toIValue Int64
x = (Int64 -> IO (Ptr IValue)) -> Int64 -> IO (ForeignPtr IValue)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Int64 -> IO (Ptr IValue)
forall a b. IValueLike a b => a -> IO b
Unmanaged.toIValue :: Int64 -> IO (Ptr IValue)) Int64
x
fromIValue :: ForeignPtr IValue -> IO Int64
fromIValue ForeignPtr IValue
x = (Ptr IValue -> IO Int64) -> ForeignPtr IValue -> IO Int64
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Ptr IValue -> IO Int64
forall a b. IValueLike a b => b -> IO a
Unmanaged.fromIValue :: Ptr IValue -> IO Int64) ForeignPtr IValue
x
instance IValueLike Bool (ForeignPtr IValue) where
toIValue :: Bool -> IO (ForeignPtr IValue)
toIValue Bool
x = (CBool -> IO (Ptr IValue)) -> Bool -> IO (ForeignPtr IValue)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (CBool -> IO (Ptr IValue)
forall a b. IValueLike a b => a -> IO b
Unmanaged.toIValue :: CBool -> IO (Ptr IValue)) Bool
x
fromIValue :: ForeignPtr IValue -> IO Bool
fromIValue ForeignPtr IValue
x = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO Bool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Ptr IValue -> IO CBool
forall a b. IValueLike a b => b -> IO a
Unmanaged.fromIValue :: Ptr IValue -> IO CBool) ForeignPtr IValue
x
instance (CppObject a, IValueLike (Ptr a) (Ptr IValue)) => IValueLike (ForeignPtr a) (ForeignPtr IValue) where
toIValue :: ForeignPtr a -> IO (ForeignPtr IValue)
toIValue ForeignPtr a
x = (Ptr a -> IO (Ptr IValue))
-> ForeignPtr a -> IO (ForeignPtr IValue)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Ptr a -> IO (Ptr IValue)
forall a b. IValueLike a b => a -> IO b
Unmanaged.toIValue :: Ptr a -> IO (Ptr IValue)) ForeignPtr a
x
fromIValue :: ForeignPtr IValue -> IO (ForeignPtr a)
fromIValue ForeignPtr IValue
x = (Ptr IValue -> IO (Ptr a))
-> ForeignPtr IValue -> IO (ForeignPtr a)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (Ptr IValue -> IO (Ptr a)
forall a b. IValueLike a b => b -> IO a
Unmanaged.fromIValue :: Ptr IValue -> IO (Ptr a)) ForeignPtr IValue
x
newIValue
:: IO (ForeignPtr IValue)
newIValue :: IO (ForeignPtr IValue)
newIValue = IO (Ptr IValue) -> IO (ForeignPtr IValue)
forall a ca. Castable a ca => IO ca -> IO a
_cast0 IO (Ptr IValue)
Unmanaged.newIValue
iValue_isAliasOf_V
:: ForeignPtr IValue
-> ForeignPtr IValue
-> IO (CBool)
iValue_isAliasOf_V :: ForeignPtr IValue -> ForeignPtr IValue -> IO CBool
iValue_isAliasOf_V = (Ptr IValue -> Ptr IValue -> IO CBool)
-> ForeignPtr IValue -> ForeignPtr IValue -> IO CBool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
_cast2 Ptr IValue -> Ptr IValue -> IO CBool
Unmanaged.iValue_isAliasOf_V
iValue_use_count
:: ForeignPtr IValue
-> IO (CSize)
iValue_use_count :: ForeignPtr IValue -> IO CSize
iValue_use_count = (Ptr IValue -> IO CSize) -> ForeignPtr IValue -> IO CSize
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CSize
Unmanaged.iValue_use_count
iValue_swap_V
:: ForeignPtr IValue
-> ForeignPtr IValue
-> IO (())
iValue_swap_V :: ForeignPtr IValue -> ForeignPtr IValue -> IO ()
iValue_swap_V = (Ptr IValue -> Ptr IValue -> IO ())
-> ForeignPtr IValue -> ForeignPtr IValue -> IO ()
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
_cast2 Ptr IValue -> Ptr IValue -> IO ()
Unmanaged.iValue_swap_V
iValue_isTensor
:: ForeignPtr IValue
-> IO (CBool)
iValue_isTensor :: ForeignPtr IValue -> IO CBool
iValue_isTensor = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isTensor
iValue_isBlob
:: ForeignPtr IValue
-> IO (CBool)
iValue_isBlob :: ForeignPtr IValue -> IO CBool
iValue_isBlob = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isBlob
iValue_isCapsule
:: ForeignPtr IValue
-> IO (CBool)
iValue_isCapsule :: ForeignPtr IValue -> IO CBool
iValue_isCapsule = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isCapsule
iValue_isTuple
:: ForeignPtr IValue
-> IO (CBool)
iValue_isTuple :: ForeignPtr IValue -> IO CBool
iValue_isTuple = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isTuple
iValue_isDouble
:: ForeignPtr IValue
-> IO (CBool)
iValue_isDouble :: ForeignPtr IValue -> IO CBool
iValue_isDouble = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isDouble
iValue_isFuture
:: ForeignPtr IValue
-> IO (CBool)
iValue_isFuture :: ForeignPtr IValue -> IO CBool
iValue_isFuture = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isFuture
iValue_isInt
:: ForeignPtr IValue
-> IO (CBool)
iValue_isInt :: ForeignPtr IValue -> IO CBool
iValue_isInt = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isInt
iValue_isIntList
:: ForeignPtr IValue
-> IO (CBool)
iValue_isIntList :: ForeignPtr IValue -> IO CBool
iValue_isIntList = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isIntList
iValue_isString
:: ForeignPtr IValue
-> IO (CBool)
iValue_isString :: ForeignPtr IValue -> IO CBool
iValue_isString = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isString
iValue_toStringRef
:: ForeignPtr IValue
-> IO (ForeignPtr StdString)
iValue_toStringRef :: ForeignPtr IValue -> IO (ForeignPtr StdString)
iValue_toStringRef = (Ptr IValue -> IO (Ptr StdString))
-> ForeignPtr IValue -> IO (ForeignPtr StdString)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO (Ptr StdString)
Unmanaged.iValue_toStringRef
iValue_isDoubleList
:: ForeignPtr IValue
-> IO (CBool)
iValue_isDoubleList :: ForeignPtr IValue -> IO CBool
iValue_isDoubleList = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isDoubleList
iValue_isBool
:: ForeignPtr IValue
-> IO (CBool)
iValue_isBool :: ForeignPtr IValue -> IO CBool
iValue_isBool = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isBool
iValue_isObject
:: ForeignPtr IValue
-> IO (CBool)
iValue_isObject :: ForeignPtr IValue -> IO CBool
iValue_isObject = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isObject
iValue_isBoolList
:: ForeignPtr IValue
-> IO (CBool)
iValue_isBoolList :: ForeignPtr IValue -> IO CBool
iValue_isBoolList = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isBoolList
iValue_isTensorList
:: ForeignPtr IValue
-> IO (CBool)
iValue_isTensorList :: ForeignPtr IValue -> IO CBool
iValue_isTensorList = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isTensorList
iValue_isList
:: ForeignPtr IValue
-> IO (CBool)
iValue_isList :: ForeignPtr IValue -> IO CBool
iValue_isList = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isList
iValue_isGenericDict
:: ForeignPtr IValue
-> IO (CBool)
iValue_isGenericDict :: ForeignPtr IValue -> IO CBool
iValue_isGenericDict = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isGenericDict
iValue_isNone
:: ForeignPtr IValue
-> IO (CBool)
iValue_isNone :: ForeignPtr IValue -> IO CBool
iValue_isNone = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isNone
iValue_toNone
:: ForeignPtr IValue
-> IO (ForeignPtr StdString)
iValue_toNone :: ForeignPtr IValue -> IO (ForeignPtr StdString)
iValue_toNone = (Ptr IValue -> IO (Ptr StdString))
-> ForeignPtr IValue -> IO (ForeignPtr StdString)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO (Ptr StdString)
Unmanaged.iValue_toNone
iValue_isScalar
:: ForeignPtr IValue
-> IO (CBool)
iValue_isScalar :: ForeignPtr IValue -> IO CBool
iValue_isScalar = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isScalar
iValue_isDevice
:: ForeignPtr IValue
-> IO (CBool)
iValue_isDevice :: ForeignPtr IValue -> IO CBool
iValue_isDevice = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isDevice
iValue_toScalarType
:: ForeignPtr IValue
-> IO (ScalarType)
iValue_toScalarType :: ForeignPtr IValue -> IO QScheme
iValue_toScalarType = (Ptr IValue -> IO QScheme) -> ForeignPtr IValue -> IO QScheme
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO QScheme
Unmanaged.iValue_toScalarType
iValue_toLayout
:: ForeignPtr IValue
-> IO (Layout)
iValue_toLayout :: ForeignPtr IValue -> IO QScheme
iValue_toLayout = (Ptr IValue -> IO QScheme) -> ForeignPtr IValue -> IO QScheme
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO QScheme
Unmanaged.iValue_toLayout
iValue_toMemoryFormat
:: ForeignPtr IValue
-> IO (MemoryFormat)
iValue_toMemoryFormat :: ForeignPtr IValue -> IO QScheme
iValue_toMemoryFormat = (Ptr IValue -> IO QScheme) -> ForeignPtr IValue -> IO QScheme
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO QScheme
Unmanaged.iValue_toMemoryFormat
iValue_toQScheme
:: ForeignPtr IValue
-> IO (QScheme)
iValue_toQScheme :: ForeignPtr IValue -> IO QScheme
iValue_toQScheme = (Ptr IValue -> IO QScheme) -> ForeignPtr IValue -> IO QScheme
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO QScheme
Unmanaged.iValue_toQScheme
iValue_tagKind
:: ForeignPtr IValue
-> IO (ForeignPtr StdString)
iValue_tagKind :: ForeignPtr IValue -> IO (ForeignPtr StdString)
iValue_tagKind = (Ptr IValue -> IO (Ptr StdString))
-> ForeignPtr IValue -> IO (ForeignPtr StdString)
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO (Ptr StdString)
Unmanaged.iValue_tagKind
iValue_isSameIdentity_V
:: ForeignPtr IValue
-> ForeignPtr IValue
-> IO (CBool)
iValue_isSameIdentity_V :: ForeignPtr IValue -> ForeignPtr IValue -> IO CBool
iValue_isSameIdentity_V = (Ptr IValue -> Ptr IValue -> IO CBool)
-> ForeignPtr IValue -> ForeignPtr IValue -> IO CBool
forall a ca x1 cx1 y cy.
(Castable a ca, Castable x1 cx1, Castable y cy) =>
(ca -> cx1 -> IO cy) -> a -> x1 -> IO y
_cast2 Ptr IValue -> Ptr IValue -> IO CBool
Unmanaged.iValue_isSameIdentity_V
iValue_isPtrType
:: ForeignPtr IValue
-> IO (CBool)
iValue_isPtrType :: ForeignPtr IValue -> IO CBool
iValue_isPtrType = (Ptr IValue -> IO CBool) -> ForeignPtr IValue -> IO CBool
forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr IValue -> IO CBool
Unmanaged.iValue_isPtrType