{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Private instance structure.

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

module GI.OSTree.Objects.MutableTree
    ( 
#if defined(ENABLE_OVERLOADING)
    MutableTreeGetSubdirsMethodInfo         ,
#endif

-- * Exported types
    MutableTree(..)                         ,
    IsMutableTree                           ,
    toMutableTree                           ,
    noMutableTree                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveMutableTreeMethod                ,
#endif


-- ** checkError #method:checkError#

#if defined(ENABLE_OVERLOADING)
    MutableTreeCheckErrorMethodInfo         ,
#endif
    mutableTreeCheckError                   ,


-- ** ensureDir #method:ensureDir#

#if defined(ENABLE_OVERLOADING)
    MutableTreeEnsureDirMethodInfo          ,
#endif
    mutableTreeEnsureDir                    ,


-- ** ensureParentDirs #method:ensureParentDirs#

#if defined(ENABLE_OVERLOADING)
    MutableTreeEnsureParentDirsMethodInfo   ,
#endif
    mutableTreeEnsureParentDirs             ,


-- ** fillEmptyFromDirtree #method:fillEmptyFromDirtree#

#if defined(ENABLE_OVERLOADING)
    MutableTreeFillEmptyFromDirtreeMethodInfo,
#endif
    mutableTreeFillEmptyFromDirtree         ,


-- ** getContentsChecksum #method:getContentsChecksum#

#if defined(ENABLE_OVERLOADING)
    MutableTreeGetContentsChecksumMethodInfo,
#endif
    mutableTreeGetContentsChecksum          ,


-- ** getFiles #method:getFiles#

#if defined(ENABLE_OVERLOADING)
    MutableTreeGetFilesMethodInfo           ,
#endif
    mutableTreeGetFiles                     ,


-- ** getMetadataChecksum #method:getMetadataChecksum#

#if defined(ENABLE_OVERLOADING)
    MutableTreeGetMetadataChecksumMethodInfo,
#endif
    mutableTreeGetMetadataChecksum          ,


-- ** lookup #method:lookup#

#if defined(ENABLE_OVERLOADING)
    MutableTreeLookupMethodInfo             ,
#endif
    mutableTreeLookup                       ,


-- ** new #method:new#

    mutableTreeNew                          ,


-- ** newFromChecksum #method:newFromChecksum#

    mutableTreeNewFromChecksum              ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    MutableTreeRemoveMethodInfo             ,
#endif
    mutableTreeRemove                       ,


-- ** replaceFile #method:replaceFile#

#if defined(ENABLE_OVERLOADING)
    MutableTreeReplaceFileMethodInfo        ,
#endif
    mutableTreeReplaceFile                  ,


-- ** setContentsChecksum #method:setContentsChecksum#

#if defined(ENABLE_OVERLOADING)
    MutableTreeSetContentsChecksumMethodInfo,
#endif
    mutableTreeSetContentsChecksum          ,


-- ** setMetadataChecksum #method:setMetadataChecksum#

#if defined(ENABLE_OVERLOADING)
    MutableTreeSetMetadataChecksumMethodInfo,
#endif
    mutableTreeSetMetadataChecksum          ,


-- ** walk #method:walk#

#if defined(ENABLE_OVERLOADING)
    MutableTreeWalkMethodInfo               ,
#endif
    mutableTreeWalk                         ,




    ) 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 {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo

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

instance GObject MutableTree where
    gobjectType :: IO GType
gobjectType = IO GType
c_ostree_mutable_tree_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `MutableTree`.
noMutableTree :: Maybe MutableTree
noMutableTree :: Maybe MutableTree
noMutableTree = Maybe MutableTree
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveMutableTreeMethod (t :: Symbol) (o :: *) :: * where
    ResolveMutableTreeMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveMutableTreeMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveMutableTreeMethod "checkError" o = MutableTreeCheckErrorMethodInfo
    ResolveMutableTreeMethod "ensureDir" o = MutableTreeEnsureDirMethodInfo
    ResolveMutableTreeMethod "ensureParentDirs" o = MutableTreeEnsureParentDirsMethodInfo
    ResolveMutableTreeMethod "fillEmptyFromDirtree" o = MutableTreeFillEmptyFromDirtreeMethodInfo
    ResolveMutableTreeMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveMutableTreeMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveMutableTreeMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveMutableTreeMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveMutableTreeMethod "lookup" o = MutableTreeLookupMethodInfo
    ResolveMutableTreeMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveMutableTreeMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveMutableTreeMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveMutableTreeMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveMutableTreeMethod "remove" o = MutableTreeRemoveMethodInfo
    ResolveMutableTreeMethod "replaceFile" o = MutableTreeReplaceFileMethodInfo
    ResolveMutableTreeMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveMutableTreeMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveMutableTreeMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveMutableTreeMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveMutableTreeMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveMutableTreeMethod "walk" o = MutableTreeWalkMethodInfo
    ResolveMutableTreeMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveMutableTreeMethod "getContentsChecksum" o = MutableTreeGetContentsChecksumMethodInfo
    ResolveMutableTreeMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveMutableTreeMethod "getFiles" o = MutableTreeGetFilesMethodInfo
    ResolveMutableTreeMethod "getMetadataChecksum" o = MutableTreeGetMetadataChecksumMethodInfo
    ResolveMutableTreeMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveMutableTreeMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveMutableTreeMethod "getSubdirs" o = MutableTreeGetSubdirsMethodInfo
    ResolveMutableTreeMethod "setContentsChecksum" o = MutableTreeSetContentsChecksumMethodInfo
    ResolveMutableTreeMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveMutableTreeMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveMutableTreeMethod "setMetadataChecksum" o = MutableTreeSetMetadataChecksumMethodInfo
    ResolveMutableTreeMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveMutableTreeMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveMutableTreeMethod t MutableTree, O.MethodInfo info MutableTree p) => OL.IsLabel t (MutableTree -> 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 MutableTree
type instance O.AttributeList MutableTree = MutableTreeAttributeList
type MutableTreeAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

-- method MutableTree::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "OSTree" , name = "MutableTree" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_mutable_tree_new" ostree_mutable_tree_new :: 
    IO (Ptr MutableTree)

-- | /No description available in the introspection data./
mutableTreeNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m MutableTree
    -- ^ __Returns:__ A new tree
mutableTreeNew :: m MutableTree
mutableTreeNew  = IO MutableTree -> m MutableTree
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutableTree -> m MutableTree)
-> IO MutableTree -> m MutableTree
forall a b. (a -> b) -> a -> b
$ do
    Ptr MutableTree
result <- IO (Ptr MutableTree)
ostree_mutable_tree_new
    Text -> Ptr MutableTree -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "mutableTreeNew" Ptr MutableTree
result
    MutableTree
result' <- ((ManagedPtr MutableTree -> MutableTree)
-> Ptr MutableTree -> IO MutableTree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MutableTree -> MutableTree
MutableTree) Ptr MutableTree
result
    MutableTree -> IO MutableTree
