{-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} module Torch.Internal.Managed.Type.TensorIndex 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.TensorIndex as Unmanaged newTensorIndexList :: IO (ForeignPtr (StdVector TensorIndex)) newTensorIndexList :: IO (ForeignPtr (StdVector TensorIndex)) newTensorIndexList = IO (Ptr (StdVector TensorIndex)) -> IO (ForeignPtr (StdVector TensorIndex)) forall a ca. Castable a ca => IO ca -> IO a _cast0 IO (Ptr (StdVector TensorIndex)) Unmanaged.newTensorIndexList newTensorIndexWithInt :: CInt -> IO (ForeignPtr TensorIndex) newTensorIndexWithInt :: CInt -> IO (ForeignPtr TensorIndex) newTensorIndexWithInt = (CInt -> IO (Ptr TensorIndex)) -> CInt -> IO (ForeignPtr TensorIndex) forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 CInt -> IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithInt newTensorIndexWithBool :: CBool -> IO (ForeignPtr TensorIndex) newTensorIndexWithBool :: CBool -> IO (ForeignPtr TensorIndex) newTensorIndexWithBool = (CBool -> IO (Ptr TensorIndex)) -> CBool -> IO (ForeignPtr TensorIndex) forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 CBool -> IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithBool newTensorIndexWithSlice :: CInt -> CInt -> CInt -> IO (ForeignPtr TensorIndex) newTensorIndexWithSlice :: CInt -> CInt -> CInt -> IO (ForeignPtr TensorIndex) newTensorIndexWithSlice = (CInt -> CInt -> CInt -> IO (Ptr TensorIndex)) -> CInt -> CInt -> CInt -> IO (ForeignPtr TensorIndex) forall a ca x1 cx1 x2 cx2 y cy. (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) => (ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y _cast3 CInt -> CInt -> CInt -> IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithSlice newTensorIndexWithTensor :: ForeignPtr Tensor -> IO (ForeignPtr TensorIndex) newTensorIndexWithTensor :: ForeignPtr Tensor -> IO (ForeignPtr TensorIndex) newTensorIndexWithTensor = (Ptr Tensor -> IO (Ptr TensorIndex)) -> ForeignPtr Tensor -> IO (ForeignPtr TensorIndex) forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 Ptr Tensor -> IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithTensor newTensorIndexWithEllipsis :: IO (ForeignPtr TensorIndex) newTensorIndexWithEllipsis :: IO (ForeignPtr TensorIndex) newTensorIndexWithEllipsis = IO (Ptr TensorIndex) -> IO (ForeignPtr TensorIndex) forall a ca. Castable a ca => IO ca -> IO a _cast0 IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithEllipsis newTensorIndexWithNone :: IO (ForeignPtr TensorIndex) newTensorIndexWithNone :: IO (ForeignPtr TensorIndex) newTensorIndexWithNone = IO (Ptr TensorIndex) -> IO (ForeignPtr TensorIndex) forall a ca. Castable a ca => IO ca -> IO a _cast0 IO (Ptr TensorIndex) Unmanaged.newTensorIndexWithNone tensorIndexList_empty :: ForeignPtr (StdVector TensorIndex) -> IO (CBool) tensorIndexList_empty :: ForeignPtr (StdVector TensorIndex) -> IO CBool tensorIndexList_empty = (Ptr (StdVector TensorIndex) -> IO CBool) -> ForeignPtr (StdVector TensorIndex) -> IO CBool forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 Ptr (StdVector TensorIndex) -> IO CBool Unmanaged.tensorIndexList_empty tensorIndexList_size :: ForeignPtr (StdVector TensorIndex) -> IO (CSize) tensorIndexList_size :: ForeignPtr (StdVector TensorIndex) -> IO CSize tensorIndexList_size = (Ptr (StdVector TensorIndex) -> IO CSize) -> ForeignPtr (StdVector TensorIndex) -> IO CSize forall a ca y cy. (Castable a ca, Castable y cy) => (ca -> IO cy) -> a -> IO y _cast1 Ptr (StdVector TensorIndex) -> IO CSize Unmanaged.tensorIndexList_size tensorIndexList_push_back :: ForeignPtr (StdVector TensorIndex) -> ForeignPtr TensorIndex -> IO () tensorIndexList_push_back :: ForeignPtr (StdVector TensorIndex) -> ForeignPtr TensorIndex -> IO () tensorIndexList_push_back = (Ptr (StdVector TensorIndex) -> Ptr TensorIndex -> IO ()) -> ForeignPtr (StdVector TensorIndex) -> ForeignPtr TensorIndex -> 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 (StdVector TensorIndex) -> Ptr TensorIndex -> IO () Unmanaged.tensorIndexList_push_back index :: ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> IO (ForeignPtr Tensor) index :: ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> IO (ForeignPtr Tensor) index = (Ptr Tensor -> Ptr (StdVector TensorIndex) -> IO (Ptr Tensor)) -> ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> IO (ForeignPtr Tensor) 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 Tensor -> Ptr (StdVector TensorIndex) -> IO (Ptr Tensor) Unmanaged.index index_put_ :: ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> ForeignPtr Tensor -> IO (ForeignPtr Tensor) index_put_ :: ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> ForeignPtr Tensor -> IO (ForeignPtr Tensor) index_put_ = (Ptr Tensor -> Ptr (StdVector TensorIndex) -> Ptr Tensor -> IO (Ptr Tensor)) -> ForeignPtr Tensor -> ForeignPtr (StdVector TensorIndex) -> ForeignPtr Tensor -> IO (ForeignPtr Tensor) forall a ca x1 cx1 x2 cx2 y cy. (Castable a ca, Castable x1 cx1, Castable x2 cx2, Castable y cy) => (ca -> cx1 -> cx2 -> IO cy) -> a -> x1 -> x2 -> IO y _cast3 Ptr Tensor -> Ptr (StdVector TensorIndex) -> Ptr Tensor -> IO (Ptr Tensor) Unmanaged.index_put_