{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}

module Torch.Internal.Managed.Type.Generator 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.Generator as Unmanaged



newCUDAGenerator
  :: Word16
  -> IO (ForeignPtr Generator)
newCUDAGenerator :: Word16 -> IO (ForeignPtr Generator)
newCUDAGenerator Word16
_device_index = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Word16 -> IO (Ptr Generator)
Unmanaged.newCUDAGenerator Word16
_device_index

newCPUGenerator
  :: Word64
  -> IO (ForeignPtr Generator)
newCPUGenerator :: Word64 -> IO (ForeignPtr Generator)
newCPUGenerator Word64
_seed_in = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Word64 -> IO (Ptr Generator)
Unmanaged.newCPUGenerator Word64
_seed_in





generator_set_current_seed
  :: ForeignPtr Generator
  -> Word64
  -> IO ()
generator_set_current_seed :: ForeignPtr Generator -> Word64 -> IO ()
generator_set_current_seed = 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 Generator -> Word64 -> IO ()
Unmanaged.generator_set_current_seed

generator_current_seed
  :: ForeignPtr Generator
  -> IO (Word64)
generator_current_seed :: ForeignPtr Generator -> IO Word64
generator_current_seed = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO Word64
Unmanaged.generator_current_seed

generator_seed
  :: ForeignPtr Generator
  -> IO (Word64)
generator_seed :: ForeignPtr Generator -> IO Word64
generator_seed = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO Word64
Unmanaged.generator_seed

generator_clone
  :: ForeignPtr Generator
  -> IO (ForeignPtr Generator)
generator_clone :: ForeignPtr Generator -> IO (ForeignPtr Generator)
generator_clone ForeignPtr Generator
_obj = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO (Ptr Generator)
Unmanaged.generator_clone ForeignPtr Generator
_obj

generator_get_device
  :: ForeignPtr Generator
  -> IO Int64
generator_get_device :: ForeignPtr Generator -> IO Int64
generator_get_device ForeignPtr Generator
_obj = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO Int64
Unmanaged.generator_get_device ForeignPtr Generator
_obj

generator_is_cpu
  :: ForeignPtr Generator
  -> IO CBool
generator_is_cpu :: ForeignPtr Generator -> IO CBool
generator_is_cpu ForeignPtr Generator
_obj = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO CBool
Unmanaged.generator_is_cpu ForeignPtr Generator
_obj

generator_is_cuda
  :: ForeignPtr Generator
  -> IO CBool
generator_is_cuda :: ForeignPtr Generator -> IO CBool
generator_is_cuda ForeignPtr Generator
_obj = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO CBool
Unmanaged.generator_is_cuda ForeignPtr Generator
_obj

generator_is_hip
  :: ForeignPtr Generator
  -> IO CBool
generator_is_hip :: ForeignPtr Generator -> IO CBool
generator_is_hip ForeignPtr Generator
_obj = forall a ca y cy.
(Castable a ca, Castable y cy) =>
(ca -> IO cy) -> a -> IO y
_cast1 Ptr Generator -> IO CBool
Unmanaged.generator_is_hip ForeignPtr Generator
_obj