forall (m :: * -> *) a. Monad m => a -> m a
return MutableTree
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MutableTree::new_from_checksum
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repo"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Repo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "The repo which contains the objects refered by the checksums."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "contents_checksum"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "dirtree checksum" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "metadata_checksum"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "dirmeta checksum" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "OSTree" , name = "MutableTree" })
-- throws : False
-- Skip return : False

foreign import ccall "ostree_mutable_tree_new_from_checksum" ostree_mutable_tree_new_from_checksum :: 
    Ptr OSTree.Repo.Repo ->                 -- repo : TInterface (Name {namespace = "OSTree", name = "Repo"})
    CString ->                              -- contents_checksum : TBasicType TUTF8
    CString ->                              -- metadata_checksum : TBasicType TUTF8
    IO (Ptr MutableTree)

-- | Creates a new OstreeMutableTree with the contents taken from the given repo
-- and checksums.  The data will be loaded from the repo lazily as needed.
mutableTreeNewFromChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Repo.IsRepo a) =>
    a
    -- ^ /@repo@/: The repo which contains the objects refered by the checksums.
    -> T.Text
    -- ^ /@contentsChecksum@/: dirtree checksum
    -> T.Text
    -- ^ /@metadataChecksum@/: dirmeta checksum
    -> m MutableTree
    -- ^ __Returns:__ A new tree
