{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.OSTree.Objects.RepoFile
    ( 

-- * Exported types
    RepoFile(..)                            ,
    IsRepoFile                              ,
    toRepoFile                              ,
    noRepoFile                              ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveRepoFileMethod                   ,
#endif


-- ** ensureResolved #method:ensureResolved#

#if defined(ENABLE_OVERLOADING)
    RepoFileEnsureResolvedMethodInfo        ,
#endif
    repoFileEnsureResolved                  ,


-- ** getChecksum #method:getChecksum#

#if defined(ENABLE_OVERLOADING)
    RepoFileGetChecksumMethodInfo           ,
#endif
    repoFileGetChecksum                     ,


-- ** getRepo #method:getRepo#

#if defined(ENABLE_OVERLOADING)
    RepoFileGetRepoMethodInfo               ,
#endif
    repoFileGetRepo                         ,


-- ** getRoot #method:getRoot#

#if defined(ENABLE_OVERLOADING)
    RepoFileGetRootMethodInfo               ,
#endif
    repoFileGetRoot                         ,


-- ** getXattrs #method:getXattrs#

#if defined(ENABLE_OVERLOADING)
    RepoFileGetXattrsMethodInfo             ,
#endif
    repoFileGetXattrs                       ,


-- ** treeFindChild #method:treeFindChild#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeFindChildMethodInfo         ,
#endif
    repoFileTreeFindChild                   ,


-- ** treeGetContents #method:treeGetContents#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeGetContentsMethodInfo       ,
#endif
    repoFileTreeGetContents                 ,


-- ** treeGetContentsChecksum #method:treeGetContentsChecksum#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeGetContentsChecksumMethodInfo,
#endif
    repoFileTreeGetContentsChecksum         ,


-- ** treeGetMetadata #method:treeGetMetadata#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeGetMetadataMethodInfo       ,
#endif
    repoFileTreeGetMetadata                 ,


-- ** treeGetMetadataChecksum #method:treeGetMetadataChecksum#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeGetMetadataChecksumMethodInfo,
#endif
    repoFileTreeGetMetadataChecksum         ,


-- ** treeQueryChild #method:treeQueryChild#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeQueryChildMethodInfo        ,
#endif
    repoFileTreeQueryChild                  ,


-- ** treeSetMetadata #method:treeSetMetadata#

#if defined(ENABLE_OVERLOADING)
    RepoFileTreeSetMetadataMethodInfo       ,
#endif
    repoFileTreeSetMetadata                 ,




    ) 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.ManagedPtr as B.ManagedPtr
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 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 GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo

-- | Memory-managed wrapper type.
newtype RepoFile = RepoFile (ManagedPtr RepoFile)
    deriving (RepoFile -> RepoFile -> Bool
(RepoFile -> RepoFile -> Bool)
-> (RepoFile -> RepoFile -> Bool) -> Eq RepoFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RepoFile -> RepoFile -> Bool
$c/= :: RepoFile -> RepoFile -> Bool
== :: RepoFile -> RepoFile -> Bool
$c== :: RepoFile -> RepoFile -> Bool
Eq)
foreign import ccall "ostree_repo_file_get_type"
    c_ostree_repo_file_get_type :: IO GType

instance GObject RepoFile where
    gobjectType :: IO GType
gobjectType = IO GType
c_ostree_repo_file_get_type
    

-- | Convert 'RepoFile' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue RepoFile where
    toGValue :: RepoFile -> IO GValue
toGValue o :: RepoFile
o = do
        GType
gtype <- IO GType
c_ostree_repo_file_get_type
        RepoFile -> (Ptr RepoFile -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RepoFile
o (GType
-> (GValue -> Ptr RepoFile -> IO ()) -> Ptr RepoFile -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr RepoFile -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO RepoFile
fromGValue gv :: GValue
gv = do
        Ptr RepoFile
ptr <- GValue -> IO (Ptr RepoFile)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr RepoFile)
        (ManagedPtr RepoFile -> RepoFile) -> Ptr RepoFile -> IO RepoFile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr RepoFile -> RepoFile
RepoFile Ptr RepoFile
ptr
        
    

-- | Type class for types which can be safely cast to `RepoFile`, for instance with `toRepoFile`.
class (GObject o, O.IsDescendantOf RepoFile o) => IsRepoFile o
instance (GObject o, O.IsDescendantOf RepoFile o) => IsRepoFile o

instance O.HasParentTypes RepoFile
type instance O.ParentTypes RepoFile = '[GObject.Object.Object, Gio.File.File]

-- | Cast to `RepoFile`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toRepoFile :: (MonadIO m, IsRepoFile o) => o -> m RepoFile
toRepoFile :: o -> m RepoFile
toRepoFile = IO RepoFile -> m RepoFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RepoFile -> m RepoFile)
-> (o -> IO RepoFile) -> o -> m RepoFile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr RepoFile -> RepoFile) -> o -> IO RepoFile
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr RepoFile -> RepoFile
RepoFile

