{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- 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(..)                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [copy]("GI.GLib.Structs.Rand#g:method:copy"), [double]("GI.GLib.Structs.Rand#g:method:double"), [doubleRange]("GI.GLib.Structs.Rand#g:method:doubleRange"), [free]("GI.GLib.Structs.Rand#g:method:free"), [int]("GI.GLib.Structs.Rand#g:method:int"), [intRange]("GI.GLib.Structs.Rand#g:method:intRange").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- [setSeed]("GI.GLib.Structs.Rand#g:method:setSeed"), [setSeedArray]("GI.GLib.Structs.Rand#g:method:setSeedArray").

#if defined(ENABLE_OVERLOADING)
    ResolveRandMethod                       ,
#endif

-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    RandCopyMethodInfo                      ,
#endif
    randCopy                                ,


-- ** 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                            ,


-- ** new #method:new#

    randNew                                 ,


-- ** newWithSeed #method:newWithSeed#

    randNewWithSeed                         ,


-- ** newWithSeedArray #method:newWithSeedArray#

    randNewWithSeedArray                    ,


-- ** 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)

#else

#endif

-- | Memory-managed wrapper type.
newtype Rand = Rand (SP.ManagedPtr Rand)
    deriving (Rand -> Rand -> Bool
(Rand -> Rand -> Bool) -> (Rand -> Rand -> Bool) -> Eq Rand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rand -> Rand -> Bool
== :: Rand -> Rand -> Bool
$c/= :: Rand -> Rand -> Bool
/= :: Rand -> Rand -> Bool
Eq)

instance SP.ManagedPtrNewtype Rand where
    toManagedPtr :: Rand -> ManagedPtr Rand
toManagedPtr (Rand ManagedPtr Rand
p) = ManagedPtr Rand
p

foreign import ccall "g_rand_get_type" c_g_rand_get_type :: 
    IO GType

type instance O.ParentTypes Rand = '[]
instance O.HasParentTypes Rand

instance B.Types.TypedObject Rand where
    glibType :: IO GType
glibType = IO GType
c_g_rand_get_type

instance B.Types.GBoxed Rand

-- | Convert 'Rand' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Rand) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_rand_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Rand -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Rand
P.Nothing = Ptr GValue -> Ptr Rand -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Rand
forall a. Ptr a
FP.nullPtr :: FP.Ptr Rand)
    gvalueSet_ Ptr GValue
gv (P.Just Rand
obj) = Rand -> (Ptr Rand -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rand
obj (Ptr GValue -> Ptr Rand -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Rand)
gvalueGet_ Ptr GValue
gv = do
        Ptr Rand
ptr <- Ptr GValue -> IO (Ptr Rand)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Rand)
        if Ptr Rand
ptr Ptr Rand -> Ptr Rand -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Rand
forall a. Ptr a
FP.nullPtr
        then Rand -> Maybe Rand
forall a. a -> Maybe a
P.Just (Rand -> Maybe Rand) -> IO Rand -> IO (Maybe Rand)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Rand -> Rand) -> Ptr Rand -> IO Rand
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Rand -> Rand
Rand Ptr Rand
ptr
        else Maybe Rand -> IO (Maybe Rand)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Rand
forall a. Maybe a
P.Nothing
        
    


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

-- method Rand::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Rand" })
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_new" g_rand_new :: 
    IO (Ptr Rand)

-- | Creates a new random number generator initialized with a seed taken
-- either from @\/dev\/urandom@ (if existing) or from the current time
-- (as a fallback).
-- 
-- On Windows, the seed is taken from @/rand_s()/@.
randNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Rand
    -- ^ __Returns:__ the new t'GI.GLib.Structs.Rand.Rand'
randNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Rand
randNew  = IO Rand -> m Rand
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rand -> m Rand) -> IO Rand -> m Rand
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
result <- IO (Ptr Rand)
g_rand_new
    Text -> Ptr Rand -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"randNew" Ptr Rand
result
    Rand
result' <- ((ManagedPtr Rand -> Rand) -> Ptr Rand -> IO Rand
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rand -> Rand
Rand) Ptr Rand
result
    Rand -> IO Rand
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rand
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "g_rand_new_with_seed" g_rand_new_with_seed :: 
    Word32 ->                               -- seed : TBasicType TUInt32
    IO (Ptr Rand)

-- | Creates a new random number generator initialized with /@seed@/.
randNewWithSeed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@seed@/: a value to initialize the random number generator
    -> m Rand
    -- ^ __Returns:__ the new t'GI.GLib.Structs.Rand.Rand'
randNewWithSeed :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Word32 -> m Rand
randNewWithSeed Word32
seed = IO Rand -> m Rand
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rand -> m Rand) -> IO Rand -> m Rand
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
result <- Word32 -> IO (Ptr Rand)
g_rand_new_with_seed Word32
seed
    Text -> Ptr Rand -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"randNewWithSeed" Ptr Rand
result
    Rand
result' <- ((ManagedPtr Rand -> Rand) -> Ptr Rand -> IO Rand
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rand -> Rand
Rand) Ptr Rand
result
    Rand -> IO Rand
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rand
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Rand::new_with_seed_array
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "seed"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an array of seeds to initialize the random number generator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "seed_length"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an array of seeds to initialize the random number\n    generator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Rand" })
-- throws : False
-- Skip return : False

foreign import ccall "g_rand_new_with_seed_array" g_rand_new_with_seed_array :: 
    Word32 ->                               -- seed : TBasicType TUInt32
    Word32 ->                               -- seed_length : TBasicType TUInt
    IO (Ptr Rand)

-- | Creates a new random number generator initialized with /@seed@/.
-- 
-- /Since: 2.4/
randNewWithSeedArray ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Word32
    -- ^ /@seed@/: an array of seeds to initialize the random number generator
    -> Word32
    -- ^ /@seedLength@/: an array of seeds to initialize the random number
    --     generator
    -> m Rand
    -- ^ __Returns:__ the new t'GI.GLib.Structs.Rand.Rand'
randNewWithSeedArray :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Word32 -> Word32 -> m Rand
randNewWithSeedArray Word32
seed Word32
seedLength = IO Rand -> m Rand
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rand -> m Rand) -> IO Rand -> m Rand
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rand
result <- Word32 -> Word32 -> IO (Ptr Rand)
g_rand_new_with_seed_array Word32
seed Word32
seedLength
    Text -> Ptr Rand -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"randNewWithSeedArray" Ptr Rand
result
    Rand
result' <- ((ManagedPtr Rand -> Rand) -> Ptr Rand -> IO Rand
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rand -> Rand
Rand) Ptr Rand
result
    Rand -> IO Rand
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rand
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Rand::copy
-- 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Rand" })
-- throws : False
-- Skip return : False

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

-- | Copies a t'GI.GLib.Structs.Rand.Rand' into a new one with the same exact state as before.
-- This way you can take a snapshot of the random number generator for
-- replaying later.
-- 
-- /Since: 2.4/
randCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rand
    -- ^ /@rand_@/: a t'GI.GLib.Structs.Rand.Rand'
    -> m Rand
    -- ^ __Returns:__ the new t'GI.GLib.Structs.Rand.Rand'
randCopy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Rand -> m Rand
randCopy Rand
rand_ = IO Rand -> m Rand
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rand -> m Rand) -> IO Rand -> m Rand
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
result <- Ptr Rand -> IO (Ptr Rand)
g_rand_copy Ptr Rand
rand_'
    Text -> Ptr Rand -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"randCopy" Ptr Rand
result
    Rand
result' <- ((ManagedPtr Rand -> Rand) -> Ptr Rand -> IO Rand
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rand -> Rand
Rand) Ptr Rand
result
    Rand -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rand
rand_
    Rand -> IO Rand
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rand
result'

#if defined(ENABLE_OVERLOADING)
data RandCopyMethodInfo
instance (signature ~ (m Rand), MonadIO m) => O.OverloadedMethod RandCopyMethodInfo Rand signature where
    overloadedMethod = randCopy

instance O.OverloadedMethodInfo RandCopyMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v:randCopy"
        })


#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
--           , argCallbackUserData = 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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Rand -> m Double
randDouble Rand
rand_ = IO Double -> m Double
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

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

instance O.OverloadedMethodInfo RandDoubleMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randDouble",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rand -> Double -> Double -> m Double
randDoubleRange Rand
rand_ Double
begin Double
end = IO Double -> m Double
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod RandDoubleRangeMethodInfo Rand signature where
    overloadedMethod = randDoubleRange

instance O.OverloadedMethodInfo RandDoubleRangeMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randDoubleRange",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Rand -> m ()
randFree Rand
rand_ = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo RandFreeMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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 :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Rand -> m Word32
randInt Rand
rand_ = IO Word32 -> m Word32
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

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

instance O.OverloadedMethodInfo RandIntMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randInt",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rand -> Int32 -> Int32 -> m Int32
randIntRange Rand
rand_ Int32
begin Int32
end = IO Int32 -> m Int32
forall a. IO a -> m a
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 a. a -> IO a
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.OverloadedMethod RandIntRangeMethodInfo Rand signature where
    overloadedMethod = randIntRange

instance O.OverloadedMethodInfo RandIntRangeMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randIntRange",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rand -> Word32 -> m ()
randSetSeed Rand
rand_ Word32
seed = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo RandSetSeedMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randSetSeed",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v: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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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
--           , argCallbackUserData = 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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rand -> Word32 -> Word32 -> m ()
randSetSeedArray Rand
rand_ Word32
seed Word32
seedLength = IO () -> m ()
forall a. IO a -> m a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo RandSetSeedArrayMethodInfo Rand where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.Rand.randSetSeedArray",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.30/docs/GI-GLib-Structs-Rand.html#v:randSetSeedArray"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRandMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveRandMethod "copy" o = RandCopyMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveRandMethod t Rand, O.OverloadedMethod info Rand p, R.HasField t Rand p) => R.HasField t Rand p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveRandMethod t Rand, O.OverloadedMethodInfo info Rand) => OL.IsLabel t (O.MethodProxy info Rand) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif