{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents the options used when doign a checkout.

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

module GI.Ggit.Objects.CheckoutOptions
    ( 

-- * Exported types
    CheckoutOptions(..)                     ,
    IsCheckoutOptions                       ,
    toCheckoutOptions                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAncestorLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:getAncestorLabel"), [getBaseline]("GI.Ggit.Objects.CheckoutOptions#g:method:getBaseline"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirMode]("GI.Ggit.Objects.CheckoutOptions#g:method:getDirMode"), [getDisableFilters]("GI.Ggit.Objects.CheckoutOptions#g:method:getDisableFilters"), [getFileMode]("GI.Ggit.Objects.CheckoutOptions#g:method:getFileMode"), [getFileOpenFlags]("GI.Ggit.Objects.CheckoutOptions#g:method:getFileOpenFlags"), [getNotifyFlags]("GI.Ggit.Objects.CheckoutOptions#g:method:getNotifyFlags"), [getOurLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:getOurLabel"), [getPaths]("GI.Ggit.Objects.CheckoutOptions#g:method:getPaths"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStrategy]("GI.Ggit.Objects.CheckoutOptions#g:method:getStrategy"), [getTargetDirectory]("GI.Ggit.Objects.CheckoutOptions#g:method:getTargetDirectory"), [getTheirLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:getTheirLabel").
-- 
-- ==== Setters
-- [setAncestorLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:setAncestorLabel"), [setBaseline]("GI.Ggit.Objects.CheckoutOptions#g:method:setBaseline"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirMode]("GI.Ggit.Objects.CheckoutOptions#g:method:setDirMode"), [setDisableFilters]("GI.Ggit.Objects.CheckoutOptions#g:method:setDisableFilters"), [setFileMode]("GI.Ggit.Objects.CheckoutOptions#g:method:setFileMode"), [setFileOpenFlags]("GI.Ggit.Objects.CheckoutOptions#g:method:setFileOpenFlags"), [setNotifyFlags]("GI.Ggit.Objects.CheckoutOptions#g:method:setNotifyFlags"), [setOurLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:setOurLabel"), [setPaths]("GI.Ggit.Objects.CheckoutOptions#g:method:setPaths"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStrategy]("GI.Ggit.Objects.CheckoutOptions#g:method:setStrategy"), [setTargetDirectory]("GI.Ggit.Objects.CheckoutOptions#g:method:setTargetDirectory"), [setTheirLabel]("GI.Ggit.Objects.CheckoutOptions#g:method:setTheirLabel").

#if defined(ENABLE_OVERLOADING)
    ResolveCheckoutOptionsMethod            ,
#endif

-- ** getAncestorLabel #method:getAncestorLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetAncestorLabelMethodInfo,
#endif
    checkoutOptionsGetAncestorLabel         ,


-- ** getBaseline #method:getBaseline#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetBaselineMethodInfo    ,
#endif
    checkoutOptionsGetBaseline              ,


-- ** getDirMode #method:getDirMode#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetDirModeMethodInfo     ,
#endif
    checkoutOptionsGetDirMode               ,


-- ** getDisableFilters #method:getDisableFilters#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetDisableFiltersMethodInfo,
#endif
    checkoutOptionsGetDisableFilters        ,


-- ** getFileMode #method:getFileMode#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetFileModeMethodInfo    ,
#endif
    checkoutOptionsGetFileMode              ,


-- ** getFileOpenFlags #method:getFileOpenFlags#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetFileOpenFlagsMethodInfo,
#endif
    checkoutOptionsGetFileOpenFlags         ,


-- ** getNotifyFlags #method:getNotifyFlags#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetNotifyFlagsMethodInfo ,
#endif
    checkoutOptionsGetNotifyFlags           ,


-- ** getOurLabel #method:getOurLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetOurLabelMethodInfo    ,
#endif
    checkoutOptionsGetOurLabel              ,


-- ** getPaths #method:getPaths#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetPathsMethodInfo       ,
#endif
    checkoutOptionsGetPaths                 ,


-- ** getStrategy #method:getStrategy#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetStrategyMethodInfo    ,
#endif
    checkoutOptionsGetStrategy              ,


-- ** getTargetDirectory #method:getTargetDirectory#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetTargetDirectoryMethodInfo,
#endif
    checkoutOptionsGetTargetDirectory       ,


-- ** getTheirLabel #method:getTheirLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsGetTheirLabelMethodInfo  ,
#endif
    checkoutOptionsGetTheirLabel            ,


-- ** new #method:new#

    checkoutOptionsNew                      ,


-- ** setAncestorLabel #method:setAncestorLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetAncestorLabelMethodInfo,
#endif
    checkoutOptionsSetAncestorLabel         ,


-- ** setBaseline #method:setBaseline#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetBaselineMethodInfo    ,
#endif
    checkoutOptionsSetBaseline              ,


-- ** setDirMode #method:setDirMode#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetDirModeMethodInfo     ,
#endif
    checkoutOptionsSetDirMode               ,


-- ** setDisableFilters #method:setDisableFilters#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetDisableFiltersMethodInfo,
#endif
    checkoutOptionsSetDisableFilters        ,


-- ** setFileMode #method:setFileMode#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetFileModeMethodInfo    ,
#endif
    checkoutOptionsSetFileMode              ,


-- ** setFileOpenFlags #method:setFileOpenFlags#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetFileOpenFlagsMethodInfo,
#endif
    checkoutOptionsSetFileOpenFlags         ,


-- ** setNotifyFlags #method:setNotifyFlags#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetNotifyFlagsMethodInfo ,
#endif
    checkoutOptionsSetNotifyFlags           ,


-- ** setOurLabel #method:setOurLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetOurLabelMethodInfo    ,
#endif
    checkoutOptionsSetOurLabel              ,


-- ** setPaths #method:setPaths#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetPathsMethodInfo       ,
#endif
    checkoutOptionsSetPaths                 ,


-- ** setStrategy #method:setStrategy#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetStrategyMethodInfo    ,
#endif
    checkoutOptionsSetStrategy              ,


-- ** setTargetDirectory #method:setTargetDirectory#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetTargetDirectoryMethodInfo,
#endif
    checkoutOptionsSetTargetDirectory       ,


-- ** setTheirLabel #method:setTheirLabel#

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsSetTheirLabelMethodInfo  ,
#endif
    checkoutOptionsSetTheirLabel            ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsAncestorLabelPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsAncestorLabel            ,
#endif
    clearCheckoutOptionsAncestorLabel       ,
    constructCheckoutOptionsAncestorLabel   ,
    getCheckoutOptionsAncestorLabel         ,
    setCheckoutOptionsAncestorLabel         ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsBaselinePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsBaseline                 ,
#endif
    clearCheckoutOptionsBaseline            ,
    constructCheckoutOptionsBaseline        ,
    getCheckoutOptionsBaseline              ,
    setCheckoutOptionsBaseline              ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsDirModePropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsDirMode                  ,
#endif
    constructCheckoutOptionsDirMode         ,
    getCheckoutOptionsDirMode               ,
    setCheckoutOptionsDirMode               ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsDisableFiltersPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsDisableFilters           ,
#endif
    constructCheckoutOptionsDisableFilters  ,
    getCheckoutOptionsDisableFilters        ,
    setCheckoutOptionsDisableFilters        ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsFileModePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsFileMode                 ,
#endif
    constructCheckoutOptionsFileMode        ,
    getCheckoutOptionsFileMode              ,
    setCheckoutOptionsFileMode              ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsFileOpenFlagsPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsFileOpenFlags            ,
#endif
    constructCheckoutOptionsFileOpenFlags   ,
    getCheckoutOptionsFileOpenFlags         ,
    setCheckoutOptionsFileOpenFlags         ,


-- ** notifyFlags #attr:notifyFlags#
-- | The checkout notify flags.

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsNotifyFlagsPropertyInfo  ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsNotifyFlags              ,
#endif
    constructCheckoutOptionsNotifyFlags     ,
    getCheckoutOptionsNotifyFlags           ,
    setCheckoutOptionsNotifyFlags           ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsOurLabelPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsOurLabel                 ,
#endif
    clearCheckoutOptionsOurLabel            ,
    constructCheckoutOptionsOurLabel        ,
    getCheckoutOptionsOurLabel              ,
    setCheckoutOptionsOurLabel              ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsStrategyPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsStrategy                 ,
#endif
    constructCheckoutOptionsStrategy        ,
    getCheckoutOptionsStrategy              ,
    setCheckoutOptionsStrategy              ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsTargetDirectoryPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsTargetDirectory          ,
#endif
    clearCheckoutOptionsTargetDirectory     ,
    constructCheckoutOptionsTargetDirectory ,
    getCheckoutOptionsTargetDirectory       ,
    setCheckoutOptionsTargetDirectory       ,


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

#if defined(ENABLE_OVERLOADING)
    CheckoutOptionsTheirLabelPropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    checkoutOptionsTheirLabel               ,
#endif
    clearCheckoutOptionsTheirLabel          ,
    constructCheckoutOptionsTheirLabel      ,
    getCheckoutOptionsTheirLabel            ,
    setCheckoutOptionsTheirLabel            ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Ggit.Flags as Ggit.Flags
import {-# SOURCE #-} qualified GI.Ggit.Objects.Tree as Ggit.Tree

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

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

foreign import ccall "ggit_checkout_options_get_type"
    c_ggit_checkout_options_get_type :: IO B.Types.GType

instance B.Types.TypedObject CheckoutOptions where
    glibType :: IO GType
glibType = IO GType
c_ggit_checkout_options_get_type

instance B.Types.GObject CheckoutOptions

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

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

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

-- | Convert 'CheckoutOptions' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe CheckoutOptions) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ggit_checkout_options_get_type
    gvalueSet_ :: Ptr GValue -> Maybe CheckoutOptions -> IO ()
gvalueSet_ Ptr GValue
gv Maybe CheckoutOptions
P.Nothing = Ptr GValue -> Ptr CheckoutOptions -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr CheckoutOptions
forall a. Ptr a
FP.nullPtr :: FP.Ptr CheckoutOptions)
    gvalueSet_ Ptr GValue
gv (P.Just CheckoutOptions
obj) = CheckoutOptions -> (Ptr CheckoutOptions -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr CheckoutOptions
obj (Ptr GValue -> Ptr CheckoutOptions -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe CheckoutOptions)
gvalueGet_ Ptr GValue
gv = do
        Ptr CheckoutOptions
ptr <- Ptr GValue -> IO (Ptr CheckoutOptions)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr CheckoutOptions)
        if Ptr CheckoutOptions
ptr Ptr CheckoutOptions -> Ptr CheckoutOptions -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr CheckoutOptions
forall a. Ptr a
FP.nullPtr
        then CheckoutOptions -> Maybe CheckoutOptions
forall a. a -> Maybe a
P.Just (CheckoutOptions -> Maybe CheckoutOptions)
-> IO CheckoutOptions -> IO (Maybe CheckoutOptions)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr CheckoutOptions -> CheckoutOptions)
-> Ptr CheckoutOptions -> IO CheckoutOptions
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr CheckoutOptions -> CheckoutOptions
CheckoutOptions Ptr CheckoutOptions
ptr
        else Maybe CheckoutOptions -> IO (Maybe CheckoutOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CheckoutOptions
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveCheckoutOptionsMethod (t :: Symbol) (o :: *) :: * where
    ResolveCheckoutOptionsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCheckoutOptionsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCheckoutOptionsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCheckoutOptionsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCheckoutOptionsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCheckoutOptionsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCheckoutOptionsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCheckoutOptionsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCheckoutOptionsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCheckoutOptionsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCheckoutOptionsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCheckoutOptionsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCheckoutOptionsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCheckoutOptionsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCheckoutOptionsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCheckoutOptionsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCheckoutOptionsMethod "getAncestorLabel" o = CheckoutOptionsGetAncestorLabelMethodInfo
    ResolveCheckoutOptionsMethod "getBaseline" o = CheckoutOptionsGetBaselineMethodInfo
    ResolveCheckoutOptionsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCheckoutOptionsMethod "getDirMode" o = CheckoutOptionsGetDirModeMethodInfo
    ResolveCheckoutOptionsMethod "getDisableFilters" o = CheckoutOptionsGetDisableFiltersMethodInfo
    ResolveCheckoutOptionsMethod "getFileMode" o = CheckoutOptionsGetFileModeMethodInfo
    ResolveCheckoutOptionsMethod "getFileOpenFlags" o = CheckoutOptionsGetFileOpenFlagsMethodInfo
    ResolveCheckoutOptionsMethod "getNotifyFlags" o = CheckoutOptionsGetNotifyFlagsMethodInfo
    ResolveCheckoutOptionsMethod "getOurLabel" o = CheckoutOptionsGetOurLabelMethodInfo
    ResolveCheckoutOptionsMethod "getPaths" o = CheckoutOptionsGetPathsMethodInfo
    ResolveCheckoutOptionsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCheckoutOptionsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCheckoutOptionsMethod "getStrategy" o = CheckoutOptionsGetStrategyMethodInfo
    ResolveCheckoutOptionsMethod "getTargetDirectory" o = CheckoutOptionsGetTargetDirectoryMethodInfo
    ResolveCheckoutOptionsMethod "getTheirLabel" o = CheckoutOptionsGetTheirLabelMethodInfo
    ResolveCheckoutOptionsMethod "setAncestorLabel" o = CheckoutOptionsSetAncestorLabelMethodInfo
    ResolveCheckoutOptionsMethod "setBaseline" o = CheckoutOptionsSetBaselineMethodInfo
    ResolveCheckoutOptionsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCheckoutOptionsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCheckoutOptionsMethod "setDirMode" o = CheckoutOptionsSetDirModeMethodInfo
    ResolveCheckoutOptionsMethod "setDisableFilters" o = CheckoutOptionsSetDisableFiltersMethodInfo
    ResolveCheckoutOptionsMethod "setFileMode" o = CheckoutOptionsSetFileModeMethodInfo
    ResolveCheckoutOptionsMethod "setFileOpenFlags" o = CheckoutOptionsSetFileOpenFlagsMethodInfo
    ResolveCheckoutOptionsMethod "setNotifyFlags" o = CheckoutOptionsSetNotifyFlagsMethodInfo
    ResolveCheckoutOptionsMethod "setOurLabel" o = CheckoutOptionsSetOurLabelMethodInfo
    ResolveCheckoutOptionsMethod "setPaths" o = CheckoutOptionsSetPathsMethodInfo
    ResolveCheckoutOptionsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCheckoutOptionsMethod "setStrategy" o = CheckoutOptionsSetStrategyMethodInfo
    ResolveCheckoutOptionsMethod "setTargetDirectory" o = CheckoutOptionsSetTargetDirectoryMethodInfo
    ResolveCheckoutOptionsMethod "setTheirLabel" o = CheckoutOptionsSetTheirLabelMethodInfo
    ResolveCheckoutOptionsMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveCheckoutOptionsMethod t CheckoutOptions, O.OverloadedMethod info CheckoutOptions p, R.HasField t CheckoutOptions p) => R.HasField t CheckoutOptions p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "ancestor-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@ancestor-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #ancestorLabel
-- @
getCheckoutOptionsAncestorLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m (Maybe T.Text)
getCheckoutOptionsAncestorLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m (Maybe Text)
getCheckoutOptionsAncestorLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"ancestor-label"

-- | Set the value of the “@ancestor-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #ancestorLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsAncestorLabel :: (MonadIO m, IsCheckoutOptions o) => o -> T.Text -> m ()
setCheckoutOptionsAncestorLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Text -> m ()
setCheckoutOptionsAncestorLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"ancestor-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@ancestor-label@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsAncestorLabel :: (IsCheckoutOptions o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCheckoutOptionsAncestorLabel :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructCheckoutOptionsAncestorLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"ancestor-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@ancestor-label@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #ancestorLabel
-- @
clearCheckoutOptionsAncestorLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m ()
clearCheckoutOptionsAncestorLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m ()
clearCheckoutOptionsAncestorLabel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"ancestor-label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsAncestorLabelPropertyInfo
instance AttrInfo CheckoutOptionsAncestorLabelPropertyInfo where
    type AttrAllowedOps CheckoutOptionsAncestorLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CheckoutOptionsAncestorLabelPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsAncestorLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CheckoutOptionsAncestorLabelPropertyInfo = (~) T.Text
    type AttrTransferType CheckoutOptionsAncestorLabelPropertyInfo = T.Text
    type AttrGetType CheckoutOptionsAncestorLabelPropertyInfo = (Maybe T.Text)
    type AttrLabel CheckoutOptionsAncestorLabelPropertyInfo = "ancestor-label"
    type AttrOrigin CheckoutOptionsAncestorLabelPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsAncestorLabel
    attrSet = setCheckoutOptionsAncestorLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsAncestorLabel
    attrClear = clearCheckoutOptionsAncestorLabel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.ancestorLabel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:ancestorLabel"
        })