-- | A convenience alias for `Nothing` :: `Maybe` `RepoFile`.
noRepoFile :: Maybe RepoFile
noRepoFile :: Maybe RepoFile
noRepoFile = Maybe RepoFile
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveRepoFileMethod (t :: Symbol) (o :: *) :: * where
    ResolveRepoFileMethod "appendTo" o = Gio.File.FileAppendToMethodInfo
    ResolveRepoFileMethod "appendToAsync" o = Gio.File.FileAppendToAsyncMethodInfo
    ResolveRepoFileMethod "appendToFinish" o = Gio.File.FileAppendToFinishMethodInfo
    ResolveRepoFileMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveRepoFileMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveRepoFileMethod "copy" o = Gio.File.FileCopyMethodInfo
    ResolveRepoFileMethod "copyAsync" o = Gio.File.FileCopyAsyncMethodInfo
    ResolveRepoFileMethod "copyAttributes" o = Gio.File.FileCopyAttributesMethodInfo
    ResolveRepoFileMethod "copyFinish" o = Gio.File.FileCopyFinishMethodInfo
    ResolveRepoFileMethod "create" o = Gio.File.FileCreateMethodInfo
    ResolveRepoFileMethod "createAsync" o = Gio.File.FileCreateAsyncMethodInfo
    ResolveRepoFileMethod "createFinish" o = Gio.File.FileCreateFinishMethodInfo
    ResolveRepoFileMethod "createReadwrite" o = Gio.File.FileCreateReadwriteMethodInfo
    ResolveRepoFileMethod "createReadwriteAsync" o = Gio.File.FileCreateReadwriteAsyncMethodInfo
    ResolveRepoFileMethod "createReadwriteFinish" o = Gio.File.FileCreateReadwriteFinishMethodInfo
    ResolveRepoFileMethod "delete" o = Gio.File.FileDeleteMethodInfo
    ResolveRepoFileMethod "deleteAsync" o = Gio.File.FileDeleteAsyncMethodInfo
    ResolveRepoFileMethod "deleteFinish" o = Gio.File.FileDeleteFinishMethodInfo
    ResolveRepoFileMethod "dup" o = Gio.File.FileDupMethodInfo
    ResolveRepoFileMethod "ejectMountable" o = Gio.File.FileEjectMountableMethodInfo
    ResolveRepoFileMethod "ejectMountableFinish" o = Gio.File.FileEjectMountableFinishMethodInfo
    ResolveRepoFileMethod "ejectMountableWithOperation" o = Gio.File.FileEjectMountableWithOperationMethodInfo
    ResolveRepoFileMethod "ejectMountableWithOperationFinish" o = Gio.File.FileEjectMountableWithOperationFinishMethodInfo
    ResolveRepoFileMethod "ensureResolved" o = RepoFileEnsureResolvedMethodInfo
    ResolveRepoFileMethod "enumerateChildren" o = Gio.File.FileEnumerateChildrenMethodInfo
    ResolveRepoFileMethod "enumerateChildrenAsync" o = Gio.File.FileEnumerateChildrenAsyncMethodInfo
    ResolveRepoFileMethod "enumerateChildrenFinish" o = Gio.File.FileEnumerateChildrenFinishMethodInfo
    ResolveRepoFileMethod "equal" o = Gio.File.FileEqualMethodInfo
    ResolveRepoFileMethod "findEnclosingMount" o = Gio.File.FileFindEnclosingMountMethodInfo
    ResolveRepoFileMethod "findEnclosingMountAsync" o = Gio.File.FileFindEnclosingMountAsyncMethodInfo
    ResolveRepoFileMethod "findEnclosingMountFinish" o = Gio.File.FileFindEnclosingMountFinishMethodInfo
    ResolveRepoFileMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveRepoFileMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveRepoFileMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveRepoFileMethod "hasParent" o = Gio.File.FileHasParentMethodInfo
    ResolveRepoFileMethod "hasPrefix" o = Gio.File.FileHasPrefixMethodInfo
    ResolveRepoFileMethod "hasUriScheme" o = Gio.File.FileHasUriSchemeMethodInfo
    ResolveRepoFileMethod "hash" o = Gio.File.FileHashMethodInfo
    ResolveRepoFileMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveRepoFileMethod "isNative" o = Gio.File.FileIsNativeMethodInfo
    ResolveRepoFileMethod "loadBytes" o = Gio.File.FileLoadBytesMethodInfo
    ResolveRepoFileMethod "loadBytesAsync" o = Gio.File.FileLoadBytesAsyncMethodInfo
    ResolveRepoFileMethod "loadBytesFinish" o = Gio.File.FileLoadBytesFinishMethodInfo
    ResolveRepoFileMethod "loadContents" o = Gio.File.FileLoadContentsMethodInfo
    ResolveRepoFileMethod "loadContentsAsync" o = Gio.File.FileLoadContentsAsyncMethodInfo
    ResolveRepoFileMethod "loadContentsFinish" o = Gio.File.FileLoadContentsFinishMethodInfo
    ResolveRepoFileMethod "loadPartialContentsFinish" o = Gio.File.FileLoadPartialContentsFinishMethodInfo
    ResolveRepoFileMethod "makeDirectory" o = Gio.File.FileMakeDirectoryMethodInfo
    ResolveRepoFileMethod "makeDirectoryAsync" o = Gio.File.FileMakeDirectoryAsyncMethodInfo
    ResolveRepoFileMethod "makeDirectoryFinish" o = Gio.File.FileMakeDirectoryFinishMethodInfo
    ResolveRepoFileMethod "makeDirectoryWithParents" o = Gio.File.FileMakeDirectoryWithParentsMethodInfo
    ResolveRepoFileMethod "makeSymbolicLink" o = Gio.File.FileMakeSymbolicLinkMethodInfo
    ResolveRepoFileMethod "measureDiskUsageFinish" o = Gio.File.FileMeasureDiskUsageFinishMethodInfo
    ResolveRepoFileMethod "monitor" o = Gio.File.FileMonitorMethodInfo
    ResolveRepoFileMethod "monitorDirectory" o = Gio.File.FileMonitorDirectoryMethodInfo
    ResolveRepoFileMethod "monitorFile" o = Gio.File.FileMonitorFileMethodInfo
    ResolveRepoFileMethod "mountEnclosingVolume" o = Gio.File.FileMountEnclosingVolumeMethodInfo
    ResolveRepoFileMethod "mountEnclosingVolumeFinish" o = Gio.File.FileMountEnclosingVolumeFinishMethodInfo
    ResolveRepoFileMethod "mountMountable" o = Gio.File.FileMountMountableMethodInfo
    ResolveRepoFileMethod "mountMountableFinish" o = Gio.File.FileMountMountableFinishMethodInfo
    ResolveRepoFileMethod "move" o = Gio.File.FileMoveMethodInfo
    ResolveRepoFileMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveRepoFileMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveRepoFileMethod "openReadwrite" o = Gio.File.FileOpenReadwriteMethodInfo
    ResolveRepoFileMethod "openReadwriteAsync" o = Gio.File.FileOpenReadwriteAsyncMethodInfo
    ResolveRepoFileMethod "openReadwriteFinish" o = Gio.File.FileOpenReadwriteFinishMethodInfo
    ResolveRepoFileMethod "peekPath" o = Gio.File.FilePeekPathMethodInfo
    ResolveRepoFileMethod "pollMountable" o = Gio.File.FilePollMountableMethodInfo
    ResolveRepoFileMethod "pollMountableFinish" o = Gio.File.FilePollMountableFinishMethodInfo
    ResolveRepoFileMethod "queryDefaultHandler" o = Gio.File.FileQueryDefaultHandlerMethodInfo
    ResolveRepoFileMethod "queryDefaultHandlerAsync" o = Gio.File.FileQueryDefaultHandlerAsyncMethodInfo
    ResolveRepoFileMethod "queryDefaultHandlerFinish" o = Gio.File.FileQueryDefaultHandlerFinishMethodInfo
    ResolveRepoFileMethod "queryExists" o = Gio.File.FileQueryExistsMethodInfo
    ResolveRepoFileMethod "queryFileType" o = Gio.File.FileQueryFileTypeMethodInfo
    ResolveRepoFileMethod "queryFilesystemInfo" o = Gio.File.FileQueryFilesystemInfoMethodInfo
    ResolveRepoFileMethod "queryFilesystemInfoAsync" o = Gio.File.FileQueryFilesystemInfoAsyncMethodInfo
    ResolveRepoFileMethod "queryFilesystemInfoFinish" o = Gio.File.FileQueryFilesystemInfoFinishMethodInfo
    ResolveRepoFileMethod "queryInfo" o = Gio.File.FileQueryInfoMethodInfo
    ResolveRepoFileMethod "queryInfoAsync" o = Gio.File.FileQueryInfoAsyncMethodInfo
    ResolveRepoFileMethod "queryInfoFinish" o = Gio.File.FileQueryInfoFinishMethodInfo
    ResolveRepoFileMethod "querySettableAttributes" o = Gio.File.FileQuerySettableAttributesMethodInfo
    ResolveRepoFileMethod "queryWritableNamespaces" o = Gio.File.FileQueryWritableNamespacesMethodInfo
    ResolveRepoFileMethod "read" o = Gio.File.FileReadMethodInfo
    ResolveRepoFileMethod "readAsync" o = Gio.File.FileReadAsyncMethodInfo
    ResolveRepoFileMethod "readFinish" o = Gio.File.FileReadFinishMethodInfo
    ResolveRepoFileMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveRepoFileMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveRepoFileMethod "replace" o = Gio.File.FileReplaceMethodInfo
    ResolveRepoFileMethod "replaceAsync" o = Gio.File.FileReplaceAsyncMethodInfo
    ResolveRepoFileMethod "replaceContents" o = Gio.File.FileReplaceContentsMethodInfo
    ResolveRepoFileMethod "replaceContentsAsync" o = Gio.File.FileReplaceContentsAsyncMethodInfo
    ResolveRepoFileMethod "replaceContentsBytesAsync" o = Gio.File.FileReplaceContentsBytesAsyncMethodInfo
    ResolveRepoFileMethod "replaceContentsFinish" o = Gio.File.FileReplaceContentsFinishMethodInfo
    ResolveRepoFileMethod "replaceFinish" o = Gio.File.FileReplaceFinishMethodInfo
    ResolveRepoFileMethod "replaceReadwrite" o = Gio.File.FileReplaceReadwriteMethodInfo
    ResolveRepoFileMethod "replaceReadwriteAsync" o = Gio.File.FileReplaceReadwriteAsyncMethodInfo
    ResolveRepoFileMethod "replaceReadwriteFinish" o = Gio.File.FileReplaceReadwriteFinishMethodInfo
    ResolveRepoFileMethod "resolveRelativePath" o = Gio.File.FileResolveRelativePathMethodInfo
    ResolveRepoFileMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveRepoFileMethod "startMountable" o = Gio.File.FileStartMountableMethodInfo
    ResolveRepoFileMethod "startMountableFinish" o = Gio.File.FileStartMountableFinishMethodInfo
    ResolveRepoFileMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveRepoFileMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveRepoFileMethod "stopMountable" o = Gio.File.FileStopMountableMethodInfo
    ResolveRepoFileMethod "stopMountableFinish" o = Gio.File.FileStopMountableFinishMethodInfo
    ResolveRepoFileMethod "supportsThreadContexts" o = Gio.File.FileSupportsThreadContextsMethodInfo
    ResolveRepoFileMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveRepoFileMethod "trash" o = Gio.File.FileTrashMethodInfo
    ResolveRepoFileMethod "trashAsync" o = Gio.File.FileTrashAsyncMethodInfo
    ResolveRepoFileMethod "trashFinish" o = Gio.File.FileTrashFinishMethodInfo
    ResolveRepoFileMethod "treeFindChild" o = RepoFileTreeFindChildMethodInfo
    ResolveRepoFileMethod "treeGetContents" o = RepoFileTreeGetContentsMethodInfo
    ResolveRepoFileMethod "treeGetContentsChecksum" o = RepoFileTreeGetContentsChecksumMethodInfo
    ResolveRepoFileMethod "treeGetMetadata" o = RepoFileTreeGetMetadataMethodInfo
    ResolveRepoFileMethod "treeGetMetadataChecksum" o = RepoFileTreeGetMetadataChecksumMethodInfo
    ResolveRepoFileMethod "treeQueryChild" o = RepoFileTreeQueryChildMethodInfo
    ResolveRepoFileMethod "treeSetMetadata" o = RepoFileTreeSetMetadataMethodInfo
    ResolveRepoFileMethod "unmountMountable" o = Gio.File.FileUnmountMountableMethodInfo
    ResolveRepoFileMethod "unmountMountableFinish" o = Gio.File.FileUnmountMountableFinishMethodInfo
    ResolveRepoFileMethod "unmountMountableWithOperation" o = Gio.File.FileUnmountMountableWithOperationMethodInfo
    ResolveRepoFileMethod "unmountMountableWithOperationFinish" o = Gio.File.FileUnmountMountableWithOperationFinishMethodInfo
    ResolveRepoFileMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveRepoFileMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveRepoFileMethod "getBasename" o = Gio.File.FileGetBasenameMethodInfo
    ResolveRepoFileMethod "getChecksum" o = RepoFileGetChecksumMethodInfo
    ResolveRepoFileMethod "getChild" o = Gio.File.FileGetChildMethodInfo
    ResolveRepoFileMethod "getChildForDisplayName" o = Gio.File.FileGetChildForDisplayNameMethodInfo
    ResolveRepoFileMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveRepoFileMethod "getParent" o = Gio.File.FileGetParentMethodInfo
    ResolveRepoFileMethod "getParseName" o = Gio.File.FileGetParseNameMethodInfo
    ResolveRepoFileMethod "getPath" o = Gio.File.FileGetPathMethodInfo
    ResolveRepoFileMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveRepoFileMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveRepoFileMethod "getRelativePath" o = Gio.File.FileGetRelativePathMethodInfo
    ResolveRepoFileMethod "getRepo" o = RepoFileGetRepoMethodInfo
    ResolveRepoFileMethod "getRoot" o = RepoFileGetRootMethodInfo
    ResolveRepoFileMethod "getUri" o = Gio.File.FileGetUriMethodInfo
    ResolveRepoFileMethod "getUriScheme" o = Gio.File.FileGetUriSchemeMethodInfo
    ResolveRepoFileMethod "getXattrs" o = RepoFileGetXattrsMethodInfo
    ResolveRepoFileMethod "setAttribute" o = Gio.File.FileSetAttributeMethodInfo
    ResolveRepoFileMethod "setAttributeByteString" o = Gio.File.FileSetAttributeByteStringMethodInfo
    ResolveRepoFileMethod "setAttributeInt32" o = Gio.File.FileSetAttributeInt32MethodInfo
    ResolveRepoFileMethod "setAttributeInt64" o = Gio.File.FileSetAttributeInt64MethodInfo
    ResolveRepoFileMethod "setAttributeString" o = Gio.File.FileSetAttributeStringMethodInfo
    ResolveRepoFileMethod "setAttributeUint32" o = Gio.File.FileSetAttributeUint32MethodInfo
    ResolveRepoFileMethod "setAttributeUint64" o = Gio.File.FileSetAttributeUint64MethodInfo
    ResolveRepoFileMethod "setAttributesAsync" o = Gio.File.FileSetAttributesAsyncMethodInfo
    ResolveRepoFileMethod "setAttributesFinish" o = Gio.File.FileSetAttributesFinishMethodInfo
    ResolveRepoFileMethod "setAttributesFromInfo" o = Gio.File.FileSetAttributesFromInfoMethodInfo
    ResolveRepoFileMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveRepoFileMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveRepoFileMethod "setDisplayName" o = Gio.File.FileSetDisplayNameMethodInfo
    ResolveRepoFileMethod "setDisplayNameAsync" o = Gio.File.FileSetDisplayNameAsyncMethodInfo
    ResolveRepoFileMethod "setDisplayNameFinish" o = Gio.File.FileSetDisplayNameFinishMethodInfo
    ResolveRepoFileMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveRepoFileMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRepoFileMethod t RepoFile, O.MethodInfo info RepoFile p) => OL.IsLabel t (RepoFile -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method RepoFile::ensure_resolved
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_repo_file_ensure_resolved" ostree_repo_file_ensure_resolved :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
repoFileEnsureResolved ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
repoFileEnsureResolved :: a -> m ()
repoFileEnsureResolved self :: a
self = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    IO () -> IO () -> IO ()
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 RepoFile -> Ptr (Ptr GError) -> IO CInt
ostree_repo_file_ensure_resolved Ptr RepoFile
self'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data RepoFileEnsureResolvedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileEnsureResolvedMethodInfo a signature where
    overloadedMethod = repoFileEnsureResolved

#endif

-- method RepoFile::get_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_get_checksum" ostree_repo_file_get_checksum :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO CString

-- | /No description available in the introspection data./
repoFileGetChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m T.Text
repoFileGetChecksum :: a -> m Text
repoFileGetChecksum self :: a
self = 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 RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr RepoFile -> IO CString
ostree_repo_file_get_checksum Ptr RepoFile
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileGetChecksum" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileGetChecksumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileGetChecksumMethodInfo a signature where
    overloadedMethod = repoFileGetChecksum

#endif

-- method RepoFile::get_repo
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "OSTree" , name = "Repo" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_get_repo" ostree_repo_file_get_repo :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO (Ptr OSTree.Repo.Repo)

-- | /No description available in the introspection data./
repoFileGetRepo ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m OSTree.Repo.Repo
    -- ^ __Returns:__ Repository
repoFileGetRepo :: a -> m Repo
repoFileGetRepo self :: a
self = IO Repo -> m Repo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Repo -> m Repo) -> IO Repo -> m Repo
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Repo
result <- Ptr RepoFile -> IO (Ptr Repo)
ostree_repo_file_get_repo Ptr RepoFile
self'
    Text -> Ptr Repo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileGetRepo" Ptr Repo
result
    Repo
result' <- ((ManagedPtr Repo -> Repo) -> Ptr Repo -> IO Repo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Repo -> Repo
OSTree.Repo.Repo) Ptr Repo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Repo -> IO Repo
forall (m :: * -> *) a. Monad m => a -> m a
return Repo
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileGetRepoMethodInfo
instance (signature ~ (m OSTree.Repo.Repo), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileGetRepoMethodInfo a signature where
    overloadedMethod = repoFileGetRepo

#endif

-- method RepoFile::get_root
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "OSTree" , name = "RepoFile" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_get_root" ostree_repo_file_get_root :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO (Ptr RepoFile)

-- | /No description available in the introspection data./
repoFileGetRoot ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m RepoFile
    -- ^ __Returns:__ The root directory for the commit referenced by this file
repoFileGetRoot :: a -> m RepoFile
repoFileGetRoot self :: a
self = IO RepoFile -> m RepoFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RepoFile -> m RepoFile) -> IO RepoFile -> m RepoFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr RepoFile
result <- Ptr RepoFile -> IO (Ptr RepoFile)
ostree_repo_file_get_root Ptr RepoFile
self'
    Text -> Ptr RepoFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileGetRoot" Ptr RepoFile
result
    RepoFile
result' <- ((ManagedPtr RepoFile -> RepoFile) -> Ptr RepoFile -> IO RepoFile
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr RepoFile -> RepoFile
RepoFile) Ptr RepoFile
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    RepoFile -> IO RepoFile
forall (m :: * -> *) a. Monad m => a -> m a
return RepoFile
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileGetRootMethodInfo
instance (signature ~ (m RepoFile), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileGetRootMethodInfo a signature where
    overloadedMethod = repoFileGetRoot

#endif

-- method RepoFile::get_xattrs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_xattrs"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_repo_file_get_xattrs" ostree_repo_file_get_xattrs :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    Ptr GVariant ->                         -- out_xattrs : TVariant
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
repoFileGetXattrs ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a, Gio.Cancellable.IsCancellable b) =>
    a
    -> GVariant
    -> Maybe (b)
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
repoFileGetXattrs :: a -> GVariant -> Maybe b -> m ()
repoFileGetXattrs self :: a
self outXattrs :: GVariant
outXattrs cancellable :: Maybe b
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GVariant
outXattrs' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
outXattrs
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: 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 (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO () -> IO () -> IO ()
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 RepoFile
-> Ptr GVariant -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
ostree_repo_file_get_xattrs Ptr RepoFile
self' Ptr GVariant
outXattrs' Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
outXattrs
        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 (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data RepoFileGetXattrsMethodInfo
instance (signature ~ (GVariant -> Maybe (b) -> m ()), MonadIO m, IsRepoFile a, Gio.Cancellable.IsCancellable b) => O.MethodInfo RepoFileGetXattrsMethodInfo a signature where
    overloadedMethod = repoFileGetXattrs

#endif

-- method RepoFile::tree_find_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "is_dir"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_container"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_find_child" ostree_repo_file_tree_find_child :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    CString ->                              -- name : TBasicType TUTF8
    CInt ->                                 -- is_dir : TBasicType TBoolean
    Ptr GVariant ->                         -- out_container : TVariant
    IO Int32

-- | /No description available in the introspection data./
repoFileTreeFindChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> T.Text
    -> Bool
    -> GVariant
    -> m Int32
repoFileTreeFindChild :: a -> Text -> Bool -> GVariant -> m Int32
repoFileTreeFindChild self :: a
self name :: Text
name isDir :: Bool
isDir outContainer :: GVariant
outContainer = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    let isDir' :: CInt
isDir' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
isDir
    Ptr GVariant
outContainer' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
outContainer
    Int32
result <- Ptr RepoFile -> CString -> CInt -> Ptr GVariant -> IO Int32
ostree_repo_file_tree_find_child Ptr RepoFile
self' CString
name' CInt
isDir' Ptr GVariant
outContainer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
outContainer
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeFindChildMethodInfo
instance (signature ~ (T.Text -> Bool -> GVariant -> m Int32), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeFindChildMethodInfo a signature where
    overloadedMethod = repoFileTreeFindChild

#endif

-- method RepoFile::tree_get_contents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_get_contents" ostree_repo_file_tree_get_contents :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO (Ptr GVariant)

-- | /No description available in the introspection data./
repoFileTreeGetContents ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m GVariant
repoFileTreeGetContents :: a -> m GVariant
repoFileTreeGetContents self :: a
self = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GVariant
result <- Ptr RepoFile -> IO (Ptr GVariant)
ostree_repo_file_tree_get_contents Ptr RepoFile
self'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileTreeGetContents" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeGetContentsMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeGetContentsMethodInfo a signature where
    overloadedMethod = repoFileTreeGetContents

#endif

-- method RepoFile::tree_get_contents_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_get_contents_checksum" ostree_repo_file_tree_get_contents_checksum :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO CString

-- | /No description available in the introspection data./
repoFileTreeGetContentsChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m T.Text
repoFileTreeGetContentsChecksum :: a -> m Text
repoFileTreeGetContentsChecksum self :: a
self = 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 RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr RepoFile -> IO CString
ostree_repo_file_tree_get_contents_checksum Ptr RepoFile
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileTreeGetContentsChecksum" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeGetContentsChecksumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeGetContentsChecksumMethodInfo a signature where
    overloadedMethod = repoFileTreeGetContentsChecksum

#endif

-- method RepoFile::tree_get_metadata
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TVariant
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_get_metadata" ostree_repo_file_tree_get_metadata :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO (Ptr GVariant)

-- | /No description available in the introspection data./
repoFileTreeGetMetadata ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m GVariant
repoFileTreeGetMetadata :: a -> m GVariant
repoFileTreeGetMetadata self :: a
self = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GVariant
result <- Ptr RepoFile -> IO (Ptr GVariant)
ostree_repo_file_tree_get_metadata Ptr RepoFile
self'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileTreeGetMetadata" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeGetMetadataMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeGetMetadataMethodInfo a signature where
    overloadedMethod = repoFileTreeGetMetadata

#endif

-- method RepoFile::tree_get_metadata_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_get_metadata_checksum" ostree_repo_file_tree_get_metadata_checksum :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    IO CString

-- | /No description available in the introspection data./
repoFileTreeGetMetadataChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> m T.Text
repoFileTreeGetMetadataChecksum :: a -> m Text
repoFileTreeGetMetadataChecksum self :: a
self = 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 RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr RepoFile -> IO CString
ostree_repo_file_tree_get_metadata_checksum Ptr RepoFile
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "repoFileTreeGetMetadataChecksum" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeGetMetadataChecksumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeGetMetadataChecksumMethodInfo a signature where
    overloadedMethod = repoFileTreeGetMetadataChecksum

#endif

-- method RepoFile::tree_query_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attributes"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileQueryInfoFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "FileInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , 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 = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_query_child" ostree_repo_file_tree_query_child :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    Int32 ->                                -- n : TBasicType TInt
    CString ->                              -- attributes : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "FileQueryInfoFlags"})
    Ptr Gio.FileInfo.FileInfo ->            -- out_info : TInterface (Name {namespace = "Gio", name = "FileInfo"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
repoFileTreeQueryChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a, Gio.FileInfo.IsFileInfo b, Gio.Cancellable.IsCancellable c) =>
    a
    -> Int32
    -> T.Text
    -> [Gio.Flags.FileQueryInfoFlags]
    -> b
    -> Maybe (c)
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
repoFileTreeQueryChild :: a -> Int32 -> Text -> [FileQueryInfoFlags] -> b -> Maybe c -> m ()
repoFileTreeQueryChild self :: a
self n :: Int32
n attributes :: Text
attributes flags :: [FileQueryInfoFlags]
flags outInfo :: b
outInfo cancellable :: Maybe c
cancellable = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
attributes' <- Text -> IO CString
textToCString Text
attributes
    let flags' :: CUInt
flags' = [FileQueryInfoFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [FileQueryInfoFlags]
flags
    Ptr FileInfo
outInfo' <- b -> IO (Ptr FileInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
outInfo
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just jCancellable :: c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO () -> IO () -> IO ()
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 RepoFile
-> Int32
-> CString
-> CUInt
-> Ptr FileInfo
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
ostree_repo_file_tree_query_child Ptr RepoFile
self' Int32
n CString
attributes' CUInt
flags' Ptr FileInfo
outInfo' Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
outInfo
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributes'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
attributes'
     )

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeQueryChildMethodInfo
instance (signature ~ (Int32 -> T.Text -> [Gio.Flags.FileQueryInfoFlags] -> b -> Maybe (c) -> m ()), MonadIO m, IsRepoFile a, Gio.FileInfo.IsFileInfo b, Gio.Cancellable.IsCancellable c) => O.MethodInfo RepoFileTreeQueryChildMethodInfo a signature where
    overloadedMethod = repoFileTreeQueryChild

#endif

-- method RepoFile::tree_set_metadata
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "checksum"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "metadata"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_repo_file_tree_set_metadata" ostree_repo_file_tree_set_metadata :: 
    Ptr RepoFile ->                         -- self : TInterface (Name {namespace = "OSTree", name = "RepoFile"})
    CString ->                              -- checksum : TBasicType TUTF8
    Ptr GVariant ->                         -- metadata : TVariant
    IO ()

-- | /No description available in the introspection data./
repoFileTreeSetMetadata ::
    (B.CallStack.HasCallStack, MonadIO m, IsRepoFile a) =>
    a
    -> T.Text
    -> GVariant
    -> m ()
repoFileTreeSetMetadata :: a -> Text -> GVariant -> m ()
repoFileTreeSetMetadata self :: a
self checksum :: Text
checksum metadata :: GVariant
metadata = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr RepoFile
self' <- a -> IO (Ptr RepoFile)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
checksum' <- Text -> IO CString
textToCString Text
checksum
    Ptr GVariant
metadata' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
metadata
    Ptr RepoFile -> CString -> Ptr GVariant -> IO ()
ostree_repo_file_tree_set_metadata Ptr RepoFile
self' CString
checksum' Ptr GVariant
metadata'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
metadata
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
checksum'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RepoFileTreeSetMetadataMethodInfo
instance (signature ~ (T.Text -> GVariant -> m ()), MonadIO m, IsRepoFile a) => O.MethodInfo RepoFileTreeSetMetadataMethodInfo a signature where
    overloadedMethod = repoFileTreeSetMetadata

#endif