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

 -- * Signals


-- ** LoadSurfaceFunction #signal:LoadSurfaceFunction#

    C_LoadSurfaceFunction                   ,
    LoadSurfaceFunction                     ,
    dynamic_LoadSurfaceFunction             ,
    genClosure_LoadSurfaceFunction          ,
    mk_LoadSurfaceFunction                  ,
    noLoadSurfaceFunction                   ,
    wrap_LoadSurfaceFunction                ,




    ) 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 GI.Cairo.Structs.Surface as Cairo.Surface

-- callback LoadSurfaceFunction
{- Callable
  { returnType =
      Just (TInterface Name { namespace = "cairo" , name = "Surface" })
  , returnMayBeNull = False
  , returnTransfer = TransferEverything
  , returnDocumentation =
      Documentation
        { rawDocText =
            Just
              "it should return a <classname>cairo_surface_t</classname> of @icon_name\nat size @size, or %NULL if no icon for @icon_name at size @size could be\nloaded."
        , sinceVersion = Nothing
        }
  , args =
      [ Arg
          { argCName = "icon_name"
          , argType = TBasicType TUTF8
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText =
                    Just
                      "an icon name as in the Icon field in a .desktop file for the\nicon to load."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "size"
          , argType = TBasicType TInt
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "the desired icon size."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "flags"
          , argType = TBasicType TUInt
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "not defined to do anything yet."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "data"
          , argType = TBasicType TPtr
          , direction = DirectionIn
          , mayBeNull = True
          , argDoc =
              Documentation
                { rawDocText =
                    Just
                      "data passed to the function, set when the #WnckLoadSurfaceFunction has\nbeen set for the #WnckTasklist."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "Specifies the type of function passed to wnck_tasklist_set_icon_loader()."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_LoadSurfaceFunction =
    CString ->
    Int32 ->
    Word32 ->
    Ptr () ->
    IO (Ptr Cairo.Surface.Surface)

-- Args: [ Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an icon name as in the Icon field in a .desktop file for the\nicon to load."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desired icon size."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "not defined to do anything yet."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "data passed to the function, set when the #WnckLoadSurfaceFunction has\nbeen set for the #WnckTasklist."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Surface" })
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_LoadSurfaceFunction :: FunPtr C_LoadSurfaceFunction -> C_LoadSurfaceFunction

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_LoadSurfaceFunction ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_LoadSurfaceFunction
    -> T.Text
    -- ^ /@iconName@/: an icon name as in the Icon field in a .desktop file for the
    -- icon to load.
    -> Int32
    -- ^ /@size@/: the desired icon size.
    -> Word32
    -- ^ /@flags@/: not defined to do anything yet.
    -> Ptr ()
    -- ^ /@data@/: data passed to the function, set when the t'GI.Wnck.Callbacks.LoadSurfaceFunction' has
    -- been set for the t'GI.Wnck.Objects.Tasklist.Tasklist'.
    -> m Cairo.Surface.Surface
    -- ^ __Returns:__ it should return a \<classname>cairo_surface_t\<\/classname> of /@iconName@/
    -- at size /@size@/, or 'P.Nothing' if no icon for /@iconName@/ at size /@size@/ could be
    -- loaded.
dynamic_LoadSurfaceFunction :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr C_LoadSurfaceFunction
-> Text -> Int32 -> Word32 -> Ptr () -> m Surface
dynamic_LoadSurfaceFunction FunPtr C_LoadSurfaceFunction
__funPtr Text
iconName Int32
size Word32
flags Ptr ()
data_ = IO Surface -> m Surface
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Surface -> m Surface) -> IO Surface -> m Surface
forall a b. (a -> b) -> a -> b
$ do
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr Surface
result <- (FunPtr C_LoadSurfaceFunction -> C_LoadSurfaceFunction
__dynamic_C_LoadSurfaceFunction FunPtr C_LoadSurfaceFunction
__funPtr) CString
iconName' Int32
size Word32
flags Ptr ()
data_
    Text -> Ptr Surface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"loadSurfaceFunction" Ptr Surface
result
    Surface
result' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Surface -> Surface
Cairo.Surface.Surface) Ptr Surface
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    Surface -> IO Surface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result'

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

-- | Specifies the type of function passed to @/wnck_tasklist_set_icon_loader()/@.
type LoadSurfaceFunction =
    T.Text
    -- ^ /@iconName@/: an icon name as in the Icon field in a .desktop file for the
    -- icon to load.
    -> Int32
    -- ^ /@size@/: the desired icon size.
    -> Word32
    -- ^ /@flags@/: not defined to do anything yet.
    -> Ptr ()
    -- ^ /@data@/: data passed to the function, set when the t'GI.Wnck.Callbacks.LoadSurfaceFunction' has
    -- been set for the t'GI.Wnck.Objects.Tasklist.Tasklist'.
    -> IO Cairo.Surface.Surface
    -- ^ __Returns:__ it should return a \<classname>cairo_surface_t\<\/classname> of /@iconName@/
    -- at size /@size@/, or 'P.Nothing' if no icon for /@iconName@/ at size /@size@/ could be
    -- loaded.

-- | A convenience synonym for @`Nothing` :: `Maybe` `LoadSurfaceFunction`@.
noLoadSurfaceFunction :: Maybe LoadSurfaceFunction
noLoadSurfaceFunction :: Maybe LoadSurfaceFunction
noLoadSurfaceFunction = Maybe LoadSurfaceFunction
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_LoadSurfaceFunction :: MonadIO m => LoadSurfaceFunction -> m (GClosure C_LoadSurfaceFunction)
genClosure_LoadSurfaceFunction :: forall (m :: * -> *).
MonadIO m =>
LoadSurfaceFunction -> m (GClosure C_LoadSurfaceFunction)
genClosure_LoadSurfaceFunction LoadSurfaceFunction
cb = IO (GClosure C_LoadSurfaceFunction)
-> m (GClosure C_LoadSurfaceFunction)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_LoadSurfaceFunction)
 -> m (GClosure C_LoadSurfaceFunction))
-> IO (GClosure C_LoadSurfaceFunction)
-> m (GClosure C_LoadSurfaceFunction)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_LoadSurfaceFunction
cb' = Maybe (Ptr (FunPtr C_LoadSurfaceFunction))
-> LoadSurfaceFunction -> C_LoadSurfaceFunction
wrap_LoadSurfaceFunction Maybe (Ptr (FunPtr C_LoadSurfaceFunction))
forall a. Maybe a
Nothing LoadSurfaceFunction
cb
    C_LoadSurfaceFunction -> IO (FunPtr C_LoadSurfaceFunction)
mk_LoadSurfaceFunction C_LoadSurfaceFunction
cb' IO (FunPtr C_LoadSurfaceFunction)
-> (FunPtr C_LoadSurfaceFunction
    -> IO (GClosure C_LoadSurfaceFunction))
-> IO (GClosure C_LoadSurfaceFunction)
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_LoadSurfaceFunction -> IO (GClosure C_LoadSurfaceFunction)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `LoadSurfaceFunction` into a `C_LoadSurfaceFunction`.
wrap_LoadSurfaceFunction :: 
    Maybe (Ptr (FunPtr C_LoadSurfaceFunction)) ->
    LoadSurfaceFunction ->
    C_LoadSurfaceFunction
wrap_LoadSurfaceFunction :: Maybe (Ptr (FunPtr C_LoadSurfaceFunction))
-> LoadSurfaceFunction -> C_LoadSurfaceFunction
wrap_LoadSurfaceFunction Maybe (Ptr (FunPtr C_LoadSurfaceFunction))
gi'funptrptr LoadSurfaceFunction
gi'cb CString
iconName Int32
size Word32
flags Ptr ()
data_ = do
    Text
iconName' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
iconName
    Surface
result <- LoadSurfaceFunction
gi'cb  Text
iconName' Int32
size Word32
flags Ptr ()
data_
    Maybe (Ptr (FunPtr C_LoadSurfaceFunction)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_LoadSurfaceFunction))
gi'funptrptr
    Ptr Surface
result' <- Surface -> IO (Ptr Surface)
forall a. (HasCallStack, GBoxed a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed Surface
result
    Ptr Surface -> IO (Ptr Surface)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Surface
result'