mutableTreeNewFromChecksum :: a -> Text -> Text -> m MutableTree
mutableTreeNewFromChecksum repo :: a
repo contentsChecksum :: Text
contentsChecksum metadataChecksum :: Text
metadataChecksum = IO MutableTree -> m MutableTree
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutableTree -> m MutableTree)
-> IO MutableTree -> m MutableTree
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repo
repo' <- a -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repo
    CString
contentsChecksum' <- Text -> IO CString
textToCString Text
contentsChecksum
    CString
metadataChecksum' <- Text -> IO CString
textToCString Text
metadataChecksum
    Ptr MutableTree
result <- Ptr Repo -> CString -> CString -> IO (Ptr MutableTree)
ostree_mutable_tree_new_from_checksum Ptr Repo
repo' CString
contentsChecksum' CString
metadataChecksum'
    Text -> Ptr MutableTree -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "mutableTreeNewFromChecksum" Ptr MutableTree
result
    MutableTree
result' <- ((ManagedPtr MutableTree -> MutableTree)
-> Ptr MutableTree -> IO MutableTree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MutableTree -> MutableTree
MutableTree) Ptr MutableTree
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repo
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
contentsChecksum'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
metadataChecksum'
    MutableTree -> IO MutableTree
forall (m :: * -> *) a. Monad m => a -> m a
return MutableTree
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MutableTree::check_error
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Tree" , 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_mutable_tree_check_error" ostree_mutable_tree_check_error :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | In some cases, a tree may be in a \"lazy\" state that loads
-- data in the background; if an error occurred during a non-throwing
-- API call, it will have been cached.  This function checks for a
-- cached error.  The tree remains in error state.
-- 
-- /Since: 2018.7/
mutableTreeCheckError ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -- ^ /@self@/: Tree
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeCheckError :: a -> m ()
mutableTreeCheckError 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
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 MutableTree -> Ptr (Ptr GError) -> IO CInt
ostree_mutable_tree_check_error Ptr MutableTree
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 MutableTreeCheckErrorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeCheckErrorMethodInfo a signature where
    overloadedMethod = mutableTreeCheckError

#endif

-- method MutableTree::ensure_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Tree" , 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 =
--                     Just "Name of subdirectory of self to retrieve/creates"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_subdir"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the subdirectory" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_mutable_tree_ensure_dir" ostree_mutable_tree_ensure_dir :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr (Ptr MutableTree) ->                -- out_subdir : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Returns the subdirectory of self with filename /@name@/, creating an empty one
-- it if it doesn\'t exist.
mutableTreeEnsureDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -- ^ /@self@/: Tree
    -> T.Text
    -- ^ /@name@/: Name of subdirectory of self to retrieve\/creates
    -> m (MutableTree)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeEnsureDir :: a -> Text -> m MutableTree
mutableTreeEnsureDir self :: a
self name :: Text
name = IO MutableTree -> m MutableTree
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutableTree -> m MutableTree)
-> IO MutableTree -> m MutableTree
forall a b. (a -> b) -> a -> b
$ do
    Ptr MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr (Ptr MutableTree)
outSubdir <- IO (Ptr (Ptr MutableTree))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr MutableTree))
    IO MutableTree -> IO () -> IO MutableTree
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 MutableTree
-> CString -> Ptr (Ptr MutableTree) -> Ptr (Ptr GError) -> IO CInt
ostree_mutable_tree_ensure_dir Ptr MutableTree
self' CString
name' Ptr (Ptr MutableTree)
outSubdir
        Ptr MutableTree
outSubdir' <- Ptr (Ptr MutableTree) -> IO (Ptr MutableTree)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr MutableTree)
outSubdir
        MutableTree
outSubdir'' <- ((ManagedPtr MutableTree -> MutableTree)
-> Ptr MutableTree -> IO MutableTree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MutableTree -> MutableTree
MutableTree) Ptr MutableTree
outSubdir'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outSubdir
        MutableTree -> IO MutableTree
forall (m :: * -> *) a. Monad m => a -> m a
return MutableTree
outSubdir''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outSubdir
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeEnsureDirMethodInfo
instance (signature ~ (T.Text -> m (MutableTree)), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeEnsureDirMethodInfo a signature where
    overloadedMethod = mutableTreeEnsureDir

#endif

-- method MutableTree::ensure_parent_dirs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Tree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "split_path"
--           , argType = TPtrArray (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "File path components"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "metadata_checksum"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "SHA256 checksum for metadata"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_parent"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The parent tree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_mutable_tree_ensure_parent_dirs" ostree_mutable_tree_ensure_parent_dirs :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (GPtrArray CString) ->              -- split_path : TPtrArray (TBasicType TUTF8)
    CString ->                              -- metadata_checksum : TBasicType TUTF8
    Ptr (Ptr MutableTree) ->                -- out_parent : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Create all parent trees necessary for the given /@splitPath@/ to
-- exist.
mutableTreeEnsureParentDirs ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -- ^ /@self@/: Tree
    -> [T.Text]
    -- ^ /@splitPath@/: File path components
    -> T.Text
    -- ^ /@metadataChecksum@/: SHA256 checksum for metadata
    -> m (MutableTree)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeEnsureParentDirs :: a -> [Text] -> Text -> m MutableTree
mutableTreeEnsureParentDirs self :: a
self splitPath :: [Text]
splitPath metadataChecksum :: Text
metadataChecksum = IO MutableTree -> m MutableTree
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutableTree -> m MutableTree)
-> IO MutableTree -> m MutableTree
forall a b. (a -> b) -> a -> b
$ do
    Ptr MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    [CString]
splitPath' <- (Text -> IO CString) -> [Text] -> IO [CString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> IO CString
textToCString [Text]
splitPath
    Ptr (GPtrArray CString)
splitPath'' <- [CString] -> IO (Ptr (GPtrArray CString))
forall a. [Ptr a] -> IO (Ptr (GPtrArray (Ptr a)))
packGPtrArray [CString]
splitPath'
    CString
metadataChecksum' <- Text -> IO CString
textToCString Text
metadataChecksum
    Ptr (Ptr MutableTree)
outParent <- IO (Ptr (Ptr MutableTree))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr MutableTree))
    IO MutableTree -> IO () -> IO MutableTree
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 MutableTree
-> Ptr (GPtrArray CString)
-> CString
-> Ptr (Ptr MutableTree)
-> Ptr (Ptr GError)
-> IO CInt
ostree_mutable_tree_ensure_parent_dirs Ptr MutableTree
self' Ptr (GPtrArray CString)
splitPath'' CString
metadataChecksum' Ptr (Ptr MutableTree)
outParent
        Ptr MutableTree
outParent' <- Ptr (Ptr MutableTree) -> IO (Ptr MutableTree)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr MutableTree)
outParent
        MutableTree
outParent'' <- ((ManagedPtr MutableTree -> MutableTree)
-> Ptr MutableTree -> IO MutableTree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MutableTree -> MutableTree
MutableTree) Ptr MutableTree
outParent'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        (CString -> IO ()) -> Ptr (GPtrArray CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GPtrArray (Ptr a)) -> IO ()
mapPtrArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GPtrArray CString)
splitPath''
        Ptr (GPtrArray CString) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray CString)
splitPath''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
metadataChecksum'
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outParent
        MutableTree -> IO MutableTree
forall (m :: * -> *) a. Monad m => a -> m a
return MutableTree
outParent''
     ) (do
        (CString -> IO ()) -> Ptr (GPtrArray CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GPtrArray (Ptr a)) -> IO ()
mapPtrArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GPtrArray CString)
splitPath''
        Ptr (GPtrArray CString) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray CString)
