-- | 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.Keybinder.Callbacks
    ( 

 -- * Signals


-- ** Handler #signal:Handler#

    C_Handler                               ,
    Handler                                 ,
    Handler_WithClosures                    ,
    drop_closures_Handler                   ,
    dynamic_Handler                         ,
    genClosure_Handler                      ,
    mk_Handler                              ,
    noHandler                               ,
    noHandler_WithClosures                  ,
    wrap_Handler                            ,




    ) 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

-- callback Handler
{- Callable
  { returnType = Nothing
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , args =
      [ Arg
          { argCName = "keystring"
          , argType = TBasicType TUTF8
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation { rawDocText = Nothing , 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 = Nothing , sinceVersion = Nothing }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , argCallbackUserData = True
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_Handler =
    CString ->
    Ptr () ->
    IO ()

-- Args: [ Arg
--           { argCName = "keystring"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_Handler :: FunPtr C_Handler -> C_Handler

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_Handler ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_Handler
    -> T.Text
    -> Ptr ()
    -> m ()
dynamic_Handler :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_Handler -> Text -> Ptr () -> m ()
dynamic_Handler FunPtr C_Handler
__funPtr Text
keystring Ptr ()
userData = 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
    CString
keystring' <- Text -> IO CString
textToCString Text
keystring
    (FunPtr C_Handler -> C_Handler
__dynamic_C_Handler FunPtr C_Handler
__funPtr) CString
keystring' Ptr ()
userData
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
keystring'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | /No description available in the introspection data./
type Handler =
    T.Text
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `Handler`@.
noHandler :: Maybe Handler
noHandler :: Maybe Handler
noHandler = Maybe Handler
forall a. Maybe a
Nothing

-- | /No description available in the introspection data./
type Handler_WithClosures =
    T.Text
    -> Ptr ()
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `Handler_WithClosures`@.
noHandler_WithClosures :: Maybe Handler_WithClosures
noHandler_WithClosures :: Maybe Handler_WithClosures
noHandler_WithClosures = Maybe Handler_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_Handler :: Handler -> Handler_WithClosures
drop_closures_Handler :: Handler -> Handler_WithClosures
drop_closures_Handler Handler
_f Text
keystring Ptr ()
_ = Handler
_f Text
keystring

-- | Wrap the callback into a `GClosure`.
genClosure_Handler :: MonadIO m => Handler -> m (GClosure C_Handler)
genClosure_Handler :: forall (m :: * -> *).
MonadIO m =>
Handler -> m (GClosure C_Handler)
genClosure_Handler Handler
cb = IO (GClosure C_Handler) -> m (GClosure C_Handler)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_Handler) -> m (GClosure C_Handler))
-> IO (GClosure C_Handler) -> m (GClosure C_Handler)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: Handler_WithClosures
cb' = Handler -> Handler_WithClosures
drop_closures_Handler Handler
cb
    let cb'' :: C_Handler
cb'' = Maybe (Ptr (FunPtr C_Handler)) -> Handler_WithClosures -> C_Handler
wrap_Handler Maybe (Ptr (FunPtr C_Handler))
forall a. Maybe a
Nothing Handler_WithClosures
cb'
    C_Handler -> IO (FunPtr C_Handler)
mk_Handler C_Handler
cb'' IO (FunPtr C_Handler)
-> (FunPtr C_Handler -> IO (GClosure C_Handler))
-> IO (GClosure C_Handler)
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_Handler -> IO (GClosure C_Handler)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `Handler` into a `C_Handler`.
wrap_Handler :: 
    Maybe (Ptr (FunPtr C_Handler)) ->
    Handler_WithClosures ->
    C_Handler
wrap_Handler :: Maybe (Ptr (FunPtr C_Handler)) -> Handler_WithClosures -> C_Handler
wrap_Handler Maybe (Ptr (FunPtr C_Handler))
gi'funptrptr Handler_WithClosures
gi'cb CString
keystring Ptr ()
userData = do
    Text
keystring' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
keystring
    Handler_WithClosures
gi'cb  Text
keystring' Ptr ()
userData
    Maybe (Ptr (FunPtr C_Handler)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_Handler))
gi'funptrptr