{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.TextMark
(
TextMark(..) ,
IsTextMark ,
toTextMark ,
#if defined(ENABLE_OVERLOADING)
ResolveTextMarkMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TextMarkGetBufferMethodInfo ,
#endif
textMarkGetBuffer ,
#if defined(ENABLE_OVERLOADING)
TextMarkGetDeletedMethodInfo ,
#endif
textMarkGetDeleted ,
#if defined(ENABLE_OVERLOADING)
TextMarkGetLeftGravityMethodInfo ,
#endif
textMarkGetLeftGravity ,
#if defined(ENABLE_OVERLOADING)
TextMarkGetNameMethodInfo ,
#endif
textMarkGetName ,
#if defined(ENABLE_OVERLOADING)
TextMarkGetVisibleMethodInfo ,
#endif
textMarkGetVisible ,
textMarkNew ,
#if defined(ENABLE_OVERLOADING)
TextMarkSetVisibleMethodInfo ,
#endif
textMarkSetVisible ,
#if defined(ENABLE_OVERLOADING)
TextMarkLeftGravityPropertyInfo ,
#endif
constructTextMarkLeftGravity ,
getTextMarkLeftGravity ,
#if defined(ENABLE_OVERLOADING)
textMarkLeftGravity ,
#endif
#if defined(ENABLE_OVERLOADING)
TextMarkNamePropertyInfo ,
#endif
constructTextMarkName ,
getTextMarkName ,
#if defined(ENABLE_OVERLOADING)
textMarkName ,
#endif
) 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.TextBuffer as Gtk.TextBuffer
newtype TextMark = TextMark (SP.ManagedPtr TextMark)
deriving (TextMark -> TextMark -> Bool
(TextMark -> TextMark -> Bool)
-> (TextMark -> TextMark -> Bool) -> Eq TextMark
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextMark -> TextMark -> Bool
== :: TextMark -> TextMark -> Bool
$c/= :: TextMark -> TextMark -> Bool
/= :: TextMark -> TextMark -> Bool
Eq)
instance SP.ManagedPtrNewtype TextMark where
toManagedPtr :: TextMark -> ManagedPtr TextMark
toManagedPtr (TextMark ManagedPtr TextMark
p) = ManagedPtr TextMark
p
foreign import ccall "gtk_text_mark_get_type"
c_gtk_text_mark_get_type :: IO B.Types.GType
instance B.Types.TypedObject TextMark where
glibType :: IO GType
glibType = IO GType
c_gtk_text_mark_get_type
instance B.Types.GObject TextMark
class (SP.GObject o, O.IsDescendantOf TextMark o) => IsTextMark o
instance (SP.GObject o, O.IsDescendantOf TextMark o) => IsTextMark o
instance O.HasParentTypes TextMark
type instance O.ParentTypes TextMark = '[GObject.Object.Object]
toTextMark :: (MIO.MonadIO m, IsTextMark o) => o -> m TextMark
toTextMark :: forall (m :: * -> *) o.
(MonadIO m, IsTextMark o) =>
o -> m TextMark
toTextMark = IO TextMark -> m TextMark
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO TextMark -> m TextMark)
-> (o -> IO TextMark) -> o -> m TextMark
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr TextMark -> TextMark) -> o -> IO TextMark
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr TextMark -> TextMark
TextMark
instance B.GValue.IsGValue (Maybe TextMark) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_text_mark_get_type
gvalueSet_ :: Ptr GValue -> Maybe TextMark -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TextMark
P.Nothing = Ptr GValue -> Ptr TextMark -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TextMark
forall a. Ptr a
FP.nullPtr :: FP.Ptr TextMark)
gvalueSet_ Ptr GValue
gv (P.Just TextMark
obj) = TextMark -> (Ptr TextMark -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TextMark
obj (Ptr GValue -> Ptr TextMark -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe TextMark)
gvalueGet_ Ptr GValue
gv = do
Ptr TextMark
ptr <- Ptr GValue -> IO (Ptr TextMark)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TextMark)
if Ptr TextMark
ptr Ptr TextMark -> Ptr TextMark -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TextMark
forall a. Ptr a
FP.nullPtr
then TextMark -> Maybe TextMark
forall a. a -> Maybe a
P.Just (TextMark -> Maybe TextMark) -> IO TextMark -> IO (Maybe TextMark)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr TextMark -> TextMark) -> Ptr TextMark -> IO TextMark
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TextMark -> TextMark
TextMark Ptr TextMark
ptr
else Maybe TextMark -> IO (Maybe TextMark)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TextMark
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveTextMarkMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveTextMarkMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveTextMarkMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveTextMarkMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveTextMarkMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveTextMarkMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveTextMarkMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveTextMarkMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveTextMarkMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveTextMarkMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveTextMarkMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveTextMarkMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveTextMarkMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveTextMarkMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveTextMarkMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveTextMarkMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveTextMarkMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveTextMarkMethod "getBuffer" o = TextMarkGetBufferMethodInfo
ResolveTextMarkMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveTextMarkMethod "getDeleted" o = TextMarkGetDeletedMethodInfo
ResolveTextMarkMethod "getLeftGravity" o = TextMarkGetLeftGravityMethodInfo
ResolveTextMarkMethod "getName" o = TextMarkGetNameMethodInfo
ResolveTextMarkMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveTextMarkMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveTextMarkMethod "getVisible" o = TextMarkGetVisibleMethodInfo
ResolveTextMarkMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveTextMarkMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveTextMarkMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveTextMarkMethod "setVisible" o = TextMarkSetVisibleMethodInfo
ResolveTextMarkMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextMarkMethod t TextMark, O.OverloadedMethod info TextMark p) => OL.IsLabel t (TextMark -> 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 ~ ResolveTextMarkMethod t TextMark, O.OverloadedMethod info TextMark p, R.HasField t TextMark p) => R.HasField t TextMark p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTextMarkMethod t TextMark, O.OverloadedMethodInfo info TextMark) => OL.IsLabel t (O.MethodProxy info TextMark) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getTextMarkLeftGravity :: (MonadIO m, IsTextMark o) => o -> m Bool
getTextMarkLeftGravity :: forall (m :: * -> *) o. (MonadIO m, IsTextMark o) => o -> m Bool
getTextMarkLeftGravity o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"left-gravity"
constructTextMarkLeftGravity :: (IsTextMark o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructTextMarkLeftGravity :: forall o (m :: * -> *).
(IsTextMark o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructTextMarkLeftGravity Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"left-gravity" Bool
val
#if defined(ENABLE_OVERLOADING)
data TextMarkLeftGravityPropertyInfo
instance AttrInfo TextMarkLeftGravityPropertyInfo where
type AttrAllowedOps TextMarkLeftGravityPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint TextMarkLeftGravityPropertyInfo = IsTextMark
type AttrSetTypeConstraint TextMarkLeftGravityPropertyInfo = (~) Bool
type AttrTransferTypeConstraint TextMarkLeftGravityPropertyInfo = (~) Bool
type AttrTransferType TextMarkLeftGravityPropertyInfo = Bool
type AttrGetType TextMarkLeftGravityPropertyInfo = Bool
type AttrLabel TextMarkLeftGravityPropertyInfo = "left-gravity"
type AttrOrigin TextMarkLeftGravityPropertyInfo = TextMark
attrGet = getTextMarkLeftGravity
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTextMarkLeftGravity
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.leftGravity"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#g:attr:leftGravity"
})
#endif
getTextMarkName :: (MonadIO m, IsTextMark o) => o -> m (Maybe T.Text)
getTextMarkName :: forall (m :: * -> *) o.
(MonadIO m, IsTextMark o) =>
o -> m (Maybe Text)
getTextMarkName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"
constructTextMarkName :: (IsTextMark o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructTextMarkName :: forall o (m :: * -> *).
(IsTextMark o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructTextMarkName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data TextMarkNamePropertyInfo
instance AttrInfo TextMarkNamePropertyInfo where
type AttrAllowedOps TextMarkNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint TextMarkNamePropertyInfo = IsTextMark
type AttrSetTypeConstraint TextMarkNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint TextMarkNamePropertyInfo = (~) T.Text
type AttrTransferType TextMarkNamePropertyInfo = T.Text
type AttrGetType TextMarkNamePropertyInfo = (Maybe T.Text)
type AttrLabel TextMarkNamePropertyInfo = "name"
type AttrOrigin TextMarkNamePropertyInfo = TextMark
attrGet = getTextMarkName
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructTextMarkName
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.name"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#g:attr:name"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TextMark
type instance O.AttributeList TextMark = TextMarkAttributeList
type TextMarkAttributeList = ('[ '("leftGravity", TextMarkLeftGravityPropertyInfo), '("name", TextMarkNamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
textMarkLeftGravity :: AttrLabelProxy "leftGravity"
textMarkLeftGravity = AttrLabelProxy
textMarkName :: AttrLabelProxy "name"
textMarkName = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TextMark = TextMarkSignalList
type TextMarkSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_text_mark_new" gtk_text_mark_new ::
CString ->
CInt ->
IO (Ptr TextMark)
textMarkNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (T.Text)
-> Bool
-> m TextMark
textMarkNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> Bool -> m TextMark
textMarkNew Maybe Text
name Bool
leftGravity = IO TextMark -> m TextMark
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextMark -> m TextMark) -> IO TextMark -> m TextMark
forall a b. (a -> b) -> a -> b
$ do
Ptr CChar
maybeName <- case Maybe Text
name 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
jName -> do
Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
let leftGravity' :: CInt
leftGravity' = (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
leftGravity
Ptr TextMark
result <- Ptr CChar -> CInt -> IO (Ptr TextMark)
gtk_text_mark_new Ptr CChar
maybeName CInt
leftGravity'
Text -> Ptr TextMark -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textMarkNew" Ptr TextMark
result
TextMark
result' <- ((ManagedPtr TextMark -> TextMark) -> Ptr TextMark -> IO TextMark
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr TextMark -> TextMark
TextMark) Ptr TextMark
result
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
TextMark -> IO TextMark
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TextMark
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_text_mark_get_buffer" gtk_text_mark_get_buffer ::
Ptr TextMark ->
IO (Ptr Gtk.TextBuffer.TextBuffer)
textMarkGetBuffer ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> m Gtk.TextBuffer.TextBuffer
textMarkGetBuffer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> m TextBuffer
textMarkGetBuffer a
mark = IO TextBuffer -> m TextBuffer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextBuffer -> m TextBuffer) -> IO TextBuffer -> m TextBuffer
forall a b. (a -> b) -> a -> b
$ do
Ptr TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
Ptr TextBuffer
result <- Ptr TextMark -> IO (Ptr TextBuffer)
gtk_text_mark_get_buffer Ptr TextMark
mark'
Text -> Ptr TextBuffer -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"textMarkGetBuffer" Ptr TextBuffer
result
TextBuffer
result' <- ((ManagedPtr TextBuffer -> TextBuffer)
-> Ptr TextBuffer -> IO TextBuffer
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr TextBuffer -> TextBuffer
Gtk.TextBuffer.TextBuffer) Ptr TextBuffer
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
TextBuffer -> IO TextBuffer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return TextBuffer
result'
#if defined(ENABLE_OVERLOADING)
data TextMarkGetBufferMethodInfo
instance (signature ~ (m Gtk.TextBuffer.TextBuffer), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkGetBufferMethodInfo a signature where
overloadedMethod = textMarkGetBuffer
instance O.OverloadedMethodInfo TextMarkGetBufferMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkGetBuffer",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkGetBuffer"
})
#endif
foreign import ccall "gtk_text_mark_get_deleted" gtk_text_mark_get_deleted ::
Ptr TextMark ->
IO CInt
textMarkGetDeleted ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> m Bool
textMarkGetDeleted :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> m Bool
textMarkGetDeleted a
mark = 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 TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
CInt
result <- Ptr TextMark -> IO CInt
gtk_text_mark_get_deleted Ptr TextMark
mark'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextMarkGetDeletedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkGetDeletedMethodInfo a signature where
overloadedMethod = textMarkGetDeleted
instance O.OverloadedMethodInfo TextMarkGetDeletedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkGetDeleted",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkGetDeleted"
})
#endif
foreign import ccall "gtk_text_mark_get_left_gravity" gtk_text_mark_get_left_gravity ::
Ptr TextMark ->
IO CInt
textMarkGetLeftGravity ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> m Bool
textMarkGetLeftGravity :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> m Bool
textMarkGetLeftGravity a
mark = 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 TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
CInt
result <- Ptr TextMark -> IO CInt
gtk_text_mark_get_left_gravity Ptr TextMark
mark'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextMarkGetLeftGravityMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkGetLeftGravityMethodInfo a signature where
overloadedMethod = textMarkGetLeftGravity
instance O.OverloadedMethodInfo TextMarkGetLeftGravityMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkGetLeftGravity",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkGetLeftGravity"
})
#endif
foreign import ccall "gtk_text_mark_get_name" gtk_text_mark_get_name ::
Ptr TextMark ->
IO CString
textMarkGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> m (Maybe T.Text)
textMarkGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> m (Maybe Text)
textMarkGetName a
mark = 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 TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
Ptr CChar
result <- Ptr TextMark -> IO (Ptr CChar)
gtk_text_mark_get_name Ptr TextMark
mark'
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'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
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 TextMarkGetNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkGetNameMethodInfo a signature where
overloadedMethod = textMarkGetName
instance O.OverloadedMethodInfo TextMarkGetNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkGetName"
})
#endif
foreign import ccall "gtk_text_mark_get_visible" gtk_text_mark_get_visible ::
Ptr TextMark ->
IO CInt
textMarkGetVisible ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> m Bool
textMarkGetVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> m Bool
textMarkGetVisible a
mark = 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 TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
CInt
result <- Ptr TextMark -> IO CInt
gtk_text_mark_get_visible Ptr TextMark
mark'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data TextMarkGetVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkGetVisibleMethodInfo a signature where
overloadedMethod = textMarkGetVisible
instance O.OverloadedMethodInfo TextMarkGetVisibleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkGetVisible",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkGetVisible"
})
#endif
foreign import ccall "gtk_text_mark_set_visible" gtk_text_mark_set_visible ::
Ptr TextMark ->
CInt ->
IO ()
textMarkSetVisible ::
(B.CallStack.HasCallStack, MonadIO m, IsTextMark a) =>
a
-> Bool
-> m ()
textMarkSetVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTextMark a) =>
a -> Bool -> m ()
textMarkSetVisible a
mark Bool
setting = 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 TextMark
mark' <- a -> IO (Ptr TextMark)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
mark
let setting' :: CInt
setting' = (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
setting
Ptr TextMark -> CInt -> IO ()
gtk_text_mark_set_visible Ptr TextMark
mark' CInt
setting'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
mark
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TextMarkSetVisibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsTextMark a) => O.OverloadedMethod TextMarkSetVisibleMethodInfo a signature where
overloadedMethod = textMarkSetVisible
instance O.OverloadedMethodInfo TextMarkSetVisibleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.TextMark.textMarkSetVisible",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Objects-TextMark.html#v:textMarkSetVisible"
})
#endif