{-# 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 merging.

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

module GI.Ggit.Structs.MergeOptions
    ( 

-- * Exported types
    MergeOptions(..)                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [copy]("GI.Ggit.Structs.MergeOptions#g:method:copy"), [free]("GI.Ggit.Structs.MergeOptions#g:method:free").
-- 
-- ==== Getters
-- [getFileFavor]("GI.Ggit.Structs.MergeOptions#g:method:getFileFavor"), [getFileFlags]("GI.Ggit.Structs.MergeOptions#g:method:getFileFlags"), [getFlags]("GI.Ggit.Structs.MergeOptions#g:method:getFlags"), [getRenameThreshold]("GI.Ggit.Structs.MergeOptions#g:method:getRenameThreshold"), [getSimilarityMetric]("GI.Ggit.Structs.MergeOptions#g:method:getSimilarityMetric"), [getTargetLimit]("GI.Ggit.Structs.MergeOptions#g:method:getTargetLimit").
-- 
-- ==== Setters
-- [setFileFavor]("GI.Ggit.Structs.MergeOptions#g:method:setFileFavor"), [setFileFlags]("GI.Ggit.Structs.MergeOptions#g:method:setFileFlags"), [setFlags]("GI.Ggit.Structs.MergeOptions#g:method:setFlags"), [setRenameThreshold]("GI.Ggit.Structs.MergeOptions#g:method:setRenameThreshold"), [setSimilarityMetric]("GI.Ggit.Structs.MergeOptions#g:method:setSimilarityMetric"), [setTargetLimit]("GI.Ggit.Structs.MergeOptions#g:method:setTargetLimit").

#if defined(ENABLE_OVERLOADING)
    ResolveMergeOptionsMethod               ,
#endif

-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsCopyMethodInfo              ,
#endif
    mergeOptionsCopy                        ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsFreeMethodInfo              ,
#endif
    mergeOptionsFree                        ,


-- ** getFileFavor #method:getFileFavor#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetFileFavorMethodInfo      ,
#endif
    mergeOptionsGetFileFavor                ,


-- ** getFileFlags #method:getFileFlags#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetFileFlagsMethodInfo      ,
#endif
    mergeOptionsGetFileFlags                ,


-- ** getFlags #method:getFlags#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetFlagsMethodInfo          ,
#endif
    mergeOptionsGetFlags                    ,


-- ** getRenameThreshold #method:getRenameThreshold#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetRenameThresholdMethodInfo,
#endif
    mergeOptionsGetRenameThreshold          ,


-- ** getSimilarityMetric #method:getSimilarityMetric#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetSimilarityMetricMethodInfo,
#endif
    mergeOptionsGetSimilarityMetric         ,


-- ** getTargetLimit #method:getTargetLimit#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsGetTargetLimitMethodInfo    ,
#endif
    mergeOptionsGetTargetLimit              ,


-- ** new #method:new#

    mergeOptionsNew                         ,


-- ** setFileFavor #method:setFileFavor#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetFileFavorMethodInfo      ,
#endif
    mergeOptionsSetFileFavor                ,


-- ** setFileFlags #method:setFileFlags#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetFileFlagsMethodInfo      ,
#endif
    mergeOptionsSetFileFlags                ,


-- ** setFlags #method:setFlags#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetFlagsMethodInfo          ,
#endif
    mergeOptionsSetFlags                    ,


-- ** setRenameThreshold #method:setRenameThreshold#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetRenameThresholdMethodInfo,
#endif
    mergeOptionsSetRenameThreshold          ,


-- ** setSimilarityMetric #method:setSimilarityMetric#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetSimilarityMetricMethodInfo,
#endif
    mergeOptionsSetSimilarityMetric         ,


-- ** setTargetLimit #method:setTargetLimit#

#if defined(ENABLE_OVERLOADING)
    MergeOptionsSetTargetLimitMethodInfo    ,
#endif
    mergeOptionsSetTargetLimit              ,




    ) 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 {-# SOURCE #-} qualified GI.Ggit.Enums as Ggit.Enums
import {-# SOURCE #-} qualified GI.Ggit.Flags as Ggit.Flags
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffSimilarityMetric as Ggit.DiffSimilarityMetric

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

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

foreign import ccall "ggit_merge_options_get_type" c_ggit_merge_options_get_type :: 
    IO GType

type instance O.ParentTypes MergeOptions = '[]
instance O.HasParentTypes MergeOptions

instance B.Types.TypedObject MergeOptions where
    glibType :: IO GType
glibType = IO GType
c_ggit_merge_options_get_type

instance B.Types.GBoxed MergeOptions

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList MergeOptions
type instance O.AttributeList MergeOptions = MergeOptionsAttributeList
type MergeOptionsAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

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

foreign import ccall "ggit_merge_options_new" ggit_merge_options_new :: 
    IO (Ptr MergeOptions)

-- | Creates a new t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
mergeOptionsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m MergeOptions
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
mergeOptionsNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m MergeOptions
mergeOptionsNew  = 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 MergeOptions
result <- IO (Ptr MergeOptions)
ggit_merge_options_new
    Text -> Ptr MergeOptions -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"mergeOptionsNew" 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
MergeOptions) Ptr MergeOptions
result
    MergeOptions -> IO MergeOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MergeOptions
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method MergeOptions::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , 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_merge_options_copy" ggit_merge_options_copy :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO (Ptr MergeOptions)

-- | Copies /@mergeOptions@/ into a newly allocated t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
mergeOptionsCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m (Maybe MergeOptions)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Structs.MergeOptions.MergeOptions' or 'P.Nothing'.
mergeOptionsCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m (Maybe MergeOptions)
mergeOptionsCopy MergeOptions
mergeOptions = IO (Maybe MergeOptions) -> m (Maybe MergeOptions)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe MergeOptions) -> m (Maybe MergeOptions))
-> IO (Maybe MergeOptions) -> m (Maybe MergeOptions)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr MergeOptions
result <- Ptr MergeOptions -> IO (Ptr MergeOptions)
ggit_merge_options_copy Ptr MergeOptions
mergeOptions'
    Maybe MergeOptions
maybeResult <- Ptr MergeOptions
-> (Ptr MergeOptions -> IO MergeOptions) -> IO (Maybe MergeOptions)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr MergeOptions
result ((Ptr MergeOptions -> IO MergeOptions) -> IO (Maybe MergeOptions))
-> (Ptr MergeOptions -> IO MergeOptions) -> IO (Maybe MergeOptions)
forall a b. (a -> b) -> a -> b
$ \Ptr MergeOptions
result' -> do
        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
MergeOptions) Ptr MergeOptions
result'
        MergeOptions -> IO MergeOptions
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MergeOptions
result''
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    Maybe MergeOptions -> IO (Maybe MergeOptions)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe MergeOptions
maybeResult

#if defined(ENABLE_OVERLOADING)
data MergeOptionsCopyMethodInfo
instance (signature ~ (m (Maybe MergeOptions)), MonadIO m) => O.OverloadedMethod MergeOptionsCopyMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsCopy

instance O.OverloadedMethodInfo MergeOptionsCopyMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsCopy"
        })


#endif

-- method MergeOptions::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , 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_merge_options_free" ggit_merge_options_free :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO ()

-- | Frees /@mergeOptions@/.
mergeOptionsFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m ()
mergeOptionsFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m ()
mergeOptionsFree 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr MergeOptions -> IO ()
ggit_merge_options_free Ptr MergeOptions
mergeOptions'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod MergeOptionsFreeMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsFree

instance O.OverloadedMethodInfo MergeOptionsFreeMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsFree",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsFree"
        })


#endif

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

foreign import ccall "ggit_merge_options_get_file_favor" ggit_merge_options_get_file_favor :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO CUInt

-- | Get flags for handling conflicting content.
mergeOptionsGetFileFavor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m Ggit.Enums.MergeFileFavor
    -- ^ __Returns:__ the file favor.
mergeOptionsGetFileFavor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m MergeFileFavor
mergeOptionsGetFileFavor MergeOptions
mergeOptions = IO MergeFileFavor -> m MergeFileFavor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MergeFileFavor -> m MergeFileFavor)
-> IO MergeFileFavor -> m MergeFileFavor
forall a b. (a -> b) -> a -> b
$ do
    Ptr MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    CUInt
result <- Ptr MergeOptions -> IO CUInt
ggit_merge_options_get_file_favor Ptr MergeOptions
mergeOptions'
    let result' :: MergeFileFavor
result' = (Int -> MergeFileFavor
forall a. Enum a => Int -> a
toEnum (Int -> MergeFileFavor)
-> (CUInt -> Int) -> CUInt -> MergeFileFavor
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    MergeFileFavor -> IO MergeFileFavor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return MergeFileFavor
result'

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetFileFavorMethodInfo
instance (signature ~ (m Ggit.Enums.MergeFileFavor), MonadIO m) => O.OverloadedMethod MergeOptionsGetFileFavorMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetFileFavor

instance O.OverloadedMethodInfo MergeOptionsGetFileFavorMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetFileFavor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetFileFavor"
        })


#endif

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

foreign import ccall "ggit_merge_options_get_file_flags" ggit_merge_options_get_file_flags :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO CUInt

-- | Get file merging flags.
mergeOptionsGetFileFlags ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m [Ggit.Flags.MergeFileFlags]
    -- ^ __Returns:__ the file merging flags.
mergeOptionsGetFileFlags :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m [MergeFileFlags]
mergeOptionsGetFileFlags MergeOptions
mergeOptions = IO [MergeFileFlags] -> m [MergeFileFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [MergeFileFlags] -> m [MergeFileFlags])
-> IO [MergeFileFlags] -> m [MergeFileFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    CUInt
result <- Ptr MergeOptions -> IO CUInt
ggit_merge_options_get_file_flags Ptr MergeOptions
mergeOptions'
    let result' :: [MergeFileFlags]
result' = CUInt -> [MergeFileFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    [MergeFileFlags] -> IO [MergeFileFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [MergeFileFlags]
result'

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetFileFlagsMethodInfo
instance (signature ~ (m [Ggit.Flags.MergeFileFlags]), MonadIO m) => O.OverloadedMethod MergeOptionsGetFileFlagsMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetFileFlags

instance O.OverloadedMethodInfo MergeOptionsGetFileFlagsMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetFileFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetFileFlags"
        })


#endif

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

foreign import ccall "ggit_merge_options_get_flags" ggit_merge_options_get_flags :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO CUInt

-- | Get the tree flags to use for merging.
mergeOptionsGetFlags ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m [Ggit.Flags.MergeFlags]
    -- ^ __Returns:__ the flags.
mergeOptionsGetFlags :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m [MergeFlags]
mergeOptionsGetFlags MergeOptions
mergeOptions = IO [MergeFlags] -> m [MergeFlags]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [MergeFlags] -> m [MergeFlags])
-> IO [MergeFlags] -> m [MergeFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    CUInt
result <- Ptr MergeOptions -> IO CUInt
ggit_merge_options_get_flags Ptr MergeOptions
mergeOptions'
    let result' :: [MergeFlags]
result' = CUInt -> [MergeFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    [MergeFlags] -> IO [MergeFlags]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [MergeFlags]
result'

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetFlagsMethodInfo
instance (signature ~ (m [Ggit.Flags.MergeFlags]), MonadIO m) => O.OverloadedMethod MergeOptionsGetFlagsMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetFlags

instance O.OverloadedMethodInfo MergeOptionsGetFlagsMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetFlags"
        })


#endif

-- method MergeOptions::get_rename_threshold
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , 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_merge_options_get_rename_threshold" ggit_merge_options_get_rename_threshold :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO Word32

-- | Get the rename threshold (defaults to 50). If @/GGIT_MERGE_TREE_FIND_RENAMES/@
-- is enabled, added files will be compared with deleted files to
-- determine their similarity. Files that are more similar than the rename
-- threshold (percentage-wise) will be treated as a rename.
mergeOptionsGetRenameThreshold ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m Word32
    -- ^ __Returns:__ the rename threshold.
mergeOptionsGetRenameThreshold :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m Word32
mergeOptionsGetRenameThreshold MergeOptions
mergeOptions = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Word32
result <- Ptr MergeOptions -> IO Word32
ggit_merge_options_get_rename_threshold Ptr MergeOptions
mergeOptions'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetRenameThresholdMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod MergeOptionsGetRenameThresholdMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetRenameThreshold

instance O.OverloadedMethodInfo MergeOptionsGetRenameThresholdMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetRenameThreshold",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetRenameThreshold"
        })


#endif

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

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

-- | Get the similarity metric.
mergeOptionsGetSimilarityMetric ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m (Maybe Ggit.DiffSimilarityMetric.DiffSimilarityMetric)
    -- ^ __Returns:__ the similarity metric, or 'P.Nothing'.
mergeOptionsGetSimilarityMetric :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m (Maybe DiffSimilarityMetric)
mergeOptionsGetSimilarityMetric MergeOptions
mergeOptions = IO (Maybe DiffSimilarityMetric) -> m (Maybe DiffSimilarityMetric)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DiffSimilarityMetric) -> m (Maybe DiffSimilarityMetric))
-> IO (Maybe DiffSimilarityMetric)
-> m (Maybe DiffSimilarityMetric)
forall a b. (a -> b) -> a -> b
$ do
    Ptr MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr DiffSimilarityMetric
result <- Ptr MergeOptions -> IO (Ptr DiffSimilarityMetric)
ggit_merge_options_get_similarity_metric Ptr MergeOptions
mergeOptions'
    Maybe DiffSimilarityMetric
maybeResult <- Ptr DiffSimilarityMetric
-> (Ptr DiffSimilarityMetric -> IO DiffSimilarityMetric)
-> IO (Maybe DiffSimilarityMetric)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DiffSimilarityMetric
result ((Ptr DiffSimilarityMetric -> IO DiffSimilarityMetric)
 -> IO (Maybe DiffSimilarityMetric))
-> (Ptr DiffSimilarityMetric -> IO DiffSimilarityMetric)
-> IO (Maybe DiffSimilarityMetric)
forall a b. (a -> b) -> a -> b
$ \Ptr DiffSimilarityMetric
result' -> do
        DiffSimilarityMetric
result'' <- ((ManagedPtr DiffSimilarityMetric -> DiffSimilarityMetric)
-> Ptr DiffSimilarityMetric -> IO DiffSimilarityMetric
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr DiffSimilarityMetric -> DiffSimilarityMetric
Ggit.DiffSimilarityMetric.DiffSimilarityMetric) Ptr DiffSimilarityMetric
result'
        DiffSimilarityMetric -> IO DiffSimilarityMetric
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DiffSimilarityMetric
result''
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    Maybe DiffSimilarityMetric -> IO (Maybe DiffSimilarityMetric)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DiffSimilarityMetric
maybeResult

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetSimilarityMetricMethodInfo
instance (signature ~ (m (Maybe Ggit.DiffSimilarityMetric.DiffSimilarityMetric)), MonadIO m) => O.OverloadedMethod MergeOptionsGetSimilarityMetricMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetSimilarityMetric

instance O.OverloadedMethodInfo MergeOptionsGetSimilarityMetricMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetSimilarityMetric",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetSimilarityMetric"
        })


#endif

-- method MergeOptions::get_target_limit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , 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_merge_options_get_target_limit" ggit_merge_options_get_target_limit :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    IO Word32

-- | Get the maximum number of similarity sources to examine for renames (defaults to 200).
-- If the number of rename candidates (add \/ delete pairs) is greater than
-- this value, inexact rename detection is aborted.
mergeOptionsGetTargetLimit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> m Word32
    -- ^ __Returns:__ the target limit.
mergeOptionsGetTargetLimit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> m Word32
mergeOptionsGetTargetLimit MergeOptions
mergeOptions = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Word32
result <- Ptr MergeOptions -> IO Word32
ggit_merge_options_get_target_limit Ptr MergeOptions
mergeOptions'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data MergeOptionsGetTargetLimitMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.OverloadedMethod MergeOptionsGetTargetLimitMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsGetTargetLimit

instance O.OverloadedMethodInfo MergeOptionsGetTargetLimitMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsGetTargetLimit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsGetTargetLimit"
        })


#endif

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

foreign import ccall "ggit_merge_options_set_file_favor" ggit_merge_options_set_file_favor :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    CUInt ->                                -- file_favor : TInterface (Name {namespace = "Ggit", name = "MergeFileFavor"})
    IO ()

-- | Set flags for handling conflicting content.
mergeOptionsSetFileFavor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> Ggit.Enums.MergeFileFavor
    -- ^ /@fileFavor@/: the file favor.
    -> m ()
mergeOptionsSetFileFavor :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> MergeFileFavor -> m ()
mergeOptionsSetFileFavor MergeOptions
mergeOptions MergeFileFavor
fileFavor = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    let fileFavor' :: CUInt
fileFavor' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (MergeFileFavor -> Int) -> MergeFileFavor -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MergeFileFavor -> Int
forall a. Enum a => a -> Int
fromEnum) MergeFileFavor
fileFavor
    Ptr MergeOptions -> CUInt -> IO ()
ggit_merge_options_set_file_favor Ptr MergeOptions
mergeOptions' CUInt
fileFavor'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetFileFavorMethodInfo
instance (signature ~ (Ggit.Enums.MergeFileFavor -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetFileFavorMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetFileFavor

instance O.OverloadedMethodInfo MergeOptionsSetFileFavorMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetFileFavor",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetFileFavor"
        })


#endif

-- method MergeOptions::set_file_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file_flags"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file 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_merge_options_set_file_flags" ggit_merge_options_set_file_flags :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    CUInt ->                                -- file_flags : TInterface (Name {namespace = "Ggit", name = "MergeFileFlags"})
    IO ()

-- | Set file merging flags.
mergeOptionsSetFileFlags ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> [Ggit.Flags.MergeFileFlags]
    -- ^ /@fileFlags@/: the file flags.
    -> m ()
mergeOptionsSetFileFlags :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> [MergeFileFlags] -> m ()
mergeOptionsSetFileFlags MergeOptions
mergeOptions [MergeFileFlags]
fileFlags = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    let fileFlags' :: CUInt
fileFlags' = [MergeFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MergeFileFlags]
fileFlags
    Ptr MergeOptions -> CUInt -> IO ()
ggit_merge_options_set_file_flags Ptr MergeOptions
mergeOptions' CUInt
fileFlags'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetFileFlagsMethodInfo
instance (signature ~ ([Ggit.Flags.MergeFileFlags] -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetFileFlagsMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetFileFlags

instance O.OverloadedMethodInfo MergeOptionsSetFileFlagsMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetFileFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetFileFlags"
        })


#endif

-- method MergeOptions::set_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_merge_options_set_flags" ggit_merge_options_set_flags :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Ggit", name = "MergeFlags"})
    IO ()

-- | /No description available in the introspection data./
mergeOptionsSetFlags ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -> [Ggit.Flags.MergeFlags]
    -> m ()
mergeOptionsSetFlags :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> [MergeFlags] -> m ()
mergeOptionsSetFlags MergeOptions
mergeOptions [MergeFlags]
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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    let flags' :: CUInt
flags' = [MergeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [MergeFlags]
flags
    Ptr MergeOptions -> CUInt -> IO ()
ggit_merge_options_set_flags Ptr MergeOptions
mergeOptions' CUInt
flags'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetFlagsMethodInfo
instance (signature ~ ([Ggit.Flags.MergeFlags] -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetFlagsMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetFlags

instance O.OverloadedMethodInfo MergeOptionsSetFlagsMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetFlags",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetFlags"
        })


#endif

-- method MergeOptions::set_rename_threshold
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rename_threshold"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "similarity to consider a file renamed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_merge_options_set_rename_threshold" ggit_merge_options_set_rename_threshold :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    Word32 ->                               -- rename_threshold : TBasicType TUInt
    IO ()

-- | Set the rename threshold (defaults to 50). If @/GGIT_MERGE_TREE_FIND_RENAMES/@
-- is enabled, added files will be compared with deleted files to
-- determine their similarity. Files that are more similar than the rename
-- threshold (percentage-wise) will be treated as a rename.
mergeOptionsSetRenameThreshold ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> Word32
    -- ^ /@renameThreshold@/: similarity to consider a file renamed.
    -> m ()
mergeOptionsSetRenameThreshold :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> Word32 -> m ()
mergeOptionsSetRenameThreshold MergeOptions
mergeOptions Word32
renameThreshold = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr MergeOptions -> Word32 -> IO ()
ggit_merge_options_set_rename_threshold Ptr MergeOptions
mergeOptions' Word32
renameThreshold
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetRenameThresholdMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetRenameThresholdMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetRenameThreshold

instance O.OverloadedMethodInfo MergeOptionsSetRenameThresholdMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetRenameThreshold",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetRenameThreshold"
        })


#endif

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

foreign import ccall "ggit_merge_options_set_similarity_metric" ggit_merge_options_set_similarity_metric :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    Ptr Ggit.DiffSimilarityMetric.DiffSimilarityMetric -> -- metric : TInterface (Name {namespace = "Ggit", name = "DiffSimilarityMetric"})
    IO ()

-- | Set the similarity metric, or 'P.Nothing' for the default similarity metric.
mergeOptionsSetSimilarityMetric ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> Ggit.DiffSimilarityMetric.DiffSimilarityMetric
    -- ^ /@metric@/: a @/GgitSimilarityMetric/@.
    -> m ()
mergeOptionsSetSimilarityMetric :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> DiffSimilarityMetric -> m ()
mergeOptionsSetSimilarityMetric MergeOptions
mergeOptions DiffSimilarityMetric
metric = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr DiffSimilarityMetric
metric' <- DiffSimilarityMetric -> IO (Ptr DiffSimilarityMetric)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr DiffSimilarityMetric
metric
    Ptr MergeOptions -> Ptr DiffSimilarityMetric -> IO ()
ggit_merge_options_set_similarity_metric Ptr MergeOptions
mergeOptions' Ptr DiffSimilarityMetric
metric'
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    DiffSimilarityMetric -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr DiffSimilarityMetric
metric
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetSimilarityMetricMethodInfo
instance (signature ~ (Ggit.DiffSimilarityMetric.DiffSimilarityMetric -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetSimilarityMetricMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetSimilarityMetric

instance O.OverloadedMethodInfo MergeOptionsSetSimilarityMetricMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetSimilarityMetric",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetSimilarityMetric"
        })


#endif

-- method MergeOptions::set_target_limit
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "merge_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "MergeOptions" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitMergeOptions."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_limit"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "maximum similarity source to examine for renames."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "ggit_merge_options_set_target_limit" ggit_merge_options_set_target_limit :: 
    Ptr MergeOptions ->                     -- merge_options : TInterface (Name {namespace = "Ggit", name = "MergeOptions"})
    Word32 ->                               -- target_limit : TBasicType TUInt
    IO ()

-- | Set the maximum number of similarity sources to examine for renames (defaults to 200).
-- If the number of rename candidates (add \/ delete pairs) is greater than
-- this value, inexact rename detection is aborted.
mergeOptionsSetTargetLimit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    MergeOptions
    -- ^ /@mergeOptions@/: a t'GI.Ggit.Structs.MergeOptions.MergeOptions'.
    -> Word32
    -- ^ /@targetLimit@/: maximum similarity source to examine for renames.
    -> m ()
mergeOptionsSetTargetLimit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
MergeOptions -> Word32 -> m ()
mergeOptionsSetTargetLimit MergeOptions
mergeOptions Word32
targetLimit = 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 MergeOptions
mergeOptions' <- MergeOptions -> IO (Ptr MergeOptions)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr MergeOptions
mergeOptions
    Ptr MergeOptions -> Word32 -> IO ()
ggit_merge_options_set_target_limit Ptr MergeOptions
mergeOptions' Word32
targetLimit
    MergeOptions -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr MergeOptions
mergeOptions
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data MergeOptionsSetTargetLimitMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m) => O.OverloadedMethod MergeOptionsSetTargetLimitMethodInfo MergeOptions signature where
    overloadedMethod = mergeOptionsSetTargetLimit

instance O.OverloadedMethodInfo MergeOptionsSetTargetLimitMethodInfo MergeOptions where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Ggit.Structs.MergeOptions.mergeOptionsSetTargetLimit",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.14/docs/GI-Ggit-Structs-MergeOptions.html#v:mergeOptionsSetTargetLimit"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveMergeOptionsMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveMergeOptionsMethod "copy" o = MergeOptionsCopyMethodInfo
    ResolveMergeOptionsMethod "free" o = MergeOptionsFreeMethodInfo
    ResolveMergeOptionsMethod "getFileFavor" o = MergeOptionsGetFileFavorMethodInfo
    ResolveMergeOptionsMethod "getFileFlags" o = MergeOptionsGetFileFlagsMethodInfo
    ResolveMergeOptionsMethod "getFlags" o = MergeOptionsGetFlagsMethodInfo
    ResolveMergeOptionsMethod "getRenameThreshold" o = MergeOptionsGetRenameThresholdMethodInfo
    ResolveMergeOptionsMethod "getSimilarityMetric" o = MergeOptionsGetSimilarityMetricMethodInfo
    ResolveMergeOptionsMethod "getTargetLimit" o = MergeOptionsGetTargetLimitMethodInfo
    ResolveMergeOptionsMethod "setFileFavor" o = MergeOptionsSetFileFavorMethodInfo
    ResolveMergeOptionsMethod "setFileFlags" o = MergeOptionsSetFileFlagsMethodInfo
    ResolveMergeOptionsMethod "setFlags" o = MergeOptionsSetFlagsMethodInfo
    ResolveMergeOptionsMethod "setRenameThreshold" o = MergeOptionsSetRenameThresholdMethodInfo
    ResolveMergeOptionsMethod "setSimilarityMetric" o = MergeOptionsSetSimilarityMetricMethodInfo
    ResolveMergeOptionsMethod "setTargetLimit" o = MergeOptionsSetTargetLimitMethodInfo
    ResolveMergeOptionsMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif