{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Extends the t'GI.Gio.Interfaces.Icon.Icon' interface and adds the ability to
-- load icons from streams.

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

module GI.Gio.Interfaces.LoadableIcon
    ( 

-- * Exported types
    LoadableIcon(..)                        ,
    IsLoadableIcon                          ,
    toLoadableIcon                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [equal]("GI.Gio.Interfaces.Icon#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [load]("GI.Gio.Interfaces.LoadableIcon#g:method:load"), [loadAsync]("GI.Gio.Interfaces.LoadableIcon#g:method:loadAsync"), [loadFinish]("GI.Gio.Interfaces.LoadableIcon#g:method:loadFinish"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [serialize]("GI.Gio.Interfaces.Icon#g:method:serialize"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [toString]("GI.Gio.Interfaces.Icon#g:method:toString"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveLoadableIconMethod               ,
#endif

-- ** load #method:load#

#if defined(ENABLE_OVERLOADING)
    LoadableIconLoadMethodInfo              ,
#endif
    loadableIconLoad                        ,


-- ** loadAsync #method:loadAsync#

#if defined(ENABLE_OVERLOADING)
    LoadableIconLoadAsyncMethodInfo         ,
#endif
    loadableIconLoadAsync                   ,


-- ** loadFinish #method:loadFinish#

#if defined(ENABLE_OVERLOADING)
    LoadableIconLoadFinishMethodInfo        ,
#endif
    loadableIconLoadFinish                  ,




    ) 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.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.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream

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

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

foreign import ccall "g_loadable_icon_get_type"
    c_g_loadable_icon_get_type :: IO B.Types.GType

instance B.Types.TypedObject LoadableIcon where
    glibType :: IO GType
glibType = IO GType
c_g_loadable_icon_get_type

instance B.Types.GObject LoadableIcon

-- | Type class for types which can be safely cast to `LoadableIcon`, for instance with `toLoadableIcon`.
class (SP.GObject o, O.IsDescendantOf LoadableIcon o) => IsLoadableIcon o
instance (SP.GObject o, O.IsDescendantOf LoadableIcon o) => IsLoadableIcon o

instance O.HasParentTypes LoadableIcon
type instance O.ParentTypes LoadableIcon = '[Gio.Icon.Icon, GObject.Object.Object]

-- | Cast to `LoadableIcon`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toLoadableIcon :: (MIO.MonadIO m, IsLoadableIcon o) => o -> m LoadableIcon
toLoadableIcon :: forall (m :: * -> *) o.
(MonadIO m, IsLoadableIcon o) =>
o -> m LoadableIcon
toLoadableIcon = IO LoadableIcon -> m LoadableIcon
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO LoadableIcon -> m LoadableIcon)
-> (o -> IO LoadableIcon) -> o -> m LoadableIcon
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr LoadableIcon -> LoadableIcon) -> o -> IO LoadableIcon
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr LoadableIcon -> LoadableIcon
LoadableIcon

-- | Convert 'LoadableIcon' 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 LoadableIcon) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_loadable_icon_get_type
    gvalueSet_ :: Ptr GValue -> Maybe LoadableIcon -> IO ()
gvalueSet_ Ptr GValue
gv Maybe LoadableIcon
P.Nothing = Ptr GValue -> Ptr LoadableIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr LoadableIcon
forall a. Ptr a
FP.nullPtr :: FP.Ptr LoadableIcon)
    gvalueSet_ Ptr GValue
gv (P.Just LoadableIcon
obj) = LoadableIcon -> (Ptr LoadableIcon -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr LoadableIcon
obj (Ptr GValue -> Ptr LoadableIcon -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe LoadableIcon)
gvalueGet_ Ptr GValue
gv = do
        Ptr LoadableIcon
ptr <- Ptr GValue -> IO (Ptr LoadableIcon)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr LoadableIcon)
        if Ptr LoadableIcon
ptr Ptr LoadableIcon -> Ptr LoadableIcon -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr LoadableIcon
forall a. Ptr a
FP.nullPtr
        then LoadableIcon -> Maybe LoadableIcon
forall a. a -> Maybe a
P.Just (LoadableIcon -> Maybe LoadableIcon)
-> IO LoadableIcon -> IO (Maybe LoadableIcon)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr LoadableIcon -> LoadableIcon)
-> Ptr LoadableIcon -> IO LoadableIcon
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr LoadableIcon -> LoadableIcon
LoadableIcon Ptr LoadableIcon
ptr
        else Maybe LoadableIcon -> IO (Maybe LoadableIcon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LoadableIcon
forall a. Maybe a
P.Nothing
        
    

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveLoadableIconMethod (t :: Symbol) (o :: *) :: * where
    ResolveLoadableIconMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveLoadableIconMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveLoadableIconMethod "equal" o = Gio.Icon.IconEqualMethodInfo
    ResolveLoadableIconMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveLoadableIconMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveLoadableIconMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveLoadableIconMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveLoadableIconMethod "load" o = LoadableIconLoadMethodInfo
    ResolveLoadableIconMethod "loadAsync" o = LoadableIconLoadAsyncMethodInfo
    ResolveLoadableIconMethod "loadFinish" o = LoadableIconLoadFinishMethodInfo
    ResolveLoadableIconMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveLoadableIconMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveLoadableIconMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveLoadableIconMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveLoadableIconMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveLoadableIconMethod "serialize" o = Gio.Icon.IconSerializeMethodInfo
    ResolveLoadableIconMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveLoadableIconMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveLoadableIconMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveLoadableIconMethod "toString" o = Gio.Icon.IconToStringMethodInfo
    ResolveLoadableIconMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveLoadableIconMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveLoadableIconMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveLoadableIconMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveLoadableIconMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveLoadableIconMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveLoadableIconMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveLoadableIconMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveLoadableIconMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method LoadableIcon::load
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "LoadableIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GLoadableIcon." , 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 "an integer." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a location to store the type of the loaded\nicon, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional #GCancellable object, %NULL to\nignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "InputStream" })
-- throws : True
-- Skip return : False

foreign import ccall "g_loadable_icon_load" g_loadable_icon_load :: 
    Ptr LoadableIcon ->                     -- icon : TInterface (Name {namespace = "Gio", name = "LoadableIcon"})
    Int32 ->                                -- size : TBasicType TInt
    Ptr CString ->                          -- type : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.InputStream.InputStream)

-- | Loads a loadable icon. For the asynchronous version of this function,
-- see 'GI.Gio.Interfaces.LoadableIcon.loadableIconLoadAsync'.
loadableIconLoad ::
    (B.CallStack.HasCallStack, MonadIO m, IsLoadableIcon a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon'.
    -> Int32
    -- ^ /@size@/: an integer.
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to
    -- ignore.
    -> m ((Gio.InputStream.InputStream, T.Text))
    -- ^ __Returns:__ a t'GI.Gio.Objects.InputStream.InputStream' to read the icon from. /(Can throw 'Data.GI.Base.GError.GError')/
loadableIconLoad :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsLoadableIcon a, IsCancellable b) =>
a -> Int32 -> Maybe b -> m (InputStream, Text)
loadableIconLoad a
icon Int32
size Maybe b
cancellable = IO (InputStream, Text) -> m (InputStream, Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (InputStream, Text) -> m (InputStream, Text))
-> IO (InputStream, Text) -> m (InputStream, Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr LoadableIcon
icon' <- a -> IO (Ptr LoadableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr CString
type_ <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (InputStream, Text) -> IO () -> IO (InputStream, Text)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr InputStream
result <- (Ptr (Ptr GError) -> IO (Ptr InputStream)) -> IO (Ptr InputStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr InputStream))
 -> IO (Ptr InputStream))
-> (Ptr (Ptr GError) -> IO (Ptr InputStream))
-> IO (Ptr InputStream)
forall a b. (a -> b) -> a -> b
$ Ptr LoadableIcon
-> Int32
-> Ptr CString
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr InputStream)
g_loadable_icon_load Ptr LoadableIcon
icon' Int32
size Ptr CString
type_ Ptr Cancellable
maybeCancellable
        Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"loadableIconLoad" Ptr InputStream
result
        InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
        CString
type_' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
type_
        Text
type_'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
type_'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
type_
        (InputStream, Text) -> IO (InputStream, Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (InputStream
result', Text
type_'')
     ) (do
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
type_
     )

#if defined(ENABLE_OVERLOADING)
data LoadableIconLoadMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> m ((Gio.InputStream.InputStream, T.Text))), MonadIO m, IsLoadableIcon a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod LoadableIconLoadMethodInfo a signature where
    overloadedMethod = loadableIconLoad

instance O.OverloadedMethodInfo LoadableIconLoadMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.LoadableIcon.loadableIconLoad",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-LoadableIcon.html#v:loadableIconLoad"
        })


#endif

-- method LoadableIcon::load_async
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "LoadableIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GLoadableIcon." , 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 "an integer." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "optional #GCancellable object, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GAsyncReadyCallback to call when the\n           request is satisfied"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the data to pass to callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_loadable_icon_load_async" g_loadable_icon_load_async :: 
    Ptr LoadableIcon ->                     -- icon : TInterface (Name {namespace = "Gio", name = "LoadableIcon"})
    Int32 ->                                -- size : TBasicType TInt
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Loads an icon asynchronously. To finish this function, see
-- 'GI.Gio.Interfaces.LoadableIcon.loadableIconLoadFinish'. For the synchronous, blocking
-- version of this function, see 'GI.Gio.Interfaces.LoadableIcon.loadableIconLoad'.
loadableIconLoadAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsLoadableIcon a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon'.
    -> Int32
    -- ^ /@size@/: an integer.
    -> Maybe (b)
    -- ^ /@cancellable@/: optional t'GI.Gio.Objects.Cancellable.Cancellable' object, 'P.Nothing' to ignore.
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a t'GI.Gio.Callbacks.AsyncReadyCallback' to call when the
    --            request is satisfied
    -> m ()
loadableIconLoadAsync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsLoadableIcon a, IsCancellable b) =>
a -> Int32 -> Maybe b -> Maybe AsyncReadyCallback -> m ()
loadableIconLoadAsync a
icon Int32
size Maybe b
cancellable Maybe AsyncReadyCallback
callback = 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 LoadableIcon
icon' <- a -> IO (Ptr LoadableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr LoadableIcon
-> Int32
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
g_loadable_icon_load_async Ptr LoadableIcon
icon' Int32
size Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LoadableIconLoadAsyncMethodInfo
instance (signature ~ (Int32 -> Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsLoadableIcon a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod LoadableIconLoadAsyncMethodInfo a signature where
    overloadedMethod = loadableIconLoadAsync

instance O.OverloadedMethodInfo LoadableIconLoadAsyncMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.LoadableIcon.loadableIconLoadAsync",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-LoadableIcon.html#v:loadableIconLoadAsync"
        })


#endif

-- method LoadableIcon::load_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "icon"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "LoadableIcon" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GLoadableIcon." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAsyncResult." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a location to store the type of the loaded\n       icon, %NULL to ignore."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "InputStream" })
-- throws : True
-- Skip return : False

foreign import ccall "g_loadable_icon_load_finish" g_loadable_icon_load_finish :: 
    Ptr LoadableIcon ->                     -- icon : TInterface (Name {namespace = "Gio", name = "LoadableIcon"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- res : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr CString ->                          -- type : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.InputStream.InputStream)

-- | Finishes an asynchronous icon load started in 'GI.Gio.Interfaces.LoadableIcon.loadableIconLoadAsync'.
loadableIconLoadFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsLoadableIcon a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.LoadableIcon.LoadableIcon'.
    -> b
    -- ^ /@res@/: a t'GI.Gio.Interfaces.AsyncResult.AsyncResult'.
    -> m ((Gio.InputStream.InputStream, T.Text))
    -- ^ __Returns:__ a t'GI.Gio.Objects.InputStream.InputStream' to read the icon from. /(Can throw 'Data.GI.Base.GError.GError')/
loadableIconLoadFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsLoadableIcon a, IsAsyncResult b) =>
a -> b -> m (InputStream, Text)
loadableIconLoadFinish a
icon b
res = IO (InputStream, Text) -> m (InputStream, Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (InputStream, Text) -> m (InputStream, Text))
-> IO (InputStream, Text) -> m (InputStream, Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr LoadableIcon
icon' <- a -> IO (Ptr LoadableIcon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
icon
    Ptr AsyncResult
res' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
res
    Ptr CString
type_ <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    IO (InputStream, Text) -> IO () -> IO (InputStream, Text)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr InputStream
result <- (Ptr (Ptr GError) -> IO (Ptr InputStream)) -> IO (Ptr InputStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr InputStream))
 -> IO (Ptr InputStream))
-> (Ptr (Ptr GError) -> IO (Ptr InputStream))
-> IO (Ptr InputStream)
forall a b. (a -> b) -> a -> b
$ Ptr LoadableIcon
-> Ptr AsyncResult
-> Ptr CString
-> Ptr (Ptr GError)
-> IO (Ptr InputStream)
g_loadable_icon_load_finish Ptr LoadableIcon
icon' Ptr AsyncResult
res' Ptr CString
type_
        Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"loadableIconLoadFinish" Ptr InputStream
result
        InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
        CString
type_' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
type_
        Text
type_'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
type_'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
type_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
icon
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
res
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
type_
        (InputStream, Text) -> IO (InputStream, Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (InputStream
result', Text
type_'')
     ) (do
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
type_
     )

#if defined(ENABLE_OVERLOADING)
data LoadableIconLoadFinishMethodInfo
instance (signature ~ (b -> m ((Gio.InputStream.InputStream, T.Text))), MonadIO m, IsLoadableIcon a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod LoadableIconLoadFinishMethodInfo a signature where
    overloadedMethod = loadableIconLoadFinish

instance O.OverloadedMethodInfo LoadableIconLoadFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Interfaces.LoadableIcon.loadableIconLoadFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.30/docs/GI-Gio-Interfaces-LoadableIcon.html#v:loadableIconLoadFinish"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList LoadableIcon = LoadableIconSignalList
type LoadableIconSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif