{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Ggit.Structs.Submodule
(
Submodule(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveSubmoduleMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SubmoduleGetFetchRecurseMethodInfo ,
#endif
submoduleGetFetchRecurse ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetHeadIdMethodInfo ,
#endif
submoduleGetHeadId ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetIgnoreMethodInfo ,
#endif
submoduleGetIgnore ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetIndexIdMethodInfo ,
#endif
submoduleGetIndexId ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetNameMethodInfo ,
#endif
submoduleGetName ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetOwnerMethodInfo ,
#endif
submoduleGetOwner ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetPathMethodInfo ,
#endif
submoduleGetPath ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetUpdateMethodInfo ,
#endif
submoduleGetUpdate ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetUrlMethodInfo ,
#endif
submoduleGetUrl ,
#if defined(ENABLE_OVERLOADING)
SubmoduleGetWorkdirIdMethodInfo ,
#endif
submoduleGetWorkdirId ,
#if defined(ENABLE_OVERLOADING)
SubmoduleInitMethodInfo ,
#endif
submoduleInit ,
#if defined(ENABLE_OVERLOADING)
SubmoduleOpenMethodInfo ,
#endif
submoduleOpen ,
#if defined(ENABLE_OVERLOADING)
SubmoduleRefMethodInfo ,
#endif
submoduleRef ,
#if defined(ENABLE_OVERLOADING)
SubmoduleReloadMethodInfo ,
#endif
submoduleReload ,
#if defined(ENABLE_OVERLOADING)
SubmoduleSyncMethodInfo ,
#endif
submoduleSync ,
#if defined(ENABLE_OVERLOADING)
SubmoduleUnrefMethodInfo ,
#endif
submoduleUnref ,
#if defined(ENABLE_OVERLOADING)
SubmoduleUpdateMethodInfo ,
#endif
submoduleUpdate ,
) 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.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.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.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.Enums as Ggit.Enums
import {-# SOURCE #-} qualified GI.Ggit.Objects.Repository as Ggit.Repository
import {-# SOURCE #-} qualified GI.Ggit.Objects.SubmoduleUpdateOptions as Ggit.SubmoduleUpdateOptions
import {-# SOURCE #-} qualified GI.Ggit.Structs.OId as Ggit.OId
#endif
newtype Submodule = Submodule (SP.ManagedPtr Submodule)
deriving (Submodule -> Submodule -> Bool
(Submodule -> Submodule -> Bool)
-> (Submodule -> Submodule -> Bool) -> Eq Submodule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Submodule -> Submodule -> Bool
== :: Submodule -> Submodule -> Bool
$c/= :: Submodule -> Submodule -> Bool
/= :: Submodule -> Submodule -> Bool
Eq)
instance SP.ManagedPtrNewtype Submodule where
toManagedPtr :: Submodule -> ManagedPtr Submodule
toManagedPtr (Submodule ManagedPtr Submodule
p) = ManagedPtr Submodule
p
foreign import ccall "ggit_submodule_get_type" c_ggit_submodule_get_type ::
IO GType
type instance O.ParentTypes Submodule = '[]
instance O.HasParentTypes Submodule
instance B.Types.TypedObject Submodule where
glibType :: IO GType
glibType = IO GType
c_ggit_submodule_get_type
instance B.Types.GBoxed Submodule
instance B.GValue.IsGValue (Maybe Submodule) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_ggit_submodule_get_type
gvalueSet_ :: Ptr GValue -> Maybe Submodule -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Submodule
P.Nothing = Ptr GValue -> Ptr Submodule -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Submodule
forall a. Ptr a
FP.nullPtr :: FP.Ptr Submodule)
gvalueSet_ Ptr GValue
gv (P.Just Submodule
obj) = Submodule -> (Ptr Submodule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Submodule
obj (Ptr GValue -> Ptr Submodule -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Submodule)
gvalueGet_ Ptr GValue
gv = do
Ptr Submodule
ptr <- Ptr GValue -> IO (Ptr Submodule)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Submodule)
if Ptr Submodule
ptr Ptr Submodule -> Ptr Submodule -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Submodule
forall a. Ptr a
FP.nullPtr
then Submodule -> Maybe Submodule
forall a. a -> Maybe a
P.Just (Submodule -> Maybe Submodule)
-> IO Submodule -> IO (Maybe Submodule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Submodule -> Submodule)
-> Ptr Submodule -> IO Submodule
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Submodule -> Submodule
Submodule Ptr Submodule
ptr
else Maybe Submodule -> IO (Maybe Submodule)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Submodule
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Submodule
type instance O.AttributeList Submodule = SubmoduleAttributeList
type SubmoduleAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "ggit_submodule_get_fetch_recurse" ggit_submodule_get_fetch_recurse ::
Ptr Submodule ->
IO CInt
submoduleGetFetchRecurse ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m Bool
submoduleGetFetchRecurse :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m Bool
submoduleGetFetchRecurse Submodule
submodule = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CInt
result <- Ptr Submodule -> IO CInt
ggit_submodule_get_fetch_recurse Ptr Submodule
submodule'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetFetchRecurseMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod SubmoduleGetFetchRecurseMethodInfo Submodule signature where
overloadedMethod = submoduleGetFetchRecurse
instance O.OverloadedMethodInfo SubmoduleGetFetchRecurseMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetFetchRecurse",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetFetchRecurse"
})
#endif
foreign import ccall "ggit_submodule_get_head_id" ggit_submodule_get_head_id ::
Ptr Submodule ->
IO (Ptr Ggit.OId.OId)
submoduleGetHeadId ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m Ggit.OId.OId
submoduleGetHeadId :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m OId
submoduleGetHeadId Submodule
submodule = IO OId -> m OId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO OId -> m OId) -> IO OId -> m OId
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr OId
result <- Ptr Submodule -> IO (Ptr OId)
ggit_submodule_get_head_id Ptr Submodule
submodule'
Text -> Ptr OId -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"submoduleGetHeadId" Ptr OId
result
OId
result' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
OId -> IO OId
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result'
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetHeadIdMethodInfo
instance (signature ~ (m Ggit.OId.OId), MonadIO m) => O.OverloadedMethod SubmoduleGetHeadIdMethodInfo Submodule signature where
overloadedMethod = submoduleGetHeadId
instance O.OverloadedMethodInfo SubmoduleGetHeadIdMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetHeadId",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetHeadId"
})
#endif
foreign import ccall "ggit_submodule_get_ignore" ggit_submodule_get_ignore ::
Ptr Submodule ->
IO CInt
submoduleGetIgnore ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m Ggit.Enums.SubmoduleIgnore
submoduleGetIgnore :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m SubmoduleIgnore
submoduleGetIgnore Submodule
submodule = IO SubmoduleIgnore -> m SubmoduleIgnore
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SubmoduleIgnore -> m SubmoduleIgnore)
-> IO SubmoduleIgnore -> m SubmoduleIgnore
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CInt
result <- Ptr Submodule -> IO CInt
ggit_submodule_get_ignore Ptr Submodule
submodule'
let result' :: SubmoduleIgnore
result' = (Int -> SubmoduleIgnore
forall a. Enum a => Int -> a
toEnum (Int -> SubmoduleIgnore)
-> (CInt -> Int) -> CInt -> SubmoduleIgnore
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
SubmoduleIgnore -> IO SubmoduleIgnore
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SubmoduleIgnore
result'
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetIgnoreMethodInfo
instance (signature ~ (m Ggit.Enums.SubmoduleIgnore), MonadIO m) => O.OverloadedMethod SubmoduleGetIgnoreMethodInfo Submodule signature where
overloadedMethod = submoduleGetIgnore
instance O.OverloadedMethodInfo SubmoduleGetIgnoreMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetIgnore",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetIgnore"
})
#endif
foreign import ccall "ggit_submodule_get_index_id" ggit_submodule_get_index_id ::
Ptr Submodule ->
IO (Ptr Ggit.OId.OId)
submoduleGetIndexId ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe Ggit.OId.OId)
submoduleGetIndexId :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe OId)
submoduleGetIndexId Submodule
submodule = IO (Maybe OId) -> m (Maybe OId)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OId) -> m (Maybe OId))
-> IO (Maybe OId) -> m (Maybe OId)
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr OId
result <- Ptr Submodule -> IO (Ptr OId)
ggit_submodule_get_index_id Ptr Submodule
submodule'
Maybe OId
maybeResult <- Ptr OId -> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr OId
result ((Ptr OId -> IO OId) -> IO (Maybe OId))
-> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. (a -> b) -> a -> b
$ \Ptr OId
result' -> do
OId
result'' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result'
OId -> IO OId
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe OId -> IO (Maybe OId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetIndexIdMethodInfo
instance (signature ~ (m (Maybe Ggit.OId.OId)), MonadIO m) => O.OverloadedMethod SubmoduleGetIndexIdMethodInfo Submodule signature where
overloadedMethod = submoduleGetIndexId
instance O.OverloadedMethodInfo SubmoduleGetIndexIdMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetIndexId",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetIndexId"
})
#endif
foreign import ccall "ggit_submodule_get_name" ggit_submodule_get_name ::
Ptr Submodule ->
IO CString
submoduleGetName ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe T.Text)
submoduleGetName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Text)
submoduleGetName Submodule
submodule = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CString
result <- Ptr Submodule -> IO CString
ggit_submodule_get_name Ptr Submodule
submodule'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod SubmoduleGetNameMethodInfo Submodule signature where
overloadedMethod = submoduleGetName
instance O.OverloadedMethodInfo SubmoduleGetNameMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetName"
})
#endif
foreign import ccall "ggit_submodule_get_owner" ggit_submodule_get_owner ::
Ptr Submodule ->
IO (Ptr Ggit.Repository.Repository)
submoduleGetOwner ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe Ggit.Repository.Repository)
submoduleGetOwner :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Repository)
submoduleGetOwner Submodule
submodule = IO (Maybe Repository) -> m (Maybe Repository)
forall a. IO a -> m a
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
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr Repository
result <- Ptr Submodule -> IO (Ptr Repository)
ggit_submodule_get_owner Ptr Submodule
submodule'
Maybe Repository
maybeResult <- Ptr Repository
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Repository
result ((Ptr Repository -> IO Repository) -> IO (Maybe Repository))
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. (a -> b) -> a -> b
$ \Ptr Repository
result' -> do
Repository
result'' <- ((ManagedPtr Repository -> Repository)
-> Ptr Repository -> IO Repository
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Repository -> Repository
Ggit.Repository.Repository) Ptr Repository
result'
Repository -> IO Repository
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Repository
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Repository -> IO (Maybe Repository)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Repository
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetOwnerMethodInfo
instance (signature ~ (m (Maybe Ggit.Repository.Repository)), MonadIO m) => O.OverloadedMethod SubmoduleGetOwnerMethodInfo Submodule signature where
overloadedMethod = submoduleGetOwner
instance O.OverloadedMethodInfo SubmoduleGetOwnerMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetOwner",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetOwner"
})
#endif
foreign import ccall "ggit_submodule_get_path" ggit_submodule_get_path ::
Ptr Submodule ->
IO CString
submoduleGetPath ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe T.Text)
submoduleGetPath :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Text)
submoduleGetPath Submodule
submodule = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CString
result <- Ptr Submodule -> IO CString
ggit_submodule_get_path Ptr Submodule
submodule'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetPathMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod SubmoduleGetPathMethodInfo Submodule signature where
overloadedMethod = submoduleGetPath
instance O.OverloadedMethodInfo SubmoduleGetPathMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetPath",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetPath"
})
#endif
foreign import ccall "ggit_submodule_get_update" ggit_submodule_get_update ::
Ptr Submodule ->
IO CUInt
submoduleGetUpdate ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m Ggit.Enums.SubmoduleUpdate
submoduleGetUpdate :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m SubmoduleUpdate
submoduleGetUpdate Submodule
submodule = IO SubmoduleUpdate -> m SubmoduleUpdate
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SubmoduleUpdate -> m SubmoduleUpdate)
-> IO SubmoduleUpdate -> m SubmoduleUpdate
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CUInt
result <- Ptr Submodule -> IO CUInt
ggit_submodule_get_update Ptr Submodule
submodule'
let result' :: SubmoduleUpdate
result' = (Int -> SubmoduleUpdate
forall a. Enum a => Int -> a
toEnum (Int -> SubmoduleUpdate)
-> (CUInt -> Int) -> CUInt -> SubmoduleUpdate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
SubmoduleUpdate -> IO SubmoduleUpdate
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SubmoduleUpdate
result'
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetUpdateMethodInfo
instance (signature ~ (m Ggit.Enums.SubmoduleUpdate), MonadIO m) => O.OverloadedMethod SubmoduleGetUpdateMethodInfo Submodule signature where
overloadedMethod = submoduleGetUpdate
instance O.OverloadedMethodInfo SubmoduleGetUpdateMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetUpdate",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetUpdate"
})
#endif
foreign import ccall "ggit_submodule_get_url" ggit_submodule_get_url ::
Ptr Submodule ->
IO CString
submoduleGetUrl ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe T.Text)
submoduleGetUrl :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Text)
submoduleGetUrl Submodule
submodule = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
CString
result <- Ptr Submodule -> IO CString
ggit_submodule_get_url Ptr Submodule
submodule'
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
$ \CString
result' -> do
Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetUrlMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod SubmoduleGetUrlMethodInfo Submodule signature where
overloadedMethod = submoduleGetUrl
instance O.OverloadedMethodInfo SubmoduleGetUrlMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetUrl",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetUrl"
})
#endif
foreign import ccall "ggit_submodule_get_workdir_id" ggit_submodule_get_workdir_id ::
Ptr Submodule ->
IO (Ptr Ggit.OId.OId)
submoduleGetWorkdirId ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe Ggit.OId.OId)
submoduleGetWorkdirId :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe OId)
submoduleGetWorkdirId Submodule
submodule = IO (Maybe OId) -> m (Maybe OId)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OId) -> m (Maybe OId))
-> IO (Maybe OId) -> m (Maybe OId)
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr OId
result <- Ptr Submodule -> IO (Ptr OId)
ggit_submodule_get_workdir_id Ptr Submodule
submodule'
Maybe OId
maybeResult <- Ptr OId -> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr OId
result ((Ptr OId -> IO OId) -> IO (Maybe OId))
-> (Ptr OId -> IO OId) -> IO (Maybe OId)
forall a b. (a -> b) -> a -> b
$ \Ptr OId
result' -> do
OId
result'' <- ((ManagedPtr OId -> OId) -> Ptr OId -> IO OId
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr OId -> OId
Ggit.OId.OId) Ptr OId
result'
OId -> IO OId
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OId
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe OId -> IO (Maybe OId)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OId
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleGetWorkdirIdMethodInfo
instance (signature ~ (m (Maybe Ggit.OId.OId)), MonadIO m) => O.OverloadedMethod SubmoduleGetWorkdirIdMethodInfo Submodule signature where
overloadedMethod = submoduleGetWorkdirId
instance O.OverloadedMethodInfo SubmoduleGetWorkdirIdMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleGetWorkdirId",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleGetWorkdirId"
})
#endif
foreign import ccall "ggit_submodule_init" ggit_submodule_init ::
Ptr Submodule ->
CInt ->
Ptr (Ptr GError) ->
IO ()
submoduleInit ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> Bool
-> m ()
submoduleInit :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> Bool -> m ()
submoduleInit Submodule
submodule Bool
overwrite = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
let overwrite' :: CInt
overwrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
overwrite
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 Submodule -> CInt -> Ptr (Ptr GError) -> IO ()
ggit_submodule_init Ptr Submodule
submodule' CInt
overwrite'
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
() -> 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 SubmoduleInitMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.OverloadedMethod SubmoduleInitMethodInfo Submodule signature where
overloadedMethod = submoduleInit
instance O.OverloadedMethodInfo SubmoduleInitMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleInit",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleInit"
})
#endif
foreign import ccall "ggit_submodule_open" ggit_submodule_open ::
Ptr Submodule ->
Ptr (Ptr GError) ->
IO (Ptr Ggit.Repository.Repository)
submoduleOpen ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe Ggit.Repository.Repository)
submoduleOpen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Repository)
submoduleOpen Submodule
submodule = IO (Maybe Repository) -> m (Maybe Repository)
forall a. IO a -> m a
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
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
IO (Maybe Repository) -> IO () -> IO (Maybe Repository)
forall a b. IO a -> IO b -> IO a
onException (do
Ptr Repository
result <- (Ptr (Ptr GError) -> IO (Ptr Repository)) -> IO (Ptr Repository)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Repository)) -> IO (Ptr Repository))
-> (Ptr (Ptr GError) -> IO (Ptr Repository)) -> IO (Ptr Repository)
forall a b. (a -> b) -> a -> b
$ Ptr Submodule -> Ptr (Ptr GError) -> IO (Ptr Repository)
ggit_submodule_open Ptr Submodule
submodule'
Maybe Repository
maybeResult <- Ptr Repository
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Repository
result ((Ptr Repository -> IO Repository) -> IO (Maybe Repository))
-> (Ptr Repository -> IO Repository) -> IO (Maybe Repository)
forall a b. (a -> b) -> a -> b
$ \Ptr Repository
result' -> do
Repository
result'' <- ((ManagedPtr Repository -> Repository)
-> Ptr Repository -> IO Repository
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Repository -> Repository
Ggit.Repository.Repository) Ptr Repository
result'
Repository -> IO Repository
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Repository
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Repository -> IO (Maybe Repository)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Repository
maybeResult
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubmoduleOpenMethodInfo
instance (signature ~ (m (Maybe Ggit.Repository.Repository)), MonadIO m) => O.OverloadedMethod SubmoduleOpenMethodInfo Submodule signature where
overloadedMethod = submoduleOpen
instance O.OverloadedMethodInfo SubmoduleOpenMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleOpen",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleOpen"
})
#endif
foreign import ccall "ggit_submodule_ref" ggit_submodule_ref ::
Ptr Submodule ->
IO (Ptr Submodule)
submoduleRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m (Maybe Submodule)
submoduleRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m (Maybe Submodule)
submoduleRef Submodule
submodule = IO (Maybe Submodule) -> m (Maybe Submodule)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Submodule) -> m (Maybe Submodule))
-> IO (Maybe Submodule) -> m (Maybe Submodule)
forall a b. (a -> b) -> a -> b
$ do
Ptr Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr Submodule
result <- Ptr Submodule -> IO (Ptr Submodule)
ggit_submodule_ref Ptr Submodule
submodule'
Maybe Submodule
maybeResult <- Ptr Submodule
-> (Ptr Submodule -> IO Submodule) -> IO (Maybe Submodule)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Submodule
result ((Ptr Submodule -> IO Submodule) -> IO (Maybe Submodule))
-> (Ptr Submodule -> IO Submodule) -> IO (Maybe Submodule)
forall a b. (a -> b) -> a -> b
$ \Ptr Submodule
result' -> do
Submodule
result'' <- ((ManagedPtr Submodule -> Submodule)
-> Ptr Submodule -> IO Submodule
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Submodule -> Submodule
Submodule) Ptr Submodule
result'
Submodule -> IO Submodule
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Submodule
result''
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
Maybe Submodule -> IO (Maybe Submodule)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Submodule
maybeResult
#if defined(ENABLE_OVERLOADING)
data SubmoduleRefMethodInfo
instance (signature ~ (m (Maybe Submodule)), MonadIO m) => O.OverloadedMethod SubmoduleRefMethodInfo Submodule signature where
overloadedMethod = submoduleRef
instance O.OverloadedMethodInfo SubmoduleRefMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleRef"
})
#endif
foreign import ccall "ggit_submodule_reload" ggit_submodule_reload ::
Ptr Submodule ->
CInt ->
Ptr (Ptr GError) ->
IO ()
submoduleReload ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> Bool
-> m ()
submoduleReload :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> Bool -> m ()
submoduleReload Submodule
submodule Bool
force = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
let force' :: CInt
force' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
force
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 Submodule -> CInt -> Ptr (Ptr GError) -> IO ()
ggit_submodule_reload Ptr Submodule
submodule' CInt
force'
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
() -> 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 SubmoduleReloadMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m) => O.OverloadedMethod SubmoduleReloadMethodInfo Submodule signature where
overloadedMethod = submoduleReload
instance O.OverloadedMethodInfo SubmoduleReloadMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleReload",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleReload"
})
#endif
foreign import ccall "ggit_submodule_sync" ggit_submodule_sync ::
Ptr Submodule ->
Ptr (Ptr GError) ->
IO ()
submoduleSync ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m ()
submoduleSync :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m ()
submoduleSync Submodule
submodule = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
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 Submodule -> Ptr (Ptr GError) -> IO ()
ggit_submodule_sync Ptr Submodule
submodule'
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
() -> 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 SubmoduleSyncMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod SubmoduleSyncMethodInfo Submodule signature where
overloadedMethod = submoduleSync
instance O.OverloadedMethodInfo SubmoduleSyncMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleSync",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleSync"
})
#endif
foreign import ccall "ggit_submodule_unref" ggit_submodule_unref ::
Ptr Submodule ->
IO ()
submoduleUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
Submodule
-> m ()
submoduleUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Submodule -> m ()
submoduleUnref Submodule
submodule = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
Ptr Submodule -> IO ()
ggit_submodule_unref Ptr Submodule
submodule'
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SubmoduleUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod SubmoduleUnrefMethodInfo Submodule signature where
overloadedMethod = submoduleUnref
instance O.OverloadedMethodInfo SubmoduleUnrefMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleUnref"
})
#endif
foreign import ccall "ggit_submodule_update" ggit_submodule_update ::
Ptr Submodule ->
CInt ->
Ptr Ggit.SubmoduleUpdateOptions.SubmoduleUpdateOptions ->
Ptr (Ptr GError) ->
IO ()
submoduleUpdate ::
(B.CallStack.HasCallStack, MonadIO m, Ggit.SubmoduleUpdateOptions.IsSubmoduleUpdateOptions a) =>
Submodule
-> Bool
-> a
-> m ()
submoduleUpdate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubmoduleUpdateOptions a) =>
Submodule -> Bool -> a -> m ()
submoduleUpdate Submodule
submodule Bool
init a
options = 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 Submodule
submodule' <- Submodule -> IO (Ptr Submodule)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Submodule
submodule
let init' :: CInt
init' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
init
Ptr SubmoduleUpdateOptions
options' <- a -> IO (Ptr SubmoduleUpdateOptions)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
options
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 Submodule
-> CInt -> Ptr SubmoduleUpdateOptions -> Ptr (Ptr GError) -> IO ()
ggit_submodule_update Ptr Submodule
submodule' CInt
init' Ptr SubmoduleUpdateOptions
options'
Submodule -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Submodule
submodule
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
options
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
)
#if defined(ENABLE_OVERLOADING)
data SubmoduleUpdateMethodInfo
instance (signature ~ (Bool -> a -> m ()), MonadIO m, Ggit.SubmoduleUpdateOptions.IsSubmoduleUpdateOptions a) => O.OverloadedMethod SubmoduleUpdateMethodInfo Submodule signature where
overloadedMethod = submoduleUpdate
instance O.OverloadedMethodInfo SubmoduleUpdateMethodInfo Submodule where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Ggit.Structs.Submodule.submoduleUpdate",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-ggit-1.0.15/docs/GI-Ggit-Structs-Submodule.html#v:submoduleUpdate"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSubmoduleMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSubmoduleMethod "init" o = SubmoduleInitMethodInfo
ResolveSubmoduleMethod "open" o = SubmoduleOpenMethodInfo
ResolveSubmoduleMethod "ref" o = SubmoduleRefMethodInfo
ResolveSubmoduleMethod "reload" o = SubmoduleReloadMethodInfo
ResolveSubmoduleMethod "sync" o = SubmoduleSyncMethodInfo
ResolveSubmoduleMethod "unref" o = SubmoduleUnrefMethodInfo
ResolveSubmoduleMethod "update" o = SubmoduleUpdateMethodInfo
ResolveSubmoduleMethod "getFetchRecurse" o = SubmoduleGetFetchRecurseMethodInfo
ResolveSubmoduleMethod "getHeadId" o = SubmoduleGetHeadIdMethodInfo
ResolveSubmoduleMethod "getIgnore" o = SubmoduleGetIgnoreMethodInfo
ResolveSubmoduleMethod "getIndexId" o = SubmoduleGetIndexIdMethodInfo
ResolveSubmoduleMethod "getName" o = SubmoduleGetNameMethodInfo
ResolveSubmoduleMethod "getOwner" o = SubmoduleGetOwnerMethodInfo
ResolveSubmoduleMethod "getPath" o = SubmoduleGetPathMethodInfo
ResolveSubmoduleMethod "getUpdate" o = SubmoduleGetUpdateMethodInfo
ResolveSubmoduleMethod "getUrl" o = SubmoduleGetUrlMethodInfo
ResolveSubmoduleMethod "getWorkdirId" o = SubmoduleGetWorkdirIdMethodInfo
ResolveSubmoduleMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSubmoduleMethod t Submodule, O.OverloadedMethod info Submodule p) => OL.IsLabel t (Submodule -> 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 ~ ResolveSubmoduleMethod t Submodule, O.OverloadedMethod info Submodule p, R.HasField t Submodule p) => R.HasField t Submodule p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSubmoduleMethod t Submodule, O.OverloadedMethodInfo info Submodule) => OL.IsLabel t (O.MethodProxy info Submodule) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif