{-# 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 cherry-pick.

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

module GI.Ggit.Objects.CherryPickOptions
    ( 

-- * Exported types
    CherryPickOptions(..)                   ,
    IsCherryPickOptions                     ,
    toCherryPickOptions                     ,


 -- * 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
-- [getCheckoutOptions]("GI.Ggit.Objects.CherryPickOptions#g:method:getCheckoutOptions"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getMainline]("GI.Ggit.Objects.CherryPickOptions#g:method:getMainline"), [getMergeOptions]("GI.Ggit.Objects.CherryPickOptions#g:method:getMergeOptions"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setCheckoutOptions]("GI.Ggit.Objects.CherryPickOptions#g:method:setCheckoutOptions"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setMainline]("GI.Ggit.Objects.CherryPickOptions#g:method:setMainline"), [setMergeOptions]("GI.Ggit.Objects.CherryPickOptions#g:method:setMergeOptions"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveCherryPickOptionsMethod          ,
#endif

-- ** getCheckoutOptions #method:getCheckoutOptions#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsGetCheckoutOptionsMethodInfo,
#endif
    cherryPickOptionsGetCheckoutOptions     ,


-- ** getMainline #method:getMainline#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsGetMainlineMethodInfo  ,
#endif
    cherryPickOptionsGetMainline            ,


-- ** getMergeOptions #method:getMergeOptions#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsGetMergeOptionsMethodInfo,
#endif
    cherryPickOptionsGetMergeOptions        ,


-- ** new #method:new#

    cherryPickOptionsNew                    ,


-- ** setCheckoutOptions #method:setCheckoutOptions#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsSetCheckoutOptionsMethodInfo,
#endif
    cherryPickOptionsSetCheckoutOptions     ,


-- ** setMainline #method:setMainline#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsSetMainlineMethodInfo  ,
#endif
    cherryPickOptionsSetMainline            ,


-- ** setMergeOptions #method:setMergeOptions#

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsSetMergeOptionsMethodInfo,
#endif
    cherryPickOptionsSetMergeOptions        ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsCheckoutOptionsPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    cherryPickOptionsCheckoutOptions        ,
#endif
    clearCherryPickOptionsCheckoutOptions   ,
    constructCherryPickOptionsCheckoutOptions,
    getCherryPickOptionsCheckoutOptions     ,
    setCherryPickOptionsCheckoutOptions     ,


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

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsMainlinePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    cherryPickOptionsMainline               ,
#endif
    constructCherryPickOptionsMainline      ,
    getCherryPickOptionsMainline            ,
    setCherryPickOptionsMainline            ,


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

#if defined(ENABLE_OVERLOADING)
    CherryPickOptionsMergeOptionsPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    cherryPickOptionsMergeOptions           ,
#endif
    clearCherryPickOptionsMergeOptions      ,
    constructCherryPickOptionsMergeOptions  ,
    getCherryPickOptionsMergeOptions        ,
    setCherryPickOptionsMergeOptions        ,




    ) 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.Kind as DK
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.Objects.CheckoutOptions as Ggit.CheckoutOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.MergeOptions as Ggit.MergeOptions

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

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

foreign import ccall "ggit_cherry_pick_options_get_type"
    c_ggit_cherry_pick_options_get_type :: IO B.Types.GType

instance B.Types.TypedObject CherryPickOptions where
    glibType :: IO GType
glibType = IO GType
c_ggit_cherry_pick_options_get_type

instance B.Types.GObject CherryPickOptions

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveCherryPickOptionsMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveCherryPickOptionsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveCherryPickOptionsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveCherryPickOptionsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveCherryPickOptionsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveCherryPickOptionsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveCherryPickOptionsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveCherryPickOptionsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveCherryPickOptionsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveCherryPickOptionsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveCherryPickOptionsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveCherryPickOptionsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveCherryPickOptionsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveCherryPickOptionsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveCherryPickOptionsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveCherryPickOptionsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveCherryPickOptionsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveCherryPickOptionsMethod "getCheckoutOptions" o = CherryPickOptionsGetCheckoutOptionsMethodInfo
    ResolveCherryPickOptionsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveCherryPickOptionsMethod "getMainline" o = CherryPickOptionsGetMainlineMethodInfo
    ResolveCherryPickOptionsMethod "getMergeOptions" o = CherryPickOptionsGetMergeOptionsMethodInfo
    ResolveCherryPickOptionsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveCherryPickOptionsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveCherryPickOptionsMethod "setCheckoutOptions" o = CherryPickOptionsSetCheckoutOptionsMethodInfo
    ResolveCherryPickOptionsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveCherryPickOptionsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveCherryPickOptionsMethod "setMainline" o = CherryPickOptionsSetMainlineMethodInfo
    ResolveCherryPickOptionsMethod "setMergeOptions" o = CherryPickOptionsSetMergeOptionsMethodInfo
    ResolveCherryPickOptionsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveCherryPickOptionsMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

-- | Get the value of the “@checkout-options@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cherryPickOptions #checkoutOptions
-- @
getCherryPickOptionsCheckoutOptions :: (MonadIO m, IsCherryPickOptions o) => o -> m Ggit.CheckoutOptions.CheckoutOptions
getCherryPickOptionsCheckoutOptions :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> m CheckoutOptions
getCherryPickOptionsCheckoutOptions o
obj = 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)
-> IO CheckoutOptions -> m CheckoutOptions
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe CheckoutOptions) -> IO CheckoutOptions
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getCherryPickOptionsCheckoutOptions" (IO (Maybe CheckoutOptions) -> IO CheckoutOptions)
-> IO (Maybe CheckoutOptions) -> IO CheckoutOptions
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr CheckoutOptions -> CheckoutOptions)
-> IO (Maybe CheckoutOptions)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"checkout-options" ManagedPtr CheckoutOptions -> CheckoutOptions
Ggit.CheckoutOptions.CheckoutOptions

