{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Entry point for using GIO functionality.

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

module GI.Gio.Objects.Vfs
    ( 

-- * Exported types
    Vfs(..)                                 ,
    IsVfs                                   ,
    toVfs                                   ,


 -- * 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"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isActive]("GI.Gio.Objects.Vfs#g:method:isActive"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [parseName]("GI.Gio.Objects.Vfs#g:method:parseName"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [registerUriScheme]("GI.Gio.Objects.Vfs#g:method:registerUriScheme"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unregisterUriScheme]("GI.Gio.Objects.Vfs#g:method:unregisterUriScheme"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getFileForPath]("GI.Gio.Objects.Vfs#g:method:getFileForPath"), [getFileForUri]("GI.Gio.Objects.Vfs#g:method:getFileForUri"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSupportedUriSchemes]("GI.Gio.Objects.Vfs#g:method:getSupportedUriSchemes").
-- 
-- ==== 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)
    ResolveVfsMethod                        ,
#endif

-- ** getDefault #method:getDefault#

    vfsGetDefault                           ,


-- ** getFileForPath #method:getFileForPath#

#if defined(ENABLE_OVERLOADING)
    VfsGetFileForPathMethodInfo             ,
#endif
    vfsGetFileForPath                       ,


-- ** getFileForUri #method:getFileForUri#

#if defined(ENABLE_OVERLOADING)
    VfsGetFileForUriMethodInfo              ,
#endif
    vfsGetFileForUri                        ,


-- ** getLocal #method:getLocal#

    vfsGetLocal                             ,


-- ** getSupportedUriSchemes #method:getSupportedUriSchemes#

#if defined(ENABLE_OVERLOADING)
    VfsGetSupportedUriSchemesMethodInfo     ,
#endif
    vfsGetSupportedUriSchemes               ,


-- ** isActive #method:isActive#

#if defined(ENABLE_OVERLOADING)
    VfsIsActiveMethodInfo                   ,
#endif
    vfsIsActive                             ,


-- ** parseName #method:parseName#

#if defined(ENABLE_OVERLOADING)
    VfsParseNameMethodInfo                  ,
#endif
    vfsParseName                            ,


-- ** registerUriScheme #method:registerUriScheme#

#if defined(ENABLE_OVERLOADING)
    VfsRegisterUriSchemeMethodInfo          ,
#endif
    vfsRegisterUriScheme                    ,


-- ** unregisterUriScheme #method:unregisterUriScheme#

#if defined(ENABLE_OVERLOADING)
    VfsUnregisterUriSchemeMethodInfo        ,
#endif
    vfsUnregisterUriScheme                  ,




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

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

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

foreign import ccall "g_vfs_get_type"
    c_g_vfs_get_type :: IO B.Types.GType

instance B.Types.TypedObject Vfs where
    glibType :: IO GType
glibType = IO GType
c_g_vfs_get_type

instance B.Types.GObject Vfs

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

instance O.HasParentTypes Vfs
type instance O.ParentTypes Vfs = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveVfsMethod (t :: Symbol) (o :: *) :: * where
    ResolveVfsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveVfsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveVfsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveVfsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveVfsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveVfsMethod "isActive" o = VfsIsActiveMethodInfo
    ResolveVfsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveVfsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveVfsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveVfsMethod "parseName" o = VfsParseNameMethodInfo
    ResolveVfsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveVfsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveVfsMethod "registerUriScheme" o = VfsRegisterUriSchemeMethodInfo
    ResolveVfsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveVfsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveVfsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveVfsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveVfsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveVfsMethod "unregisterUriScheme" o = VfsUnregisterUriSchemeMethodInfo
    ResolveVfsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveVfsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveVfsMethod "getFileForPath" o = VfsGetFileForPathMethodInfo
    ResolveVfsMethod "getFileForUri" o = VfsGetFileForUriMethodInfo
    ResolveVfsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveVfsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveVfsMethod "getSupportedUriSchemes" o = VfsGetSupportedUriSchemesMethodInfo
    ResolveVfsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveVfsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveVfsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveVfsMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method Vfs::get_file_for_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing a VFS path."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_get_file_for_path" g_vfs_get_file_for_path :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    CString ->                              -- path : TBasicType TUTF8
    IO (Ptr Gio.File.File)

-- | Gets a t'GI.Gio.Interfaces.File.File' for /@path@/.
vfsGetFileForPath ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'.
    -> T.Text
    -- ^ /@path@/: a string containing a VFS path.
    -> m Gio.File.File
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.File.File'.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
vfsGetFileForPath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> Text -> m File
vfsGetFileForPath a
vfs Text
path = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr File
result <- Ptr Vfs -> CString -> IO (Ptr File)
g_vfs_get_file_for_path Ptr Vfs
vfs' CString
path'
    Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsGetFileForPath" Ptr File
result
    File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'

#if defined(ENABLE_OVERLOADING)
data VfsGetFileForPathMethodInfo
instance (signature ~ (T.Text -> m Gio.File.File), MonadIO m, IsVfs a) => O.OverloadedMethod VfsGetFileForPathMethodInfo a signature where
    overloadedMethod = vfsGetFileForPath

instance O.OverloadedMethodInfo VfsGetFileForPathMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsGetFileForPath",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsGetFileForPath"
        }


#endif

-- method Vfs::get_file_for_uri
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a#GVfs." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string containing a URI"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_get_file_for_uri" g_vfs_get_file_for_uri :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    CString ->                              -- uri : TBasicType TUTF8
    IO (Ptr Gio.File.File)

-- | Gets a t'GI.Gio.Interfaces.File.File' for /@uri@/.
-- 
-- This operation never fails, but the returned object
-- might not support any I\/O operation if the URI
-- is malformed or if the URI scheme is not supported.
vfsGetFileForUri ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: at'GI.Gio.Objects.Vfs.Vfs'.
    -> T.Text
    -- ^ /@uri@/: a string containing a URI
    -> m Gio.File.File
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.File.File'.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
vfsGetFileForUri :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> Text -> m File
vfsGetFileForUri a
vfs Text
uri = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CString
uri' <- Text -> IO CString
textToCString Text
uri
    Ptr File
result <- Ptr Vfs -> CString -> IO (Ptr File)
g_vfs_get_file_for_uri Ptr Vfs
vfs' CString
uri'
    Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsGetFileForUri" Ptr File
result
    File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
uri'
    File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'

#if defined(ENABLE_OVERLOADING)
data VfsGetFileForUriMethodInfo
instance (signature ~ (T.Text -> m Gio.File.File), MonadIO m, IsVfs a) => O.OverloadedMethod VfsGetFileForUriMethodInfo a signature where
    overloadedMethod = vfsGetFileForUri

instance O.OverloadedMethodInfo VfsGetFileForUriMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsGetFileForUri",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsGetFileForUri"
        }


#endif

-- method Vfs::get_supported_uri_schemes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_get_supported_uri_schemes" g_vfs_get_supported_uri_schemes :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    IO (Ptr CString)

-- | Gets a list of URI schemes supported by /@vfs@/.
vfsGetSupportedUriSchemes ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'.
    -> m [T.Text]
    -- ^ __Returns:__ a 'P.Nothing'-terminated array of strings.
    --     The returned array belongs to GIO and must
    --     not be freed or modified.
vfsGetSupportedUriSchemes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> m [Text]
vfsGetSupportedUriSchemes a
vfs = IO [Text] -> m [Text]
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 Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    Ptr CString
result <- Ptr Vfs -> IO (Ptr CString)
g_vfs_get_supported_uri_schemes Ptr Vfs
vfs'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsGetSupportedUriSchemes" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data VfsGetSupportedUriSchemesMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsVfs a) => O.OverloadedMethod VfsGetSupportedUriSchemesMethodInfo a signature where
    overloadedMethod = vfsGetSupportedUriSchemes

instance O.OverloadedMethodInfo VfsGetSupportedUriSchemesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsGetSupportedUriSchemes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsGetSupportedUriSchemes"
        }


#endif

-- method Vfs::is_active
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_is_active" g_vfs_is_active :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    IO CInt

-- | Checks if the VFS is active.
vfsIsActive ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if construction of the /@vfs@/ was successful
    --     and it is now active.
vfsIsActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> m Bool
vfsIsActive a
vfs = IO Bool -> m Bool
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
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CInt
result <- Ptr Vfs -> IO CInt
g_vfs_is_active Ptr Vfs
vfs'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VfsIsActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsVfs a) => O.OverloadedMethod VfsIsActiveMethodInfo a signature where
    overloadedMethod = vfsIsActive

instance O.OverloadedMethodInfo VfsIsActiveMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsIsActive",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsIsActive"
        }


#endif

-- method Vfs::parse_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parse_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string to be parsed by the VFS module."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "File" })
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_parse_name" g_vfs_parse_name :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    CString ->                              -- parse_name : TBasicType TUTF8
    IO (Ptr Gio.File.File)