#endif

-- VVV Prop "baseline"
   -- Type: TInterface (Name {namespace = "Ggit", name = "Tree"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

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

-- | Set the value of the “@baseline@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #baseline 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsBaseline :: (MonadIO m, IsCheckoutOptions o, Ggit.Tree.IsTree a) => o -> a -> m ()
setCheckoutOptionsBaseline :: forall (m :: * -> *) o a.
(MonadIO m, IsCheckoutOptions o, IsTree a) =>
o -> a -> m ()
setCheckoutOptionsBaseline o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"baseline" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@baseline@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsBaseline :: (IsCheckoutOptions o, MIO.MonadIO m, Ggit.Tree.IsTree a) => a -> m (GValueConstruct o)
constructCheckoutOptionsBaseline :: forall o (m :: * -> *) a.
(IsCheckoutOptions o, MonadIO m, IsTree a) =>
a -> m (GValueConstruct o)
constructCheckoutOptionsBaseline a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"baseline" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@baseline@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #baseline
-- @
clearCheckoutOptionsBaseline :: (MonadIO m, IsCheckoutOptions o) => o -> m ()
clearCheckoutOptionsBaseline :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m ()
clearCheckoutOptionsBaseline o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Tree -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"baseline" (Maybe Tree
forall a. Maybe a
Nothing :: Maybe Ggit.Tree.Tree)

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsBaselinePropertyInfo
instance AttrInfo CheckoutOptionsBaselinePropertyInfo where
    type AttrAllowedOps CheckoutOptionsBaselinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CheckoutOptionsBaselinePropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsBaselinePropertyInfo = Ggit.Tree.IsTree
    type AttrTransferTypeConstraint CheckoutOptionsBaselinePropertyInfo = Ggit.Tree.IsTree
    type AttrTransferType CheckoutOptionsBaselinePropertyInfo = Ggit.Tree.Tree
    type AttrGetType CheckoutOptionsBaselinePropertyInfo = (Maybe Ggit.Tree.Tree)
    type AttrLabel CheckoutOptionsBaselinePropertyInfo = "baseline"
    type AttrOrigin CheckoutOptionsBaselinePropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsBaseline
    attrSet = setCheckoutOptionsBaseline
    attrTransfer _ v = do
        unsafeCastTo Ggit.Tree.Tree v
    attrConstruct = constructCheckoutOptionsBaseline
    attrClear = clearCheckoutOptionsBaseline
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.baseline"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:baseline"
        })