splitPath''
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
metadataChecksum'
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outParent
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeEnsureParentDirsMethodInfo
instance (signature ~ ([T.Text] -> T.Text -> m (MutableTree)), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeEnsureParentDirsMethodInfo a signature where
    overloadedMethod = mutableTreeEnsureParentDirs

#endif

-- method MutableTree::fill_empty_from_dirtree
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "repo"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Repo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "contents_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_checksum"
--           , argType = TBasicType TUTF8
--           , 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 : False
-- Skip return : False

foreign import ccall "ostree_mutable_tree_fill_empty_from_dirtree" ostree_mutable_tree_fill_empty_from_dirtree :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr OSTree.Repo.Repo ->                 -- repo : TInterface (Name {namespace = "OSTree", name = "Repo"})
    CString ->                              -- contents_checksum : TBasicType TUTF8
    CString ->                              -- metadata_checksum : TBasicType TUTF8
    IO CInt

-- | Merges /@self@/ with the tree given by /@contentsChecksum@/ and
-- /@metadataChecksum@/, but only if it\'s possible without writing new objects to
-- the /@repo@/.  We can do this if either /@self@/ is empty, the tree given by
-- /@contentsChecksum@/ is empty or if both trees already have the same
-- /@contentsChecksum@/.
mutableTreeFillEmptyFromDirtree ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a, OSTree.Repo.IsRepo b) =>
    a
    -> b
    -> T.Text
    -> T.Text
    -> m Bool
    -- ^ __Returns:__ /@tRUE@/ if merge was successful, /@fALSE@/ if it was not possible.
    -- 
    -- This function enables optimisations when composing trees.  The provided
    -- checksums are not loaded or checked when this function is called.  Instead
    -- the contents will be loaded only when needed.
mutableTreeFillEmptyFromDirtree :: a -> b -> Text -> Text -> m Bool
mutableTreeFillEmptyFromDirtree self :: a
self repo :: b
repo contentsChecksum :: Text
contentsChecksum metadataChecksum :: Text
metadataChecksum = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Repo
repo' <- b -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
repo
    CString
contentsChecksum' <- Text -> IO CString
textToCString Text
contentsChecksum
    CString
metadataChecksum' <- Text -> IO CString
textToCString Text
metadataChecksum
    CInt
result <- Ptr MutableTree -> Ptr Repo -> CString -> CString -> IO CInt
ostree_mutable_tree_fill_empty_from_dirtree Ptr MutableTree
self' Ptr Repo
repo' CString
contentsChecksum' CString
metadataChecksum'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
repo
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
contentsChecksum'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
metadataChecksum'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data MutableTreeFillEmptyFromDirtreeMethodInfo
instance (signature ~ (b -> T.Text -> T.Text -> m Bool), MonadIO m, IsMutableTree a, OSTree.Repo.IsRepo b) => O.MethodInfo MutableTreeFillEmptyFromDirtreeMethodInfo a signature where
    overloadedMethod = mutableTreeFillEmptyFromDirtree

#endif

-- method MutableTree::get_contents_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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_mutable_tree_get_contents_checksum" ostree_mutable_tree_get_contents_checksum :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    IO CString

-- | /No description available in the introspection data./
mutableTreeGetContentsChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> m T.Text
mutableTreeGetContentsChecksum :: a -> m Text
mutableTreeGetContentsChecksum 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr MutableTree -> IO CString
ostree_mutable_tree_get_contents_checksum Ptr MutableTree
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "mutableTreeGetContentsChecksum" 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 MutableTreeGetContentsChecksumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeGetContentsChecksumMethodInfo a signature where
    overloadedMethod = mutableTreeGetContentsChecksum

#endif

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

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

-- | /No description available in the introspection data./
mutableTreeGetFiles ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> m (Map.Map T.Text T.Text)
    -- ^ __Returns:__ All children files (the value is a checksum)
