{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Represents a diff list.

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

module GI.Ggit.Objects.Diff
    ( 
#if defined(ENABLE_OVERLOADING)
    DiffForeachMethodInfo                   ,
#endif
#if defined(ENABLE_OVERLOADING)
    DiffBlobToBufferMethodInfo              ,
#endif
#if defined(ENABLE_OVERLOADING)
    DiffBlobsMethodInfo                     ,
#endif

-- * Exported types
    Diff(..)                                ,
    IsDiff                                  ,
    toDiff                                  ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDiffMethod                       ,
#endif


-- ** findSimilar #method:findSimilar#

#if defined(ENABLE_OVERLOADING)
    DiffFindSimilarMethodInfo               ,
#endif
    diffFindSimilar                         ,


-- ** formatEmail #method:formatEmail#

#if defined(ENABLE_OVERLOADING)
    DiffFormatEmailMethodInfo               ,
#endif
    diffFormatEmail                         ,


-- ** getDelta #method:getDelta#

#if defined(ENABLE_OVERLOADING)
    DiffGetDeltaMethodInfo                  ,
#endif
    diffGetDelta                            ,


-- ** getNumDeltas #method:getNumDeltas#

#if defined(ENABLE_OVERLOADING)
    DiffGetNumDeltasMethodInfo              ,
#endif
    diffGetNumDeltas                        ,


-- ** merge #method:merge#

#if defined(ENABLE_OVERLOADING)
    DiffMergeMethodInfo                     ,
#endif
    diffMerge                               ,


-- ** newBuffers #method:newBuffers#

    diffNewBuffers                          ,


-- ** newIndexToWorkdir #method:newIndexToWorkdir#

    diffNewIndexToWorkdir                   ,


-- ** newTreeToIndex #method:newTreeToIndex#

    diffNewTreeToIndex                      ,


-- ** newTreeToTree #method:newTreeToTree#

    diffNewTreeToTree                       ,


-- ** newTreeToWorkdir #method:newTreeToWorkdir#

    diffNewTreeToWorkdir                    ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    DiffPrintMethodInfo                     ,
#endif
    diffPrint                               ,




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

#if defined(ENABLE_OVERLOADING)
    DiffRepositoryPropertyInfo              ,
#endif
    constructDiffRepository                 ,
#if defined(ENABLE_OVERLOADING)
    diffRepository                          ,
#endif
    getDiffRepository                       ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Ggit.Callbacks as Ggit.Callbacks
import {-# SOURCE #-} qualified GI.Ggit.Enums as Ggit.Enums
import {-# SOURCE #-} qualified GI.Ggit.Objects.DiffFindOptions as Ggit.DiffFindOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.DiffFormatEmailOptions as Ggit.DiffFormatEmailOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.DiffOptions as Ggit.DiffOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.Index as Ggit.Index
import {-# SOURCE #-} qualified GI.Ggit.Objects.Native as Ggit.Native
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase
import {-# SOURCE #-} qualified GI.Ggit.Objects.Repository as Ggit.Repository
import {-# SOURCE #-} qualified GI.Ggit.Objects.Tree as Ggit.Tree
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffDelta as Ggit.DiffDelta

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

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

foreign import ccall "ggit_diff_get_type"
    c_ggit_diff_get_type :: IO B.Types.GType

instance B.Types.TypedObject Diff where
    glibType :: IO GType
glibType = IO GType
c_ggit_diff_get_type

instance B.Types.GObject Diff

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

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

instance O.HasParentTypes Diff
type instance O.ParentTypes Diff = '[Ggit.Native.Native, Ggit.ObjectFactoryBase.ObjectFactoryBase, GObject.Object.Object]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDiffMethod (t :: Symbol) (o :: *) :: * where
    ResolveDiffMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDiffMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDiffMethod "findSimilar" o = DiffFindSimilarMethodInfo
    ResolveDiffMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDiffMethod "foreach" o = DiffForeachMethodInfo
    ResolveDiffMethod "formatEmail" o = DiffFormatEmailMethodInfo
    ResolveDiffMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDiffMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDiffMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDiffMethod "merge" o = DiffMergeMethodInfo
    ResolveDiffMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDiffMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDiffMethod "print" o = DiffPrintMethodInfo
    ResolveDiffMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDiffMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDiffMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDiffMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDiffMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDiffMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDiffMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDiffMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDiffMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDiffMethod "getDelta" o = DiffGetDeltaMethodInfo
    ResolveDiffMethod "getNumDeltas" o = DiffGetNumDeltasMethodInfo
    ResolveDiffMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDiffMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDiffMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDiffMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDiffMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDiffMethod l o = O.MethodResolutionFailed l o

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

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data DiffRepositoryPropertyInfo
instance AttrInfo DiffRepositoryPropertyInfo where
    type AttrAllowedOps DiffRepositoryPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DiffRepositoryPropertyInfo = IsDiff
    type AttrSetTypeConstraint DiffRepositoryPropertyInfo = Ggit.Repository.IsRepository
    type AttrTransferTypeConstraint DiffRepositoryPropertyInfo = Ggit.Repository.IsRepository
    type AttrTransferType DiffRepositoryPropertyInfo = Ggit.Repository.Repository
    type AttrGetType DiffRepositoryPropertyInfo = (Maybe Ggit.Repository.Repository)
    type AttrLabel DiffRepositoryPropertyInfo = "repository"
    type AttrOrigin DiffRepositoryPropertyInfo = Diff
    attrGet = getDiffRepository
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Ggit.Repository.Repository v
    attrConstruct = constructDiffRepository
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Diff
type instance O.AttributeList Diff = DiffAttributeList
type DiffAttributeList = ('[ '("native", Ggit.Native.NativeNativePropertyInfo), '("repository", DiffRepositoryPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
diffRepository :: AttrLabelProxy "repository"
diffRepository = AttrLabelProxy

#endif

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

#endif

-- method Diff::new_buffers
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "buffer1"
--           , argType = TCArray False (-1) 1 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a buffer to diff from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer1_len"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @buffer1."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer1_as_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "treat @buffer1 as if it had this filename, or %NULL,"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer2"
--           , argType = TCArray False (-1) 4 (TBasicType TUInt8)
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a buffer to diff to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer2_len"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @buffer2."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "buffer2_as_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "treat @buffer2 as if it had this filename, or %NULL,"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "diff_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffOptions, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "buffer2_len"
--              , argType = TBasicType TInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @buffer2."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          , Arg
--              { argCName = "buffer1_len"
--              , argType = TBasicType TInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @buffer1."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Diff" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_new_buffers" ggit_diff_new_buffers :: 
    Ptr Word8 ->                            -- buffer1 : TCArray False (-1) 1 (TBasicType TUInt8)
    Int64 ->                                -- buffer1_len : TBasicType TInt64
    CString ->                              -- buffer1_as_path : TBasicType TUTF8
    Ptr Word8 ->                            -- buffer2 : TCArray False (-1) 4 (TBasicType TUInt8)
    Int64 ->                                -- buffer2_len : TBasicType TInt64
    CString ->                              -- buffer2_as_path : TBasicType TUTF8
    Ptr Ggit.DiffOptions.DiffOptions ->     -- diff_options : TInterface (Name {namespace = "Ggit", name = "DiffOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Diff)

-- | Same as 'GI.Ggit.Objects.Diff.diffBlobs' but using a buffers.
-- Creates a t'GI.Ggit.Objects.Diff.Diff' which compares /@buffer1@/ and /@buffer2@/.
-- 
-- If /@diffOptions@/ is 'P.Nothing' then the defaults specified in
-- 'GI.Ggit.Objects.DiffOptions.diffOptionsNew' are used.
diffNewBuffers ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.DiffOptions.IsDiffOptions a) =>
    Maybe (ByteString)
    -- ^ /@buffer1@/: a buffer to diff from.
    -> Maybe (T.Text)
    -- ^ /@buffer1AsPath@/: treat /@buffer1@/ as if it had this filename, or 'P.Nothing',
    -> Maybe (ByteString)
    -- ^ /@buffer2@/: a buffer to diff to.
    -> Maybe (T.Text)
    -- ^ /@buffer2AsPath@/: treat /@buffer2@/ as if it had this filename, or 'P.Nothing',
    -> Maybe (a)
    -- ^ /@diffOptions@/: a t'GI.Ggit.Objects.DiffOptions.DiffOptions', or 'P.Nothing'.
    -> m (Maybe Diff)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Objects.Diff.Diff' if
    -- there was no error, 'P.Nothing' otherwise. /(Can throw 'Data.GI.Base.GError.GError')/
diffNewBuffers :: Maybe ByteString
-> Maybe Text
-> Maybe ByteString
-> Maybe Text
-> Maybe a
-> m (Maybe Diff)
diffNewBuffers Maybe ByteString
buffer1 Maybe Text
buffer1AsPath Maybe ByteString
buffer2 Maybe Text
buffer2AsPath Maybe a
diffOptions = IO (Maybe Diff) -> m (Maybe Diff)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Diff) -> m (Maybe Diff))
-> IO (Maybe Diff) -> m (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ do
    let buffer2Len :: Int64
buffer2Len = case Maybe ByteString
buffer2 of
            Maybe ByteString
Nothing -> Int64
0
            Just ByteString
jBuffer2 -> Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jBuffer2
    let buffer1Len :: Int64
buffer1Len = case Maybe ByteString
buffer1 of
            Maybe ByteString
Nothing -> Int64
0
            Just ByteString
jBuffer1 -> Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ ByteString -> Int
B.length ByteString
jBuffer1
    Ptr Word8
maybeBuffer1 <- case Maybe ByteString
buffer1 of
        Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
        Just ByteString
jBuffer1 -> do
            Ptr Word8
jBuffer1' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jBuffer1
            Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jBuffer1'
    Ptr CChar
maybeBuffer1AsPath <- case Maybe Text
buffer1AsPath of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jBuffer1AsPath -> do
            Ptr CChar
jBuffer1AsPath' <- Text -> IO (Ptr CChar)
textToCString Text
jBuffer1AsPath
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jBuffer1AsPath'
    Ptr Word8
maybeBuffer2 <- case Maybe ByteString
buffer2 of
        Maybe ByteString
Nothing -> Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
forall a. Ptr a
nullPtr
        Just ByteString
jBuffer2 -> do
            Ptr Word8
jBuffer2' <- ByteString -> IO (Ptr Word8)
packByteString ByteString
jBuffer2
            Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
jBuffer2'
    Ptr CChar
maybeBuffer2AsPath <- case Maybe Text
buffer2AsPath of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jBuffer2AsPath -> do
            Ptr CChar
jBuffer2AsPath' <- Text -> IO (Ptr CChar)
textToCString Text
jBuffer2AsPath
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jBuffer2AsPath'
    Ptr DiffOptions
maybeDiffOptions <- case Maybe a
diffOptions of
        Maybe a
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
        Just a
jDiffOptions -> do
            Ptr DiffOptions
jDiffOptions' <- a -> IO (Ptr DiffOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jDiffOptions
            Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
    IO (Maybe Diff) -> IO () -> IO (Maybe Diff)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Diff
result <- (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff))
-> (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a b. (a -> b) -> a -> b
$ Ptr Word8
-> Int64
-> Ptr CChar
-> Ptr Word8
-> Int64
-> Ptr CChar
-> Ptr DiffOptions
-> Ptr (Ptr GError)
-> IO (Ptr Diff)
ggit_diff_new_buffers Ptr Word8
maybeBuffer1 Int64
buffer1Len Ptr CChar
maybeBuffer1AsPath Ptr Word8
maybeBuffer2 Int64
buffer2Len Ptr CChar
maybeBuffer2AsPath Ptr DiffOptions
maybeDiffOptions
        Maybe Diff
maybeResult <- Ptr Diff -> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Diff
result ((Ptr Diff -> IO Diff) -> IO (Maybe Diff))
-> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ \Ptr Diff
result' -> do
            Diff
result'' <- ((ManagedPtr Diff -> Diff) -> Ptr Diff -> IO Diff
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Diff -> Diff
Diff) Ptr Diff
result'
            Diff -> IO Diff
forall (m :: * -> *) a. Monad m => a -> m a
return Diff
result''
        Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
diffOptions a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer1
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeBuffer1AsPath
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer2
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeBuffer2AsPath
        Maybe Diff -> IO (Maybe Diff)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Diff
maybeResult
     ) (do
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer1
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeBuffer1AsPath
        Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word8
maybeBuffer2
        Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeBuffer2AsPath
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Diff::new_index_to_workdir
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitRepository." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "diff_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffOptions, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Diff" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_new_index_to_workdir" ggit_diff_new_index_to_workdir :: 
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr Ggit.Index.Index ->                 -- index : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Ggit.DiffOptions.DiffOptions ->     -- diff_options : TInterface (Name {namespace = "Ggit", name = "DiffOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Diff)

-- | Creates a t'GI.Ggit.Objects.Diff.Diff' which compares the working directory and the index.
-- 
-- If /@index@/ is 'P.Nothing' then /@repository@/ index is used.
-- If /@diffOptions@/ is 'P.Nothing' then the defaults specified in
-- 'GI.Ggit.Objects.DiffOptions.diffOptionsNew' are used.
diffNewIndexToWorkdir ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Index.IsIndex b, Ggit.DiffOptions.IsDiffOptions c) =>
    a
    -- ^ /@repository@/: a t'GI.Ggit.Objects.Repository.Repository'.
    -> Maybe (b)
    -- ^ /@index@/: a t'GI.Ggit.Objects.Index.Index', or 'P.Nothing'.
    -> Maybe (c)
    -- ^ /@diffOptions@/: a t'GI.Ggit.Objects.DiffOptions.DiffOptions', or 'P.Nothing'.
    -> m (Maybe Diff)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Objects.Diff.Diff' if
    -- there was no error, 'P.Nothing' otherwise. /(Can throw 'Data.GI.Base.GError.GError')/
diffNewIndexToWorkdir :: a -> Maybe b -> Maybe c -> m (Maybe Diff)
diffNewIndexToWorkdir a
repository Maybe b
index Maybe c
diffOptions = IO (Maybe Diff) -> m (Maybe Diff)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Diff) -> m (Maybe Diff))
-> IO (Maybe Diff) -> m (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repository
repository' <- a -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repository
    Ptr Index
maybeIndex <- case Maybe b
index of
        Maybe b
Nothing -> Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
forall a. Ptr a
nullPtr
        Just b
jIndex -> do
            Ptr Index
jIndex' <- b -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIndex
            Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
jIndex'
    Ptr DiffOptions
maybeDiffOptions <- case Maybe c
diffOptions of
        Maybe c
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
        Just c
jDiffOptions -> do
            Ptr DiffOptions
jDiffOptions' <- c -> IO (Ptr DiffOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jDiffOptions
            Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
    IO (Maybe Diff) -> IO () -> IO (Maybe Diff)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Diff
result <- (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff))
-> (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a b. (a -> b) -> a -> b
$ Ptr Repository
-> Ptr Index
-> Ptr DiffOptions
-> Ptr (Ptr GError)
-> IO (Ptr Diff)
ggit_diff_new_index_to_workdir Ptr Repository
repository' Ptr Index
maybeIndex Ptr DiffOptions
maybeDiffOptions
        Maybe Diff
maybeResult <- Ptr Diff -> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Diff
result ((Ptr Diff -> IO Diff) -> IO (Maybe Diff))
-> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ \Ptr Diff
result' -> do
            Diff
result'' <- ((ManagedPtr Diff -> Diff) -> Ptr Diff -> IO Diff
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Diff -> Diff
Diff) Ptr Diff
result'
            Diff -> IO Diff
forall (m :: * -> *) a. Monad m => a -> m a
return Diff
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repository
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
index b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
diffOptions c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Diff -> IO (Maybe Diff)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Diff
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Diff::new_tree_to_index
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitRepository." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree to diff from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Index" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitIndex, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "diff_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffOptions, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Diff" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_new_tree_to_index" ggit_diff_new_tree_to_index :: 
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr Ggit.Tree.Tree ->                   -- old_tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    Ptr Ggit.Index.Index ->                 -- index : TInterface (Name {namespace = "Ggit", name = "Index"})
    Ptr Ggit.DiffOptions.DiffOptions ->     -- diff_options : TInterface (Name {namespace = "Ggit", name = "DiffOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Diff)

-- | Creates a t'GI.Ggit.Objects.Diff.Diff' which compares /@oldTree@/ and the index.
-- 
-- If /@index@/ is 'P.Nothing' then /@repository@/ index is used.
-- If /@diffOptions@/ is 'P.Nothing' then the defaults specified in
-- 'GI.Ggit.Objects.DiffOptions.diffOptionsNew' are used.
diffNewTreeToIndex ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.Index.IsIndex c, Ggit.DiffOptions.IsDiffOptions d) =>
    a
    -- ^ /@repository@/: a t'GI.Ggit.Objects.Repository.Repository'.
    -> Maybe (b)
    -- ^ /@oldTree@/: a t'GI.Ggit.Objects.Tree.Tree' to diff from.
    -> Maybe (c)
    -- ^ /@index@/: a t'GI.Ggit.Objects.Index.Index', or 'P.Nothing'.
    -> Maybe (d)
    -- ^ /@diffOptions@/: a t'GI.Ggit.Objects.DiffOptions.DiffOptions', or 'P.Nothing'.
    -> m (Maybe Diff)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Objects.Diff.Diff' if
    -- there was no error, 'P.Nothing' otherwise. /(Can throw 'Data.GI.Base.GError.GError')/
diffNewTreeToIndex :: a -> Maybe b -> Maybe c -> Maybe d -> m (Maybe Diff)
diffNewTreeToIndex a
repository Maybe b
oldTree Maybe c
index Maybe d
diffOptions = IO (Maybe Diff) -> m (Maybe Diff)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Diff) -> m (Maybe Diff))
-> IO (Maybe Diff) -> m (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repository
repository' <- a -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repository
    Ptr Tree
maybeOldTree <- case Maybe b
oldTree of
        Maybe b
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
        Just b
jOldTree -> do
            Ptr Tree
jOldTree' <- b -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jOldTree
            Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
jOldTree'
    Ptr Index
maybeIndex <- case Maybe c
index of
        Maybe c
Nothing -> Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
forall a. Ptr a
nullPtr
        Just c
jIndex -> do
            Ptr Index
jIndex' <- c -> IO (Ptr Index)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jIndex
            Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
jIndex'
    Ptr DiffOptions
maybeDiffOptions <- case Maybe d
diffOptions of
        Maybe d
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
        Just d
jDiffOptions -> do
            Ptr DiffOptions
jDiffOptions' <- d -> IO (Ptr DiffOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jDiffOptions
            Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
    IO (Maybe Diff) -> IO () -> IO (Maybe Diff)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Diff
result <- (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff))
-> (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a b. (a -> b) -> a -> b
$ Ptr Repository
-> Ptr Tree
-> Ptr Index
-> Ptr DiffOptions
-> Ptr (Ptr GError)
-> IO (Ptr Diff)
ggit_diff_new_tree_to_index Ptr Repository
repository' Ptr Tree
maybeOldTree Ptr Index
maybeIndex Ptr DiffOptions
maybeDiffOptions
        Maybe Diff
maybeResult <- Ptr Diff -> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Diff
result ((Ptr Diff -> IO Diff) -> IO (Maybe Diff))
-> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ \Ptr Diff
result' -> do
            Diff
result'' <- ((ManagedPtr Diff -> Diff) -> Ptr Diff -> IO Diff
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Diff -> Diff
Diff) Ptr Diff
result'
            Diff -> IO Diff
forall (m :: * -> *) a. Monad m => a -> m a
return Diff
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repository
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
oldTree b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
index c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
diffOptions d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Diff -> IO (Maybe Diff)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Diff
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Diff::new_tree_to_tree
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitRepository." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree to diff from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "new_tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree to diff to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "diff_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffOptions, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Diff" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_new_tree_to_tree" ggit_diff_new_tree_to_tree :: 
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr Ggit.Tree.Tree ->                   -- old_tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    Ptr Ggit.Tree.Tree ->                   -- new_tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    Ptr Ggit.DiffOptions.DiffOptions ->     -- diff_options : TInterface (Name {namespace = "Ggit", name = "DiffOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Diff)

-- | Creates a t'GI.Ggit.Objects.Diff.Diff' which compares /@oldTree@/ and /@newTree@/.
-- 
-- If /@diffOptions@/ is 'P.Nothing' then the defaults specified in
-- 'GI.Ggit.Objects.DiffOptions.diffOptionsNew' are used.
diffNewTreeToTree ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.Tree.IsTree c, Ggit.DiffOptions.IsDiffOptions d) =>
    a
    -- ^ /@repository@/: a t'GI.Ggit.Objects.Repository.Repository'.
    -> Maybe (b)
    -- ^ /@oldTree@/: a t'GI.Ggit.Objects.Tree.Tree' to diff from.
    -> Maybe (c)
    -- ^ /@newTree@/: a t'GI.Ggit.Objects.Tree.Tree' to diff to.
    -> Maybe (d)
    -- ^ /@diffOptions@/: a t'GI.Ggit.Objects.DiffOptions.DiffOptions', or 'P.Nothing'.
    -> m (Maybe Diff)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Objects.Diff.Diff' if
    -- there was no error, 'P.Nothing' otherwise. /(Can throw 'Data.GI.Base.GError.GError')/
diffNewTreeToTree :: a -> Maybe b -> Maybe c -> Maybe d -> m (Maybe Diff)
diffNewTreeToTree a
repository Maybe b
oldTree Maybe c
newTree Maybe d
diffOptions = IO (Maybe Diff) -> m (Maybe Diff)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Diff) -> m (Maybe Diff))
-> IO (Maybe Diff) -> m (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repository
repository' <- a -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repository
    Ptr Tree
maybeOldTree <- case Maybe b
oldTree of
        Maybe b
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
        Just b
jOldTree -> do
            Ptr Tree
jOldTree' <- b -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jOldTree
            Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
jOldTree'
    Ptr Tree
maybeNewTree <- case Maybe c
newTree of
        Maybe c
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
        Just c
jNewTree -> do
            Ptr Tree
jNewTree' <- c -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jNewTree
            Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
jNewTree'
    Ptr DiffOptions
maybeDiffOptions <- case Maybe d
diffOptions of
        Maybe d
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
        Just d
jDiffOptions -> do
            Ptr DiffOptions
jDiffOptions' <- d -> IO (Ptr DiffOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jDiffOptions
            Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
    IO (Maybe Diff) -> IO () -> IO (Maybe Diff)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Diff
result <- (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff))
-> (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a b. (a -> b) -> a -> b
$ Ptr Repository
-> Ptr Tree
-> Ptr Tree
-> Ptr DiffOptions
-> Ptr (Ptr GError)
-> IO (Ptr Diff)
ggit_diff_new_tree_to_tree Ptr Repository
repository' Ptr Tree
maybeOldTree Ptr Tree
maybeNewTree Ptr DiffOptions
maybeDiffOptions
        Maybe Diff
maybeResult <- Ptr Diff -> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Diff
result ((Ptr Diff -> IO Diff) -> IO (Maybe Diff))
-> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ \Ptr Diff
result' -> do
            Diff
result'' <- ((ManagedPtr Diff -> Diff) -> Ptr Diff -> IO Diff
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Diff -> Diff
Diff) Ptr Diff
result'
            Diff -> IO Diff
forall (m :: * -> *) a. Monad m => a -> m a
return Diff
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repository
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
oldTree b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
newTree c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
diffOptions d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Diff -> IO (Maybe Diff)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Diff
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Diff::new_tree_to_workdir
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "repository"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "Repository" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitRepository." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_tree"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Tree" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitTree to diff from."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "diff_options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffOptions, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "Diff" })
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_new_tree_to_workdir" ggit_diff_new_tree_to_workdir :: 
    Ptr Ggit.Repository.Repository ->       -- repository : TInterface (Name {namespace = "Ggit", name = "Repository"})
    Ptr Ggit.Tree.Tree ->                   -- old_tree : TInterface (Name {namespace = "Ggit", name = "Tree"})
    Ptr Ggit.DiffOptions.DiffOptions ->     -- diff_options : TInterface (Name {namespace = "Ggit", name = "DiffOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Diff)

-- | Creates a t'GI.Ggit.Objects.Diff.Diff' which compares the working directory and /@oldTree@/.
-- 
-- If /@diffOptions@/ is 'P.Nothing' then the defaults specified in
-- 'GI.Ggit.Objects.DiffOptions.diffOptionsNew' are used.
diffNewTreeToWorkdir ::
    (B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.DiffOptions.IsDiffOptions c) =>
    a
    -- ^ /@repository@/: a t'GI.Ggit.Objects.Repository.Repository'.
    -> Maybe (b)
    -- ^ /@oldTree@/: a t'GI.Ggit.Objects.Tree.Tree' to diff from.
    -> Maybe (c)
    -- ^ /@diffOptions@/: a t'GI.Ggit.Objects.DiffOptions.DiffOptions', or 'P.Nothing'.
    -> m (Maybe Diff)
    -- ^ __Returns:__ a newly allocated t'GI.Ggit.Objects.Diff.Diff' if
    -- there was no error, 'P.Nothing' otherwise. /(Can throw 'Data.GI.Base.GError.GError')/
diffNewTreeToWorkdir :: a -> Maybe b -> Maybe c -> m (Maybe Diff)
diffNewTreeToWorkdir a
repository Maybe b
oldTree Maybe c
diffOptions = IO (Maybe Diff) -> m (Maybe Diff)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Diff) -> m (Maybe Diff))
-> IO (Maybe Diff) -> m (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Repository
repository' <- a -> IO (Ptr Repository)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
repository
    Ptr Tree
maybeOldTree <- case Maybe b
oldTree of
        Maybe b
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
        Just b
jOldTree -> do
            Ptr Tree
jOldTree' <- b -> IO (Ptr Tree)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jOldTree
            Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
jOldTree'
    Ptr DiffOptions
maybeDiffOptions <- case Maybe c
diffOptions of
        Maybe c
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
        Just c
jDiffOptions -> do
            Ptr DiffOptions
jDiffOptions' <- c -> IO (Ptr DiffOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jDiffOptions
            Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
    IO (Maybe Diff) -> IO () -> IO (Maybe Diff)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Diff
result <- (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff))
-> (Ptr (Ptr GError) -> IO (Ptr Diff)) -> IO (Ptr Diff)
forall a b. (a -> b) -> a -> b
$ Ptr Repository
-> Ptr Tree -> Ptr DiffOptions -> Ptr (Ptr GError) -> IO (Ptr Diff)
ggit_diff_new_tree_to_workdir Ptr Repository
repository' Ptr Tree
maybeOldTree Ptr DiffOptions
maybeDiffOptions
        Maybe Diff
maybeResult <- Ptr Diff -> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Diff
result ((Ptr Diff -> IO Diff) -> IO (Maybe Diff))
-> (Ptr Diff -> IO Diff) -> IO (Maybe Diff)
forall a b. (a -> b) -> a -> b
$ \Ptr Diff
result' -> do
            Diff
result'' <- ((ManagedPtr Diff -> Diff) -> Ptr Diff -> IO Diff
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Diff -> Diff
Diff) Ptr Diff
result'
            Diff -> IO Diff
forall (m :: * -> *) a. Monad m => a -> m a
return Diff
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
repository
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
oldTree b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
diffOptions c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Diff -> IO (Maybe Diff)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Diff
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Diff::find_similar
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "diff"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiff." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "options"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffFindOptions" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffFindOptions or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_find_similar" ggit_diff_find_similar :: 
    Ptr Diff ->                             -- diff : TInterface (Name {namespace = "Ggit", name = "Diff"})
    Ptr Ggit.DiffFindOptions.DiffFindOptions -> -- options : TInterface (Name {namespace = "Ggit", name = "DiffFindOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Transform /@diff@/ marking file renames, copies, etc.. If /@options@/ is set to
-- 'P.Nothing', then the default options will be used.
diffFindSimilar ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a, Ggit.DiffFindOptions.IsDiffFindOptions b) =>
    a
    -- ^ /@diff@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> Maybe (b)
    -- ^ /@options@/: a t'GI.Ggit.Objects.DiffFindOptions.DiffFindOptions' or 'P.Nothing'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
diffFindSimilar :: a -> Maybe b -> m ()
diffFindSimilar a
diff Maybe b
options = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
diff' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
diff
    Ptr DiffFindOptions
maybeOptions <- case Maybe b
options of
        Maybe b
Nothing -> Ptr DiffFindOptions -> IO (Ptr DiffFindOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffFindOptions
forall a. Ptr a
nullPtr
        Just b
jOptions -> do
            Ptr DiffFindOptions
jOptions' <- b -> IO (Ptr DiffFindOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jOptions
            Ptr DiffFindOptions -> IO (Ptr DiffFindOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffFindOptions
jOptions'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Diff -> Ptr DiffFindOptions -> Ptr (Ptr GError) -> IO CInt
ggit_diff_find_similar Ptr Diff
diff' Ptr DiffFindOptions
maybeOptions
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
options b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DiffFindSimilarMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsDiff a, Ggit.DiffFindOptions.IsDiffFindOptions b) => O.MethodInfo DiffFindSimilarMethodInfo a signature where
    overloadedMethod = diffFindSimilar

#endif

-- XXX Could not generate method Diff::foreach
{-  Not implemented: Closure for multiple callbacks unsupportedArg
      { argCName = "binary_cb"
      , argType =
          TInterface
            Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
      , direction = DirectionIn
      , mayBeNull = True
      , argDoc =
          Documentation
            { rawDocText = Just "\n a #GgitDiffBinaryCallback."
            , sinceVersion = Nothing
            }
      , argScope = ScopeTypeCall
      , argClosure = 5
      , argDestroy = -1
      , argCallerAllocates = False
      , transfer = TransferNothing
      }
    Callable
      { returnType = Nothing
      , returnMayBeNull = False
      , returnTransfer = TransferNothing
      , returnDocumentation =
          Documentation { rawDocText = Nothing , sinceVersion = Nothing }
      , args =
          [ Arg
              { argCName = "diff"
              , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
              , direction = DirectionIn
              , mayBeNull = False
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitDiff." , sinceVersion = Nothing }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "file_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffFileCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffFileCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 5
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "binary_cb"
              , argType =
                  TInterface
                    Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffBinaryCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 5
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "hunk_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffHunkCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffHunkCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 5
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "line_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffLineCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffLineCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 5
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "user_data"
              , argType = TBasicType TPtr
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "callback user data."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          ]
      , skipReturn = False
      , callableThrows = True
      , callableDeprecated = Nothing
      , callableDocumentation =
          Documentation
            { rawDocText =
                Just
                  "Iterates over the diff calling @file_cb, @binary_cb, @hunk_cb and @line_cb."
            , sinceVersion = Nothing
            }
      , callableResolvable = Just True
      }
-}
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data DiffForeachMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "foreach" Diff) => O.MethodInfo DiffForeachMethodInfo o p where
    overloadedMethod = undefined
#endif

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

foreign import ccall "ggit_diff_format_email" ggit_diff_format_email :: 
    Ptr Diff ->                             -- diff : TInterface (Name {namespace = "Ggit", name = "Diff"})
    Ptr Ggit.DiffFormatEmailOptions.DiffFormatEmailOptions -> -- options : TInterface (Name {namespace = "Ggit", name = "DiffFormatEmailOptions"})
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Create an e-mail ready patch from a diff.
diffFormatEmail ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a, Ggit.DiffFormatEmailOptions.IsDiffFormatEmailOptions b) =>
    a
    -- ^ /@diff@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> b
    -- ^ /@options@/: a t'GI.Ggit.Objects.DiffFormatEmailOptions.DiffFormatEmailOptions'.
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the patch or 'P.Nothing' if an error occurred. /(Can throw 'Data.GI.Base.GError.GError')/
diffFormatEmail :: a -> b -> m (Maybe Text)
diffFormatEmail a
diff b
options = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
diff' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
diff
    Ptr DiffFormatEmailOptions
options' <- b -> IO (Ptr DiffFormatEmailOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
options
    IO (Maybe Text) -> IO () -> IO (Maybe Text)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CChar
result <- (Ptr (Ptr GError) -> IO (Ptr CChar)) -> IO (Ptr CChar)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CChar)) -> IO (Ptr CChar))
-> (Ptr (Ptr GError) -> IO (Ptr CChar)) -> IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ Ptr Diff
-> Ptr DiffFormatEmailOptions -> Ptr (Ptr GError) -> IO (Ptr CChar)
ggit_diff_format_email Ptr Diff
diff' Ptr DiffFormatEmailOptions
options'
        Maybe Text
maybeResult <- Ptr CChar -> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr CChar
result ((Ptr CChar -> IO Text) -> IO (Maybe Text))
-> (Ptr CChar -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr CChar
result' -> do
            Text
result'' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result'
            Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
result'
            Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
options
        Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DiffFormatEmailMethodInfo
instance (signature ~ (b -> m (Maybe T.Text)), MonadIO m, IsDiff a, Ggit.DiffFormatEmailOptions.IsDiffFormatEmailOptions b) => O.MethodInfo DiffFormatEmailMethodInfo a signature where
    overloadedMethod = diffFormatEmail

#endif

-- method Diff::get_delta
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "diff"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiff." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Ggit" , name = "DiffDelta" })
-- throws : False
-- Skip return : False

foreign import ccall "ggit_diff_get_delta" ggit_diff_get_delta :: 
    Ptr Diff ->                             -- diff : TInterface (Name {namespace = "Ggit", name = "Diff"})
    Word64 ->                               -- index : TBasicType TUInt64
    IO (Ptr Ggit.DiffDelta.DiffDelta)

-- | Get the delta at the specified index.
diffGetDelta ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
    a
    -- ^ /@diff@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> Word64
    -- ^ /@index@/: the index.
    -> m (Maybe Ggit.DiffDelta.DiffDelta)
    -- ^ __Returns:__ a t'GI.Ggit.Structs.DiffDelta.DiffDelta' or 'P.Nothing'.
diffGetDelta :: a -> Word64 -> m (Maybe DiffDelta)
diffGetDelta a
diff Word64
index = IO (Maybe DiffDelta) -> m (Maybe DiffDelta)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DiffDelta) -> m (Maybe DiffDelta))
-> IO (Maybe DiffDelta) -> m (Maybe DiffDelta)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
diff' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
diff
    Ptr DiffDelta
result <- Ptr Diff -> Word64 -> IO (Ptr DiffDelta)
ggit_diff_get_delta Ptr Diff
diff' Word64
index
    Maybe DiffDelta
maybeResult <- Ptr DiffDelta
-> (Ptr DiffDelta -> IO DiffDelta) -> IO (Maybe DiffDelta)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DiffDelta
result ((Ptr DiffDelta -> IO DiffDelta) -> IO (Maybe DiffDelta))
-> (Ptr DiffDelta -> IO DiffDelta) -> IO (Maybe DiffDelta)
forall a b. (a -> b) -> a -> b
$ \Ptr DiffDelta
result' -> do
        DiffDelta
result'' <- ((ManagedPtr DiffDelta -> DiffDelta)
-> Ptr DiffDelta -> IO DiffDelta
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DiffDelta -> DiffDelta
Ggit.DiffDelta.DiffDelta) Ptr DiffDelta
result'
        DiffDelta -> IO DiffDelta
forall (m :: * -> *) a. Monad m => a -> m a
return DiffDelta
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
    Maybe DiffDelta -> IO (Maybe DiffDelta)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DiffDelta
maybeResult

#if defined(ENABLE_OVERLOADING)
data DiffGetDeltaMethodInfo
instance (signature ~ (Word64 -> m (Maybe Ggit.DiffDelta.DiffDelta)), MonadIO m, IsDiff a) => O.MethodInfo DiffGetDeltaMethodInfo a signature where
    overloadedMethod = diffGetDelta

#endif

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

foreign import ccall "ggit_diff_get_num_deltas" ggit_diff_get_num_deltas :: 
    Ptr Diff ->                             -- diff : TInterface (Name {namespace = "Ggit", name = "Diff"})
    IO Word64

-- | Get the number of deltas in the diff.
diffGetNumDeltas ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
    a
    -- ^ /@diff@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> m Word64
    -- ^ __Returns:__ the number of deltas.
diffGetNumDeltas :: a -> m Word64
diffGetNumDeltas a
diff = IO Word64 -> m Word64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
diff' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
diff
    Word64
result <- Ptr Diff -> IO Word64
ggit_diff_get_num_deltas Ptr Diff
diff'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data DiffGetNumDeltasMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsDiff a) => O.MethodInfo DiffGetNumDeltasMethodInfo a signature where
    overloadedMethod = diffGetNumDeltas

#endif

-- method Diff::merge
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "onto"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GgitDiff to merge into."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "from"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GgitDiff to merge."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_merge" ggit_diff_merge :: 
    Ptr Diff ->                             -- onto : TInterface (Name {namespace = "Ggit", name = "Diff"})
    Ptr Diff ->                             -- from : TInterface (Name {namespace = "Ggit", name = "Diff"})
    Ptr (Ptr GError) ->                     -- error
    IO ()

-- | Merges /@from@/ into /@onto@/ unless /@error@/ is set.
diffMerge ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a, IsDiff b) =>
    a
    -- ^ /@onto@/: the t'GI.Ggit.Objects.Diff.Diff' to merge into.
    -> b
    -- ^ /@from@/: the t'GI.Ggit.Objects.Diff.Diff' to merge.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
diffMerge :: a -> b -> m ()
diffMerge a
onto b
from = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
onto' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
onto
    Ptr Diff
from' <- b -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
from
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Diff -> Ptr Diff -> Ptr (Ptr GError) -> IO ()
ggit_diff_merge Ptr Diff
onto' Ptr Diff
from'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
onto
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
from
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DiffMergeMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDiff a, IsDiff b) => O.MethodInfo DiffMergeMethodInfo a signature where
    overloadedMethod = diffMerge

#endif

-- method Diff::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "diff"
--           , argType = TInterface Name { namespace = "Ggit" , name = "Diff" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiff." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffFormatType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffFormatType."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "print_cb"
--           , argType =
--               TInterface Name { namespace = "Ggit" , name = "DiffLineCallback" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GgitDiffLineCallback."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "callback user data."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : True
-- Skip return : False

foreign import ccall "ggit_diff_print" ggit_diff_print :: 
    Ptr Diff ->                             -- diff : TInterface (Name {namespace = "Ggit", name = "Diff"})
    CUInt ->                                -- type : TInterface (Name {namespace = "Ggit", name = "DiffFormatType"})
    FunPtr Ggit.Callbacks.C_DiffLineCallback -> -- print_cb : TInterface (Name {namespace = "Ggit", name = "DiffLineCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    Ptr (Ptr GError) ->                     -- error
    IO ()

-- | Iterates over /@diff@/ generating text output like \"git diff\".
diffPrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
    a
    -- ^ /@diff@/: a t'GI.Ggit.Objects.Diff.Diff'.
    -> Ggit.Enums.DiffFormatType
    -- ^ /@type@/: a t'GI.Ggit.Enums.DiffFormatType'.
    -> Ggit.Callbacks.DiffLineCallback
    -- ^ /@printCb@/: a t'GI.Ggit.Callbacks.DiffLineCallback'.
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
diffPrint :: a -> DiffFormatType -> DiffLineCallback -> m ()
diffPrint a
diff DiffFormatType
type_ DiffLineCallback
printCb = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Diff
diff' <- a -> IO (Ptr Diff)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
diff
    let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (DiffFormatType -> Int) -> DiffFormatType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DiffFormatType -> Int
forall a. Enum a => a -> Int
fromEnum) DiffFormatType
type_
    FunPtr C_DiffLineCallback
printCb' <- C_DiffLineCallback -> IO (FunPtr C_DiffLineCallback)
Ggit.Callbacks.mk_DiffLineCallback (Maybe (Ptr (FunPtr C_DiffLineCallback))
-> DiffLineCallback_WithClosures -> C_DiffLineCallback
Ggit.Callbacks.wrap_DiffLineCallback Maybe (Ptr (FunPtr C_DiffLineCallback))
forall a. Maybe a
Nothing (DiffLineCallback -> DiffLineCallback_WithClosures
Ggit.Callbacks.drop_closures_DiffLineCallback DiffLineCallback
printCb))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Diff
-> CUInt
-> FunPtr C_DiffLineCallback
-> Ptr ()
-> Ptr (Ptr GError)
-> IO ()
ggit_diff_print Ptr Diff
diff' CUInt
type_' FunPtr C_DiffLineCallback
printCb' Ptr ()
forall a. Ptr a
userData
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_DiffLineCallback -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DiffLineCallback
printCb'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_DiffLineCallback -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_DiffLineCallback
printCb'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data DiffPrintMethodInfo
instance (signature ~ (Ggit.Enums.DiffFormatType -> Ggit.Callbacks.DiffLineCallback -> m ()), MonadIO m, IsDiff a) => O.MethodInfo DiffPrintMethodInfo a signature where
    overloadedMethod = diffPrint

#endif

-- XXX Could not generate method Diff::blob_to_buffer
{-  Not implemented: Closure for multiple callbacks unsupportedArg
      { argCName = "binary_cb"
      , argType =
          TInterface
            Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
      , direction = DirectionIn
      , mayBeNull = True
      , argDoc =
          Documentation
            { rawDocText = Just "\n a #GgitDiffBinaryCallback."
            , sinceVersion = Nothing
            }
      , argScope = ScopeTypeCall
      , argClosure = 10
      , argDestroy = -1
      , argCallerAllocates = False
      , transfer = TransferNothing
      }
    Callable
      { returnType = Nothing
      , returnMayBeNull = False
      , returnTransfer = TransferNothing
      , returnDocumentation =
          Documentation { rawDocText = Nothing , sinceVersion = Nothing }
      , args =
          [ Arg
              { argCName = "old_blob"
              , argType = TInterface Name { namespace = "Ggit" , name = "Blob" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitBlob to diff from."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "old_as_path"
              , argType = TBasicType TUTF8
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText =
                        Just "treat @old_blob as if it had this filename, or %NULL,"
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "buffer"
              , argType = TCArray False (-1) 3 (TBasicType TUInt8)
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a buffer to diff to."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "buffer_len"
              , argType = TBasicType TInt64
              , direction = DirectionIn
              , mayBeNull = False
              , argDoc =
                  Documentation
                    { rawDocText = Just "length of @buffer." , sinceVersion = Nothing }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "buffer_as_path"
              , argType = TBasicType TUTF8
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText =
                        Just "treat @buffer as if it had this filename, or %NULL,"
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "diff_options"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitDiffOptions, or %NULL."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "file_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffFileCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffFileCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 10
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "binary_cb"
              , argType =
                  TInterface
                    Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffBinaryCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 10
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "hunk_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffHunkCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffHunkCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 10
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "line_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffLineCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffLineCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 10
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "user_data"
              , argType = TBasicType TPtr
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "callback user data."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          ]
      , skipReturn = False
      , callableThrows = True
      , callableDeprecated = Nothing
      , callableDocumentation =
          Documentation
            { rawDocText = Just "Same as ggit_diff_blobs() but using a buffer."
            , sinceVersion = Nothing
            }
      , callableResolvable = Just True
      }
-}
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data DiffBlobToBufferMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "blobToBuffer" Diff) => O.MethodInfo DiffBlobToBufferMethodInfo o p where
    overloadedMethod = undefined
#endif

-- XXX Could not generate method Diff::blobs
{-  Not implemented: Closure for multiple callbacks unsupportedArg
      { argCName = "binary_cb"
      , argType =
          TInterface
            Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
      , direction = DirectionIn
      , mayBeNull = True
      , argDoc =
          Documentation
            { rawDocText = Just "\n a #GgitDiffBinaryCallback."
            , sinceVersion = Nothing
            }
      , argScope = ScopeTypeCall
      , argClosure = 9
      , argDestroy = -1
      , argCallerAllocates = False
      , transfer = TransferNothing
      }
    Callable
      { returnType = Nothing
      , returnMayBeNull = False
      , returnTransfer = TransferNothing
      , returnDocumentation =
          Documentation { rawDocText = Nothing , sinceVersion = Nothing }
      , args =
          [ Arg
              { argCName = "old_blob"
              , argType = TInterface Name { namespace = "Ggit" , name = "Blob" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitBlob to diff from."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "old_as_path"
              , argType = TBasicType TUTF8
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText =
                        Just "treat @old_blob as if it had this filename, or %NULL,"
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "new_blob"
              , argType = TInterface Name { namespace = "Ggit" , name = "Blob" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitBlob to diff to."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "new_as_path"
              , argType = TBasicType TUTF8
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText =
                        Just "treat @new_blob as if it had this filename, or %NULL,"
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "diff_options"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffOptions" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "a #GgitDiffOptions, or %NULL."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "file_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffFileCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffFileCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 9
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "binary_cb"
              , argType =
                  TInterface
                    Name { namespace = "Ggit" , name = "DiffBinaryCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffBinaryCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 9
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "hunk_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffHunkCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffHunkCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 9
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "line_cb"
              , argType =
                  TInterface Name { namespace = "Ggit" , name = "DiffLineCallback" }
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "\n a #GgitDiffLineCallback."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeCall
              , argClosure = 9
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          , Arg
              { argCName = "user_data"
              , argType = TBasicType TPtr
              , direction = DirectionIn
              , mayBeNull = True
              , argDoc =
                  Documentation
                    { rawDocText = Just "callback user data."
                    , sinceVersion = Nothing
                    }
              , argScope = ScopeTypeInvalid
              , argClosure = -1
              , argDestroy = -1
              , argCallerAllocates = False
              , transfer = TransferNothing
              }
          ]
      , skipReturn = False
      , callableThrows = True
      , callableDeprecated = Nothing
      , callableDocumentation =
          Documentation
            { rawDocText =
                Just
                  "Iterates over the diff calling @file_cb, @binary_cb, @hunk_cb and @line_cb.\n\nThe #GgitDiffFile mode always be 0, path will be %NULL and when a blob is\n%NULL the oid will be 0.\n\nIf @diff_options is %NULL then the defaults specified in\nggit_diff_options_new() are used."
            , sinceVersion = Nothing
            }
      , callableResolvable = Just True
      }
-}
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data DiffBlobsMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "blobs" Diff) => O.MethodInfo DiffBlobsMethodInfo o p where
    overloadedMethod = undefined
#endif