{-# 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.SysrootUpgrader
    ( 

-- * Exported types
    SysrootUpgrader(..)                     ,
    IsSysrootUpgrader                       ,
    toSysrootUpgrader                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveSysrootUpgraderMethod            ,
#endif


-- ** checkTimestamps #method:checkTimestamps#

    sysrootUpgraderCheckTimestamps          ,


-- ** deploy #method:deploy#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderDeployMethodInfo         ,
#endif
    sysrootUpgraderDeploy                   ,


-- ** dupOrigin #method:dupOrigin#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderDupOriginMethodInfo      ,
#endif
    sysrootUpgraderDupOrigin                ,


-- ** getOrigin #method:getOrigin#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderGetOriginMethodInfo      ,
#endif
    sysrootUpgraderGetOrigin                ,


-- ** getOriginDescription #method:getOriginDescription#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderGetOriginDescriptionMethodInfo,
#endif
    sysrootUpgraderGetOriginDescription     ,


-- ** new #method:new#

    sysrootUpgraderNew                      ,


-- ** newForOs #method:newForOs#

    sysrootUpgraderNewForOs                 ,


-- ** newForOsWithFlags #method:newForOsWithFlags#

    sysrootUpgraderNewForOsWithFlags        ,


-- ** pull #method:pull#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderPullMethodInfo           ,
#endif
    sysrootUpgraderPull                     ,


-- ** pullOneDir #method:pullOneDir#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderPullOneDirMethodInfo     ,
#endif
    sysrootUpgraderPullOneDir               ,


-- ** setOrigin #method:setOrigin#

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderSetOriginMethodInfo      ,
#endif
    sysrootUpgraderSetOrigin                ,




 -- * Properties
-- ** flags #attr:flags#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderFlagsPropertyInfo        ,
#endif
    constructSysrootUpgraderFlags           ,
    getSysrootUpgraderFlags                 ,
#if defined(ENABLE_OVERLOADING)
    sysrootUpgraderFlags                    ,
#endif


-- ** osname #attr:osname#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderOsnamePropertyInfo       ,
#endif
    constructSysrootUpgraderOsname          ,
    getSysrootUpgraderOsname                ,
#if defined(ENABLE_OVERLOADING)
    sysrootUpgraderOsname                   ,
#endif


-- ** sysroot #attr:sysroot#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    SysrootUpgraderSysrootPropertyInfo      ,
#endif
    constructSysrootUpgraderSysroot         ,
    getSysrootUpgraderSysroot               ,
#if defined(ENABLE_OVERLOADING)
    sysrootUpgraderSysroot                  ,
#endif




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.OSTree.Flags as OSTree.Flags
import {-# SOURCE #-} qualified GI.OSTree.Objects.AsyncProgress as OSTree.AsyncProgress
import {-# SOURCE #-} qualified GI.OSTree.Objects.Repo as OSTree.Repo
import {-# SOURCE #-} qualified GI.OSTree.Objects.Sysroot as OSTree.Sysroot

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

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

foreign import ccall "ostree_sysroot_upgrader_get_type"
    c_ostree_sysroot_upgrader_get_type :: IO B.Types.GType

instance B.Types.TypedObject SysrootUpgrader where
    glibType :: IO GType
glibType = IO GType
c_ostree_sysroot_upgrader_get_type

instance B.Types.GObject SysrootUpgrader

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

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

instance O.HasParentTypes SysrootUpgrader
type instance O.ParentTypes SysrootUpgrader = '[GObject.Object.Object, Gio.Initable.Initable]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSysrootUpgraderMethod (t :: Symbol) (o :: *) :: * where
    ResolveSysrootUpgraderMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSysrootUpgraderMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSysrootUpgraderMethod "deploy" o = SysrootUpgraderDeployMethodInfo
    ResolveSysrootUpgraderMethod "dupOrigin" o = SysrootUpgraderDupOriginMethodInfo
    ResolveSysrootUpgraderMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSysrootUpgraderMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSysrootUpgraderMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSysrootUpgraderMethod "init" o = Gio.Initable.InitableInitMethodInfo
    ResolveSysrootUpgraderMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSysrootUpgraderMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSysrootUpgraderMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSysrootUpgraderMethod "pull" o = SysrootUpgraderPullMethodInfo
    ResolveSysrootUpgraderMethod "pullOneDir" o = SysrootUpgraderPullOneDirMethodInfo
    ResolveSysrootUpgraderMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSysrootUpgraderMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSysrootUpgraderMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSysrootUpgraderMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSysrootUpgraderMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSysrootUpgraderMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSysrootUpgraderMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSysrootUpgraderMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSysrootUpgraderMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSysrootUpgraderMethod "getOrigin" o = SysrootUpgraderGetOriginMethodInfo
    ResolveSysrootUpgraderMethod "getOriginDescription" o = SysrootUpgraderGetOriginDescriptionMethodInfo
    ResolveSysrootUpgraderMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSysrootUpgraderMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSysrootUpgraderMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSysrootUpgraderMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSysrootUpgraderMethod "setOrigin" o = SysrootUpgraderSetOriginMethodInfo
    ResolveSysrootUpgraderMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSysrootUpgraderMethod l o = O.MethodResolutionFailed l o

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

#endif

-- VVV Prop "flags"
   -- Type: TInterface (Name {namespace = "OSTree", name = "SysrootUpgraderFlags"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' sysrootUpgrader #flags
-- @
getSysrootUpgraderFlags :: (MonadIO m, IsSysrootUpgrader o) => o -> m [OSTree.Flags.SysrootUpgraderFlags]
getSysrootUpgraderFlags :: o -> m [SysrootUpgraderFlags]
getSysrootUpgraderFlags o
obj = IO [SysrootUpgraderFlags] -> m [SysrootUpgraderFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [SysrootUpgraderFlags] -> m [SysrootUpgraderFlags])
-> IO [SysrootUpgraderFlags] -> m [SysrootUpgraderFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [SysrootUpgraderFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"flags"

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSysrootUpgraderFlags :: (IsSysrootUpgrader o, MIO.MonadIO m) => [OSTree.Flags.SysrootUpgraderFlags] -> m (GValueConstruct o)
constructSysrootUpgraderFlags :: [SysrootUpgraderFlags] -> m (GValueConstruct o)
constructSysrootUpgraderFlags [SysrootUpgraderFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [SysrootUpgraderFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [SysrootUpgraderFlags]
val

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderFlagsPropertyInfo
instance AttrInfo SysrootUpgraderFlagsPropertyInfo where
    type AttrAllowedOps SysrootUpgraderFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint SysrootUpgraderFlagsPropertyInfo = IsSysrootUpgrader
    type AttrSetTypeConstraint SysrootUpgraderFlagsPropertyInfo = (~) [OSTree.Flags.SysrootUpgraderFlags]
    type AttrTransferTypeConstraint SysrootUpgraderFlagsPropertyInfo = (~) [OSTree.Flags.SysrootUpgraderFlags]
    type AttrTransferType SysrootUpgraderFlagsPropertyInfo = [OSTree.Flags.SysrootUpgraderFlags]
    type AttrGetType SysrootUpgraderFlagsPropertyInfo = [OSTree.Flags.SysrootUpgraderFlags]
    type AttrLabel SysrootUpgraderFlagsPropertyInfo = "flags"
    type AttrOrigin SysrootUpgraderFlagsPropertyInfo = SysrootUpgrader
    attrGet = getSysrootUpgraderFlags
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSysrootUpgraderFlags
    attrClear = undefined
#endif

-- VVV Prop "osname"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@osname@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' sysrootUpgrader #osname
-- @
getSysrootUpgraderOsname :: (MonadIO m, IsSysrootUpgrader o) => o -> m (Maybe T.Text)
getSysrootUpgraderOsname :: o -> m (Maybe Text)
getSysrootUpgraderOsname o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"osname"

-- | Construct a `GValueConstruct` with valid value for the “@osname@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSysrootUpgraderOsname :: (IsSysrootUpgrader o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSysrootUpgraderOsname :: Text -> m (GValueConstruct o)
constructSysrootUpgraderOsname Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"osname" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderOsnamePropertyInfo
instance AttrInfo SysrootUpgraderOsnamePropertyInfo where
    type AttrAllowedOps SysrootUpgraderOsnamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SysrootUpgraderOsnamePropertyInfo = IsSysrootUpgrader
    type AttrSetTypeConstraint SysrootUpgraderOsnamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint SysrootUpgraderOsnamePropertyInfo = (~) T.Text
    type AttrTransferType SysrootUpgraderOsnamePropertyInfo = T.Text
    type AttrGetType SysrootUpgraderOsnamePropertyInfo = (Maybe T.Text)
    type AttrLabel SysrootUpgraderOsnamePropertyInfo = "osname"
    type AttrOrigin SysrootUpgraderOsnamePropertyInfo = SysrootUpgrader
    attrGet = getSysrootUpgraderOsname
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSysrootUpgraderOsname
    attrClear = undefined
#endif

-- VVV Prop "sysroot"
   -- Type: TInterface (Name {namespace = "OSTree", name = "Sysroot"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@sysroot@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' sysrootUpgrader #sysroot
-- @
getSysrootUpgraderSysroot :: (MonadIO m, IsSysrootUpgrader o) => o -> m (Maybe OSTree.Sysroot.Sysroot)
getSysrootUpgraderSysroot :: o -> m (Maybe Sysroot)
getSysrootUpgraderSysroot o
obj = IO (Maybe Sysroot) -> m (Maybe Sysroot)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Sysroot) -> m (Maybe Sysroot))
-> IO (Maybe Sysroot) -> m (Maybe Sysroot)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Sysroot -> Sysroot) -> IO (Maybe Sysroot)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"sysroot" ManagedPtr Sysroot -> Sysroot
OSTree.Sysroot.Sysroot

-- | Construct a `GValueConstruct` with valid value for the “@sysroot@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSysrootUpgraderSysroot :: (IsSysrootUpgrader o, MIO.MonadIO m, OSTree.Sysroot.IsSysroot a) => a -> m (GValueConstruct o)
constructSysrootUpgraderSysroot :: a -> m (GValueConstruct o)
constructSysrootUpgraderSysroot a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"sysroot" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderSysrootPropertyInfo
instance AttrInfo SysrootUpgraderSysrootPropertyInfo where
    type AttrAllowedOps SysrootUpgraderSysrootPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint SysrootUpgraderSysrootPropertyInfo = IsSysrootUpgrader
    type AttrSetTypeConstraint SysrootUpgraderSysrootPropertyInfo = OSTree.Sysroot.IsSysroot
    type AttrTransferTypeConstraint SysrootUpgraderSysrootPropertyInfo = OSTree.Sysroot.IsSysroot
    type AttrTransferType SysrootUpgraderSysrootPropertyInfo = OSTree.Sysroot.Sysroot
    type AttrGetType SysrootUpgraderSysrootPropertyInfo = (Maybe OSTree.Sysroot.Sysroot)
    type AttrLabel SysrootUpgraderSysrootPropertyInfo = "sysroot"
    type AttrOrigin SysrootUpgraderSysrootPropertyInfo = SysrootUpgrader
    attrGet = getSysrootUpgraderSysroot
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo OSTree.Sysroot.Sysroot v
    attrConstruct = constructSysrootUpgraderSysroot
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SysrootUpgrader
type instance O.AttributeList SysrootUpgrader = SysrootUpgraderAttributeList
type SysrootUpgraderAttributeList = ('[ '("flags", SysrootUpgraderFlagsPropertyInfo), '("osname", SysrootUpgraderOsnamePropertyInfo), '("sysroot", SysrootUpgraderSysrootPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
sysrootUpgraderFlags :: AttrLabelProxy "flags"
sysrootUpgraderFlags = AttrLabelProxy

sysrootUpgraderOsname :: AttrLabelProxy "osname"
sysrootUpgraderOsname = AttrLabelProxy

sysrootUpgraderSysroot :: AttrLabelProxy "sysroot"
sysrootUpgraderSysroot = AttrLabelProxy

#endif

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

#endif

-- method SysrootUpgrader::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "sysroot"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Sysroot" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #OstreeSysroot" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "OSTree" , name = "SysrootUpgrader" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sysroot_upgrader_new" ostree_sysroot_upgrader_new :: 
    Ptr OSTree.Sysroot.Sysroot ->           -- sysroot : TInterface (Name {namespace = "OSTree", name = "Sysroot"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SysrootUpgrader)

-- | /No description available in the introspection data./
sysrootUpgraderNew ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Sysroot.IsSysroot a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@sysroot@/: An t'GI.OSTree.Objects.Sysroot.Sysroot'
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m SysrootUpgrader
    -- ^ __Returns:__ An upgrader /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderNew :: a -> Maybe b -> m SysrootUpgrader
sysrootUpgraderNew a
sysroot Maybe b
cancellable = IO SysrootUpgrader -> m SysrootUpgrader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SysrootUpgrader -> m SysrootUpgrader)
-> IO SysrootUpgrader -> m SysrootUpgrader
forall a b. (a -> b) -> a -> b
$ do
    Ptr Sysroot
sysroot' <- a -> IO (Ptr Sysroot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
sysroot
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SysrootUpgrader -> IO () -> IO SysrootUpgrader
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SysrootUpgrader
result <- (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
 -> IO (Ptr SysrootUpgrader))
-> (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a b. (a -> b) -> a -> b
$ Ptr Sysroot
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader)
ostree_sysroot_upgrader_new Ptr Sysroot
sysroot' Ptr Cancellable
maybeCancellable
        Text -> Ptr SysrootUpgrader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderNew" Ptr SysrootUpgrader
result
        SysrootUpgrader
result' <- ((ManagedPtr SysrootUpgrader -> SysrootUpgrader)
-> Ptr SysrootUpgrader -> IO SysrootUpgrader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SysrootUpgrader -> SysrootUpgrader
SysrootUpgrader) Ptr SysrootUpgrader
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
sysroot
        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
        SysrootUpgrader -> IO SysrootUpgrader
forall (m :: * -> *) a. Monad m => a -> m a
return SysrootUpgrader
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SysrootUpgrader::new_for_os
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "sysroot"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Sysroot" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #OstreeSysroot" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "osname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Operating system name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "OSTree" , name = "SysrootUpgrader" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sysroot_upgrader_new_for_os" ostree_sysroot_upgrader_new_for_os :: 
    Ptr OSTree.Sysroot.Sysroot ->           -- sysroot : TInterface (Name {namespace = "OSTree", name = "Sysroot"})
    CString ->                              -- osname : TBasicType TUTF8
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SysrootUpgrader)

-- | /No description available in the introspection data./
sysrootUpgraderNewForOs ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Sysroot.IsSysroot a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@sysroot@/: An t'GI.OSTree.Objects.Sysroot.Sysroot'
    -> Maybe (T.Text)
    -- ^ /@osname@/: Operating system name
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m SysrootUpgrader
    -- ^ __Returns:__ An upgrader /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderNewForOs :: a -> Maybe Text -> Maybe b -> m SysrootUpgrader
sysrootUpgraderNewForOs a
sysroot Maybe Text
osname Maybe b
cancellable = IO SysrootUpgrader -> m SysrootUpgrader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SysrootUpgrader -> m SysrootUpgrader)
-> IO SysrootUpgrader -> m SysrootUpgrader
forall a b. (a -> b) -> a -> b
$ do
    Ptr Sysroot
sysroot' <- a -> IO (Ptr Sysroot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
sysroot
    Ptr CChar
maybeOsname <- case Maybe Text
osname of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jOsname -> do
            Ptr CChar
jOsname' <- Text -> IO (Ptr CChar)
textToCString Text
jOsname
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jOsname'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SysrootUpgrader -> IO () -> IO SysrootUpgrader
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SysrootUpgrader
result <- (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
 -> IO (Ptr SysrootUpgrader))
-> (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a b. (a -> b) -> a -> b
$ Ptr Sysroot
-> Ptr CChar
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr SysrootUpgrader)
ostree_sysroot_upgrader_new_for_os Ptr Sysroot
sysroot' Ptr CChar
maybeOsname Ptr Cancellable
maybeCancellable
        Text -> Ptr SysrootUpgrader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderNewForOs" Ptr SysrootUpgrader
result
        SysrootUpgrader
result' <- ((ManagedPtr SysrootUpgrader -> SysrootUpgrader)
-> Ptr SysrootUpgrader -> IO SysrootUpgrader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SysrootUpgrader -> SysrootUpgrader
SysrootUpgrader) Ptr SysrootUpgrader
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
sysroot
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOsname
        SysrootUpgrader -> IO SysrootUpgrader
forall (m :: * -> *) a. Monad m => a -> m a
return SysrootUpgrader
result'
     ) (do
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOsname
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SysrootUpgrader::new_for_os_with_flags
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "sysroot"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Sysroot" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "An #OstreeSysroot" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "osname"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Operating system name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "SysrootUpgraderFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "OSTree" , name = "SysrootUpgrader" })
-- throws : True
-- Skip return : False

foreign import ccall "ostree_sysroot_upgrader_new_for_os_with_flags" ostree_sysroot_upgrader_new_for_os_with_flags :: 
    Ptr OSTree.Sysroot.Sysroot ->           -- sysroot : TInterface (Name {namespace = "OSTree", name = "Sysroot"})
    CString ->                              -- osname : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "OSTree", name = "SysrootUpgraderFlags"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SysrootUpgrader)

-- | /No description available in the introspection data./
sysrootUpgraderNewForOsWithFlags ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Sysroot.IsSysroot a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@sysroot@/: An t'GI.OSTree.Objects.Sysroot.Sysroot'
    -> Maybe (T.Text)
    -- ^ /@osname@/: Operating system name
    -> [OSTree.Flags.SysrootUpgraderFlags]
    -- ^ /@flags@/: Flags
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m SysrootUpgrader
    -- ^ __Returns:__ An upgrader /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderNewForOsWithFlags :: a
-> Maybe Text
-> [SysrootUpgraderFlags]
-> Maybe b
-> m SysrootUpgrader
sysrootUpgraderNewForOsWithFlags a
sysroot Maybe Text
osname [SysrootUpgraderFlags]
flags Maybe b
cancellable = IO SysrootUpgrader -> m SysrootUpgrader
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SysrootUpgrader -> m SysrootUpgrader)
-> IO SysrootUpgrader -> m SysrootUpgrader
forall a b. (a -> b) -> a -> b
$ do
    Ptr Sysroot
sysroot' <- a -> IO (Ptr Sysroot)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
sysroot
    Ptr CChar
maybeOsname <- case Maybe Text
osname of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jOsname -> do
            Ptr CChar
jOsname' <- Text -> IO (Ptr CChar)
textToCString Text
jOsname
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jOsname'
    let flags' :: CUInt
flags' = [SysrootUpgraderFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SysrootUpgraderFlags]
flags
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO SysrootUpgrader -> IO () -> IO SysrootUpgrader
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr SysrootUpgrader
result <- (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
 -> IO (Ptr SysrootUpgrader))
-> (Ptr (Ptr GError) -> IO (Ptr SysrootUpgrader))
-> IO (Ptr SysrootUpgrader)
forall a b. (a -> b) -> a -> b
$ Ptr Sysroot
-> Ptr CChar
-> CUInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO (Ptr SysrootUpgrader)
ostree_sysroot_upgrader_new_for_os_with_flags Ptr Sysroot
sysroot' Ptr CChar
maybeOsname CUInt
flags' Ptr Cancellable
maybeCancellable
        Text -> Ptr SysrootUpgrader -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderNewForOsWithFlags" Ptr SysrootUpgrader
result
        SysrootUpgrader
result' <- ((ManagedPtr SysrootUpgrader -> SysrootUpgrader)
-> Ptr SysrootUpgrader -> IO SysrootUpgrader
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SysrootUpgrader -> SysrootUpgrader
SysrootUpgrader) Ptr SysrootUpgrader
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
sysroot
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOsname
        SysrootUpgrader -> IO SysrootUpgrader
forall (m :: * -> *) a. Monad m => a -> m a
return SysrootUpgrader
result'
     ) (do
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOsname
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method SysrootUpgrader::deploy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SysrootUpgrader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Self" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , 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_sysroot_upgrader_deploy" ostree_sysroot_upgrader_deploy :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Write the new deployment to disk, perform a configuration merge
-- with \/etc, and update the bootloader configuration.
sysrootUpgraderDeploy ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: Self
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderDeploy :: a -> Maybe b -> m ()
sysrootUpgraderDeploy a
self 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 SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (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 SysrootUpgrader
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
ostree_sysroot_upgrader_deploy Ptr SysrootUpgrader
self' Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        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 SysrootUpgraderDeployMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsSysrootUpgrader a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SysrootUpgraderDeployMethodInfo a signature where
    overloadedMethod = sysrootUpgraderDeploy

#endif

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

foreign import ccall "ostree_sysroot_upgrader_dup_origin" ostree_sysroot_upgrader_dup_origin :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    IO (Ptr GLib.KeyFile.KeyFile)

-- | /No description available in the introspection data./
sysrootUpgraderDupOrigin ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a) =>
    a
    -- ^ /@self@/: Sysroot
    -> m GLib.KeyFile.KeyFile
    -- ^ __Returns:__ A copy of the origin file, or 'P.Nothing' if unknown
sysrootUpgraderDupOrigin :: a -> m KeyFile
sysrootUpgraderDupOrigin a
self = IO KeyFile -> m KeyFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO KeyFile -> m KeyFile) -> IO KeyFile -> m KeyFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr KeyFile
result <- Ptr SysrootUpgrader -> IO (Ptr KeyFile)
ostree_sysroot_upgrader_dup_origin Ptr SysrootUpgrader
self'
    Text -> Ptr KeyFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderDupOrigin" Ptr KeyFile
result
    KeyFile
result' <- ((ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr KeyFile -> KeyFile
GLib.KeyFile.KeyFile) Ptr KeyFile
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    KeyFile -> IO KeyFile
forall (m :: * -> *) a. Monad m => a -> m a
return KeyFile
result'

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderDupOriginMethodInfo
instance (signature ~ (m GLib.KeyFile.KeyFile), MonadIO m, IsSysrootUpgrader a) => O.MethodInfo SysrootUpgraderDupOriginMethodInfo a signature where
    overloadedMethod = sysrootUpgraderDupOrigin

#endif

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

foreign import ccall "ostree_sysroot_upgrader_get_origin" ostree_sysroot_upgrader_get_origin :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    IO (Ptr GLib.KeyFile.KeyFile)

-- | /No description available in the introspection data./
sysrootUpgraderGetOrigin ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a) =>
    a
    -- ^ /@self@/: Sysroot
    -> m GLib.KeyFile.KeyFile
    -- ^ __Returns:__ The origin file, or 'P.Nothing' if unknown
sysrootUpgraderGetOrigin :: a -> m KeyFile
sysrootUpgraderGetOrigin a
self = IO KeyFile -> m KeyFile
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO KeyFile -> m KeyFile) -> IO KeyFile -> m KeyFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr KeyFile
result <- Ptr SysrootUpgrader -> IO (Ptr KeyFile)
ostree_sysroot_upgrader_get_origin Ptr SysrootUpgrader
self'
    Text -> Ptr KeyFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderGetOrigin" Ptr KeyFile
result
    KeyFile
result' <- ((ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr KeyFile -> KeyFile
GLib.KeyFile.KeyFile) Ptr KeyFile
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    KeyFile -> IO KeyFile
forall (m :: * -> *) a. Monad m => a -> m a
return KeyFile
result'

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderGetOriginMethodInfo
instance (signature ~ (m GLib.KeyFile.KeyFile), MonadIO m, IsSysrootUpgrader a) => O.MethodInfo SysrootUpgraderGetOriginMethodInfo a signature where
    overloadedMethod = sysrootUpgraderGetOrigin

#endif

-- method SysrootUpgrader::get_origin_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SysrootUpgrader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Upgrader" , 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_sysroot_upgrader_get_origin_description" ostree_sysroot_upgrader_get_origin_description :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    IO CString

-- | /No description available in the introspection data./
sysrootUpgraderGetOriginDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a) =>
    a
    -- ^ /@self@/: Upgrader
    -> m T.Text
    -- ^ __Returns:__ A one-line descriptive summary of the origin, or 'P.Nothing' if unknown
sysrootUpgraderGetOriginDescription :: a -> m Text
sysrootUpgraderGetOriginDescription 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 SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
result <- Ptr SysrootUpgrader -> IO (Ptr CChar)
ostree_sysroot_upgrader_get_origin_description Ptr SysrootUpgrader
self'
    Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"sysrootUpgraderGetOriginDescription" Ptr CChar
result
    Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
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 SysrootUpgraderGetOriginDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsSysrootUpgrader a) => O.MethodInfo SysrootUpgraderGetOriginDescriptionMethodInfo a signature where
    overloadedMethod = sysrootUpgraderGetOriginDescription

#endif

-- method SysrootUpgrader::pull
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SysrootUpgrader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Upgrader" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoPullFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags controlling pull behavior"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "upgrader_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "SysrootUpgraderPullFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags controlling upgrader behavior"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "progress"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "AsyncProgress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Progress" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_changed"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether or not the origin changed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , 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_sysroot_upgrader_pull" ostree_sysroot_upgrader_pull :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "OSTree", name = "RepoPullFlags"})
    CUInt ->                                -- upgrader_flags : TInterface (Name {namespace = "OSTree", name = "SysrootUpgraderPullFlags"})
    Ptr OSTree.AsyncProgress.AsyncProgress -> -- progress : TInterface (Name {namespace = "OSTree", name = "AsyncProgress"})
    Ptr CInt ->                             -- out_changed : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Perform a pull from the origin.  First check if the ref has
-- changed, if so download the linked objects, and store the updated
-- ref locally.  Then /@outChanged@/ will be 'P.True'.
-- 
-- If the origin remote is unchanged, /@outChanged@/ will be set to
-- 'P.False'.
sysrootUpgraderPull ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a, OSTree.AsyncProgress.IsAsyncProgress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: Upgrader
    -> [OSTree.Flags.RepoPullFlags]
    -- ^ /@flags@/: Flags controlling pull behavior
    -> [OSTree.Flags.SysrootUpgraderPullFlags]
    -- ^ /@upgraderFlags@/: Flags controlling upgrader behavior
    -> Maybe (b)
    -- ^ /@progress@/: Progress
    -> Maybe (c)
    -- ^ /@cancellable@/: Cancellable
    -> m (Bool)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderPull :: a
-> [RepoPullFlags]
-> [SysrootUpgraderPullFlags]
-> Maybe b
-> Maybe c
-> m Bool
sysrootUpgraderPull a
self [RepoPullFlags]
flags [SysrootUpgraderPullFlags]
upgraderFlags Maybe b
progress Maybe c
cancellable = 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 SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let flags' :: CUInt
flags' = [RepoPullFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [RepoPullFlags]
flags
    let upgraderFlags' :: CUInt
upgraderFlags' = [SysrootUpgraderPullFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SysrootUpgraderPullFlags]
upgraderFlags
    Ptr AsyncProgress
maybeProgress <- case Maybe b
progress of
        Maybe b
Nothing -> Ptr AsyncProgress -> IO (Ptr AsyncProgress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AsyncProgress
forall a. Ptr a
nullPtr
        Just b
jProgress -> do
            Ptr AsyncProgress
jProgress' <- b -> IO (Ptr AsyncProgress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jProgress
            Ptr AsyncProgress -> IO (Ptr AsyncProgress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AsyncProgress
jProgress'
    Ptr CInt
outChanged <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just 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 Bool -> IO () -> IO Bool
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 SysrootUpgrader
-> CUInt
-> CUInt
-> Ptr AsyncProgress
-> Ptr CInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
ostree_sysroot_upgrader_pull Ptr SysrootUpgrader
self' CUInt
flags' CUInt
upgraderFlags' Ptr AsyncProgress
maybeProgress Ptr CInt
outChanged Ptr Cancellable
maybeCancellable
        CInt
outChanged' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
outChanged
        let outChanged'' :: Bool
outChanged'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
outChanged'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
progress b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        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
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
outChanged
        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
outChanged''
     ) (do
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
outChanged
     )

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderPullMethodInfo
instance (signature ~ ([OSTree.Flags.RepoPullFlags] -> [OSTree.Flags.SysrootUpgraderPullFlags] -> Maybe (b) -> Maybe (c) -> m (Bool)), MonadIO m, IsSysrootUpgrader a, OSTree.AsyncProgress.IsAsyncProgress b, Gio.Cancellable.IsCancellable c) => O.MethodInfo SysrootUpgraderPullMethodInfo a signature where
    overloadedMethod = sysrootUpgraderPull

#endif

-- method SysrootUpgrader::pull_one_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SysrootUpgrader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Upgrader" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dir_to_pull"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Subdirectory path (should include a leading /)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "RepoPullFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags controlling pull behavior"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "upgrader_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "OSTree" , name = "SysrootUpgraderPullFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Flags controlling upgrader behavior"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "progress"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "AsyncProgress" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Progress" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "out_changed"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Whether or not the origin changed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , 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_sysroot_upgrader_pull_one_dir" ostree_sysroot_upgrader_pull_one_dir :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    CString ->                              -- dir_to_pull : TBasicType TUTF8
    CUInt ->                                -- flags : TInterface (Name {namespace = "OSTree", name = "RepoPullFlags"})
    CUInt ->                                -- upgrader_flags : TInterface (Name {namespace = "OSTree", name = "SysrootUpgraderPullFlags"})
    Ptr OSTree.AsyncProgress.AsyncProgress -> -- progress : TInterface (Name {namespace = "OSTree", name = "AsyncProgress"})
    Ptr CInt ->                             -- out_changed : TBasicType TBoolean
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Like 'GI.OSTree.Objects.SysrootUpgrader.sysrootUpgraderPull', but allows retrieving just a
-- subpath of the tree.  This can be used to download metadata files
-- from inside the tree such as package databases.
sysrootUpgraderPullOneDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a, OSTree.AsyncProgress.IsAsyncProgress b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: Upgrader
    -> T.Text
    -- ^ /@dirToPull@/: Subdirectory path (should include a leading \/)
    -> [OSTree.Flags.RepoPullFlags]
    -- ^ /@flags@/: Flags controlling pull behavior
    -> [OSTree.Flags.SysrootUpgraderPullFlags]
    -- ^ /@upgraderFlags@/: Flags controlling upgrader behavior
    -> Maybe (b)
    -- ^ /@progress@/: Progress
    -> Maybe (c)
    -- ^ /@cancellable@/: Cancellable
    -> m (Bool)
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderPullOneDir :: a
-> Text
-> [RepoPullFlags]
-> [SysrootUpgraderPullFlags]
-> Maybe b
-> Maybe c
-> m Bool
sysrootUpgraderPullOneDir a
self Text
dirToPull [RepoPullFlags]
flags [SysrootUpgraderPullFlags]
upgraderFlags Maybe b
progress Maybe c
cancellable = 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 SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CChar
dirToPull' <- Text -> IO (Ptr CChar)
textToCString Text
dirToPull
    let flags' :: CUInt
flags' = [RepoPullFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [RepoPullFlags]
flags
    let upgraderFlags' :: CUInt
upgraderFlags' = [SysrootUpgraderPullFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SysrootUpgraderPullFlags]
upgraderFlags
    Ptr AsyncProgress
maybeProgress <- case Maybe b
progress of
        Maybe b
Nothing -> Ptr AsyncProgress -> IO (Ptr AsyncProgress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AsyncProgress
forall a. Ptr a
nullPtr
        Just b
jProgress -> do
            Ptr AsyncProgress
jProgress' <- b -> IO (Ptr AsyncProgress)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jProgress
            Ptr AsyncProgress -> IO (Ptr AsyncProgress)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AsyncProgress
jProgress'
    Ptr CInt
outChanged <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just 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 Bool -> IO () -> IO Bool
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 SysrootUpgrader
-> Ptr CChar
-> CUInt
-> CUInt
-> Ptr AsyncProgress
-> Ptr CInt
-> Ptr Cancellable
-> Ptr (Ptr GError)
-> IO CInt
ostree_sysroot_upgrader_pull_one_dir Ptr SysrootUpgrader
self' Ptr CChar
dirToPull' CUInt
flags' CUInt
upgraderFlags' Ptr AsyncProgress
maybeProgress Ptr CInt
outChanged Ptr Cancellable
maybeCancellable
        CInt
outChanged' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
outChanged
        let outChanged'' :: Bool
outChanged'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
outChanged'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
progress b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        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
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
dirToPull'
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
outChanged
        Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
outChanged''
     ) (do
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
dirToPull'
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
outChanged
     )

#if defined(ENABLE_OVERLOADING)
data SysrootUpgraderPullOneDirMethodInfo
instance (signature ~ (T.Text -> [OSTree.Flags.RepoPullFlags] -> [OSTree.Flags.SysrootUpgraderPullFlags] -> Maybe (b) -> Maybe (c) -> m (Bool)), MonadIO m, IsSysrootUpgrader a, OSTree.AsyncProgress.IsAsyncProgress b, Gio.Cancellable.IsCancellable c) => O.MethodInfo SysrootUpgraderPullOneDirMethodInfo a signature where
    overloadedMethod = sysrootUpgraderPullOneDir

#endif

-- method SysrootUpgrader::set_origin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "SysrootUpgrader" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Sysroot" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "origin"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new origin" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Cancellable" , 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_sysroot_upgrader_set_origin" ostree_sysroot_upgrader_set_origin :: 
    Ptr SysrootUpgrader ->                  -- self : TInterface (Name {namespace = "OSTree", name = "SysrootUpgrader"})
    Ptr GLib.KeyFile.KeyFile ->             -- origin : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Replace the origin with /@origin@/.
sysrootUpgraderSetOrigin ::
    (B.CallStack.HasCallStack, MonadIO m, IsSysrootUpgrader a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: Sysroot
    -> Maybe (GLib.KeyFile.KeyFile)
    -- ^ /@origin@/: The new origin
    -> Maybe (b)
    -- ^ /@cancellable@/: Cancellable
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderSetOrigin :: a -> Maybe KeyFile -> Maybe b -> m ()
sysrootUpgraderSetOrigin a
self Maybe KeyFile
origin 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 SysrootUpgrader
self' <- a -> IO (Ptr SysrootUpgrader)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr KeyFile
maybeOrigin <- case Maybe KeyFile
origin of
        Maybe KeyFile
Nothing -> Ptr KeyFile -> IO (Ptr KeyFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr KeyFile
forall a. Ptr a
nullPtr
        Just KeyFile
jOrigin -> do
            Ptr KeyFile
jOrigin' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
jOrigin
            Ptr KeyFile -> IO (Ptr KeyFile)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr KeyFile
jOrigin'
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (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 SysrootUpgrader
-> Ptr KeyFile -> Ptr Cancellable -> Ptr (Ptr GError) -> IO CInt
ostree_sysroot_upgrader_set_origin Ptr SysrootUpgrader
self' Ptr KeyFile
maybeOrigin Ptr Cancellable
maybeCancellable
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe KeyFile -> (KeyFile -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe KeyFile
origin KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        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 SysrootUpgraderSetOriginMethodInfo
instance (signature ~ (Maybe (GLib.KeyFile.KeyFile) -> Maybe (b) -> m ()), MonadIO m, IsSysrootUpgrader a, Gio.Cancellable.IsCancellable b) => O.MethodInfo SysrootUpgraderSetOriginMethodInfo a signature where
    overloadedMethod = sysrootUpgraderSetOrigin

#endif

-- method SysrootUpgrader::check_timestamps
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "repo"
--           , argType =
--               TInterface Name { namespace = "OSTree" , name = "Repo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Just "Repo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "from_rev"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "From revision" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "to_rev"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "To revision" , 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_sysroot_upgrader_check_timestamps" ostree_sysroot_upgrader_check_timestamps :: 
    Ptr OSTree.Repo.Repo ->                 -- repo : TInterface (Name {namespace = "OSTree", name = "Repo"})
    CString ->                              -- from_rev : TBasicType TUTF8
    CString ->                              -- to_rev : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Check that the timestamp on /@toRev@/ is equal to or newer than
-- /@fromRev@/.  This protects systems against man-in-the-middle
-- attackers which provide a client with an older commit.
sysrootUpgraderCheckTimestamps ::
    (B.CallStack.HasCallStack, MonadIO m, OSTree.Repo.IsRepo a) =>
    a
    -- ^ /@repo@/: Repo
    -> T.Text
    -- ^ /@fromRev@/: From revision
    -> T.Text
    -- ^ /@toRev@/: To revision
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
sysrootUpgraderCheckTimestamps :: a -> Text -> Text -> m ()
sysrootUpgraderCheckTimestamps a
repo Text
fromRev Text
toRev = 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 Repo
repo' <- a -> IO (Ptr Repo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repo
    Ptr CChar
fromRev' <- Text -> IO (Ptr CChar)
textToCString Text
fromRev
    Ptr CChar
toRev' <- Text -> IO (Ptr CChar)
textToCString Text
toRev
    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 Repo -> Ptr CChar -> Ptr CChar -> Ptr (Ptr GError) -> IO CInt
ostree_sysroot_upgrader_check_timestamps Ptr Repo
repo' Ptr CChar
fromRev' Ptr CChar
toRev'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repo
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
fromRev'
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
toRev'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
fromRev'
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
toRev'
     )

#if defined(ENABLE_OVERLOADING)
#endif