mutableTreeGetFiles :: a -> m (Map Text Text)
mutableTreeGetFiles self :: a
self = IO (Map Text Text) -> m (Map Text Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map Text Text) -> m (Map Text Text))
-> IO (Map Text Text) -> m (Map Text Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr (GHashTable CString CString)
result <- Ptr MutableTree -> IO (Ptr (GHashTable CString CString))
ostree_mutable_tree_get_files Ptr MutableTree
self'
    Text -> Ptr (GHashTable CString CString) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "mutableTreeGetFiles" Ptr (GHashTable CString CString)
result
    [(PtrWrapped CString, PtrWrapped CString)]
result' <- Ptr (GHashTable CString CString)
-> IO [(PtrWrapped CString, PtrWrapped CString)]
forall a b.
Ptr (GHashTable a b) -> IO [(PtrWrapped a, PtrWrapped b)]
unpackGHashTable Ptr (GHashTable CString CString)
result
    let result'' :: [(CString, PtrWrapped CString)]
result'' = (PtrWrapped CString -> CString)
-> [(PtrWrapped CString, PtrWrapped CString)]
-> [(CString, PtrWrapped CString)]
forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFirst PtrWrapped CString -> CString
cstringUnpackPtr [(PtrWrapped CString, PtrWrapped CString)]
result'
    [(Text, PtrWrapped CString)]
result''' <- (CString -> IO Text)
-> [(CString, PtrWrapped CString)]
-> IO [(Text, PtrWrapped CString)]
forall (f :: * -> *) a c b.
Applicative f =>
(a -> f c) -> [(a, b)] -> f [(c, b)]
mapFirstA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(CString, PtrWrapped CString)]
result''
    let result'''' :: [(Text, CString)]
result'''' = (PtrWrapped CString -> CString)
-> [(Text, PtrWrapped CString)] -> [(Text, CString)]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped CString -> CString
cstringUnpackPtr [(Text, PtrWrapped CString)]
result'''
    [(Text, Text)]
result''''' <- (CString -> IO Text) -> [(Text, CString)] -> IO [(Text, Text)]
forall (f :: * -> *) b c a.
Applicative f =>
(b -> f c) -> [(a, b)] -> f [(a, c)]
mapSecondA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(Text, CString)]
result''''
    let result'''''' :: Map Text Text
result'''''' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
result'''''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Map Text Text -> IO (Map Text Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Map Text Text
result''''''

#if defined(ENABLE_OVERLOADING)
data MutableTreeGetFilesMethodInfo
instance (signature ~ (m (Map.Map T.Text T.Text)), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeGetFilesMethodInfo a signature where
    overloadedMethod = mutableTreeGetFiles

#endif

-- method MutableTree::get_metadata_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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_mutable_tree_get_metadata_checksum" ostree_mutable_tree_get_metadata_checksum :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    IO CString

-- | /No description available in the introspection data./
mutableTreeGetMetadataChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> m T.Text
mutableTreeGetMetadataChecksum :: a -> m Text
mutableTreeGetMetadataChecksum 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr MutableTree -> IO CString
ostree_mutable_tree_get_metadata_checksum Ptr MutableTree
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "mutableTreeGetMetadataChecksum" 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 MutableTreeGetMetadataChecksumMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeGetMetadataChecksumMethodInfo a signature where
    overloadedMethod = mutableTreeGetMetadataChecksum

#endif

-- XXX Could not generate method MutableTree::get_subdirs
-- Error was : Not implemented: "GHashTable element of type TInterface (Name {namespace = \"OSTree\", name = \"MutableTree\"}) unsupported."
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data MutableTreeGetSubdirsMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "getSubdirs" MutableTree) => O.MethodInfo MutableTreeGetSubdirsMethodInfo o p where
    overloadedMethod = undefined
#endif

-- method MutableTree::lookup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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 = "out_file_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 = "out_subdir"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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_mutable_tree_lookup" ostree_mutable_tree_lookup :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- out_file_checksum : TBasicType TUTF8
    Ptr MutableTree ->                      -- out_subdir : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
mutableTreeLookup ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a, IsMutableTree b) =>
    a
    -> T.Text
    -> T.Text
    -> b
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeLookup :: a -> Text -> Text -> b -> m ()
mutableTreeLookup self :: a
self name :: Text
name outFileChecksum :: Text
outFileChecksum outSubdir :: b
outSubdir = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
outFileChecksum' <- Text -> IO CString
textToCString Text
outFileChecksum
    Ptr MutableTree
outSubdir' <- b -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
outSubdir
    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 MutableTree
-> CString
-> CString
-> Ptr MutableTree
-> Ptr (Ptr GError)
-> IO CInt
ostree_mutable_tree_lookup Ptr MutableTree
self' CString
name' CString
outFileChecksum' Ptr MutableTree
outSubdir'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
outSubdir
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
outFileChecksum'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
outFileChecksum'
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeLookupMethodInfo
instance (signature ~ (T.Text -> T.Text -> b -> m ()), MonadIO m, IsMutableTree a, IsMutableTree b) => O.MethodInfo MutableTreeLookupMethodInfo a signature where
    overloadedMethod = mutableTreeLookup

#endif

-- method MutableTree::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Tree" , 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 = Just "Name of file or subdirectory to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "allow_noent"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "If @FALSE, an error will be thrown if @name does not exist in the tree"
--                 , 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_mutable_tree_remove" ostree_mutable_tree_remove :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- name : TBasicType TUTF8
    CInt ->                                 -- allow_noent : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Remove the file or subdirectory named /@name@/ from the mutable tree /@self@/.
mutableTreeRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -- ^ /@self@/: Tree
    -> T.Text
    -- ^ /@name@/: Name of file or subdirectory to remove
    -> Bool
    -- ^ /@allowNoent@/: If /@fALSE@/, an error will be thrown if /@name@/ does not exist in the tree
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeRemove :: a -> Text -> Bool -> m ()
mutableTreeRemove self :: a
self name :: Text
name allowNoent :: Bool
allowNoent = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    let allowNoent' :: CInt
allowNoent' = (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
allowNoent
    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 MutableTree -> CString -> CInt -> Ptr (Ptr GError) -> IO CInt
ostree_mutable_tree_remove Ptr MutableTree
self' CString
name' CInt
allowNoent'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeRemoveMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeRemoveMethodInfo a signature where
    overloadedMethod = mutableTreeRemove

#endif

-- method MutableTree::replace_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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 = "checksum"
--           , argType = TBasicType TUTF8
--           , 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_mutable_tree_replace_file" ostree_mutable_tree_replace_file :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- name : TBasicType TUTF8
    CString ->                              -- checksum : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | /No description available in the introspection data./
mutableTreeReplaceFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> T.Text
    -> T.Text
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeReplaceFile :: a -> Text -> Text -> m ()
mutableTreeReplaceFile self :: a
self name :: Text
name checksum :: Text
checksum = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
name' <- Text -> IO CString
textToCString Text
name
    CString
checksum' <- Text -> IO CString
textToCString Text
checksum
    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 MutableTree
-> CString -> CString -> Ptr (Ptr GError) -> IO CInt
ostree_mutable_tree_replace_file Ptr MutableTree
self' CString
name' CString
checksum'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
checksum'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
checksum'
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeReplaceFileMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeReplaceFileMethodInfo a signature where
    overloadedMethod = mutableTreeReplaceFile

#endif

-- method MutableTree::set_contents_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_mutable_tree_set_contents_checksum" ostree_mutable_tree_set_contents_checksum :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- checksum : TBasicType TUTF8
    IO ()

-- | /No description available in the introspection data./
mutableTreeSetContentsChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> T.Text
    -> m ()
mutableTreeSetContentsChecksum :: a -> Text -> m ()
mutableTreeSetContentsChecksum self :: a
self checksum :: Text
checksum = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
checksum' <- Text -> IO CString
textToCString Text
checksum
    Ptr MutableTree -> CString -> IO ()
ostree_mutable_tree_set_contents_checksum Ptr MutableTree
self' CString
checksum'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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 MutableTreeSetContentsChecksumMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeSetContentsChecksumMethodInfo a signature where
    overloadedMethod = mutableTreeSetContentsChecksum

#endif

-- method MutableTree::set_metadata_checksum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , 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
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ostree_mutable_tree_set_metadata_checksum" ostree_mutable_tree_set_metadata_checksum :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    CString ->                              -- checksum : TBasicType TUTF8
    IO ()

-- | /No description available in the introspection data./
mutableTreeSetMetadataChecksum ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -> T.Text
    -> m ()
mutableTreeSetMetadataChecksum :: a -> Text -> m ()
mutableTreeSetMetadataChecksum self :: a
self checksum :: Text
checksum = 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 MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
checksum' <- Text -> IO CString
textToCString Text
checksum
    Ptr MutableTree -> CString -> IO ()
ostree_mutable_tree_set_metadata_checksum Ptr MutableTree
self' CString
checksum'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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 MutableTreeSetMetadataChecksumMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeSetMetadataChecksumMethodInfo a signature where
    overloadedMethod = mutableTreeSetMetadataChecksum

#endif

-- method MutableTree::walk
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Tree" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "split_path"
--           , argType = TPtrArray (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Split pathname" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Descend from this number of elements in @split_path"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_subdir"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "MutableTree" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Target parent" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ostree_mutable_tree_walk" ostree_mutable_tree_walk :: 
    Ptr MutableTree ->                      -- self : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (GPtrArray CString) ->              -- split_path : TPtrArray (TBasicType TUTF8)
    Word32 ->                               -- start : TBasicType TUInt
    Ptr (Ptr MutableTree) ->                -- out_subdir : TInterface (Name {namespace = "OSTree", name = "MutableTree"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Traverse /@start@/ number of elements starting from /@splitPath@/; the
-- child will be returned in /@outSubdir@/.
mutableTreeWalk ::
    (B.CallStack.HasCallStack, MonadIO m, IsMutableTree a) =>
    a
    -- ^ /@self@/: Tree
    -> [T.Text]
    -- ^ /@splitPath@/: Split pathname
    -> Word32
    -- ^ /@start@/: Descend from this number of elements in /@splitPath@/
    -> m (MutableTree)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
mutableTreeWalk :: a -> [Text] -> Word32 -> m MutableTree
mutableTreeWalk self :: a
self splitPath :: [Text]
splitPath start :: Word32
start = IO MutableTree -> m MutableTree
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MutableTree -> m MutableTree)
-> IO MutableTree -> m MutableTree
forall a b. (a -> b) -> a -> b
$ do
    Ptr MutableTree
self' <- a -> IO (Ptr MutableTree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    [CString]
splitPath' <- (Text -> IO CString) -> [Text] -> IO [CString]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> IO CString
textToCString [Text]
splitPath
    Ptr (GPtrArray CString)
splitPath'' <- [CString] -> IO (Ptr (GPtrArray CString))
forall a. [Ptr a] -> IO (Ptr (GPtrArray (Ptr a)))
packGPtrArray [CString]
splitPath'
    Ptr (Ptr MutableTree)
outSubdir <- IO (Ptr (Ptr MutableTree))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr MutableTree))
    IO MutableTree -> IO () -> IO MutableTree
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 MutableTree
-> Ptr (GPtrArray CString)
-> Word32
-> Ptr (Ptr MutableTree)
-> Ptr (Ptr GError)
-> IO CInt
ostree_mutable_tree_walk Ptr MutableTree
self' Ptr (GPtrArray CString)
splitPath'' Word32
start Ptr (Ptr MutableTree)
outSubdir
        Ptr MutableTree
outSubdir' <- Ptr (Ptr MutableTree) -> IO (Ptr MutableTree)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr MutableTree)
outSubdir
        MutableTree
outSubdir'' <- ((ManagedPtr MutableTree -> MutableTree)
-> Ptr MutableTree -> IO MutableTree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr MutableTree -> MutableTree
MutableTree) Ptr MutableTree
outSubdir'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        (CString -> IO ()) -> Ptr (GPtrArray CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GPtrArray (Ptr a)) -> IO ()
mapPtrArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GPtrArray CString)
splitPath''
        Ptr (GPtrArray CString) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray CString)
splitPath''
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outSubdir
        MutableTree -> IO MutableTree
forall (m :: * -> *) a. Monad m => a -> m a
return MutableTree
outSubdir''
     ) (do
        (CString -> IO ()) -> Ptr (GPtrArray CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (GPtrArray (Ptr a)) -> IO ()
mapPtrArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (GPtrArray CString)
splitPath''
        Ptr (GPtrArray CString) -> IO ()
forall a. Ptr (GPtrArray a) -> IO ()
unrefPtrArray Ptr (GPtrArray CString)
splitPath''
        Ptr (Ptr MutableTree) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr MutableTree)
outSubdir
     )

#if defined(ENABLE_OVERLOADING)
data MutableTreeWalkMethodInfo
instance (signature ~ ([T.Text] -> Word32 -> m (MutableTree)), MonadIO m, IsMutableTree a) => O.MethodInfo MutableTreeWalkMethodInfo a signature where
    overloadedMethod = mutableTreeWalk

#endif