-- | Set the value of the “@checkout-options@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cherryPickOptions [ #checkoutOptions 'Data.GI.Base.Attributes.:=' value ]
-- @
setCherryPickOptionsCheckoutOptions :: (MonadIO m, IsCherryPickOptions o, Ggit.CheckoutOptions.IsCheckoutOptions a) => o -> a -> m ()
setCherryPickOptionsCheckoutOptions :: forall (m :: * -> *) o a.
(MonadIO m, IsCherryPickOptions o, IsCheckoutOptions a) =>
o -> a -> m ()
setCherryPickOptionsCheckoutOptions 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
"checkout-options" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

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

-- | Set the value of the “@checkout-options@” 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' #checkoutOptions
-- @
clearCherryPickOptionsCheckoutOptions :: (MonadIO m, IsCherryPickOptions o) => o -> m ()
clearCherryPickOptionsCheckoutOptions :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> m ()
clearCherryPickOptionsCheckoutOptions 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 CheckoutOptions -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"checkout-options" (Maybe CheckoutOptions
forall a. Maybe a
Nothing :: Maybe Ggit.CheckoutOptions.CheckoutOptions)

#if defined(ENABLE_OVERLOADING)
data CherryPickOptionsCheckoutOptionsPropertyInfo
instance AttrInfo CherryPickOptionsCheckoutOptionsPropertyInfo where
    type AttrAllowedOps CherryPickOptionsCheckoutOptionsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CherryPickOptionsCheckoutOptionsPropertyInfo = IsCherryPickOptions
    type AttrSetTypeConstraint CherryPickOptionsCheckoutOptionsPropertyInfo = Ggit.CheckoutOptions.IsCheckoutOptions
    type AttrTransferTypeConstraint CherryPickOptionsCheckoutOptionsPropertyInfo = Ggit.CheckoutOptions.IsCheckoutOptions
    type AttrTransferType CherryPickOptionsCheckoutOptionsPropertyInfo = Ggit.CheckoutOptions.CheckoutOptions
    type AttrGetType CherryPickOptionsCheckoutOptionsPropertyInfo = Ggit.CheckoutOptions.CheckoutOptions
    type AttrLabel CherryPickOptionsCheckoutOptionsPropertyInfo = "checkout-options"
    type AttrOrigin CherryPickOptionsCheckoutOptionsPropertyInfo = CherryPickOptions
    attrGet = getCherryPickOptionsCheckoutOptions
    attrSet = setCherryPickOptionsCheckoutOptions
    attrTransfer _ v = do
        unsafeCastTo Ggit.CheckoutOptions.CheckoutOptions v
    attrConstruct = constructCherryPickOptionsCheckoutOptions
    attrClear = clearCherryPickOptionsCheckoutOptions
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CherryPickOptions.checkoutOptions"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Objects-CherryPickOptions.html#g:attr:checkoutOptions"
        })
#endif

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

-- | Get the value of the “@mainline@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' cherryPickOptions #mainline
-- @
getCherryPickOptionsMainline :: (MonadIO m, IsCherryPickOptions o) => o -> m Word32
getCherryPickOptionsMainline :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> m Word32
getCherryPickOptionsMainline 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
"mainline"

-- | Set the value of the “@mainline@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cherryPickOptions [ #mainline 'Data.GI.Base.Attributes.:=' value ]
-- @
setCherryPickOptionsMainline :: (MonadIO m, IsCherryPickOptions o) => o -> Word32 -> m ()
setCherryPickOptionsMainline :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> Word32 -> m ()
setCherryPickOptionsMainline 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
"mainline" Word32
val

-- | Construct a `GValueConstruct` with valid value for the “@mainline@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCherryPickOptionsMainline :: (IsCherryPickOptions o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructCherryPickOptionsMainline :: forall o (m :: * -> *).
(IsCherryPickOptions o, MonadIO m) =>
Word32 -> m (GValueConstruct o)
constructCherryPickOptionsMainline 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
"mainline" Word32
val

#if defined(ENABLE_OVERLOADING)
data CherryPickOptionsMainlinePropertyInfo
instance AttrInfo CherryPickOptionsMainlinePropertyInfo where
    type AttrAllowedOps CherryPickOptionsMainlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint CherryPickOptionsMainlinePropertyInfo = IsCherryPickOptions
    type AttrSetTypeConstraint CherryPickOptionsMainlinePropertyInfo = (~) Word32
    type AttrTransferTypeConstraint CherryPickOptionsMainlinePropertyInfo = (~) Word32
    type AttrTransferType CherryPickOptionsMainlinePropertyInfo = Word32
    type AttrGetType CherryPickOptionsMainlinePropertyInfo = Word32
    type AttrLabel CherryPickOptionsMainlinePropertyInfo = "mainline"
    type AttrOrigin CherryPickOptionsMainlinePropertyInfo = CherryPickOptions
    attrGet = getCherryPickOptionsMainline
    attrSet = setCherryPickOptionsMainline
    attrTransfer _ v = do
        return v
    attrConstruct = constructCherryPickOptionsMainline
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CherryPickOptions.mainline"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Objects-CherryPickOptions.html#g:attr:mainline"
        })
#endif

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

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

-- | Set the value of the “@merge-options@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' cherryPickOptions [ #mergeOptions 'Data.GI.Base.Attributes.:=' value ]
-- @
setCherryPickOptionsMergeOptions :: (MonadIO m, IsCherryPickOptions o) => o -> Ggit.MergeOptions.MergeOptions -> m ()
setCherryPickOptionsMergeOptions :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> MergeOptions -> m ()
setCherryPickOptionsMergeOptions o
obj MergeOptions
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 MergeOptions -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"merge-options" (MergeOptions -> Maybe MergeOptions
forall a. a -> Maybe a
Just MergeOptions
val)

-- | Construct a `GValueConstruct` with valid value for the “@merge-options@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructCherryPickOptionsMergeOptions :: (IsCherryPickOptions o, MIO.MonadIO m) => Ggit.MergeOptions.MergeOptions -> m (GValueConstruct o)
constructCherryPickOptionsMergeOptions :: forall o (m :: * -> *).
(IsCherryPickOptions o, MonadIO m) =>
MergeOptions -> m (GValueConstruct o)
constructCherryPickOptionsMergeOptions MergeOptions
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 MergeOptions -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"merge-options" (MergeOptions -> Maybe MergeOptions
forall a. a -> Maybe a
P.Just MergeOptions
val)

-- | Set the value of the “@merge-options@” 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' #mergeOptions
-- @
clearCherryPickOptionsMergeOptions :: (MonadIO m, IsCherryPickOptions o) => o -> m ()
clearCherryPickOptionsMergeOptions :: forall (m :: * -> *) o.
(MonadIO m, IsCherryPickOptions o) =>
o -> m ()
clearCherryPickOptionsMergeOptions 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 MergeOptions -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"merge-options" (Maybe MergeOptions
forall a. Maybe a
Nothing :: Maybe Ggit.MergeOptions.MergeOptions)

