{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Opaque datatype that records a start time.

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

module GI.GLib.Structs.Timer
    ( 

-- * Exported types
    Timer(..)                               ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [continue]("GI.GLib.Structs.Timer#g:method:continue"), [destroy]("GI.GLib.Structs.Timer#g:method:destroy"), [elapsed]("GI.GLib.Structs.Timer#g:method:elapsed"), [isActive]("GI.GLib.Structs.Timer#g:method:isActive"), [reset]("GI.GLib.Structs.Timer#g:method:reset"), [start]("GI.GLib.Structs.Timer#g:method:start"), [stop]("GI.GLib.Structs.Timer#g:method:stop").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveTimerMethod                      ,
#endif

-- ** continue #method:continue#

#if defined(ENABLE_OVERLOADING)
    TimerContinueMethodInfo                 ,
#endif
    timerContinue                           ,


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    TimerDestroyMethodInfo                  ,
#endif
    timerDestroy                            ,


-- ** elapsed #method:elapsed#

#if defined(ENABLE_OVERLOADING)
    TimerElapsedMethodInfo                  ,
#endif
    timerElapsed                            ,


-- ** isActive #method:isActive#

#if defined(ENABLE_OVERLOADING)
    TimerIsActiveMethodInfo                 ,
#endif
    timerIsActive                           ,


-- ** reset #method:reset#

#if defined(ENABLE_OVERLOADING)
    TimerResetMethodInfo                    ,
#endif
    timerReset                              ,


-- ** start #method:start#

#if defined(ENABLE_OVERLOADING)
    TimerStartMethodInfo                    ,
#endif
    timerStart                              ,


-- ** stop #method:stop#

#if defined(ENABLE_OVERLOADING)
    TimerStopMethodInfo                     ,
#endif
    timerStop                               ,




    ) 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.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.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
import qualified GHC.Records as R


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

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

-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance BoxedPtr Timer where
    boxedPtrCopy :: Timer -> IO Timer
boxedPtrCopy = Timer -> IO Timer
forall (m :: * -> *) a. Monad m => a -> m a
return
    boxedPtrFree :: Timer -> IO ()
boxedPtrFree = \Timer
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()


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

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

foreign import ccall "g_timer_continue" g_timer_continue :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO ()

-- | Resumes a timer that has previously been stopped with
-- 'GI.GLib.Structs.Timer.timerStop'. 'GI.GLib.Structs.Timer.timerStop' must be called before using this
-- function.
-- 
-- /Since: 2.4/
timerContinue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> m ()
timerContinue :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m ()
timerContinue Timer
timer = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    Ptr Timer -> IO ()
g_timer_continue Ptr Timer
timer'
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimerContinueMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TimerContinueMethodInfo Timer signature where
    overloadedMethod = timerContinue

instance O.OverloadedMethodInfo TimerContinueMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerContinue",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerContinue"
        }


#endif

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

foreign import ccall "g_timer_destroy" g_timer_destroy :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO ()

-- | Destroys a timer, freeing associated resources.
timerDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer' to destroy.
    -> m ()
timerDestroy :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m ()
timerDestroy Timer
timer = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    Ptr Timer -> IO ()
g_timer_destroy Ptr Timer
timer'
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimerDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TimerDestroyMethodInfo Timer signature where
    overloadedMethod = timerDestroy

instance O.OverloadedMethodInfo TimerDestroyMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerDestroy",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerDestroy"
        }


#endif

-- method Timer::elapsed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "timer"
--           , argType = TInterface Name { namespace = "GLib" , name = "Timer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTimer." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "microseconds"
--           , argType = TBasicType TULong
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the fractional part of seconds\n               elapsed, in microseconds (that is, the total number\n               of microseconds elapsed, modulo 1000000), or %NULL"
--                 , 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_timer_elapsed" g_timer_elapsed :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    CULong ->                               -- microseconds : TBasicType TULong
    IO CDouble

-- | If /@timer@/ has been started but not stopped, obtains the time since
-- the timer was started. If /@timer@/ has been stopped, obtains the
-- elapsed time between the time it was started and the time it was
-- stopped. The return value is the number of seconds elapsed,
-- including any fractional part. The /@microseconds@/ out parameter is
-- essentially useless.
timerElapsed ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> CULong
    -- ^ /@microseconds@/: return location for the fractional part of seconds
    --                elapsed, in microseconds (that is, the total number
    --                of microseconds elapsed, modulo 1000000), or 'P.Nothing'
    -> m Double
    -- ^ __Returns:__ seconds elapsed as a floating point value, including any
    --          fractional part.
timerElapsed :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Timer -> CULong -> m Double
timerElapsed Timer
timer CULong
microseconds = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    CDouble
result <- Ptr Timer -> CULong -> IO CDouble
g_timer_elapsed Ptr Timer
timer' CULong
microseconds
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data TimerElapsedMethodInfo
instance (signature ~ (CULong -> m Double), MonadIO m) => O.OverloadedMethod TimerElapsedMethodInfo Timer signature where
    overloadedMethod = timerElapsed

instance O.OverloadedMethodInfo TimerElapsedMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerElapsed",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerElapsed"
        }