-- | This operation never fails, but the returned object might
-- not support any I\/O operations if the /@parseName@/ cannot
-- be parsed by the t'GI.Gio.Objects.Vfs.Vfs' module.
vfsParseName ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'.
    -> T.Text
    -- ^ /@parseName@/: a string to be parsed by the VFS module.
    -> m Gio.File.File
    -- ^ __Returns:__ a t'GI.Gio.Interfaces.File.File' for the given /@parseName@/.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref'.
vfsParseName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> Text -> m File
vfsParseName a
vfs Text
parseName = IO File -> m File
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO File -> m File) -> IO File -> m File
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CString
parseName' <- Text -> IO CString
textToCString Text
parseName
    Ptr File
result <- Ptr Vfs -> CString -> IO (Ptr File)
g_vfs_parse_name Ptr Vfs
vfs' CString
parseName'
    Text -> Ptr File -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsParseName" Ptr File
result
    File
result' <- ((ManagedPtr File -> File) -> Ptr File -> IO File
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr File -> File
Gio.File.File) Ptr File
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
parseName'
    File -> IO File
forall (m :: * -> *) a. Monad m => a -> m a
return File
result'

#if defined(ENABLE_OVERLOADING)
data VfsParseNameMethodInfo
instance (signature ~ (T.Text -> m Gio.File.File), MonadIO m, IsVfs a) => O.OverloadedMethod VfsParseNameMethodInfo a signature where
    overloadedMethod = vfsParseName

instance O.OverloadedMethodInfo VfsParseNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsParseName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsParseName"
        }


#endif

-- method Vfs::register_uri_scheme
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scheme"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an URI scheme, e.g. \"http\""
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "VfsFileLookupFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfsFileLookupFunc"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 3
--           , argDestroy = 4
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "custom data passed to be passed to @uri_func, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uri_destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "function to be called when unregistering the\n    URI scheme, or when @vfs is disposed, to free the resources used\n    by the URI lookup function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parse_name_func"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "VfsFileLookupFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfsFileLookupFunc"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeNotified
--           , argClosure = 6
--           , argDestroy = 7
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parse_name_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "custom data passed to be passed to\n    @parse_name_func, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parse_name_destroy"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "DestroyNotify" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "function to be called when unregistering the\n    URI scheme, or when @vfs is disposed, to free the resources used\n    by the parse name lookup function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_register_uri_scheme" g_vfs_register_uri_scheme :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    CString ->                              -- scheme : TBasicType TUTF8
    FunPtr Gio.Callbacks.C_VfsFileLookupFunc -> -- uri_func : TInterface (Name {namespace = "Gio", name = "VfsFileLookupFunc"})
    Ptr () ->                               -- uri_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- uri_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    FunPtr Gio.Callbacks.C_VfsFileLookupFunc -> -- parse_name_func : TInterface (Name {namespace = "Gio", name = "VfsFileLookupFunc"})
    Ptr () ->                               -- parse_name_data : TBasicType TPtr
    FunPtr GLib.Callbacks.C_DestroyNotify -> -- parse_name_destroy : TInterface (Name {namespace = "GLib", name = "DestroyNotify"})
    IO CInt

-- | Registers /@uriFunc@/ and /@parseNameFunc@/ as the t'GI.Gio.Interfaces.File.File' URI and parse name
-- lookup functions for URIs with a scheme matching /@scheme@/.
-- Note that /@scheme@/ is registered only within the running application, as
-- opposed to desktop-wide as it happens with GVfs backends.
-- 
-- When a t'GI.Gio.Interfaces.File.File' is requested with an URI containing /@scheme@/ (e.g. through
-- 'GI.Gio.Functions.fileNewForUri'), /@uriFunc@/ will be called to allow a custom
-- constructor. The implementation of /@uriFunc@/ should not be blocking, and
-- must not call 'GI.Gio.Objects.Vfs.vfsRegisterUriScheme' or 'GI.Gio.Objects.Vfs.vfsUnregisterUriScheme'.
-- 
-- When 'GI.Gio.Functions.fileParseName' is called with a parse name obtained from such file,
-- /@parseNameFunc@/ will be called to allow the t'GI.Gio.Interfaces.File.File' to be created again. In
-- that case, it\'s responsibility of /@parseNameFunc@/ to make sure the parse
-- name matches what the custom t'GI.Gio.Interfaces.File.File' implementation returned when
-- 'GI.Gio.Interfaces.File.fileGetParseName' was previously called. The implementation of
-- /@parseNameFunc@/ should not be blocking, and must not call
-- 'GI.Gio.Objects.Vfs.vfsRegisterUriScheme' or 'GI.Gio.Objects.Vfs.vfsUnregisterUriScheme'.
-- 
-- It\'s an error to call this function twice with the same scheme. To unregister
-- a custom URI scheme, use 'GI.Gio.Objects.Vfs.vfsUnregisterUriScheme'.
-- 
-- /Since: 2.50/
vfsRegisterUriScheme ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'
    -> T.Text
    -- ^ /@scheme@/: an URI scheme, e.g. \"http\"
    -> Maybe (Gio.Callbacks.VfsFileLookupFunc)
    -- ^ /@uriFunc@/: a t'GI.Gio.Callbacks.VfsFileLookupFunc'
    -> Maybe (Gio.Callbacks.VfsFileLookupFunc)
    -- ^ /@parseNameFunc@/: a t'GI.Gio.Callbacks.VfsFileLookupFunc'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@scheme@/ was successfully registered, or 'P.False' if a handler
    --     for /@scheme@/ already exists.
vfsRegisterUriScheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a
-> Text
-> Maybe VfsFileLookupFunc
-> Maybe VfsFileLookupFunc
-> m Bool
vfsRegisterUriScheme a
vfs Text
scheme Maybe VfsFileLookupFunc
uriFunc Maybe VfsFileLookupFunc
parseNameFunc = IO Bool -> m Bool
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
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CString
scheme' <- Text -> IO CString
textToCString Text
scheme
    FunPtr C_VfsFileLookupFunc
maybeUriFunc <- case Maybe VfsFileLookupFunc
uriFunc of
        Maybe VfsFileLookupFunc
Nothing -> FunPtr C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_VfsFileLookupFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just VfsFileLookupFunc
jUriFunc -> do
            FunPtr C_VfsFileLookupFunc
jUriFunc' <- C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
Gio.Callbacks.mk_VfsFileLookupFunc (Maybe (Ptr (FunPtr C_VfsFileLookupFunc))
-> VfsFileLookupFunc_WithClosures -> C_VfsFileLookupFunc
Gio.Callbacks.wrap_VfsFileLookupFunc Maybe (Ptr (FunPtr C_VfsFileLookupFunc))
forall a. Maybe a
Nothing (VfsFileLookupFunc -> VfsFileLookupFunc_WithClosures
Gio.Callbacks.drop_closures_VfsFileLookupFunc VfsFileLookupFunc
jUriFunc))
            FunPtr C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_VfsFileLookupFunc
jUriFunc'
    FunPtr C_VfsFileLookupFunc
maybeParseNameFunc <- case Maybe VfsFileLookupFunc
parseNameFunc of
        Maybe VfsFileLookupFunc
Nothing -> FunPtr C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_VfsFileLookupFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just VfsFileLookupFunc
jParseNameFunc -> do
            FunPtr C_VfsFileLookupFunc
jParseNameFunc' <- C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
Gio.Callbacks.mk_VfsFileLookupFunc (Maybe (Ptr (FunPtr C_VfsFileLookupFunc))
-> VfsFileLookupFunc_WithClosures -> C_VfsFileLookupFunc
Gio.Callbacks.wrap_VfsFileLookupFunc Maybe (Ptr (FunPtr C_VfsFileLookupFunc))
forall a. Maybe a
Nothing (VfsFileLookupFunc -> VfsFileLookupFunc_WithClosures
Gio.Callbacks.drop_closures_VfsFileLookupFunc VfsFileLookupFunc
jParseNameFunc))
            FunPtr C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_VfsFileLookupFunc
jParseNameFunc'
    let uriData :: Ptr ()
uriData = FunPtr C_VfsFileLookupFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_VfsFileLookupFunc
maybeUriFunc
    let uriDestroy :: FunPtr (Ptr a -> IO ())
uriDestroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    let parseNameData :: Ptr ()
parseNameData = FunPtr C_VfsFileLookupFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_VfsFileLookupFunc
maybeParseNameFunc
    let parseNameDestroy :: FunPtr (Ptr a -> IO ())
parseNameDestroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
    CInt
result <- Ptr Vfs
-> CString
-> FunPtr C_VfsFileLookupFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> FunPtr C_VfsFileLookupFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO CInt
g_vfs_register_uri_scheme Ptr Vfs
vfs' CString
scheme' FunPtr C_VfsFileLookupFunc
maybeUriFunc Ptr ()
uriData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
uriDestroy FunPtr C_VfsFileLookupFunc
maybeParseNameFunc Ptr ()
parseNameData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
parseNameDestroy
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
scheme'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VfsRegisterUriSchemeMethodInfo
instance (signature ~ (T.Text -> Maybe (Gio.Callbacks.VfsFileLookupFunc) -> Maybe (Gio.Callbacks.VfsFileLookupFunc) -> m Bool), MonadIO m, IsVfs a) => O.OverloadedMethod VfsRegisterUriSchemeMethodInfo a signature where
    overloadedMethod = vfsRegisterUriScheme

instance O.OverloadedMethodInfo VfsRegisterUriSchemeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsRegisterUriScheme",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsRegisterUriScheme"
        }


#endif

-- method Vfs::unregister_uri_scheme
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "vfs"
--           , argType = TInterface Name { namespace = "Gio" , name = "Vfs" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GVfs" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scheme"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an URI scheme, e.g. \"http\""
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_unregister_uri_scheme" g_vfs_unregister_uri_scheme :: 
    Ptr Vfs ->                              -- vfs : TInterface (Name {namespace = "Gio", name = "Vfs"})
    CString ->                              -- scheme : TBasicType TUTF8
    IO CInt

-- | Unregisters the URI handler for /@scheme@/ previously registered with
-- 'GI.Gio.Objects.Vfs.vfsRegisterUriScheme'.
-- 
-- /Since: 2.50/
vfsUnregisterUriScheme ::
    (B.CallStack.HasCallStack, MonadIO m, IsVfs a) =>
    a
    -- ^ /@vfs@/: a t'GI.Gio.Objects.Vfs.Vfs'
    -> T.Text
    -- ^ /@scheme@/: an URI scheme, e.g. \"http\"
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@scheme@/ was successfully unregistered, or 'P.False' if a
    --     handler for /@scheme@/ does not exist.
vfsUnregisterUriScheme :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsVfs a) =>
a -> Text -> m Bool
vfsUnregisterUriScheme a
vfs Text
scheme = IO Bool -> m Bool
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
    Ptr Vfs
vfs' <- a -> IO (Ptr Vfs)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
vfs
    CString
scheme' <- Text -> IO CString
textToCString Text
scheme
    CInt
result <- Ptr Vfs -> CString -> IO CInt
g_vfs_unregister_uri_scheme Ptr Vfs
vfs' CString
scheme'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
vfs
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
scheme'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data VfsUnregisterUriSchemeMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsVfs a) => O.OverloadedMethod VfsUnregisterUriSchemeMethodInfo a signature where
    overloadedMethod = vfsUnregisterUriScheme

instance O.OverloadedMethodInfo VfsUnregisterUriSchemeMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gio.Objects.Vfs.vfsUnregisterUriScheme",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gio-2.0.28/docs/GI-Gio-Objects-Vfs.html#v:vfsUnregisterUriScheme"
        }


#endif

-- method Vfs::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Vfs" })
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_get_default" g_vfs_get_default :: 
    IO (Ptr Vfs)

-- | Gets the default t'GI.Gio.Objects.Vfs.Vfs' for the system.
vfsGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vfs
    -- ^ __Returns:__ a t'GI.Gio.Objects.Vfs.Vfs'.
vfsGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vfs
vfsGetDefault  = IO Vfs -> m Vfs
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vfs -> m Vfs) -> IO Vfs -> m Vfs
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vfs
result <- IO (Ptr Vfs)
g_vfs_get_default
    Text -> Ptr Vfs -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsGetDefault" Ptr Vfs
result
    Vfs
result' <- ((ManagedPtr Vfs -> Vfs) -> Ptr Vfs -> IO Vfs
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Vfs -> Vfs
Vfs) Ptr Vfs
result
    Vfs -> IO Vfs
forall (m :: * -> *) a. Monad m => a -> m a
return Vfs
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Vfs::get_local
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Vfs" })
-- throws : False
-- Skip return : False

foreign import ccall "g_vfs_get_local" g_vfs_get_local :: 
    IO (Ptr Vfs)

-- | Gets the local t'GI.Gio.Objects.Vfs.Vfs' for the system.
vfsGetLocal ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Vfs
    -- ^ __Returns:__ a t'GI.Gio.Objects.Vfs.Vfs'.
vfsGetLocal :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Vfs
vfsGetLocal  = IO Vfs -> m Vfs
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Vfs -> m Vfs) -> IO Vfs -> m Vfs
forall a b. (a -> b) -> a -> b
$ do
    Ptr Vfs
result <- IO (Ptr Vfs)
g_vfs_get_local
    Text -> Ptr Vfs -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"vfsGetLocal" Ptr Vfs
result
    Vfs
result' <- ((ManagedPtr Vfs -> Vfs) -> Ptr Vfs -> IO Vfs
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Vfs -> Vfs
Vfs) Ptr Vfs
result
    Vfs -> IO Vfs
forall (m :: * -> *) a. Monad m => a -> m a
return Vfs
result'

#if defined(ENABLE_OVERLOADING)
#endif