#if defined(ENABLE_OVERLOADING)
data CherryPickOptionsMergeOptionsPropertyInfo
instance AttrInfo CherryPickOptionsMergeOptionsPropertyInfo where
    type AttrAllowedOps CherryPickOptionsMergeOptionsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint CherryPickOptionsMergeOptionsPropertyInfo = IsCherryPickOptions
    type AttrSetTypeConstraint CherryPickOptionsMergeOptionsPropertyInfo = (~) Ggit.MergeOptions.MergeOptions
    type AttrTransferTypeConstraint CherryPickOptionsMergeOptionsPropertyInfo = (~) Ggit.MergeOptions.MergeOptions
    type AttrTransferType CherryPickOptionsMergeOptionsPropertyInfo = Ggit.MergeOptions.MergeOptions
    type AttrGetType CherryPickOptionsMergeOptionsPropertyInfo = (Maybe Ggit.MergeOptions.MergeOptions)
    type AttrLabel CherryPickOptionsMergeOptionsPropertyInfo = "merge-options"
    type AttrOrigin CherryPickOptionsMergeOptionsPropertyInfo = CherryPickOptions
    attrGet = getCherryPickOptionsMergeOptions
    attrSet = setCherryPickOptionsMergeOptions
    attrTransfer _ v = do
        return v
    attrConstruct = constructCherryPickOptionsMergeOptions
    attrClear = clearCherryPickOptionsMergeOptions
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Objects.CherryPickOptions.mergeOptions"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Objects-CherryPickOptions.html#g:attr:mergeOptions"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList CherryPickOptions
type instance O.AttributeList CherryPickOptions = CherryPickOptionsAttributeList
type CherryPickOptionsAttributeList = ('[ '("checkoutOptions", CherryPickOptionsCheckoutOptionsPropertyInfo), '("mainline", CherryPickOptionsMainlinePropertyInfo), '("mergeOptions", CherryPickOptionsMergeOptionsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
cherryPickOptionsCheckoutOptions :: AttrLabelProxy "checkoutOptions"
cherryPickOptionsCheckoutOptions = AttrLabelProxy

cherryPickOptionsMainline :: AttrLabelProxy "mainline"
cherryPickOptionsMainline = AttrLabelProxy

cherryPickOptionsMergeOptions :: AttrLabelProxy "mergeOptions"
cherryPickOptionsMergeOptions = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList CherryPickOptions = CherryPickOptionsSignalList
type CherryPickOptionsSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "ggit_cherry_pick_options_new" ggit_cherry_pick_options_new :: 
    IO (Ptr CherryPickOptions)

-- | Create a new cherry-pick options object.
cherryPickOptionsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m CherryPickOptions
    -- ^ __Returns:__ a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
cherryPickOptionsNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m CherryPickOptions
cherryPickOptionsNew  = IO CherryPickOptions -> m CherryPickOptions
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CherryPickOptions -> m CherryPickOptions)
-> IO CherryPickOptions -> m CherryPickOptions
forall a b. (a -> b) -> a -> b
$ do
    Ptr CherryPickOptions
result <- IO (Ptr CherryPickOptions)
ggit_cherry_pick_options_new
    Text -> Ptr CherryPickOptions -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cherryPickOptionsNew" Ptr CherryPickOptions
result
    CherryPickOptions
result' <- ((ManagedPtr CherryPickOptions -> CherryPickOptions)
-> Ptr CherryPickOptions -> IO CherryPickOptions
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr CherryPickOptions -> CherryPickOptions
CherryPickOptions) Ptr CherryPickOptions
result
    CherryPickOptions -> IO CherryPickOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CherryPickOptions
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Get the checkout options.
cherryPickOptionsGetCheckoutOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> m Ggit.CheckoutOptions.CheckoutOptions
    -- ^ __Returns:__ a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
cherryPickOptionsGetCheckoutOptions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCherryPickOptions a) =>
a -> m CheckoutOptions
cherryPickOptionsGetCheckoutOptions a
options = IO CheckoutOptions -> m CheckoutOptions
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CheckoutOptions -> m CheckoutOptions)
-> IO CheckoutOptions -> m CheckoutOptions
forall a b. (a -> b) -> a -> b
$ do
    Ptr CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CheckoutOptions
result <- Ptr CherryPickOptions -> IO (Ptr CheckoutOptions)
ggit_cherry_pick_options_get_checkout_options Ptr CherryPickOptions
options'
    Text -> Ptr CheckoutOptions -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cherryPickOptionsGetCheckoutOptions" Ptr CheckoutOptions
result
    CheckoutOptions
result' <- ((ManagedPtr CheckoutOptions -> CheckoutOptions)
-> Ptr CheckoutOptions -> IO CheckoutOptions
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr CheckoutOptions -> CheckoutOptions
Ggit.CheckoutOptions.CheckoutOptions) Ptr CheckoutOptions
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    CheckoutOptions -> IO CheckoutOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CheckoutOptions
result'

#if defined(ENABLE_OVERLOADING)
data CherryPickOptionsGetCheckoutOptionsMethodInfo
instance (signature ~ (m Ggit.CheckoutOptions.CheckoutOptions), MonadIO m, IsCherryPickOptions a) => O.OverloadedMethod CherryPickOptionsGetCheckoutOptionsMethodInfo a signature where
    overloadedMethod = cherryPickOptionsGetCheckoutOptions

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


#endif

-- method CherryPickOptions::get_mainline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "CherryPickOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitCherryPickOptions."
--                 , 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_cherry_pick_options_get_mainline" ggit_cherry_pick_options_get_mainline :: 
    Ptr CherryPickOptions ->                -- options : TInterface (Name {namespace = "Ggit", name = "CherryPickOptions"})
    IO Word32

-- | Get the mainline parent to use when cherry-picking a merge commit.
cherryPickOptionsGetMainline ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> m Word32
    -- ^ __Returns:__ the mainline parent.
cherryPickOptionsGetMainline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCherryPickOptions a) =>
a -> m Word32
cherryPickOptionsGetMainline 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 CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Word32
result <- Ptr CherryPickOptions -> IO Word32
ggit_cherry_pick_options_get_mainline Ptr CherryPickOptions
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 CherryPickOptionsGetMainlineMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsCherryPickOptions a) => O.OverloadedMethod CherryPickOptionsGetMainlineMethodInfo a signature where
    overloadedMethod = cherryPickOptionsGetMainline

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


#endif

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

foreign import ccall "ggit_cherry_pick_options_get_merge_options" ggit_cherry_pick_options_get_merge_options :: 
    Ptr CherryPickOptions ->                -- options : TInterface (Name {namespace = "Ggit", name = "CherryPickOptions"})
    IO (Ptr Ggit.MergeOptions.MergeOptions)

-- | Get the merge options.
cherryPickOptionsGetMergeOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> m Ggit.MergeOptions.MergeOptions
    -- ^ __Returns:__ a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
cherryPickOptionsGetMergeOptions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCherryPickOptions a) =>
a -> m MergeOptions
cherryPickOptionsGetMergeOptions a
options = IO MergeOptions -> m MergeOptions
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MergeOptions -> m MergeOptions)
-> IO MergeOptions -> m MergeOptions
forall a b. (a -> b) -> a -> b
$ do
    Ptr CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr MergeOptions
result <- Ptr CherryPickOptions -> IO (Ptr MergeOptions)
ggit_cherry_pick_options_get_merge_options Ptr CherryPickOptions
options'
    Text -> Ptr MergeOptions -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"cherryPickOptionsGetMergeOptions" Ptr MergeOptions
result
    MergeOptions
result' <- ((ManagedPtr MergeOptions -> MergeOptions)
-> Ptr MergeOptions -> IO MergeOptions
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr MergeOptions -> MergeOptions
Ggit.MergeOptions.MergeOptions) Ptr MergeOptions
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    MergeOptions -> IO MergeOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MergeOptions
result'

#if defined(ENABLE_OVERLOADING)
data CherryPickOptionsGetMergeOptionsMethodInfo
instance (signature ~ (m Ggit.MergeOptions.MergeOptions), MonadIO m, IsCherryPickOptions a) => O.OverloadedMethod CherryPickOptionsGetMergeOptionsMethodInfo a signature where
    overloadedMethod = cherryPickOptionsGetMergeOptions

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


#endif

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

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

-- | Set the checkout options.
cherryPickOptionsSetCheckoutOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a, Ggit.CheckoutOptions.IsCheckoutOptions b) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> Maybe (b)
    -- ^ /@checkoutOptions@/: a t'GI.Ggit.Objects.CheckoutOptions.CheckoutOptions'.
    -> m ()
cherryPickOptionsSetCheckoutOptions :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsCherryPickOptions a,
 IsCheckoutOptions b) =>
a -> Maybe b -> m ()
cherryPickOptionsSetCheckoutOptions a
options Maybe b
checkoutOptions = 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 CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CheckoutOptions
maybeCheckoutOptions <- case Maybe b
checkoutOptions of
        Maybe b
Nothing -> Ptr CheckoutOptions -> IO (Ptr CheckoutOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CheckoutOptions
forall a. Ptr a
nullPtr
        Just b
jCheckoutOptions -> do
            Ptr CheckoutOptions
jCheckoutOptions' <- b -> IO (Ptr CheckoutOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCheckoutOptions
            Ptr CheckoutOptions -> IO (Ptr CheckoutOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CheckoutOptions
jCheckoutOptions'
    Ptr CherryPickOptions -> Ptr CheckoutOptions -> IO ()
ggit_cherry_pick_options_set_checkout_options Ptr CherryPickOptions
options' Ptr CheckoutOptions
maybeCheckoutOptions
    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
checkoutOptions 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 CherryPickOptionsSetCheckoutOptionsMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsCherryPickOptions a, Ggit.CheckoutOptions.IsCheckoutOptions b) => O.OverloadedMethod CherryPickOptionsSetCheckoutOptionsMethodInfo a signature where
    overloadedMethod = cherryPickOptionsSetCheckoutOptions

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


#endif

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

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

-- | Set the mainline parent to use when cherry-picking a merge commit.
cherryPickOptionsSetMainline ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> Word32
    -- ^ /@mainline@/: the mainline parent.
    -> m ()
cherryPickOptionsSetMainline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCherryPickOptions a) =>
a -> Word32 -> m ()
cherryPickOptionsSetMainline a
options Word32
mainline = 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 CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr CherryPickOptions -> Word32 -> IO ()
ggit_cherry_pick_options_set_mainline Ptr CherryPickOptions
options' Word32
mainline
    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 CherryPickOptionsSetMainlineMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsCherryPickOptions a) => O.OverloadedMethod CherryPickOptionsSetMainlineMethodInfo a signature where
    overloadedMethod = cherryPickOptionsSetMainline

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


#endif

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

foreign import ccall "ggit_cherry_pick_options_set_merge_options" ggit_cherry_pick_options_set_merge_options :: 
    Ptr CherryPickOptions ->                -- options : TInterface (Name {namespace = "Ggit", name = "CherryPickOptions"})
    Ptr Ggit.MergeOptions.MergeOptions ->   -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO ()

-- | Set the merge options.
cherryPickOptionsSetMergeOptions ::
    (B.CallStack.HasCallStack, MonadIO m, IsCherryPickOptions a) =>
    a
    -- ^ /@options@/: a t'GI.Ggit.Objects.CherryPickOptions.CherryPickOptions'.
    -> Maybe (Ggit.MergeOptions.MergeOptions)
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m ()
cherryPickOptionsSetMergeOptions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsCherryPickOptions a) =>
a -> Maybe MergeOptions -> m ()
cherryPickOptionsSetMergeOptions a
options Maybe MergeOptions
mergeOptions = 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 CherryPickOptions
options' <- a -> IO (Ptr CherryPickOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
    Ptr MergeOptions
maybeMergeOptions <- case Maybe MergeOptions
mergeOptions of
        Maybe MergeOptions
Nothing -> Ptr MergeOptions -> IO (Ptr MergeOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MergeOptions
forall a. Ptr a
nullPtr
        Just MergeOptions
jMergeOptions -> do
            Ptr MergeOptions
jMergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
jMergeOptions
            Ptr MergeOptions -> IO (Ptr MergeOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr MergeOptions
jMergeOptions'
    Ptr CherryPickOptions -> Ptr MergeOptions -> IO ()
ggit_cherry_pick_options_set_merge_options Ptr CherryPickOptions
options' Ptr MergeOptions
maybeMergeOptions
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
    Maybe MergeOptions -> (MergeOptions -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe MergeOptions
mergeOptions MergeOptions -> 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 CherryPickOptionsSetMergeOptionsMethodInfo
instance (signature ~ (Maybe (Ggit.MergeOptions.MergeOptions) -> m ()), MonadIO m, IsCherryPickOptions a) => O.OverloadedMethod CherryPickOptionsSetMergeOptionsMethodInfo a signature where
    overloadedMethod = cherryPickOptionsSetMergeOptions

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


#endif