#endif

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

foreign import ccall "g_timer_is_active" g_timer_is_active :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO CInt

-- | Exposes whether the timer is currently active.
-- 
-- /Since: 2.62/
timerIsActive ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the timer is running, 'P.False' otherwise
timerIsActive :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m Bool
timerIsActive Timer
timer = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    CInt
result <- Ptr Timer -> IO CInt
g_timer_is_active Ptr Timer
timer'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TimerIsActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod TimerIsActiveMethodInfo Timer signature where
    overloadedMethod = timerIsActive

instance O.OverloadedMethodInfo TimerIsActiveMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerIsActive",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerIsActive"
        }


#endif

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

foreign import ccall "g_timer_reset" g_timer_reset :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO ()

-- | This function is useless; it\'s fine to call 'GI.GLib.Structs.Timer.timerStart' on an
-- already-started timer to reset the start time, so 'GI.GLib.Structs.Timer.timerReset'
-- serves no purpose.
timerReset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> m ()
timerReset :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m ()
timerReset Timer
timer = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    Ptr Timer -> IO ()
g_timer_reset Ptr Timer
timer'
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimerResetMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TimerResetMethodInfo Timer signature where
    overloadedMethod = timerReset

instance O.OverloadedMethodInfo TimerResetMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerReset",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerReset"
        }


#endif

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

foreign import ccall "g_timer_start" g_timer_start :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO ()

-- | Marks a start time, so that future calls to 'GI.GLib.Structs.Timer.timerElapsed' will
-- report the time since 'GI.GLib.Structs.Timer.timerStart' was called. @/g_timer_new()/@
-- automatically marks the start time, so no need to call
-- 'GI.GLib.Structs.Timer.timerStart' immediately after creating the timer.
timerStart ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> m ()
timerStart :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m ()
timerStart Timer
timer = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    Ptr Timer -> IO ()
g_timer_start Ptr Timer
timer'
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimerStartMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TimerStartMethodInfo Timer signature where
    overloadedMethod = timerStart

instance O.OverloadedMethodInfo TimerStartMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerStart",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerStart"
        }


#endif

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

foreign import ccall "g_timer_stop" g_timer_stop :: 
    Ptr Timer ->                            -- timer : TInterface (Name {namespace = "GLib", name = "Timer"})
    IO ()

-- | Marks an end time, so calls to 'GI.GLib.Structs.Timer.timerElapsed' will return the
-- difference between this end time and the start time.
timerStop ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Timer
    -- ^ /@timer@/: a t'GI.GLib.Structs.Timer.Timer'.
    -> m ()
timerStop :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Timer -> m ()
timerStop Timer
timer = 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 Timer
timer' <- Timer -> IO (Ptr Timer)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Timer
timer
    Ptr Timer -> IO ()
g_timer_stop Ptr Timer
timer'
    Timer -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Timer
timer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TimerStopMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod TimerStopMethodInfo Timer signature where
    overloadedMethod = timerStop

instance O.OverloadedMethodInfo TimerStopMethodInfo Timer where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.GLib.Structs.Timer.timerStop",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-glib-2.0.25/docs/GI-GLib-Structs-Timer.html#v:timerStop"
        }


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveTimerMethod (t :: Symbol) (o :: *) :: * where
    ResolveTimerMethod "continue" o = TimerContinueMethodInfo
    ResolveTimerMethod "destroy" o = TimerDestroyMethodInfo
    ResolveTimerMethod "elapsed" o = TimerElapsedMethodInfo
    ResolveTimerMethod "isActive" o = TimerIsActiveMethodInfo
    ResolveTimerMethod "reset" o = TimerResetMethodInfo
    ResolveTimerMethod "start" o = TimerStartMethodInfo
    ResolveTimerMethod "stop" o = TimerStopMethodInfo
    ResolveTimerMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveTimerMethod t Timer, O.OverloadedMethod info Timer p) => OL.IsLabel t (Timer -> 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 ~ ResolveTimerMethod t Timer, O.OverloadedMethod info Timer p, R.HasField t Timer p) => R.HasField t Timer p where
    getField = O.overloadedMethod @info

#endif

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

#endif