{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
module Torch.Internal.Managed.Type.Tuple 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.Tuple as Unmanaged
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor))
-> IO (A (ForeignPtr (StdTuple '(Tensor, Tensor))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor))
-> IO (B (ForeignPtr (StdTuple '(Tensor, Tensor))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO
(A (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO
(B (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO
(C (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple4 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) where
type D (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get3 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO
(D (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
get3 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple4 m => m -> IO (D m)
get3 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple5 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) where
type E (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get4 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
-> IO
(E (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))))
get4 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple5 m => m -> IO (E m)
get4 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
-> IO
(A (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,TensorList)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
-> IO
(B (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,TensorList)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) = ForeignPtr Tensor
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
-> IO
(C (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,TensorList)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v
instance CppTuple4 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) where
type D (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,TensorList))) = ForeignPtr TensorList
get3 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
-> IO
(D (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))))
get3 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple4 m => m -> IO (D m)
get3 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,TensorList)) -> IO (Ptr TensorList)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, TensorList))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
-> IO
(A (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
-> IO
(B (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) = ForeignPtr Tensor
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
-> IO
(C (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v
instance CppTuple4 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) where
type D (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) = ForeignPtr Tensor
get3 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
-> IO
(D (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))))
get3 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple4 m => m -> IO (D m)
get3 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v
instance CppTuple5 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) where
type E (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64))) = Int64
get4 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
-> IO
(E (ForeignPtr
(StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))))
get4 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple5 m => m -> IO (E m)
get4 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor,Int64)) -> IO (Int64)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor, Int64))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
-> IO (A (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
-> IO (B (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
-> IO (C (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
-> IO (A (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
-> IO (B (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
-> IO (C (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple4 (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) where
type D (ForeignPtr (StdTuple '(Tensor,Tensor,Tensor,Tensor))) = ForeignPtr Tensor
get3 :: ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
-> IO (D (ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))))
get3 ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple4 m => m -> IO (D m)
get3 :: Ptr (StdTuple '(Tensor,Tensor,Tensor,Tensor)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, Tensor, Tensor))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) where
type A (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) = ForeignPtr Tensor
get0 :: ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
-> IO (A (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))))
get0 ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Tensor,CDouble,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
-> IO (B (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))))
get1 ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Tensor,CDouble,Int64)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v
instance CppTuple3 (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) where
type C (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) = CDouble
get2 :: ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
-> IO (C (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))))
get2 ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple3 m => m -> IO (C m)
get2 :: Ptr (StdTuple '(Tensor,Tensor,CDouble,Int64)) -> IO (CDouble)) ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v
instance CppTuple4 (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) where
type D (ForeignPtr (StdTuple '(Tensor,Tensor,CDouble,Int64))) = Int64
get3 :: ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
-> IO (D (ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))))
get3 ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple4 m => m -> IO (D m)
get3 :: Ptr (StdTuple '(Tensor,Tensor,CDouble,Int64)) -> IO (Int64)) ForeignPtr (StdTuple '(Tensor, Tensor, CDouble, Int64))
v
instance CppTuple2 (ForeignPtr (StdTuple '(CDouble,Int64))) where
type A (ForeignPtr (StdTuple '(CDouble,Int64))) = CDouble
type B (ForeignPtr (StdTuple '(CDouble,Int64))) = Int64
get0 :: ForeignPtr (StdTuple '(CDouble, Int64))
-> IO (A (ForeignPtr (StdTuple '(CDouble, Int64))))
get0 ForeignPtr (StdTuple '(CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(CDouble,Int64)) -> IO (CDouble)) ForeignPtr (StdTuple '(CDouble, Int64))
v
get1 :: ForeignPtr (StdTuple '(CDouble, Int64))
-> IO (B (ForeignPtr (StdTuple '(CDouble, Int64))))
get1 ForeignPtr (StdTuple '(CDouble, Int64))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(CDouble,Int64)) -> IO (Int64)) ForeignPtr (StdTuple '(CDouble, Int64))
v
instance CppTuple2 (ForeignPtr (StdTuple '(CDouble,CDouble))) where
type A (ForeignPtr (StdTuple '(CDouble,CDouble))) = CDouble
type B (ForeignPtr (StdTuple '(CDouble,CDouble))) = CDouble
get0 :: ForeignPtr (StdTuple '(CDouble, CDouble))
-> IO (A (ForeignPtr (StdTuple '(CDouble, CDouble))))
get0 ForeignPtr (StdTuple '(CDouble, CDouble))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(CDouble,CDouble)) -> IO (CDouble)) ForeignPtr (StdTuple '(CDouble, CDouble))
v
get1 :: ForeignPtr (StdTuple '(CDouble, CDouble))
-> IO (B (ForeignPtr (StdTuple '(CDouble, CDouble))))
get1 ForeignPtr (StdTuple '(CDouble, CDouble))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(CDouble,CDouble)) -> IO (CDouble)) ForeignPtr (StdTuple '(CDouble, CDouble))
v
instance CppTuple2 (ForeignPtr (StdTuple '(Tensor,Generator))) where
type A (ForeignPtr (StdTuple '(Tensor,Generator))) = ForeignPtr Tensor
type B (ForeignPtr (StdTuple '(Tensor,Generator))) = ForeignPtr Generator
get0 :: ForeignPtr (StdTuple '(Tensor, Generator))
-> IO (A (ForeignPtr (StdTuple '(Tensor, Generator))))
get0 ForeignPtr (StdTuple '(Tensor, Generator))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (A m)
get0 :: Ptr (StdTuple '(Tensor,Generator)) -> IO (Ptr Tensor)) ForeignPtr (StdTuple '(Tensor, Generator))
v
get1 :: ForeignPtr (StdTuple '(Tensor, Generator))
-> IO (B (ForeignPtr (StdTuple '(Tensor, Generator))))
get1 ForeignPtr (StdTuple '(Tensor, Generator))
v = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 (forall m. CppTuple2 m => m -> IO (B m)
get1 :: Ptr (StdTuple '(Tensor,Generator)) -> IO (Ptr Generator)) ForeignPtr (StdTuple '(Tensor, Generator))
v
makeTuple2 :: (A (ForeignPtr (StdTuple '(Tensor, Generator))),
B (ForeignPtr (StdTuple '(Tensor, Generator))))
-> IO (ForeignPtr (StdTuple '(Tensor, Generator)))
makeTuple2 (A (ForeignPtr (StdTuple '(Tensor, Generator)))
a,B (ForeignPtr (StdTuple '(Tensor, Generator)))
b) =
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr A (ForeignPtr (StdTuple '(Tensor, Generator)))
a forall a b. (a -> b) -> a -> b
$ \Ptr Tensor
a' -> do
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr B (ForeignPtr (StdTuple '(Tensor, Generator)))
b forall a b. (a -> b) -> a -> b
$ \Ptr Generator
b' -> do
forall a. CppObject a => Ptr a -> IO (ForeignPtr a)
fromPtr forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall m. CppTuple2 m => (A m, B m) -> IO m
makeTuple2 (Ptr Tensor
a',Ptr Generator
b')