{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.Resource
(
Resource(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveResourceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ResourceEnumerateChildrenMethodInfo ,
#endif
resourceEnumerateChildren ,
#if defined(ENABLE_OVERLOADING)
ResourceGetInfoMethodInfo ,
#endif
resourceGetInfo ,
resourceLoad ,
#if defined(ENABLE_OVERLOADING)
ResourceLookupDataMethodInfo ,
#endif
resourceLookupData ,
resourceNewFromData ,
#if defined(ENABLE_OVERLOADING)
ResourceOpenStreamMethodInfo ,
#endif
resourceOpenStream ,
#if defined(ENABLE_OVERLOADING)
ResourceRefMethodInfo ,
#endif
resourceRef ,
#if defined(ENABLE_OVERLOADING)
ResourceUnrefMethodInfo ,
#endif
resourceUnref ,
) 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
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
#else
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
#endif
newtype Resource = Resource (SP.ManagedPtr Resource)
deriving (Resource -> Resource -> Bool
(Resource -> Resource -> Bool)
-> (Resource -> Resource -> Bool) -> Eq Resource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Resource -> Resource -> Bool
== :: Resource -> Resource -> Bool
$c/= :: Resource -> Resource -> Bool
/= :: Resource -> Resource -> Bool
Eq)
instance SP.ManagedPtrNewtype Resource where
toManagedPtr :: Resource -> ManagedPtr Resource
toManagedPtr (Resource ManagedPtr Resource
p) = ManagedPtr Resource
p
foreign import ccall "g_resource_get_type" c_g_resource_get_type ::
IO GType
type instance O.ParentTypes Resource = '[]
instance O.HasParentTypes Resource
instance B.Types.TypedObject Resource where
glibType :: IO GType
glibType = IO GType
c_g_resource_get_type
instance B.Types.GBoxed Resource
instance B.GValue.IsGValue (Maybe Resource) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_resource_get_type
gvalueSet_ :: Ptr GValue -> Maybe Resource -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Resource
P.Nothing = Ptr GValue -> Ptr Resource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Resource
forall a. Ptr a
FP.nullPtr :: FP.Ptr Resource)
gvalueSet_ Ptr GValue
gv (P.Just Resource
obj) = Resource -> (Ptr Resource -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Resource
obj (Ptr GValue -> Ptr Resource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Resource)
gvalueGet_ Ptr GValue
gv = do
Ptr Resource
ptr <- Ptr GValue -> IO (Ptr Resource)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Resource)
if Ptr Resource
ptr Ptr Resource -> Ptr Resource -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Resource
forall a. Ptr a
FP.nullPtr
then Resource -> Maybe Resource
forall a. a -> Maybe a
P.Just (Resource -> Maybe Resource) -> IO Resource -> IO (Maybe Resource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Resource -> Resource
Resource Ptr Resource
ptr
else Maybe Resource -> IO (Maybe Resource)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Resource
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Resource
type instance O.AttributeList Resource = ResourceAttributeList
type ResourceAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "g_resource_new_from_data" g_resource_new_from_data ::
Ptr GLib.Bytes.Bytes ->
Ptr (Ptr GError) ->
IO (Ptr Resource)
resourceNewFromData ::
(B.CallStack.HasCallStack, MonadIO m) =>
GLib.Bytes.Bytes
-> m Resource
resourceNewFromData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bytes -> m Resource
resourceNewFromData Bytes
data_ = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
Ptr Bytes
data_' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
data_
IO Resource -> IO () -> IO Resource
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Resource
result <- (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource))
-> (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a b. (a -> b) -> a -> b
$ Ptr Bytes -> Ptr (Ptr GError) -> IO (Ptr Resource)
g_resource_new_from_data Ptr Bytes
data_'
Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceNewFromData" Ptr Resource
result
Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
data_
Resource -> IO Resource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_resource_enumerate_children" g_resource_enumerate_children ::
Ptr Resource ->
CString ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr CString)
resourceEnumerateChildren ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> T.Text
-> [Gio.Flags.ResourceLookupFlags]
-> m [T.Text]
resourceEnumerateChildren :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m [Text]
resourceEnumerateChildren Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
CString
path' <- Text -> IO CString
textToCString Text
path
let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
IO [Text] -> IO () -> IO [Text]
forall a b. IO a -> IO b -> IO a
onException (do
Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr CString)
g_resource_enumerate_children Ptr Resource
resource' CString
path' CUInt
lookupFlags'
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceEnumerateChildren" Ptr CString
result
[Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
[Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
)
#if defined(ENABLE_OVERLOADING)
data ResourceEnumerateChildrenMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m [T.Text]), MonadIO m) => O.OverloadedMethod ResourceEnumerateChildrenMethodInfo Resource signature where
overloadedMethod = resourceEnumerateChildren
instance O.OverloadedMethodInfo ResourceEnumerateChildrenMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceEnumerateChildren",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceEnumerateChildren"
})
#endif
foreign import ccall "g_resource_get_info" g_resource_get_info ::
Ptr Resource ->
CString ->
CUInt ->
Ptr FCT.CSize ->
Ptr Word32 ->
Ptr (Ptr GError) ->
IO CInt
resourceGetInfo ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> T.Text
-> [Gio.Flags.ResourceLookupFlags]
-> m ((FCT.CSize, Word32))
resourceGetInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m (CSize, Word32)
resourceGetInfo Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO (CSize, Word32) -> m (CSize, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (CSize, Word32) -> m (CSize, Word32))
-> IO (CSize, Word32) -> m (CSize, Word32)
forall a b. (a -> b) -> a -> b
$ do
Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
CString
path' <- Text -> IO CString
textToCString Text
path
let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
Ptr CSize
size <- IO (Ptr CSize)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr FCT.CSize)
Ptr Word32
flags <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
IO (CSize, Word32) -> IO () -> IO (CSize, Word32)
forall a b. IO a -> IO b -> IO a
onException (do
CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString
-> CUInt
-> Ptr CSize
-> Ptr Word32
-> Ptr (Ptr GError)
-> IO CInt
g_resource_get_info Ptr Resource
resource' CString
path' CUInt
lookupFlags' Ptr CSize
size Ptr Word32
flags
CSize
size' <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
size
Word32
flags' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
flags
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
size
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
flags
(CSize, Word32) -> IO (CSize, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSize
size', Word32
flags')
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
size
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
flags
)
#if defined(ENABLE_OVERLOADING)
data ResourceGetInfoMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m ((FCT.CSize, Word32))), MonadIO m) => O.OverloadedMethod ResourceGetInfoMethodInfo Resource signature where
overloadedMethod = resourceGetInfo
instance O.OverloadedMethodInfo ResourceGetInfoMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceGetInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceGetInfo"
})
#endif
foreign import ccall "g_resource_lookup_data" g_resource_lookup_data ::
Ptr Resource ->
CString ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr GLib.Bytes.Bytes)
resourceLookupData ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> T.Text
-> [Gio.Flags.ResourceLookupFlags]
-> m GLib.Bytes.Bytes
resourceLookupData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m Bytes
resourceLookupData Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
CString
path' <- Text -> IO CString
textToCString Text
path
let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
IO Bytes -> IO () -> IO Bytes
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Bytes
result <- (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes))
-> (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Bytes)
g_resource_lookup_data Ptr Resource
resource' CString
path' CUInt
lookupFlags'
Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceLookupData" Ptr Bytes
result
Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
Bytes -> IO Bytes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
)
#if defined(ENABLE_OVERLOADING)
data ResourceLookupDataMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m GLib.Bytes.Bytes), MonadIO m) => O.OverloadedMethod ResourceLookupDataMethodInfo Resource signature where
overloadedMethod = resourceLookupData
instance O.OverloadedMethodInfo ResourceLookupDataMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceLookupData",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceLookupData"
})
#endif
foreign import ccall "g_resource_open_stream" g_resource_open_stream ::
Ptr Resource ->
CString ->
CUInt ->
Ptr (Ptr GError) ->
IO (Ptr Gio.InputStream.InputStream)
resourceOpenStream ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> T.Text
-> [Gio.Flags.ResourceLookupFlags]
-> m Gio.InputStream.InputStream
resourceOpenStream :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m InputStream
resourceOpenStream Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO InputStream -> m InputStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
CString
path' <- Text -> IO CString
textToCString Text
path
let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
IO InputStream -> IO () -> IO InputStream
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 Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr InputStream)
g_resource_open_stream Ptr Resource
resource' CString
path' CUInt
lookupFlags'
Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceOpenStream" 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
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
InputStream -> IO InputStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
)
#if defined(ENABLE_OVERLOADING)
data ResourceOpenStreamMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m Gio.InputStream.InputStream), MonadIO m) => O.OverloadedMethod ResourceOpenStreamMethodInfo Resource signature where
overloadedMethod = resourceOpenStream
instance O.OverloadedMethodInfo ResourceOpenStreamMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceOpenStream",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceOpenStream"
})
#endif
foreign import ccall "g_resource_ref" g_resource_ref ::
Ptr Resource ->
IO (Ptr Resource)
resourceRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> m Resource
resourceRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> m Resource
resourceRef Resource
resource = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
Ptr Resource
result <- Ptr Resource -> IO (Ptr Resource)
g_resource_ref Ptr Resource
resource'
Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceRef" Ptr Resource
result
Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
Resource -> IO Resource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'
#if defined(ENABLE_OVERLOADING)
data ResourceRefMethodInfo
instance (signature ~ (m Resource), MonadIO m) => O.OverloadedMethod ResourceRefMethodInfo Resource signature where
overloadedMethod = resourceRef
instance O.OverloadedMethodInfo ResourceRefMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceRef"
})
#endif
foreign import ccall "g_resource_unref" g_resource_unref ::
Ptr Resource ->
IO ()
resourceUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Resource
-> m ()
resourceUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Resource -> m ()
resourceUnref Resource
resource = 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 Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
Ptr Resource -> IO ()
g_resource_unref Ptr Resource
resource'
Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ResourceUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ResourceUnrefMethodInfo Resource signature where
overloadedMethod = resourceUnref
instance O.OverloadedMethodInfo ResourceUnrefMethodInfo Resource where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceUnref"
})
#endif
foreign import ccall "g_resource_load" g_resource_load ::
CString ->
Ptr (Ptr GError) ->
IO (Ptr Resource)
resourceLoad ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Char]
-> m Resource
resourceLoad :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[Char] -> m Resource
resourceLoad [Char]
filename = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
IO Resource -> IO () -> IO Resource
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Resource
result <- (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource))
-> (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Resource)
g_resource_load CString
filename'
Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"resourceLoad" Ptr Resource
result
Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
Resource -> IO Resource
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
)
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveResourceMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveResourceMethod "enumerateChildren" o = ResourceEnumerateChildrenMethodInfo
ResolveResourceMethod "lookupData" o = ResourceLookupDataMethodInfo
ResolveResourceMethod "openStream" o = ResourceOpenStreamMethodInfo
ResolveResourceMethod "ref" o = ResourceRefMethodInfo
ResolveResourceMethod "unref" o = ResourceUnrefMethodInfo
ResolveResourceMethod "getInfo" o = ResourceGetInfoMethodInfo
ResolveResourceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveResourceMethod t Resource, O.OverloadedMethod info Resource p) => OL.IsLabel t (Resource -> 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 ~ ResolveResourceMethod t Resource, O.OverloadedMethod info Resource p, R.HasField t Resource p) => R.HasField t Resource p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveResourceMethod t Resource, O.OverloadedMethodInfo info Resource) => OL.IsLabel t (O.MethodProxy info Resource) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif