{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Ggit.Structs.Patch
(
Patch(..) ,
#if defined(ENABLE_OVERLOADING)
ResolvePatchMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PatchGetDeltaMethodInfo ,
#endif
patchGetDelta ,
#if defined(ENABLE_OVERLOADING)
PatchGetHunkMethodInfo ,
#endif
patchGetHunk ,
#if defined(ENABLE_OVERLOADING)
PatchGetLineStatsMethodInfo ,
#endif
patchGetLineStats ,
#if defined(ENABLE_OVERLOADING)
PatchGetNumHunksMethodInfo ,
#endif
patchGetNumHunks ,
#if defined(ENABLE_OVERLOADING)
PatchGetNumLinesInHunkMethodInfo ,
#endif
patchGetNumLinesInHunk ,
patchNewFromBlobs ,
patchNewFromDiff ,
#if defined(ENABLE_OVERLOADING)
PatchRefMethodInfo ,
#endif
patchRef ,
#if defined(ENABLE_OVERLOADING)
PatchToStreamMethodInfo ,
#endif
patchToStream ,
#if defined(ENABLE_OVERLOADING)
PatchToStringMethodInfo ,
#endif
patchToString ,
#if defined(ENABLE_OVERLOADING)
PatchUnrefMethodInfo ,
#endif
patchUnref ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.MatchInfo as GLib.MatchInfo
import qualified GI.GLib.Structs.Regex as GLib.Regex
import qualified GI.GLib.Structs.TimeZone as GLib.TimeZone
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.Flags as Ggit.Flags
import {-# SOURCE #-} qualified GI.Ggit.Objects.Blame as Ggit.Blame
import {-# SOURCE #-} qualified GI.Ggit.Objects.Blob as Ggit.Blob
import {-# SOURCE #-} qualified GI.Ggit.Objects.BlobOutputStream as Ggit.BlobOutputStream
import {-# SOURCE #-} qualified GI.Ggit.Objects.Branch as Ggit.Branch
import {-# SOURCE #-} qualified GI.Ggit.Objects.CheckoutOptions as Ggit.CheckoutOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.CherryPickOptions as Ggit.CherryPickOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.CloneOptions as Ggit.CloneOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.Commit as Ggit.Commit
import {-# SOURCE #-} qualified GI.Ggit.Objects.CommitParents as Ggit.CommitParents
import {-# SOURCE #-} qualified GI.Ggit.Objects.Config as Ggit.Config
import {-# SOURCE #-} qualified GI.Ggit.Objects.Diff as Ggit.Diff
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.Object as Ggit.Object
import {-# SOURCE #-} qualified GI.Ggit.Objects.ObjectFactoryBase as Ggit.ObjectFactoryBase
import {-# SOURCE #-} qualified GI.Ggit.Objects.ProxyOptions as Ggit.ProxyOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.PushOptions as Ggit.PushOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.Rebase as Ggit.Rebase
import {-# SOURCE #-} qualified GI.Ggit.Objects.Ref as Ggit.Ref
import {-# SOURCE #-} qualified GI.Ggit.Objects.Remote as Ggit.Remote
import {-# SOURCE #-} qualified GI.Ggit.Objects.RemoteCallbacks as Ggit.RemoteCallbacks
import {-# SOURCE #-} qualified GI.Ggit.Objects.Repository as Ggit.Repository
import {-# SOURCE #-} qualified GI.Ggit.Objects.Signature as Ggit.Signature
import {-# SOURCE #-} qualified GI.Ggit.Objects.SubmoduleUpdateOptions as Ggit.SubmoduleUpdateOptions
import {-# SOURCE #-} qualified GI.Ggit.Objects.Tag as Ggit.Tag
import {-# SOURCE #-} qualified GI.Ggit.Objects.Tree as Ggit.Tree
import {-# SOURCE #-} qualified GI.Ggit.Objects.TreeBuilder as Ggit.TreeBuilder
import {-# SOURCE #-} qualified GI.Ggit.Structs.AnnotatedCommit as Ggit.AnnotatedCommit
import {-# SOURCE #-} qualified GI.Ggit.Structs.BlameHunk as Ggit.BlameHunk
import {-# SOURCE #-} qualified GI.Ggit.Structs.BlameOptions as Ggit.BlameOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.BranchEnumerator as Ggit.BranchEnumerator
import {-# SOURCE #-} qualified GI.Ggit.Structs.ConfigEntry as Ggit.ConfigEntry
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffDelta as Ggit.DiffDelta
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffFile as Ggit.DiffFile
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffHunk as Ggit.DiffHunk
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffSimilarityMetric as Ggit.DiffSimilarityMetric
import {-# SOURCE #-} qualified GI.Ggit.Structs.FetchOptions as Ggit.FetchOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntries as Ggit.IndexEntries
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntriesResolveUndo as Ggit.IndexEntriesResolveUndo
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntry as Ggit.IndexEntry
import {-# SOURCE #-} qualified GI.Ggit.Structs.IndexEntryResolveUndo as Ggit.IndexEntryResolveUndo
import {-# SOURCE #-} qualified GI.Ggit.Structs.MergeOptions as Ggit.MergeOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.Note as Ggit.Note
import {-# SOURCE #-} qualified GI.Ggit.Structs.OId as Ggit.OId
import {-# SOURCE #-} qualified GI.Ggit.Structs.RebaseOperation as Ggit.RebaseOperation
import {-# SOURCE #-} qualified GI.Ggit.Structs.RebaseOptions as Ggit.RebaseOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.Reflog as Ggit.Reflog
import {-# SOURCE #-} qualified GI.Ggit.Structs.ReflogEntry as Ggit.ReflogEntry
import {-# SOURCE #-} qualified GI.Ggit.Structs.RemoteHead as Ggit.RemoteHead
import {-# SOURCE #-} qualified GI.Ggit.Structs.RevertOptions as Ggit.RevertOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.StatusOptions as Ggit.StatusOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.Submodule as Ggit.Submodule
import {-# SOURCE #-} qualified GI.Ggit.Structs.TransferProgress as Ggit.TransferProgress
import {-# SOURCE #-} qualified GI.Ggit.Structs.TreeEntry as Ggit.TreeEntry
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
#else
import {-# SOURCE #-} qualified GI.Ggit.Objects.Blob as Ggit.Blob
import {-# SOURCE #-} qualified GI.Ggit.Objects.Diff as Ggit.Diff
import {-# SOURCE #-} qualified GI.Ggit.Objects.DiffOptions as Ggit.DiffOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffDelta as Ggit.DiffDelta
import {-# SOURCE #-} qualified GI.Ggit.Structs.DiffHunk as Ggit.DiffHunk
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
#endif
newtype Patch = Patch (SP.ManagedPtr Patch)
deriving (Patch -> Patch -> Bool
(Patch -> Patch -> Bool) -> (Patch -> Patch -> Bool) -> Eq Patch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Patch -> Patch -> Bool
== :: Patch -> Patch -> Bool
$c/= :: Patch -> Patch -> Bool
/= :: Patch -> Patch -> Bool
Eq)
instance SP.ManagedPtrNewtype Patch where
toManagedPtr :: Patch -> ManagedPtr Patch
toManagedPtr (Patch ManagedPtr Patch
p) = ManagedPtr Patch
p
foreign import ccall "ggit_patch_get_type" c_ggit_patch_get_type ::
IO GType
type instance O.ParentTypes Patch = '[]
instance O.HasParentTypes Patch
instance B.Types.TypedObject Patch where
glibType :: IO GType
glibType = IO GType
c_ggit_patch_get_type
instance B.Types.GBoxed Patch
instance B.GValue.IsGValue (Maybe Patch) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ggit_patch_get_type
gvalueSet_ :: Ptr GValue -> Maybe Patch -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Patch
P.Nothing = Ptr GValue -> Ptr Patch -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Patch
forall a. Ptr a
FP.nullPtr :: FP.Ptr Patch)
gvalueSet_ Ptr GValue
gv (P.Just Patch
obj) = Patch -> (Ptr Patch -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Patch
obj (Ptr GValue -> Ptr Patch -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Patch)
gvalueGet_ Ptr GValue
gv = do
Ptr Patch
ptr <- Ptr GValue -> IO (Ptr Patch)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Patch)
if Ptr Patch
ptr Ptr Patch -> Ptr Patch -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Patch
forall a. Ptr a
FP.nullPtr
then Patch -> Maybe Patch
forall a. a -> Maybe a
P.Just (Patch -> Maybe Patch) -> IO Patch -> IO (Maybe Patch)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Patch -> Patch) -> Ptr Patch -> IO Patch
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Patch -> Patch
Patch Ptr Patch
ptr
else Maybe Patch -> IO (Maybe Patch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Patch
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Patch
type instance O.AttributeList Patch = PatchAttributeList
type PatchAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ggit_patch_new_from_blobs" ggit_patch_new_from_blobs ::
Ptr Ggit.Blob.Blob ->
CString ->
Ptr Ggit.Blob.Blob ->
CString ->
Ptr Ggit.DiffOptions.DiffOptions ->
Ptr (Ptr GError) ->
IO (Ptr Patch)
patchNewFromBlobs ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Blob.IsBlob a, Ggit.Blob.IsBlob b, Ggit.DiffOptions.IsDiffOptions c) =>
Maybe (a)
-> Maybe (T.Text)
-> Maybe (b)
-> Maybe (T.Text)
-> Maybe (c)
-> m (Maybe Patch)
patchNewFromBlobs :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsBlob a, IsBlob b, IsDiffOptions c) =>
Maybe a
-> Maybe Text
-> Maybe b
-> Maybe Text
-> Maybe c
-> m (Maybe Patch)
patchNewFromBlobs Maybe a
oldBlob Maybe Text
oldAsPath Maybe b
newBlob Maybe Text
newAsPath Maybe c
diffOptions = IO (Maybe Patch) -> m (Maybe Patch)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Patch) -> m (Maybe Patch))
-> IO (Maybe Patch) -> m (Maybe Patch)
forall a b. (a -> b) -> a -> b
$ do
Ptr Blob
maybeOldBlob <- case Maybe a
oldBlob of
Maybe a
Nothing -> Ptr Blob -> IO (Ptr Blob)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Blob
forall a. Ptr a
nullPtr
Just a
jOldBlob -> do
Ptr Blob
jOldBlob' <- a -> IO (Ptr Blob)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jOldBlob
Ptr Blob -> IO (Ptr Blob)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Blob
jOldBlob'
Ptr CChar
maybeOldAsPath <- case Maybe Text
oldAsPath of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jOldAsPath -> do
Ptr CChar
jOldAsPath' <- Text -> IO (Ptr CChar)
textToCString Text
jOldAsPath
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jOldAsPath'
Ptr Blob
maybeNewBlob <- case Maybe b
newBlob of
Maybe b
Nothing -> Ptr Blob -> IO (Ptr Blob)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Blob
forall a. Ptr a
nullPtr
Just b
jNewBlob -> do
Ptr Blob
jNewBlob' <- b -> IO (Ptr Blob)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jNewBlob
Ptr Blob -> IO (Ptr Blob)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Blob
jNewBlob'
Ptr CChar
maybeNewAsPath <- case Maybe Text
newAsPath of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jNewAsPath -> do
Ptr CChar
jNewAsPath' <- Text -> IO (Ptr CChar)
textToCString Text
jNewAsPath
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jNewAsPath'
Ptr DiffOptions
maybeDiffOptions <- case Maybe c
diffOptions of
Maybe c
Nothing -> Ptr DiffOptions -> IO (Ptr DiffOptions)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr DiffOptions
jDiffOptions'
IO (Maybe Patch) -> IO () -> IO (Maybe Patch)
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Patch
result <- (Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch))
-> (Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch)
forall a b. (a -> b) -> a -> b
$ Ptr Blob
-> Ptr CChar
-> Ptr Blob
-> Ptr CChar
-> Ptr DiffOptions
-> Ptr (Ptr GError)
-> IO (Ptr Patch)
ggit_patch_new_from_blobs Ptr Blob
maybeOldBlob Ptr CChar
maybeOldAsPath Ptr Blob
maybeNewBlob Ptr CChar
maybeNewAsPath Ptr DiffOptions
maybeDiffOptions
Maybe Patch
maybeResult <- Ptr Patch -> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Patch
result ((Ptr Patch -> IO Patch) -> IO (Maybe Patch))
-> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. (a -> b) -> a -> b
$ \Ptr Patch
result' -> do
Patch
result'' <- ((ManagedPtr Patch -> Patch) -> Ptr Patch -> IO Patch
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Patch -> Patch
Patch) Ptr Patch
result'
Patch -> IO Patch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Patch
result''
Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
oldBlob a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
newBlob 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
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOldAsPath
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeNewAsPath
Maybe Patch -> IO (Maybe Patch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Patch
maybeResult
) (do
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeOldAsPath
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeNewAsPath
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "ggit_patch_new_from_diff" ggit_patch_new_from_diff ::
Ptr Ggit.Diff.Diff ->
FCT.CSize ->
Ptr (Ptr GError) ->
IO (Ptr Patch)
patchNewFromDiff ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.Diff.IsDiff a) =>
a
-> FCT.CSize
-> m (Maybe Patch)
patchNewFromDiff :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDiff a) =>
a -> CSize -> m (Maybe Patch)
patchNewFromDiff a
diff CSize
idx = IO (Maybe Patch) -> m (Maybe Patch)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Patch) -> m (Maybe Patch))
-> IO (Maybe Patch) -> m (Maybe Patch)
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
IO (Maybe Patch) -> IO () -> IO (Maybe Patch)
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Patch
result <- (Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch))
-> (Ptr (Ptr GError) -> IO (Ptr Patch)) -> IO (Ptr Patch)
forall a b. (a -> b) -> a -> b
$ Ptr Diff -> CSize -> Ptr (Ptr GError) -> IO (Ptr Patch)
ggit_patch_new_from_diff Ptr Diff
diff' CSize
idx
Maybe Patch
maybeResult <- Ptr Patch -> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Patch
result ((Ptr Patch -> IO Patch) -> IO (Maybe Patch))
-> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. (a -> b) -> a -> b
$ \Ptr Patch
result' -> do
Patch
result'' <- ((ManagedPtr Patch -> Patch) -> Ptr Patch -> IO Patch
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Patch -> Patch
Patch) Ptr Patch
result'
Patch -> IO Patch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Patch
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
diff
Maybe Patch -> IO (Maybe Patch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Patch
maybeResult
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "ggit_patch_get_delta" ggit_patch_get_delta ::
Ptr Patch ->
IO (Ptr Ggit.DiffDelta.DiffDelta)
patchGetDelta ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m (Maybe Ggit.DiffDelta.DiffDelta)
patchGetDelta :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> m (Maybe DiffDelta)
patchGetDelta Patch
patch = IO (Maybe DiffDelta) -> m (Maybe DiffDelta)
forall a. IO a -> m a
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 Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Ptr DiffDelta
result <- Ptr Patch -> IO (Ptr DiffDelta)
ggit_patch_get_delta Ptr Patch
patch'
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DiffDelta
result''
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Maybe DiffDelta -> IO (Maybe DiffDelta)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DiffDelta
maybeResult
#if defined(ENABLE_OVERLOADING)
data PatchGetDeltaMethodInfo
instance (signature ~ (m (Maybe Ggit.DiffDelta.DiffDelta)), MonadIO m) => O.OverloadedMethod PatchGetDeltaMethodInfo Patch signature where
overloadedMethod = patchGetDelta
instance O.OverloadedMethodInfo PatchGetDeltaMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchGetDelta",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchGetDelta"
})
#endif
foreign import ccall "ggit_patch_get_hunk" ggit_patch_get_hunk ::
Ptr Patch ->
FCT.CSize ->
Ptr (Ptr GError) ->
IO (Ptr Ggit.DiffHunk.DiffHunk)
patchGetHunk ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> FCT.CSize
-> m (Maybe Ggit.DiffHunk.DiffHunk)
patchGetHunk :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> CSize -> m (Maybe DiffHunk)
patchGetHunk Patch
patch CSize
idx = IO (Maybe DiffHunk) -> m (Maybe DiffHunk)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DiffHunk) -> m (Maybe DiffHunk))
-> IO (Maybe DiffHunk) -> m (Maybe DiffHunk)
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
IO (Maybe DiffHunk) -> IO () -> IO (Maybe DiffHunk)
forall a b. IO a -> IO b -> IO a
onException (do
Ptr DiffHunk
result <- (Ptr (Ptr GError) -> IO (Ptr DiffHunk)) -> IO (Ptr DiffHunk)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr DiffHunk)) -> IO (Ptr DiffHunk))
-> (Ptr (Ptr GError) -> IO (Ptr DiffHunk)) -> IO (Ptr DiffHunk)
forall a b. (a -> b) -> a -> b
$ Ptr Patch -> CSize -> Ptr (Ptr GError) -> IO (Ptr DiffHunk)
ggit_patch_get_hunk Ptr Patch
patch' CSize
idx
Maybe DiffHunk
maybeResult <- Ptr DiffHunk
-> (Ptr DiffHunk -> IO DiffHunk) -> IO (Maybe DiffHunk)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DiffHunk
result ((Ptr DiffHunk -> IO DiffHunk) -> IO (Maybe DiffHunk))
-> (Ptr DiffHunk -> IO DiffHunk) -> IO (Maybe DiffHunk)
forall a b. (a -> b) -> a -> b
$ \Ptr DiffHunk
result' -> do
DiffHunk
result'' <- ((ManagedPtr DiffHunk -> DiffHunk) -> Ptr DiffHunk -> IO DiffHunk
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr DiffHunk -> DiffHunk
Ggit.DiffHunk.DiffHunk) Ptr DiffHunk
result'
DiffHunk -> IO DiffHunk
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DiffHunk
result''
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Maybe DiffHunk -> IO (Maybe DiffHunk)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DiffHunk
maybeResult
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data PatchGetHunkMethodInfo
instance (signature ~ (FCT.CSize -> m (Maybe Ggit.DiffHunk.DiffHunk)), MonadIO m) => O.OverloadedMethod PatchGetHunkMethodInfo Patch signature where
overloadedMethod = patchGetHunk
instance O.OverloadedMethodInfo PatchGetHunkMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchGetHunk",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchGetHunk"
})
#endif
foreign import ccall "ggit_patch_get_line_stats" ggit_patch_get_line_stats ::
Ptr Patch ->
Ptr FCT.CSize ->
Ptr FCT.CSize ->
Ptr FCT.CSize ->
Ptr (Ptr GError) ->
IO CInt
patchGetLineStats ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m ((FCT.CSize, FCT.CSize, FCT.CSize))
patchGetLineStats :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> m (CSize, CSize, CSize)
patchGetLineStats Patch
patch = IO (CSize, CSize, CSize) -> m (CSize, CSize, CSize)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (CSize, CSize, CSize) -> m (CSize, CSize, CSize))
-> IO (CSize, CSize, CSize) -> m (CSize, CSize, CSize)
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Ptr CSize
totalContext <- IO (Ptr CSize)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr FCT.CSize)
Ptr CSize
totalAdditions <- IO (Ptr CSize)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr FCT.CSize)
Ptr CSize
totalDeletions <- IO (Ptr CSize)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr FCT.CSize)
IO (CSize, CSize, CSize) -> IO () -> IO (CSize, CSize, CSize)
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 Patch
-> Ptr CSize
-> Ptr CSize
-> Ptr CSize
-> Ptr (Ptr GError)
-> IO CInt
ggit_patch_get_line_stats Ptr Patch
patch' Ptr CSize
totalContext Ptr CSize
totalAdditions Ptr CSize
totalDeletions
CSize
totalContext' <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
totalContext
CSize
totalAdditions' <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
totalAdditions
CSize
totalDeletions' <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek Ptr CSize
totalDeletions
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalContext
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalAdditions
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalDeletions
(CSize, CSize, CSize) -> IO (CSize, CSize, CSize)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (CSize
totalContext', CSize
totalAdditions', CSize
totalDeletions')
) (do
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalContext
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalAdditions
Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CSize
totalDeletions
)
#if defined(ENABLE_OVERLOADING)
data PatchGetLineStatsMethodInfo
instance (signature ~ (m ((FCT.CSize, FCT.CSize, FCT.CSize))), MonadIO m) => O.OverloadedMethod PatchGetLineStatsMethodInfo Patch signature where
overloadedMethod = patchGetLineStats
instance O.OverloadedMethodInfo PatchGetLineStatsMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchGetLineStats",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchGetLineStats"
})
#endif
foreign import ccall "ggit_patch_get_num_hunks" ggit_patch_get_num_hunks ::
Ptr Patch ->
IO FCT.CSize
patchGetNumHunks ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m FCT.CSize
patchGetNumHunks :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Patch -> m CSize
patchGetNumHunks Patch
patch = IO CSize -> m CSize
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CSize -> m CSize) -> IO CSize -> m CSize
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
CSize
result <- Ptr Patch -> IO CSize
ggit_patch_get_num_hunks Ptr Patch
patch'
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
CSize -> IO CSize
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CSize
result
#if defined(ENABLE_OVERLOADING)
data PatchGetNumHunksMethodInfo
instance (signature ~ (m FCT.CSize), MonadIO m) => O.OverloadedMethod PatchGetNumHunksMethodInfo Patch signature where
overloadedMethod = patchGetNumHunks
instance O.OverloadedMethodInfo PatchGetNumHunksMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchGetNumHunks",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchGetNumHunks"
})
#endif
foreign import ccall "ggit_patch_get_num_lines_in_hunk" ggit_patch_get_num_lines_in_hunk ::
Ptr Patch ->
FCT.CSize ->
IO Int32
patchGetNumLinesInHunk ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> FCT.CSize
-> m Int32
patchGetNumLinesInHunk :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> CSize -> m Int32
patchGetNumLinesInHunk Patch
patch CSize
hunk = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Int32
result <- Ptr Patch -> CSize -> IO Int32
ggit_patch_get_num_lines_in_hunk Ptr Patch
patch' CSize
hunk
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data PatchGetNumLinesInHunkMethodInfo
instance (signature ~ (FCT.CSize -> m Int32), MonadIO m) => O.OverloadedMethod PatchGetNumLinesInHunkMethodInfo Patch signature where
overloadedMethod = patchGetNumLinesInHunk
instance O.OverloadedMethodInfo PatchGetNumLinesInHunkMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchGetNumLinesInHunk",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchGetNumLinesInHunk"
})
#endif
foreign import ccall "ggit_patch_ref" ggit_patch_ref ::
Ptr Patch ->
IO (Ptr Patch)
patchRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m (Maybe Patch)
patchRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> m (Maybe Patch)
patchRef Patch
patch = IO (Maybe Patch) -> m (Maybe Patch)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Patch) -> m (Maybe Patch))
-> IO (Maybe Patch) -> m (Maybe Patch)
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Ptr Patch
result <- Ptr Patch -> IO (Ptr Patch)
ggit_patch_ref Ptr Patch
patch'
Maybe Patch
maybeResult <- Ptr Patch -> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Patch
result ((Ptr Patch -> IO Patch) -> IO (Maybe Patch))
-> (Ptr Patch -> IO Patch) -> IO (Maybe Patch)
forall a b. (a -> b) -> a -> b
$ \Ptr Patch
result' -> do
Patch
result'' <- ((ManagedPtr Patch -> Patch) -> Ptr Patch -> IO Patch
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Patch -> Patch
Patch) Ptr Patch
result'
Patch -> IO Patch
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Patch
result''
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Maybe Patch -> IO (Maybe Patch)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Patch
maybeResult
#if defined(ENABLE_OVERLOADING)
data PatchRefMethodInfo
instance (signature ~ (m (Maybe Patch)), MonadIO m) => O.OverloadedMethod PatchRefMethodInfo Patch signature where
overloadedMethod = patchRef
instance O.OverloadedMethodInfo PatchRefMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchRef"
})
#endif
foreign import ccall "ggit_patch_to_stream" ggit_patch_to_stream ::
Ptr Patch ->
Ptr Gio.OutputStream.OutputStream ->
Ptr (Ptr GError) ->
IO CInt
patchToStream ::
(B.CallStack.HasCallStack, MonadIO m, Gio.OutputStream.IsOutputStream a) =>
Patch
-> a
-> m ()
patchToStream :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsOutputStream a) =>
Patch -> a -> m ()
patchToStream Patch
patch a
stream = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Ptr OutputStream
stream' <- a -> IO (Ptr OutputStream)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
stream
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 Patch -> Ptr OutputStream -> Ptr (Ptr GError) -> IO CInt
ggit_patch_to_stream Ptr Patch
patch' Ptr OutputStream
stream'
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
stream
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data PatchToStreamMethodInfo
instance (signature ~ (a -> m ()), MonadIO m, Gio.OutputStream.IsOutputStream a) => O.OverloadedMethod PatchToStreamMethodInfo Patch signature where
overloadedMethod = patchToStream
instance O.OverloadedMethodInfo PatchToStreamMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchToStream",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchToStream"
})
#endif
foreign import ccall "ggit_patch_to_string" ggit_patch_to_string ::
Ptr Patch ->
Ptr (Ptr GError) ->
IO CString
patchToString ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m (Maybe T.Text)
patchToString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Patch -> m (Maybe Text)
patchToString Patch
patch = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
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 Patch -> Ptr (Ptr GError) -> IO (Ptr CChar)
ggit_patch_to_string Ptr Patch
patch'
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data PatchToStringMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod PatchToStringMethodInfo Patch signature where
overloadedMethod = patchToString
instance O.OverloadedMethodInfo PatchToStringMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchToString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchToString"
})
#endif
foreign import ccall "ggit_patch_unref" ggit_patch_unref ::
Ptr Patch ->
IO ()
patchUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Patch
-> m ()
patchUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Patch -> m ()
patchUnref Patch
patch = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Patch
patch' <- Patch -> IO (Ptr Patch)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Patch
patch
Ptr Patch -> IO ()
ggit_patch_unref Ptr Patch
patch'
Patch -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Patch
patch
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PatchUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PatchUnrefMethodInfo Patch signature where
overloadedMethod = patchUnref
instance O.OverloadedMethodInfo PatchUnrefMethodInfo Patch where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Patch.patchUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Patch.html#v:patchUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePatchMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePatchMethod "ref" o = PatchRefMethodInfo
ResolvePatchMethod "toStream" o = PatchToStreamMethodInfo
ResolvePatchMethod "toString" o = PatchToStringMethodInfo
ResolvePatchMethod "unref" o = PatchUnrefMethodInfo
ResolvePatchMethod "getDelta" o = PatchGetDeltaMethodInfo
ResolvePatchMethod "getHunk" o = PatchGetHunkMethodInfo
ResolvePatchMethod "getLineStats" o = PatchGetLineStatsMethodInfo
ResolvePatchMethod "getNumHunks" o = PatchGetNumHunksMethodInfo
ResolvePatchMethod "getNumLinesInHunk" o = PatchGetNumLinesInHunkMethodInfo
ResolvePatchMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePatchMethod t Patch, O.OverloadedMethod info Patch p) => OL.IsLabel t (Patch -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePatchMethod t Patch, O.OverloadedMethod info Patch p, R.HasField t Patch p) => R.HasField t Patch p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePatchMethod t Patch, O.OverloadedMethodInfo info Patch) => OL.IsLabel t (O.MethodProxy info Patch) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif