-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria

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

module GI.GtkSource.Callbacks
    ( 

 -- * Signals


-- ** SchedulerCallback #signal:SchedulerCallback#

    C_SchedulerCallback                     ,
    SchedulerCallback                       ,
    SchedulerCallback_WithClosures          ,
    drop_closures_SchedulerCallback         ,
    dynamic_SchedulerCallback               ,
    genClosure_SchedulerCallback            ,
    mk_SchedulerCallback                    ,
    noSchedulerCallback                     ,
    noSchedulerCallback_WithClosures        ,
    wrap_SchedulerCallback                  ,




    ) 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


-- callback SchedulerCallback
{- Callable
  { returnType = Just (TBasicType TBoolean)
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation
        { rawDocText =
            Just
              "%TRUE if there is more work to process, otherwise %FALSE and the\n  handler is unregistered."
        , sinceVersion = Nothing
        }
  , args =
      [ Arg
          { argCName = "deadline"
          , argType = TBasicType TInt64
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "the time the callback should complete by"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , argCallbackUserData = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "user_data"
          , argType = TBasicType TPtr
          , direction = DirectionIn
          , mayBeNull = True
          , argDoc =
              Documentation
                { rawDocText =
                    Just "closure data provided when registering callback"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , argCallbackUserData = True
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "This function is called incrementally to process additional background work.\nA deadline is provided which can be checked using [func@GLib.get_monotonic_time] so\nthat additional work can be processed each frame.\n\nThis is useful for situations where you are incrementally performing\nbackground work such as spell checking or semantic syntax highlighting."
        , sinceVersion = Just "5.2"
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_SchedulerCallback =
    Int64 ->
    Ptr () ->
    IO CInt

-- Args: [ Arg
--           { argCName = "deadline"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the time the callback should complete by"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "closure data provided when registering callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_SchedulerCallback :: FunPtr C_SchedulerCallback -> C_SchedulerCallback

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_SchedulerCallback ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_SchedulerCallback
    -> Int64
    -- ^ /@deadline@/: the time the callback should complete by
    -> Ptr ()
    -- ^ /@userData@/: closure data provided when registering callback
    -> m Bool
    -- ^ __Returns:__ 'P.True' if there is more work to process, otherwise 'P.False' and the
    --   handler is unregistered.
dynamic_SchedulerCallback :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_SchedulerCallback -> Int64 -> Ptr () -> m Bool
dynamic_SchedulerCallback FunPtr C_SchedulerCallback
__funPtr Int64
deadline Ptr ()
userData = IO Bool -> m Bool
forall a. IO a -> m a
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
    CInt
result <- (FunPtr C_SchedulerCallback -> C_SchedulerCallback
__dynamic_C_SchedulerCallback FunPtr C_SchedulerCallback
__funPtr) Int64
deadline Ptr ()
userData
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

-- | Generate a function pointer callable from C code, from a `C_SchedulerCallback`.
foreign import ccall "wrapper"
    mk_SchedulerCallback :: C_SchedulerCallback -> IO (FunPtr C_SchedulerCallback)

-- | This function is called incrementally to process additional background work.
-- A deadline is provided which can be checked using 'GI.GLib.Functions.getMonotonicTime' so
-- that additional work can be processed each frame.
-- 
-- This is useful for situations where you are incrementally performing
-- background work such as spell checking or semantic syntax highlighting.
-- 
-- /Since: 5.2/
type SchedulerCallback =
    Int64
    -- ^ /@deadline@/: the time the callback should complete by
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if there is more work to process, otherwise 'P.False' and the
    --   handler is unregistered.

-- | A convenience synonym for @`Nothing` :: `Maybe` `SchedulerCallback`@.
noSchedulerCallback :: Maybe SchedulerCallback
noSchedulerCallback :: Maybe SchedulerCallback
noSchedulerCallback = Maybe SchedulerCallback
forall a. Maybe a
Nothing

-- | This function is called incrementally to process additional background work.
-- A deadline is provided which can be checked using 'GI.GLib.Functions.getMonotonicTime' so
-- that additional work can be processed each frame.
-- 
-- This is useful for situations where you are incrementally performing
-- background work such as spell checking or semantic syntax highlighting.
-- 
-- /Since: 5.2/
type SchedulerCallback_WithClosures =
    Int64
    -- ^ /@deadline@/: the time the callback should complete by
    -> Ptr ()
    -- ^ /@userData@/: closure data provided when registering callback
    -> IO Bool
    -- ^ __Returns:__ 'P.True' if there is more work to process, otherwise 'P.False' and the
    --   handler is unregistered.

-- | A convenience synonym for @`Nothing` :: `Maybe` `SchedulerCallback_WithClosures`@.
noSchedulerCallback_WithClosures :: Maybe SchedulerCallback_WithClosures
noSchedulerCallback_WithClosures :: Maybe SchedulerCallback_WithClosures
noSchedulerCallback_WithClosures = Maybe SchedulerCallback_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_SchedulerCallback :: SchedulerCallback -> SchedulerCallback_WithClosures
drop_closures_SchedulerCallback :: SchedulerCallback -> SchedulerCallback_WithClosures
drop_closures_SchedulerCallback SchedulerCallback
_f Int64
deadline Ptr ()
_ = SchedulerCallback
_f Int64
deadline

-- | Wrap the callback into a `GClosure`.
genClosure_SchedulerCallback :: MonadIO m => SchedulerCallback -> m (GClosure C_SchedulerCallback)
genClosure_SchedulerCallback :: forall (m :: * -> *).
MonadIO m =>
SchedulerCallback -> m (GClosure C_SchedulerCallback)
genClosure_SchedulerCallback SchedulerCallback
cb = IO (GClosure C_SchedulerCallback)
-> m (GClosure C_SchedulerCallback)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SchedulerCallback)
 -> m (GClosure C_SchedulerCallback))
-> IO (GClosure C_SchedulerCallback)
-> m (GClosure C_SchedulerCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: SchedulerCallback_WithClosures
cb' = SchedulerCallback -> SchedulerCallback_WithClosures
drop_closures_SchedulerCallback SchedulerCallback
cb
    let cb'' :: C_SchedulerCallback
cb'' = Maybe (Ptr (FunPtr C_SchedulerCallback))
-> SchedulerCallback_WithClosures -> C_SchedulerCallback
wrap_SchedulerCallback Maybe (Ptr (FunPtr C_SchedulerCallback))
forall a. Maybe a
Nothing SchedulerCallback_WithClosures
cb'
    C_SchedulerCallback -> IO (FunPtr C_SchedulerCallback)
mk_SchedulerCallback C_SchedulerCallback
cb'' IO (FunPtr C_SchedulerCallback)
-> (FunPtr C_SchedulerCallback
    -> IO (GClosure C_SchedulerCallback))
-> IO (GClosure C_SchedulerCallback)
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SchedulerCallback -> IO (GClosure C_SchedulerCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SchedulerCallback` into a `C_SchedulerCallback`.
wrap_SchedulerCallback :: 
    Maybe (Ptr (FunPtr C_SchedulerCallback)) ->
    SchedulerCallback_WithClosures ->
    C_SchedulerCallback
wrap_SchedulerCallback :: Maybe (Ptr (FunPtr C_SchedulerCallback))
-> SchedulerCallback_WithClosures -> C_SchedulerCallback
wrap_SchedulerCallback Maybe (Ptr (FunPtr C_SchedulerCallback))
gi'funptrptr SchedulerCallback_WithClosures
gi'cb Int64
deadline Ptr ()
userData = do
    Bool
result <- SchedulerCallback_WithClosures
gi'cb  Int64
deadline Ptr ()
userData
    Maybe (Ptr (FunPtr C_SchedulerCallback)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_SchedulerCallback))
gi'funptrptr
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
result
    CInt -> IO CInt
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'