{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GRand struct is an opaque data structure. It should only be
-- accessed through the g_rand_* functions.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.GLib.Structs.Rand
    ( 

-- * Exported types
    Rand(..)                                ,
    noRand                                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveRandMethod                       ,
#endif


-- ** double #method:double#

#if defined(ENABLE_OVERLOADING)
    RandDoubleMethodInfo                    ,
#endif
    randDouble                              ,


-- ** doubleRange #method:doubleRange#

#if defined(ENABLE_OVERLOADING)
    RandDoubleRangeMethodInfo               ,
#endif
    randDoubleRange                         ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    RandFreeMethodInfo                      ,
#endif
    randFree                                ,


-- ** int #method:int#

#if defined(ENABLE_OVERLOADING)
    RandIntMethodInfo                       ,
#endif
    randInt                                 ,


-- ** intRange #method:intRange#

#if defined(ENABLE_OVERLOADING)
    RandIntRangeMethodInfo                  ,
#endif
    randIntRange                            ,


-- ** setSeed #method:setSeed#

#if defined(ENABLE_OVERLOADING)
    RandSetSeedMethodInfo                   ,
#endif
    randSetSeed                             ,


-- ** setSeedArray #method:setSeedArray#

#if defined(ENABLE_OVERLOADING)
    RandSetSeedArrayMethodInfo              ,
#endif
    randSetSeedArray                        ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL


-- | Memory-managed wrapper type.
newtype Rand = Rand (ManagedPtr Rand)
    deriving (Rand -> Rand -> Bool
(Rand -> Rand -> Bool) -> (Rand -> Rand -> Bool) -> Eq Rand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rand -> Rand -> Bool
$c/= :: Rand -> Rand -> Bool
== :: Rand -> Rand -> Bool
$c== :: Rand -> Rand -> Bool
Eq)
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr Rand where
    wrappedPtrCalloc :: IO (Ptr Rand)
wrappedPtrCalloc = Ptr Rand -> IO (Ptr Rand)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Rand
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: Rand -> IO Rand
wrappedPtrCopy = Rand -> IO Rand
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify Rand)
wrappedPtrFree = Maybe (GDestroyNotify Rand)
forall a. Maybe a
Nothing

-- | A convenience alias for `Nothing` :: `Maybe` `Rand`.
noRand :: Maybe Rand
noRand :: Maybe Rand
noRand = Maybe Rand
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Rand
type instance O.AttributeList Rand = RandAttributeList
type RandAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method Rand::double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_double" g_rand_double :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    IO CDouble

-- | Returns the next random @/gdouble/@ from /@rand_@/ equally distributed over
-- the range [0..1).
randDouble ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> m Double
    -- ^ __Returns:__ a random number
randDouble :: Rand -> m Double
randDouble rand_ :: Rand
rand_ = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    CDouble
result <- Ptr Rand -> IO CDouble
g_rand_double Ptr Rand
rand_'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data RandDoubleMethodInfo
instance (signature ~ (m Double), MonadIO m) => O.MethodInfo RandDoubleMethodInfo Rand signature where
    overloadedMethod = randDouble

#endif

-- method Rand::double_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "begin"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "lower closed bound of the interval"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "upper open bound of the interval"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_double_range" g_rand_double_range :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    CDouble ->                              -- begin : TBasicType TDouble
    CDouble ->                              -- end : TBasicType TDouble
    IO CDouble

-- | Returns the next random @/gdouble/@ from /@rand_@/ equally distributed over
-- the range [/@begin@/../@end@/).
randDoubleRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> Double
    -- ^ /@begin@/: lower closed bound of the interval
    -> Double
    -- ^ /@end@/: upper open bound of the interval
    -> m Double
    -- ^ __Returns:__ a random number
randDoubleRange :: Rand -> Double -> Double -> m Double
randDoubleRange rand_ :: Rand
rand_ begin :: Double
begin end :: Double
end = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    let begin' :: CDouble
begin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
begin
    let end' :: CDouble
end' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
end
    CDouble
result <- Ptr Rand -> CDouble -> CDouble -> IO CDouble
g_rand_double_range Ptr Rand
rand_' CDouble
begin' CDouble
end'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data RandDoubleRangeMethodInfo
instance (signature ~ (Double -> Double -> m Double), MonadIO m) => O.MethodInfo RandDoubleRangeMethodInfo Rand signature where
    overloadedMethod = randDoubleRange

#endif

-- method Rand::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_free" g_rand_free :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    IO ()

-- | Frees the memory allocated for the t'GI.GLib.Structs.Rand.Rand'.
randFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> m ()
randFree :: Rand -> m ()
randFree rand_ :: Rand
rand_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    Ptr Rand -> IO ()
g_rand_free Ptr Rand
rand_'
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RandFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo RandFreeMethodInfo Rand signature where
    overloadedMethod = randFree

#endif

-- method Rand::int
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_int" g_rand_int :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    IO Word32

-- | Returns the next random @/guint32/@ from /@rand_@/ equally distributed over
-- the range [0..2^32-1].
randInt ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> m Word32
    -- ^ __Returns:__ a random number
randInt :: Rand -> m Word32
randInt rand_ :: Rand
rand_ = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    Word32
result <- Ptr Rand -> IO Word32
g_rand_int Ptr Rand
rand_'
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data RandIntMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo RandIntMethodInfo Rand signature where
    overloadedMethod = randInt

#endif

-- method Rand::int_range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "begin"
--           , argType = TBasicType TInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "lower closed bound of the interval"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end"
--           , argType = TBasicType TInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "upper open bound of the interval"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_int_range" g_rand_int_range :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    Int32 ->                                -- begin : TBasicType TInt32
    Int32 ->                                -- end : TBasicType TInt32
    IO Int32

-- | Returns the next random @/gint32/@ from /@rand_@/ equally distributed over
-- the range [/@begin@/../@end@/-1].
randIntRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> Int32
    -- ^ /@begin@/: lower closed bound of the interval
    -> Int32
    -- ^ /@end@/: upper open bound of the interval
    -> m Int32
    -- ^ __Returns:__ a random number
randIntRange :: Rand -> Int32 -> Int32 -> m Int32
randIntRange rand_ :: Rand
rand_ begin :: Int32
begin end :: Int32
end = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    Int32
result <- Ptr Rand -> Int32 -> Int32 -> IO Int32
g_rand_int_range Ptr Rand
rand_' Int32
begin Int32
end
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RandIntRangeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Int32), MonadIO m) => O.MethodInfo RandIntRangeMethodInfo Rand signature where
    overloadedMethod = randIntRange

#endif

-- method Rand::set_seed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "seed"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a value to reinitialize the random number generator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_set_seed" g_rand_set_seed :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    Word32 ->                               -- seed : TBasicType TUInt32
    IO ()

-- | Sets the seed for the random number generator t'GI.GLib.Structs.Rand.Rand' to /@seed@/.
randSetSeed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> Word32
    -- ^ /@seed@/: a value to reinitialize the random number generator
    -> m ()
randSetSeed :: Rand -> Word32 -> m ()
randSetSeed rand_ :: Rand
rand_ seed :: Word32
seed = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    Ptr Rand -> Word32 -> IO ()
g_rand_set_seed Ptr Rand
rand_' Word32
seed
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RandSetSeedMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.MethodInfo RandSetSeedMethodInfo Rand signature where
    overloadedMethod = randSetSeed

#endif

-- method Rand::set_seed_array
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rand_"
--           , argType = TInterface Name { namespace = "GLib" , name = "Rand" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GRand" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "seed"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "array to initialize with"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "seed_length"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of array" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_set_seed_array" g_rand_set_seed_array :: 
    Ptr Rand ->                             -- rand_ : TInterface (Name {namespace = "GLib", name = "Rand"})
    Word32 ->                               -- seed : TBasicType TUInt32
    Word32 ->                               -- seed_length : TBasicType TUInt
    IO ()

-- | Initializes the random number generator by an array of longs.
-- Array can be of arbitrary size, though only the first 624 values
-- are taken.  This function is useful if you have many low entropy
-- seeds, or if you require more then 32 bits of actual entropy for
-- your application.
-- 
-- /Since: 2.4/
randSetSeedArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> Word32
    -- ^ /@seed@/: array to initialize with
    -> Word32
    -- ^ /@seedLength@/: length of array
    -> m ()
randSetSeedArray :: Rand -> Word32 -> Word32 -> m ()
randSetSeedArray rand_ :: Rand
rand_ seed :: Word32
seed seedLength :: Word32
seedLength = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
rand_' <- Rand -> IO (Ptr Rand)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rand
rand_
    Ptr Rand -> Word32 -> Word32 -> IO ()
g_rand_set_seed_array Ptr Rand
rand_' Word32
seed Word32
seedLength
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RandSetSeedArrayMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m) => O.MethodInfo RandSetSeedArrayMethodInfo Rand signature where
    overloadedMethod = randSetSeedArray

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRandMethod (t :: Symbol) (o :: *) :: * where
    ResolveRandMethod "double" o = RandDoubleMethodInfo
    ResolveRandMethod "doubleRange" o = RandDoubleRangeMethodInfo
    ResolveRandMethod "free" o = RandFreeMethodInfo
    ResolveRandMethod "int" o = RandIntMethodInfo
    ResolveRandMethod "intRange" o = RandIntRangeMethodInfo
    ResolveRandMethod "setSeed" o = RandSetSeedMethodInfo
    ResolveRandMethod "setSeedArray" o = RandSetSeedArrayMethodInfo
    ResolveRandMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRandMethod t Rand, O.MethodInfo info Rand p) => OL.IsLabel t (Rand -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif