{-# LANGUAGE TypeApplications #-}
#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
Diff(..) ,
IsDiff ,
toDiff ,
noDiff ,
#if defined(ENABLE_OVERLOADING)
ResolveDiffMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DiffFindSimilarMethodInfo ,
#endif
diffFindSimilar ,
#if defined(ENABLE_OVERLOADING)
DiffFormatEmailMethodInfo ,
#endif
diffFormatEmail ,
#if defined(ENABLE_OVERLOADING)
DiffGetDeltaMethodInfo ,
#endif
diffGetDelta ,
#if defined(ENABLE_OVERLOADING)
DiffGetNumDeltasMethodInfo ,
#endif
diffGetNumDeltas ,
#if defined(ENABLE_OVERLOADING)
DiffMergeMethodInfo ,
#endif
diffMerge ,
diffNewIndexToWorkdir ,
diffNewTreeToIndex ,
diffNewTreeToTree ,
diffNewTreeToWorkdir ,
#if defined(ENABLE_OVERLOADING)
DiffPrintMethodInfo ,
#endif
diffPrint ,
#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.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 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
newtype Diff = Diff (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)
foreign import ccall "ggit_diff_get_type"
c_ggit_diff_get_type :: IO GType
instance GObject Diff where
gobjectType :: IO GType
gobjectType = IO GType
c_ggit_diff_get_type
instance B.GValue.IsGValue Diff where
toGValue :: Diff -> IO GValue
toGValue o :: 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 gv :: 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
class (GObject o, O.IsDescendantOf Diff o) => IsDiff o
instance (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]
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Diff -> Diff
Diff
noDiff :: Maybe Diff
noDiff :: Maybe Diff
noDiff = Maybe Diff
forall a. Maybe a
Nothing
#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
getDiffRepository :: (MonadIO m, IsDiff o) => o -> m (Maybe Ggit.Repository.Repository)
getDiffRepository :: o -> m (Maybe Repository)
getDiffRepository obj :: 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 "repository" ManagedPtr Repository -> Repository
Ggit.Repository.Repository
constructDiffRepository :: (IsDiff o, Ggit.Repository.IsRepository a) => a -> IO (GValueConstruct o)
constructDiffRepository :: a -> IO (GValueConstruct o)
constructDiffRepository val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "repository" (a -> Maybe a
forall a. a -> Maybe a
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
foreign import ccall "ggit_diff_new_index_to_workdir" ggit_diff_new_index_to_workdir ::
Ptr Ggit.Repository.Repository ->
Ptr Ggit.Index.Index ->
Ptr Ggit.DiffOptions.DiffOptions ->
Ptr (Ptr GError) ->
IO (Ptr Diff)
diffNewIndexToWorkdir ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Index.IsIndex b, Ggit.DiffOptions.IsDiffOptions c) =>
a
-> Maybe (b)
-> Maybe (c)
-> m (Maybe Diff)
diffNewIndexToWorkdir :: a -> Maybe b -> Maybe c -> m (Maybe Diff)
diffNewIndexToWorkdir repository :: a
repository index :: Maybe b
index diffOptions :: 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
Nothing -> Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
forall a. Ptr a
nullPtr
Just jIndex :: 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
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
Just jDiffOptions :: 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
$ \result' :: 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
foreign import ccall "ggit_diff_new_tree_to_index" ggit_diff_new_tree_to_index ::
Ptr Ggit.Repository.Repository ->
Ptr Ggit.Tree.Tree ->
Ptr Ggit.Index.Index ->
Ptr Ggit.DiffOptions.DiffOptions ->
Ptr (Ptr GError) ->
IO (Ptr Diff)
diffNewTreeToIndex ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.Index.IsIndex c, Ggit.DiffOptions.IsDiffOptions d) =>
a
-> Maybe (b)
-> Maybe (c)
-> Maybe (d)
-> m (Maybe Diff)
diffNewTreeToIndex :: a -> Maybe b -> Maybe c -> Maybe d -> m (Maybe Diff)
diffNewTreeToIndex repository :: a
repository oldTree :: Maybe b
oldTree index :: Maybe c
index diffOptions :: 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
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
Just jOldTree :: 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
Nothing -> Ptr Index -> IO (Ptr Index)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Index
forall a. Ptr a
nullPtr
Just jIndex :: 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
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
Just jDiffOptions :: 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
$ \result' :: 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
foreign import ccall "ggit_diff_new_tree_to_tree" ggit_diff_new_tree_to_tree ::
Ptr Ggit.Repository.Repository ->
Ptr Ggit.Tree.Tree ->
Ptr Ggit.Tree.Tree ->
Ptr Ggit.DiffOptions.DiffOptions ->
Ptr (Ptr GError) ->
IO (Ptr Diff)
diffNewTreeToTree ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.Tree.IsTree c, Ggit.DiffOptions.IsDiffOptions d) =>
a
-> Maybe (b)
-> Maybe (c)
-> Maybe (d)
-> m (Maybe Diff)
diffNewTreeToTree :: a -> Maybe b -> Maybe c -> Maybe d -> m (Maybe Diff)
diffNewTreeToTree repository :: a
repository oldTree :: Maybe b
oldTree newTree :: Maybe c
newTree diffOptions :: 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
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
Just jOldTree :: 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
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
Just jNewTree :: 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
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
Just jDiffOptions :: 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
$ \result' :: 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
foreign import ccall "ggit_diff_new_tree_to_workdir" ggit_diff_new_tree_to_workdir ::
Ptr Ggit.Repository.Repository ->
Ptr Ggit.Tree.Tree ->
Ptr Ggit.DiffOptions.DiffOptions ->
Ptr (Ptr GError) ->
IO (Ptr Diff)
diffNewTreeToWorkdir ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Repository.IsRepository a, Ggit.Tree.IsTree b, Ggit.DiffOptions.IsDiffOptions c) =>
a
-> Maybe (b)
-> Maybe (c)
-> m (Maybe Diff)
diffNewTreeToWorkdir :: a -> Maybe b -> Maybe c -> m (Maybe Diff)
diffNewTreeToWorkdir repository :: a
repository oldTree :: Maybe b
oldTree diffOptions :: 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
Nothing -> Ptr Tree -> IO (Ptr Tree)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Tree
forall a. Ptr a
nullPtr
Just jOldTree :: 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
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
forall a. Ptr a
nullPtr
Just jDiffOptions :: 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
$ \result' :: 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
foreign import ccall "ggit_diff_find_similar" ggit_diff_find_similar ::
Ptr Diff ->
Ptr Ggit.DiffFindOptions.DiffFindOptions ->
Ptr (Ptr GError) ->
IO CInt
diffFindSimilar ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a, Ggit.DiffFindOptions.IsDiffFindOptions b) =>
a
-> Maybe (b)
-> m ()
diffFindSimilar :: a -> Maybe b -> m ()
diffFindSimilar diff :: a
diff options :: 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
Nothing -> Ptr DiffFindOptions -> IO (Ptr DiffFindOptions)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffFindOptions
forall a. Ptr a
nullPtr
Just jOptions :: 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
#if defined(ENABLE_OVERLOADING)
data DiffForeachMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "foreach" Diff) => O.MethodInfo DiffForeachMethodInfo o p where
overloadedMethod = undefined
#endif
foreign import ccall "ggit_diff_format_email" ggit_diff_format_email ::
Ptr Diff ->
Ptr Ggit.DiffFormatEmailOptions.DiffFormatEmailOptions ->
Ptr (Ptr GError) ->
IO CString
diffFormatEmail ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a, Ggit.DiffFormatEmailOptions.IsDiffFormatEmailOptions b) =>
a
-> b
-> m (Maybe T.Text)
diffFormatEmail :: a -> b -> m (Maybe Text)
diffFormatEmail diff :: a
diff options :: 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
CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr Diff
-> Ptr DiffFormatEmailOptions -> Ptr (Ptr GError) -> IO CString
ggit_diff_format_email Ptr Diff
diff' Ptr DiffFormatEmailOptions
options'
Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
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
foreign import ccall "ggit_diff_get_delta" ggit_diff_get_delta ::
Ptr Diff ->
Word64 ->
IO (Ptr Ggit.DiffDelta.DiffDelta)
diffGetDelta ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
a
-> Word64
-> m (Maybe Ggit.DiffDelta.DiffDelta)
diffGetDelta :: a -> Word64 -> m (Maybe DiffDelta)
diffGetDelta diff :: a
diff index :: 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
$ \result' :: Ptr DiffDelta
result' -> do
DiffDelta
result'' <- ((ManagedPtr DiffDelta -> DiffDelta)
-> Ptr DiffDelta -> IO DiffDelta
forall a.
(HasCallStack, BoxedObject 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
foreign import ccall "ggit_diff_get_num_deltas" ggit_diff_get_num_deltas ::
Ptr Diff ->
IO Word64
diffGetNumDeltas ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
a
-> m Word64
diffGetNumDeltas :: a -> m Word64
diffGetNumDeltas diff :: 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
foreign import ccall "ggit_diff_merge" ggit_diff_merge ::
Ptr Diff ->
Ptr Diff ->
Ptr (Ptr GError) ->
IO ()
diffMerge ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a, IsDiff b) =>
a
-> b
-> m ()
diffMerge :: a -> b -> m ()
diffMerge onto :: a
onto from :: 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
foreign import ccall "ggit_diff_print" ggit_diff_print ::
Ptr Diff ->
CUInt ->
FunPtr Ggit.Callbacks.C_DiffLineCallback ->
Ptr () ->
Ptr (Ptr GError) ->
IO ()
diffPrint ::
(B.CallStack.HasCallStack, MonadIO m, IsDiff a) =>
a
-> Ggit.Enums.DiffFormatType
-> Ggit.Callbacks.DiffLineCallback
-> m ()
diffPrint :: a -> DiffFormatType -> DiffLineCallback -> m ()
diffPrint diff :: a
diff type_ :: DiffFormatType
type_ printCb :: 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
#if defined(ENABLE_OVERLOADING)
data DiffBlobToBufferMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "blobToBuffer" Diff) => O.MethodInfo DiffBlobToBufferMethodInfo o p where
overloadedMethod = undefined
#endif
#if defined(ENABLE_OVERLOADING)
data DiffBlobsMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "blobs" Diff) => O.MethodInfo DiffBlobsMethodInfo o p where
overloadedMethod = undefined
#endif