#endif

-- VVV Prop "dir-mode"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@dir-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #dirMode
-- @
getCheckoutOptionsDirMode :: (MonadIO m, IsCheckoutOptions o) => o -> m Word32
getCheckoutOptionsDirMode :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m Word32
getCheckoutOptionsDirMode o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"dir-mode"

-- | Set the value of the “@dir-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #dirMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsDirMode :: (MonadIO m, IsCheckoutOptions o) => o -> Word32 -> m ()
setCheckoutOptionsDirMode :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Word32 -> m ()
setCheckoutOptionsDirMode o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"dir-mode" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@dir-mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsDirMode :: (IsCheckoutOptions o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructCheckoutOptionsDirMode :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructCheckoutOptionsDirMode Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"dir-mode" Word32
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsDirModePropertyInfo
instance AttrInfo CheckoutOptionsDirModePropertyInfo where
    type AttrAllowedOps CheckoutOptionsDirModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsDirModePropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsDirModePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint CheckoutOptionsDirModePropertyInfo = (~) Word32
    type AttrTransferType CheckoutOptionsDirModePropertyInfo = Word32
    type AttrGetType CheckoutOptionsDirModePropertyInfo = Word32
    type AttrLabel CheckoutOptionsDirModePropertyInfo = "dir-mode"
    type AttrOrigin CheckoutOptionsDirModePropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsDirMode
    attrSet = setCheckoutOptionsDirMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsDirMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.dirMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:dirMode"
        })
#endif

-- VVV Prop "disable-filters"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@disable-filters@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #disableFilters
-- @
getCheckoutOptionsDisableFilters :: (MonadIO m, IsCheckoutOptions o) => o -> m Bool
getCheckoutOptionsDisableFilters :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m Bool
getCheckoutOptionsDisableFilters o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"disable-filters"

-- | Set the value of the “@disable-filters@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #disableFilters 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsDisableFilters :: (MonadIO m, IsCheckoutOptions o) => o -> Bool -> m ()
setCheckoutOptionsDisableFilters :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Bool -> m ()
setCheckoutOptionsDisableFilters o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"disable-filters" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@disable-filters@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsDisableFilters :: (IsCheckoutOptions o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructCheckoutOptionsDisableFilters :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructCheckoutOptionsDisableFilters Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"disable-filters" Bool
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsDisableFiltersPropertyInfo
instance AttrInfo CheckoutOptionsDisableFiltersPropertyInfo where
    type AttrAllowedOps CheckoutOptionsDisableFiltersPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsDisableFiltersPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsDisableFiltersPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint CheckoutOptionsDisableFiltersPropertyInfo = (~) Bool
    type AttrTransferType CheckoutOptionsDisableFiltersPropertyInfo = Bool
    type AttrGetType CheckoutOptionsDisableFiltersPropertyInfo = Bool
    type AttrLabel CheckoutOptionsDisableFiltersPropertyInfo = "disable-filters"
    type AttrOrigin CheckoutOptionsDisableFiltersPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsDisableFilters
    attrSet = setCheckoutOptionsDisableFilters
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsDisableFilters
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.disableFilters"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:disableFilters"
        })
#endif

-- VVV Prop "file-mode"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@file-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #fileMode
-- @
getCheckoutOptionsFileMode :: (MonadIO m, IsCheckoutOptions o) => o -> m Word32
getCheckoutOptionsFileMode :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m Word32
getCheckoutOptionsFileMode o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"file-mode"

-- | Set the value of the “@file-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #fileMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsFileMode :: (MonadIO m, IsCheckoutOptions o) => o -> Word32 -> m ()
setCheckoutOptionsFileMode :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Word32 -> m ()
setCheckoutOptionsFileMode o
obj Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"file-mode" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@file-mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsFileMode :: (IsCheckoutOptions o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructCheckoutOptionsFileMode :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructCheckoutOptionsFileMode Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"file-mode" Word32
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsFileModePropertyInfo
instance AttrInfo CheckoutOptionsFileModePropertyInfo where
    type AttrAllowedOps CheckoutOptionsFileModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsFileModePropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsFileModePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint CheckoutOptionsFileModePropertyInfo = (~) Word32
    type AttrTransferType CheckoutOptionsFileModePropertyInfo = Word32
    type AttrGetType CheckoutOptionsFileModePropertyInfo = Word32
    type AttrLabel CheckoutOptionsFileModePropertyInfo = "file-mode"
    type AttrOrigin CheckoutOptionsFileModePropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsFileMode
    attrSet = setCheckoutOptionsFileMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsFileMode
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.fileMode"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:fileMode"
        })
#endif

-- VVV Prop "file-open-flags"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@file-open-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #fileOpenFlags
-- @
getCheckoutOptionsFileOpenFlags :: (MonadIO m, IsCheckoutOptions o) => o -> m Int32
getCheckoutOptionsFileOpenFlags :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m Int32
getCheckoutOptionsFileOpenFlags o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"file-open-flags"

-- | Set the value of the “@file-open-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #fileOpenFlags 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsFileOpenFlags :: (MonadIO m, IsCheckoutOptions o) => o -> Int32 -> m ()
setCheckoutOptionsFileOpenFlags :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Int32 -> m ()
setCheckoutOptionsFileOpenFlags o
obj Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"file-open-flags" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@file-open-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsFileOpenFlags :: (IsCheckoutOptions o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructCheckoutOptionsFileOpenFlags :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructCheckoutOptionsFileOpenFlags Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"file-open-flags" Int32
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsFileOpenFlagsPropertyInfo
instance AttrInfo CheckoutOptionsFileOpenFlagsPropertyInfo where
    type AttrAllowedOps CheckoutOptionsFileOpenFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsFileOpenFlagsPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsFileOpenFlagsPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint CheckoutOptionsFileOpenFlagsPropertyInfo = (~) Int32
    type AttrTransferType CheckoutOptionsFileOpenFlagsPropertyInfo = Int32
    type AttrGetType CheckoutOptionsFileOpenFlagsPropertyInfo = Int32
    type AttrLabel CheckoutOptionsFileOpenFlagsPropertyInfo = "file-open-flags"
    type AttrOrigin CheckoutOptionsFileOpenFlagsPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsFileOpenFlags
    attrSet = setCheckoutOptionsFileOpenFlags
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsFileOpenFlags
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.fileOpenFlags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:fileOpenFlags"
        })
#endif

-- VVV Prop "notify-flags"
   -- Type: TInterface (Name {namespace = "Ggit", name = "CheckoutNotifyFlags"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@notify-flags@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #notifyFlags 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsNotifyFlags :: (MonadIO m, IsCheckoutOptions o) => o -> [Ggit.Flags.CheckoutNotifyFlags] -> m ()
setCheckoutOptionsNotifyFlags :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> [CheckoutNotifyFlags] -> m ()
setCheckoutOptionsNotifyFlags o
obj [CheckoutNotifyFlags]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [CheckoutNotifyFlags] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"notify-flags" [CheckoutNotifyFlags]
val

-- | Construct a `GValueConstruct` with valid value for the “@notify-flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsNotifyFlags :: (IsCheckoutOptions o, MIO.MonadIO m) => [Ggit.Flags.CheckoutNotifyFlags] -> m (GValueConstruct o)
constructCheckoutOptionsNotifyFlags :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
[CheckoutNotifyFlags] -> m (GValueConstruct o)
constructCheckoutOptionsNotifyFlags [CheckoutNotifyFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [CheckoutNotifyFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"notify-flags" [CheckoutNotifyFlags]
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsNotifyFlagsPropertyInfo
instance AttrInfo CheckoutOptionsNotifyFlagsPropertyInfo where
    type AttrAllowedOps CheckoutOptionsNotifyFlagsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsNotifyFlagsPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsNotifyFlagsPropertyInfo = (~) [Ggit.Flags.CheckoutNotifyFlags]
    type AttrTransferTypeConstraint CheckoutOptionsNotifyFlagsPropertyInfo = (~) [Ggit.Flags.CheckoutNotifyFlags]
    type AttrTransferType CheckoutOptionsNotifyFlagsPropertyInfo = [Ggit.Flags.CheckoutNotifyFlags]
    type AttrGetType CheckoutOptionsNotifyFlagsPropertyInfo = [Ggit.Flags.CheckoutNotifyFlags]
    type AttrLabel CheckoutOptionsNotifyFlagsPropertyInfo = "notify-flags"
    type AttrOrigin CheckoutOptionsNotifyFlagsPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsNotifyFlags
    attrSet = setCheckoutOptionsNotifyFlags
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsNotifyFlags
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.notifyFlags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:notifyFlags"
        })
#endif

-- VVV Prop "our-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@our-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #ourLabel
-- @
getCheckoutOptionsOurLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m (Maybe T.Text)
getCheckoutOptionsOurLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m (Maybe Text)
getCheckoutOptionsOurLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"our-label"

-- | Set the value of the “@our-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #ourLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsOurLabel :: (MonadIO m, IsCheckoutOptions o) => o -> T.Text -> m ()
setCheckoutOptionsOurLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Text -> m ()
setCheckoutOptionsOurLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"our-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@our-label@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsOurLabel :: (IsCheckoutOptions o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCheckoutOptionsOurLabel :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructCheckoutOptionsOurLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"our-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@our-label@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #ourLabel
-- @
clearCheckoutOptionsOurLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m ()
clearCheckoutOptionsOurLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m ()
clearCheckoutOptionsOurLabel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"our-label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsOurLabelPropertyInfo
instance AttrInfo CheckoutOptionsOurLabelPropertyInfo where
    type AttrAllowedOps CheckoutOptionsOurLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CheckoutOptionsOurLabelPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsOurLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CheckoutOptionsOurLabelPropertyInfo = (~) T.Text
    type AttrTransferType CheckoutOptionsOurLabelPropertyInfo = T.Text
    type AttrGetType CheckoutOptionsOurLabelPropertyInfo = (Maybe T.Text)
    type AttrLabel CheckoutOptionsOurLabelPropertyInfo = "our-label"
    type AttrOrigin CheckoutOptionsOurLabelPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsOurLabel
    attrSet = setCheckoutOptionsOurLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsOurLabel
    attrClear = clearCheckoutOptionsOurLabel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.ourLabel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:ourLabel"
        })
#endif

-- VVV Prop "strategy"
   -- Type: TInterface (Name {namespace = "Ggit", name = "CheckoutStrategy"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@strategy@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #strategy 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsStrategy :: (MonadIO m, IsCheckoutOptions o) => o -> [Ggit.Flags.CheckoutStrategy] -> m ()
setCheckoutOptionsStrategy :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> [CheckoutStrategy] -> m ()
setCheckoutOptionsStrategy o
obj [CheckoutStrategy]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [CheckoutStrategy] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"strategy" [CheckoutStrategy]
val

-- | Construct a `GValueConstruct` with valid value for the “@strategy@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsStrategy :: (IsCheckoutOptions o, MIO.MonadIO m) => [Ggit.Flags.CheckoutStrategy] -> m (GValueConstruct o)
constructCheckoutOptionsStrategy :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
[CheckoutStrategy] -> m (GValueConstruct o)
constructCheckoutOptionsStrategy [CheckoutStrategy]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [CheckoutStrategy] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"strategy" [CheckoutStrategy]
val

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsStrategyPropertyInfo
instance AttrInfo CheckoutOptionsStrategyPropertyInfo where
    type AttrAllowedOps CheckoutOptionsStrategyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CheckoutOptionsStrategyPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsStrategyPropertyInfo = (~) [Ggit.Flags.CheckoutStrategy]
    type AttrTransferTypeConstraint CheckoutOptionsStrategyPropertyInfo = (~) [Ggit.Flags.CheckoutStrategy]
    type AttrTransferType CheckoutOptionsStrategyPropertyInfo = [Ggit.Flags.CheckoutStrategy]
    type AttrGetType CheckoutOptionsStrategyPropertyInfo = [Ggit.Flags.CheckoutStrategy]
    type AttrLabel CheckoutOptionsStrategyPropertyInfo = "strategy"
    type AttrOrigin CheckoutOptionsStrategyPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsStrategy
    attrSet = setCheckoutOptionsStrategy
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsStrategy
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.strategy"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:strategy"
        })
#endif

-- VVV Prop "target-directory"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@target-directory@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #targetDirectory
-- @
getCheckoutOptionsTargetDirectory :: (MonadIO m, IsCheckoutOptions o) => o -> m (Maybe T.Text)
getCheckoutOptionsTargetDirectory :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m (Maybe Text)
getCheckoutOptionsTargetDirectory o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"target-directory"

-- | Set the value of the “@target-directory@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #targetDirectory 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsTargetDirectory :: (MonadIO m, IsCheckoutOptions o) => o -> T.Text -> m ()
setCheckoutOptionsTargetDirectory :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Text -> m ()
setCheckoutOptionsTargetDirectory o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"target-directory" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@target-directory@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsTargetDirectory :: (IsCheckoutOptions o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCheckoutOptionsTargetDirectory :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructCheckoutOptionsTargetDirectory Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"target-directory" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@target-directory@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #targetDirectory
-- @
clearCheckoutOptionsTargetDirectory :: (MonadIO m, IsCheckoutOptions o) => o -> m ()
clearCheckoutOptionsTargetDirectory :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m ()
clearCheckoutOptionsTargetDirectory o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"target-directory" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsTargetDirectoryPropertyInfo
instance AttrInfo CheckoutOptionsTargetDirectoryPropertyInfo where
    type AttrAllowedOps CheckoutOptionsTargetDirectoryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CheckoutOptionsTargetDirectoryPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsTargetDirectoryPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CheckoutOptionsTargetDirectoryPropertyInfo = (~) T.Text
    type AttrTransferType CheckoutOptionsTargetDirectoryPropertyInfo = T.Text
    type AttrGetType CheckoutOptionsTargetDirectoryPropertyInfo = (Maybe T.Text)
    type AttrLabel CheckoutOptionsTargetDirectoryPropertyInfo = "target-directory"
    type AttrOrigin CheckoutOptionsTargetDirectoryPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsTargetDirectory
    attrSet = setCheckoutOptionsTargetDirectory
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsTargetDirectory
    attrClear = clearCheckoutOptionsTargetDirectory
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.targetDirectory"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:targetDirectory"
        })
#endif

-- VVV Prop "their-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@their-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' checkoutOptions #theirLabel
-- @
getCheckoutOptionsTheirLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m (Maybe T.Text)
getCheckoutOptionsTheirLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m (Maybe Text)
getCheckoutOptionsTheirLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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
"their-label"

-- | Set the value of the “@their-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' checkoutOptions [ #theirLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setCheckoutOptionsTheirLabel :: (MonadIO m, IsCheckoutOptions o) => o -> T.Text -> m ()
setCheckoutOptionsTheirLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> Text -> m ()
setCheckoutOptionsTheirLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"their-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@their-label@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCheckoutOptionsTheirLabel :: (IsCheckoutOptions o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructCheckoutOptionsTheirLabel :: forall o (m :: * -> *).
(IsCheckoutOptions o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructCheckoutOptionsTheirLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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
"their-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@their-label@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #theirLabel
-- @
clearCheckoutOptionsTheirLabel :: (MonadIO m, IsCheckoutOptions o) => o -> m ()
clearCheckoutOptionsTheirLabel :: forall (m :: * -> *) o.
(MonadIO m, IsCheckoutOptions o) =>
o -> m ()
clearCheckoutOptionsTheirLabel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"their-label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsTheirLabelPropertyInfo
instance AttrInfo CheckoutOptionsTheirLabelPropertyInfo where
    type AttrAllowedOps CheckoutOptionsTheirLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CheckoutOptionsTheirLabelPropertyInfo = IsCheckoutOptions
    type AttrSetTypeConstraint CheckoutOptionsTheirLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint CheckoutOptionsTheirLabelPropertyInfo = (~) T.Text
    type AttrTransferType CheckoutOptionsTheirLabelPropertyInfo = T.Text
    type AttrGetType CheckoutOptionsTheirLabelPropertyInfo = (Maybe T.Text)
    type AttrLabel CheckoutOptionsTheirLabelPropertyInfo = "their-label"
    type AttrOrigin CheckoutOptionsTheirLabelPropertyInfo = CheckoutOptions
    attrGet = getCheckoutOptionsTheirLabel
    attrSet = setCheckoutOptionsTheirLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructCheckoutOptionsTheirLabel
    attrClear = clearCheckoutOptionsTheirLabel
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.theirLabel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#g:attr:theirLabel"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CheckoutOptions
type instance O.AttributeList CheckoutOptions = CheckoutOptionsAttributeList
type CheckoutOptionsAttributeList = ('[ '("ancestorLabel", CheckoutOptionsAncestorLabelPropertyInfo), '("baseline", CheckoutOptionsBaselinePropertyInfo), '("dirMode", CheckoutOptionsDirModePropertyInfo), '("disableFilters", CheckoutOptionsDisableFiltersPropertyInfo), '("fileMode", CheckoutOptionsFileModePropertyInfo), '("fileOpenFlags", CheckoutOptionsFileOpenFlagsPropertyInfo), '("notifyFlags", CheckoutOptionsNotifyFlagsPropertyInfo), '("ourLabel", CheckoutOptionsOurLabelPropertyInfo), '("strategy", CheckoutOptionsStrategyPropertyInfo), '("targetDirectory", CheckoutOptionsTargetDirectoryPropertyInfo), '("theirLabel", CheckoutOptionsTheirLabelPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
checkoutOptionsAncestorLabel :: AttrLabelProxy "ancestorLabel"
checkoutOptionsAncestorLabel = AttrLabelProxy

checkoutOptionsBaseline :: AttrLabelProxy "baseline"
checkoutOptionsBaseline = AttrLabelProxy

checkoutOptionsDirMode :: AttrLabelProxy "dirMode"
checkoutOptionsDirMode = AttrLabelProxy

checkoutOptionsDisableFilters :: AttrLabelProxy "disableFilters"
checkoutOptionsDisableFilters = AttrLabelProxy

checkoutOptionsFileMode :: AttrLabelProxy "fileMode"
checkoutOptionsFileMode = AttrLabelProxy

checkoutOptionsFileOpenFlags :: AttrLabelProxy "fileOpenFlags"
checkoutOptionsFileOpenFlags = AttrLabelProxy

checkoutOptionsNotifyFlags :: AttrLabelProxy "notifyFlags"
checkoutOptionsNotifyFlags = AttrLabelProxy

checkoutOptionsOurLabel :: AttrLabelProxy "ourLabel"
checkoutOptionsOurLabel = AttrLabelProxy

checkoutOptionsStrategy :: AttrLabelProxy "strategy"
checkoutOptionsStrategy = AttrLabelProxy

checkoutOptionsTargetDirectory :: AttrLabelProxy "targetDirectory"
checkoutOptionsTargetDirectory = AttrLabelProxy

checkoutOptionsTheirLabel :: AttrLabelProxy "theirLabel"
checkoutOptionsTheirLabel = AttrLabelProxy

#endif

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

#endif

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

foreign import ccall "ggit_checkout_options_new" ggit_checkout_options_new :: 
    IO (Ptr CheckoutOptions)

-- | Create a new checkout options object.
checkoutOptionsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe CheckoutOptions)
    -- ^ __Returns:__ a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions' or 'P.Nothing'.
checkoutOptionsNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m (Maybe CheckoutOptions)
checkoutOptionsNew  = IO (Maybe CheckoutOptions) -> m (Maybe CheckoutOptions)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe CheckoutOptions) -> m (Maybe CheckoutOptions))
-> IO (Maybe CheckoutOptions) -> m (Maybe CheckoutOptions)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
result <- IO (Ptr CheckoutOptions)
ggit_checkout_options_new
    Maybe CheckoutOptions
maybeResult <- Ptr CheckoutOptions
-> (Ptr CheckoutOptions -> IO CheckoutOptions)
-> IO (Maybe CheckoutOptions)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CheckoutOptions
result ((Ptr CheckoutOptions -> IO CheckoutOptions)
 -> IO (Maybe CheckoutOptions))
-> (Ptr CheckoutOptions -> IO CheckoutOptions)
-> IO (Maybe CheckoutOptions)
forall a b. (a -> b) -> a -> b
$ \Ptr CheckoutOptions
result' -> do
        CheckoutOptions
result'' <- ((ManagedPtr CheckoutOptions -> CheckoutOptions)
-> Ptr CheckoutOptions -> IO CheckoutOptions
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CheckoutOptions -> CheckoutOptions
CheckoutOptions) Ptr CheckoutOptions
result'
        CheckoutOptions -> IO CheckoutOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CheckoutOptions
result''
    Maybe CheckoutOptions -> IO (Maybe CheckoutOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CheckoutOptions
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method CheckoutOptions::get_ancestor_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , 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 "ggit_checkout_options_get_ancestor_label" ggit_checkout_options_get_ancestor_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CString

-- | Get the checkout ancestor label.
checkoutOptionsGetAncestorLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the checkout ancestor label or 'P.Nothing'.
checkoutOptionsGetAncestorLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe Text)
checkoutOptionsGetAncestorLabel a
options = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
result <- Ptr CheckoutOptions -> IO CString
ggit_checkout_options_get_ancestor_label Ptr CheckoutOptions
options'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetAncestorLabelMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetAncestorLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetAncestorLabel

instance O.OverloadedMethodInfo CheckoutOptionsGetAncestorLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetAncestorLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetAncestorLabel"
        })


#endif

-- method CheckoutOptions::get_baseline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Tree" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_get_baseline" ggit_checkout_options_get_baseline :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO (Ptr Ggit.Tree.Tree)

-- | Get the baseline, i.e. the expected content of workdir. Defaults to HEAD.
checkoutOptionsGetBaseline ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe Ggit.Tree.Tree)
    -- ^ __Returns:__ a t'GI.Ggit.Objects.Tree.Tree' or 'P.Nothing'.
checkoutOptionsGetBaseline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe Tree)
checkoutOptionsGetBaseline a
options = IO (Maybe Tree) -> m (Maybe Tree)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Tree) -> m (Maybe Tree))
-> IO (Maybe Tree) -> m (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr Tree
result <- Ptr CheckoutOptions -> IO (Ptr Tree)
ggit_checkout_options_get_baseline Ptr CheckoutOptions
options'
    Maybe Tree
maybeResult <- Ptr Tree -> (Ptr Tree -> IO Tree) -> IO (Maybe Tree)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Tree
result ((Ptr Tree -> IO Tree) -> IO (Maybe Tree))
-> (Ptr Tree -> IO Tree) -> IO (Maybe Tree)
forall a b. (a -> b) -> a -> b
$ \Ptr Tree
result' -> do
        Tree
result'' <- ((ManagedPtr Tree -> Tree) -> Ptr Tree -> IO Tree
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Tree -> Tree
Ggit.Tree.Tree) Ptr Tree
result'
        Tree -> IO Tree
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Tree
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe Tree -> IO (Maybe Tree)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Tree
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetBaselineMethodInfo
instance (signature ~ (m (Maybe Ggit.Tree.Tree)), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetBaselineMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetBaseline

instance O.OverloadedMethodInfo CheckoutOptionsGetBaselineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetBaseline",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetBaseline"
        })


#endif

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

foreign import ccall "ggit_checkout_options_get_dir_mode" ggit_checkout_options_get_dir_mode :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO Word32

-- | Get the default checkout directory mode.
checkoutOptionsGetDirMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m Word32
    -- ^ __Returns:__ the default directory mode.
checkoutOptionsGetDirMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m Word32
checkoutOptionsGetDirMode a
options = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Word32
result <- Ptr CheckoutOptions -> IO Word32
ggit_checkout_options_get_dir_mode Ptr CheckoutOptions
options'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetDirModeMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetDirModeMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetDirMode

instance O.OverloadedMethodInfo CheckoutOptionsGetDirModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetDirMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetDirMode"
        })


#endif

-- method CheckoutOptions::get_disable_filters
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , 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 "ggit_checkout_options_get_disable_filters" ggit_checkout_options_get_disable_filters :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CInt

-- | Get whether filters are disabled.
checkoutOptionsGetDisableFilters ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if filters are disabled, 'P.False' otherwise.
checkoutOptionsGetDisableFilters :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m Bool
checkoutOptionsGetDisableFilters a
options = IO Bool -> m Bool
forall a. IO a -> m a
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 CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CInt
result <- Ptr CheckoutOptions -> IO CInt
ggit_checkout_options_get_disable_filters Ptr CheckoutOptions
options'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetDisableFiltersMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetDisableFiltersMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetDisableFilters

instance O.OverloadedMethodInfo CheckoutOptionsGetDisableFiltersMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetDisableFilters",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetDisableFilters"
        })


#endif

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

foreign import ccall "ggit_checkout_options_get_file_mode" ggit_checkout_options_get_file_mode :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO Word32

-- | Get the default checkout file mode.
checkoutOptionsGetFileMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m Word32
    -- ^ __Returns:__ the default checkout file mode.
checkoutOptionsGetFileMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m Word32
checkoutOptionsGetFileMode a
options = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Word32
result <- Ptr CheckoutOptions -> IO Word32
ggit_checkout_options_get_file_mode Ptr CheckoutOptions
options'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetFileModeMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetFileModeMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetFileMode

instance O.OverloadedMethodInfo CheckoutOptionsGetFileModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetFileMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetFileMode"
        })


#endif

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

foreign import ccall "ggit_checkout_options_get_file_open_flags" ggit_checkout_options_get_file_open_flags :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO Int32

-- | Get the checkout file open flags. These flags are platform specific,
-- e.g. on Unix these would include O_CREAT, O_TRUNC, etc.
checkoutOptionsGetFileOpenFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m Int32
    -- ^ __Returns:__ the checkout file open flags.
checkoutOptionsGetFileOpenFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m Int32
checkoutOptionsGetFileOpenFlags a
options = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Int32
result <- Ptr CheckoutOptions -> IO Int32
ggit_checkout_options_get_file_open_flags Ptr CheckoutOptions
options'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetFileOpenFlagsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetFileOpenFlagsMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetFileOpenFlags

instance O.OverloadedMethodInfo CheckoutOptionsGetFileOpenFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetFileOpenFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetFileOpenFlags"
        })


#endif

-- method CheckoutOptions::get_notify_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Ggit" , name = "CheckoutNotifyFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_get_notify_flags" ggit_checkout_options_get_notify_flags :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CUInt

-- | Get the checkout notify flags.
checkoutOptionsGetNotifyFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m [Ggit.Flags.CheckoutNotifyFlags]
    -- ^ __Returns:__ a t'GI.Ggit.Flags.CheckoutNotifyFlags'.
checkoutOptionsGetNotifyFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m [CheckoutNotifyFlags]
checkoutOptionsGetNotifyFlags a
options = IO [CheckoutNotifyFlags] -> m [CheckoutNotifyFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [CheckoutNotifyFlags] -> m [CheckoutNotifyFlags])
-> IO [CheckoutNotifyFlags] -> m [CheckoutNotifyFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CUInt
result <- Ptr CheckoutOptions -> IO CUInt
ggit_checkout_options_get_notify_flags Ptr CheckoutOptions
options'
    let result' :: [CheckoutNotifyFlags]
result' = CUInt -> [CheckoutNotifyFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    [CheckoutNotifyFlags] -> IO [CheckoutNotifyFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [CheckoutNotifyFlags]
result'

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetNotifyFlagsMethodInfo
instance (signature ~ (m [Ggit.Flags.CheckoutNotifyFlags]), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetNotifyFlagsMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetNotifyFlags

instance O.OverloadedMethodInfo CheckoutOptionsGetNotifyFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetNotifyFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetNotifyFlags"
        })


#endif

-- method CheckoutOptions::get_our_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , 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 "ggit_checkout_options_get_our_label" ggit_checkout_options_get_our_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CString

-- | Get the checkout our label.
checkoutOptionsGetOurLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the checkout our label or 'P.Nothing'.
checkoutOptionsGetOurLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe Text)
checkoutOptionsGetOurLabel a
options = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
result <- Ptr CheckoutOptions -> IO CString
ggit_checkout_options_get_our_label Ptr CheckoutOptions
options'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetOurLabelMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetOurLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetOurLabel

instance O.OverloadedMethodInfo CheckoutOptionsGetOurLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetOurLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetOurLabel"
        })


#endif

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

foreign import ccall "ggit_checkout_options_get_paths" ggit_checkout_options_get_paths :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO (Ptr CString)

-- | Get the list of file paths to checkout.
checkoutOptionsGetPaths ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe [T.Text])
    -- ^ __Returns:__ a 'P.Nothing' terminated list of file paths, or 'P.Nothing'.
checkoutOptionsGetPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe [Text])
checkoutOptionsGetPaths a
options = IO (Maybe [Text]) -> m (Maybe [Text])
forall a. IO a -> m a
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
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CString
result <- Ptr CheckoutOptions -> IO (Ptr CString)
ggit_checkout_options_get_paths Ptr CheckoutOptions
options'
    Maybe [Text]
maybeResult <- Ptr CString -> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CString
result ((Ptr CString -> IO [Text]) -> IO (Maybe [Text]))
-> (Ptr CString -> IO [Text]) -> IO (Maybe [Text])
forall a b. (a -> b) -> a -> b
$ \Ptr CString
result' -> do
        [Text]
result'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result'
        [Text] -> IO [Text]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe [Text] -> IO (Maybe [Text])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe [Text]
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetPathsMethodInfo
instance (signature ~ (m (Maybe [T.Text])), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetPathsMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetPaths

instance O.OverloadedMethodInfo CheckoutOptionsGetPathsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetPaths",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetPaths"
        })


#endif

-- method CheckoutOptions::get_strategy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Ggit" , name = "CheckoutStrategy" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_get_strategy" ggit_checkout_options_get_strategy :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CUInt

-- | Get the checkout strategy.
checkoutOptionsGetStrategy ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m [Ggit.Flags.CheckoutStrategy]
    -- ^ __Returns:__ a t'GI.Ggit.Flags.CheckoutStrategy'.
checkoutOptionsGetStrategy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m [CheckoutStrategy]
checkoutOptionsGetStrategy a
options = IO [CheckoutStrategy] -> m [CheckoutStrategy]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [CheckoutStrategy] -> m [CheckoutStrategy])
-> IO [CheckoutStrategy] -> m [CheckoutStrategy]
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CUInt
result <- Ptr CheckoutOptions -> IO CUInt
ggit_checkout_options_get_strategy Ptr CheckoutOptions
options'
    let result' :: [CheckoutStrategy]
result' = CUInt -> [CheckoutStrategy]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    [CheckoutStrategy] -> IO [CheckoutStrategy]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [CheckoutStrategy]
result'

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetStrategyMethodInfo
instance (signature ~ (m [Ggit.Flags.CheckoutStrategy]), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetStrategyMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetStrategy

instance O.OverloadedMethodInfo CheckoutOptionsGetStrategyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetStrategy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetStrategy"
        })


#endif

-- method CheckoutOptions::get_target_directory
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , 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 "ggit_checkout_options_get_target_directory" ggit_checkout_options_get_target_directory :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CString

-- | Get the checkout target directory.
checkoutOptionsGetTargetDirectory ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the checkout target directory or 'P.Nothing'.
checkoutOptionsGetTargetDirectory :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe Text)
checkoutOptionsGetTargetDirectory a
options = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
result <- Ptr CheckoutOptions -> IO CString
ggit_checkout_options_get_target_directory Ptr CheckoutOptions
options'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetTargetDirectoryMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetTargetDirectoryMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetTargetDirectory

instance O.OverloadedMethodInfo CheckoutOptionsGetTargetDirectoryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetTargetDirectory",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetTargetDirectory"
        })


#endif

-- method CheckoutOptions::get_their_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , 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 "ggit_checkout_options_get_their_label" ggit_checkout_options_get_their_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    IO CString

-- | Get the checkout their label.
checkoutOptionsGetTheirLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the checkout their label or 'P.Nothing'.
checkoutOptionsGetTheirLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> m (Maybe Text)
checkoutOptionsGetTheirLabel a
options = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
result <- Ptr CheckoutOptions -> IO CString
ggit_checkout_options_get_their_label Ptr CheckoutOptions
options'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsGetTheirLabelMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsGetTheirLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsGetTheirLabel

instance O.OverloadedMethodInfo CheckoutOptionsGetTheirLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsGetTheirLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsGetTheirLabel"
        })


#endif

-- method CheckoutOptions::set_ancestor_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the ancestor label."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_ancestor_label" ggit_checkout_options_set_ancestor_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Set the checkout ancestor label.
checkoutOptionsSetAncestorLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe (T.Text)
    -- ^ /@label@/: the ancestor label.
    -> m ()
checkoutOptionsSetAncestorLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Maybe Text -> m ()
checkoutOptionsSetAncestorLabel a
options Maybe Text
label = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    Ptr CheckoutOptions -> CString -> IO ()
ggit_checkout_options_set_ancestor_label Ptr CheckoutOptions
options' CString
maybeLabel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetAncestorLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetAncestorLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetAncestorLabel

instance O.OverloadedMethodInfo CheckoutOptionsSetAncestorLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetAncestorLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetAncestorLabel"
        })


#endif

-- method CheckoutOptions::set_baseline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_baseline" ggit_checkout_options_set_baseline :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    Ptr Ggit.Tree.Tree ->                   -- tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    IO ()

-- | Set the baseline, i.e. the expected content of workdir. If /@tree@/ is set
-- to 'P.Nothing', the default (HEAD) will be used as the baseline.
checkoutOptionsSetBaseline ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a, Ggit.Tree.IsTree b) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe (b)
    -- ^ /@tree@/: a t'GI.Ggit.Objects.Tree.Tree'.
    -> m ()
checkoutOptionsSetBaseline :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCheckoutOptions a, IsTree b) =>
a -> Maybe b -> m ()
checkoutOptionsSetBaseline a
options Maybe b
tree = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr Tree
maybeTree <- case Maybe b
tree of
        Maybe b
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
        Just b
jTree -> do
            Ptr Tree
jTree' <- b -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jTree
            Ptr Tree -> IO (Ptr Tree)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
jTree'
    Ptr CheckoutOptions -> Ptr Tree -> IO ()
ggit_checkout_options_set_baseline Ptr CheckoutOptions
options' Ptr Tree
maybeTree
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
tree b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetBaselineMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCheckoutOptions a, Ggit.Tree.IsTree b) => O.OverloadedMethod CheckoutOptionsSetBaselineMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetBaseline

instance O.OverloadedMethodInfo CheckoutOptionsSetBaselineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetBaseline",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetBaseline"
        })


#endif

-- method CheckoutOptions::set_dir_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dir_mode"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the dir mode." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_dir_mode" ggit_checkout_options_set_dir_mode :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    Word32 ->                               -- dir_mode : TBasicType TUInt
    IO ()

-- | Set the default checkout directory mode.
checkoutOptionsSetDirMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Word32
    -- ^ /@dirMode@/: the dir mode.
    -> m ()
checkoutOptionsSetDirMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Word32 -> m ()
checkoutOptionsSetDirMode a
options Word32
dirMode = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CheckoutOptions -> Word32 -> IO ()
ggit_checkout_options_set_dir_mode Ptr CheckoutOptions
options' Word32
dirMode
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetDirModeMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetDirModeMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetDirMode

instance O.OverloadedMethodInfo CheckoutOptionsSetDirModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetDirMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetDirMode"
        })


#endif

-- method CheckoutOptions::set_disable_filters
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "disable"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "disable filters." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_disable_filters" ggit_checkout_options_set_disable_filters :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CInt ->                                 -- disable : TBasicType TBoolean
    IO ()

-- | Set whether to disable filters.
checkoutOptionsSetDisableFilters ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Bool
    -- ^ /@disable@/: disable filters.
    -> m ()
checkoutOptionsSetDisableFilters :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Bool -> m ()
checkoutOptionsSetDisableFilters a
options Bool
disable = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    let disable' :: CInt
disable' = (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
disable
    Ptr CheckoutOptions -> CInt -> IO ()
ggit_checkout_options_set_disable_filters Ptr CheckoutOptions
options' CInt
disable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetDisableFiltersMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetDisableFiltersMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetDisableFilters

instance O.OverloadedMethodInfo CheckoutOptionsSetDisableFiltersMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetDisableFilters",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetDisableFilters"
        })


#endif

-- method CheckoutOptions::set_file_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file_mode"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file mode." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_file_mode" ggit_checkout_options_set_file_mode :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    Word32 ->                               -- file_mode : TBasicType TUInt
    IO ()

-- | Set the default checkout file mode.
checkoutOptionsSetFileMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Word32
    -- ^ /@fileMode@/: the file mode.
    -> m ()
checkoutOptionsSetFileMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Word32 -> m ()
checkoutOptionsSetFileMode a
options Word32
fileMode = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CheckoutOptions -> Word32 -> IO ()
ggit_checkout_options_set_file_mode Ptr CheckoutOptions
options' Word32
fileMode
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetFileModeMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetFileModeMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetFileMode

instance O.OverloadedMethodInfo CheckoutOptionsSetFileModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetFileMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetFileMode"
        })


#endif

-- method CheckoutOptions::set_file_open_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file open flags."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_file_open_flags" ggit_checkout_options_set_file_open_flags :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    Int32 ->                                -- flags : TBasicType TInt
    IO ()

-- | Set the checkout file open flags. These flags are platform dependent,
-- e.g. on Unix use O_CREAT, O_TRUNC, etc.
checkoutOptionsSetFileOpenFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Int32
    -- ^ /@flags@/: the file open flags.
    -> m ()
checkoutOptionsSetFileOpenFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Int32 -> m ()
checkoutOptionsSetFileOpenFlags a
options Int32
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CheckoutOptions -> Int32 -> IO ()
ggit_checkout_options_set_file_open_flags Ptr CheckoutOptions
options' Int32
flags
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetFileOpenFlagsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetFileOpenFlagsMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetFileOpenFlags

instance O.OverloadedMethodInfo CheckoutOptionsSetFileOpenFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetFileOpenFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetFileOpenFlags"
        })


#endif

-- method CheckoutOptions::set_notify_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Ggit" , name = "CheckoutNotifyFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutNotifyFlags."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_notify_flags" ggit_checkout_options_set_notify_flags :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Ggit", name = "CheckoutNotifyFlags"})
    IO ()

-- | Set the checkout notify flags.
checkoutOptionsSetNotifyFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> [Ggit.Flags.CheckoutNotifyFlags]
    -- ^ /@flags@/: a t'GI.Ggit.Flags.CheckoutNotifyFlags'.
    -> m ()
checkoutOptionsSetNotifyFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> [CheckoutNotifyFlags] -> m ()
checkoutOptionsSetNotifyFlags a
options [CheckoutNotifyFlags]
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    let flags' :: CUInt
flags' = [CheckoutNotifyFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [CheckoutNotifyFlags]
flags
    Ptr CheckoutOptions -> CUInt -> IO ()
ggit_checkout_options_set_notify_flags Ptr CheckoutOptions
options' CUInt
flags'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetNotifyFlagsMethodInfo
instance (signature ~ ([Ggit.Flags.CheckoutNotifyFlags] -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetNotifyFlagsMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetNotifyFlags

instance O.OverloadedMethodInfo CheckoutOptionsSetNotifyFlagsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetNotifyFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetNotifyFlags"
        })


#endif

-- method CheckoutOptions::set_our_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the our label." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_our_label" ggit_checkout_options_set_our_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Set the checkout our label.
checkoutOptionsSetOurLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe (T.Text)
    -- ^ /@label@/: the our label.
    -> m ()
checkoutOptionsSetOurLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Maybe Text -> m ()
checkoutOptionsSetOurLabel a
options Maybe Text
label = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    Ptr CheckoutOptions -> CString -> IO ()
ggit_checkout_options_set_our_label Ptr CheckoutOptions
options' CString
maybeLabel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetOurLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetOurLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetOurLabel

instance O.OverloadedMethodInfo CheckoutOptionsSetOurLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetOurLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetOurLabel"
        })


#endif

-- method CheckoutOptions::set_paths
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "paths"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a %NULL terminated list of paths."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_paths" ggit_checkout_options_set_paths :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    Ptr CString ->                          -- paths : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Set the list of file paths to checkout. If /@paths@/ is 'P.Nothing', then all files
-- will be checked out.
checkoutOptionsSetPaths ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe ([T.Text])
    -- ^ /@paths@/: a 'P.Nothing' terminated list of paths.
    -> m ()
checkoutOptionsSetPaths :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Maybe [Text] -> m ()
checkoutOptionsSetPaths a
options Maybe [Text]
paths = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CString
maybePaths <- case Maybe [Text]
paths of
        Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
nullPtr
        Just [Text]
jPaths -> do
            Ptr CString
jPaths' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jPaths
            Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
jPaths'
    Ptr CheckoutOptions -> Ptr CString -> IO ()
ggit_checkout_options_set_paths Ptr CheckoutOptions
options' Ptr CString
maybePaths
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybePaths
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
maybePaths
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetPathsMethodInfo
instance (signature ~ (Maybe ([T.Text]) -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetPathsMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetPaths

instance O.OverloadedMethodInfo CheckoutOptionsSetPathsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetPaths",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetPaths"
        })


#endif

-- method CheckoutOptions::set_strategy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strategy"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutStrategy" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutStrategy."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_strategy" ggit_checkout_options_set_strategy :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CUInt ->                                -- strategy : TInterface (Name {namespace = "Ggit", name = "CheckoutStrategy"})
    IO ()

-- | Set the checkout strategy.
checkoutOptionsSetStrategy ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> [Ggit.Flags.CheckoutStrategy]
    -- ^ /@strategy@/: a t'GI.Ggit.Flags.CheckoutStrategy'.
    -> m ()
checkoutOptionsSetStrategy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> [CheckoutStrategy] -> m ()
checkoutOptionsSetStrategy a
options [CheckoutStrategy]
strategy = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    let strategy' :: CUInt
strategy' = [CheckoutStrategy] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [CheckoutStrategy]
strategy
    Ptr CheckoutOptions -> CUInt -> IO ()
ggit_checkout_options_set_strategy Ptr CheckoutOptions
options' CUInt
strategy'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetStrategyMethodInfo
instance (signature ~ ([Ggit.Flags.CheckoutStrategy] -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetStrategyMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetStrategy

instance O.OverloadedMethodInfo CheckoutOptionsSetStrategyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetStrategy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetStrategy"
        })


#endif

-- method CheckoutOptions::set_target_directory
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "directory"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the target directory."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_target_directory" ggit_checkout_options_set_target_directory :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CString ->                              -- directory : TBasicType TUTF8
    IO ()

-- | Set the checkout target directory.
checkoutOptionsSetTargetDirectory ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe (T.Text)
    -- ^ /@directory@/: the target directory.
    -> m ()
checkoutOptionsSetTargetDirectory :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Maybe Text -> m ()
checkoutOptionsSetTargetDirectory a
options Maybe Text
directory = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
maybeDirectory <- case Maybe Text
directory of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jDirectory -> do
            CString
jDirectory' <- Text -> IO CString
textToCString Text
jDirectory
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDirectory'
    Ptr CheckoutOptions -> CString -> IO ()
ggit_checkout_options_set_target_directory Ptr CheckoutOptions
options' CString
maybeDirectory
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDirectory
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetTargetDirectoryMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetTargetDirectoryMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetTargetDirectory

instance O.OverloadedMethodInfo CheckoutOptionsSetTargetDirectoryMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetTargetDirectory",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetTargetDirectory"
        })


#endif

-- method CheckoutOptions::set_their_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CheckoutOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCheckoutOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the their label." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_checkout_options_set_their_label" ggit_checkout_options_set_their_label :: 
    Ptr CheckoutOptions ->                  -- options : TInterface (Name {namespace = "Ggit", name = "CheckoutOptions"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Set the checkout their label.
checkoutOptionsSetTheirLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsCheckoutOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> Maybe (T.Text)
    -- ^ /@label@/: the their label.
    -> m ()
checkoutOptionsSetTheirLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCheckoutOptions a) =>
a -> Maybe Text -> m ()
checkoutOptionsSetTheirLabel a
options Maybe Text
label = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr CheckoutOptions
options' <- a -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    Ptr CheckoutOptions -> CString -> IO ()
ggit_checkout_options_set_their_label Ptr CheckoutOptions
options' CString
maybeLabel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data CheckoutOptionsSetTheirLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsCheckoutOptions a) => O.OverloadedMethod CheckoutOptionsSetTheirLabelMethodInfo a signature where
    overloadedMethod = checkoutOptionsSetTheirLabel

instance O.OverloadedMethodInfo CheckoutOptionsSetTheirLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CheckoutOptions.checkoutOptionsSetTheirLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.12/docs/GI-Ggit-Objects-CheckoutOptions.html#v:checkoutOptionsSetTheirLabel"
        })


#endif