{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.StringList
(
StringList(..) ,
IsStringList ,
toStringList ,
#if defined(ENABLE_OVERLOADING)
ResolveStringListMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
StringListAppendMethodInfo ,
#endif
stringListAppend ,
#if defined(ENABLE_OVERLOADING)
StringListFindMethodInfo ,
#endif
stringListFind ,
#if defined(ENABLE_OVERLOADING)
StringListGetStringMethodInfo ,
#endif
stringListGetString ,
stringListNew ,
#if defined(ENABLE_OVERLOADING)
StringListRemoveMethodInfo ,
#endif
stringListRemove ,
#if defined(ENABLE_OVERLOADING)
StringListSpliceMethodInfo ,
#endif
stringListSplice ,
#if defined(ENABLE_OVERLOADING)
StringListTakeMethodInfo ,
#endif
stringListTake ,
#if defined(ENABLE_OVERLOADING)
StringListItemTypePropertyInfo ,
#endif
getStringListItemType ,
#if defined(ENABLE_OVERLOADING)
stringListItemType ,
#endif
#if defined(ENABLE_OVERLOADING)
StringListNItemsPropertyInfo ,
#endif
getStringListNItems ,
#if defined(ENABLE_OVERLOADING)
stringListNItems ,
#endif
#if defined(ENABLE_OVERLOADING)
StringListStringsPropertyInfo ,
#endif
constructStringListStrings ,
#if defined(ENABLE_OVERLOADING)
stringListStrings ,
#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 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.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
#endif
newtype StringList = StringList (SP.ManagedPtr StringList)
deriving (StringList -> StringList -> Bool
(StringList -> StringList -> Bool)
-> (StringList -> StringList -> Bool) -> Eq StringList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StringList -> StringList -> Bool
== :: StringList -> StringList -> Bool
$c/= :: StringList -> StringList -> Bool
/= :: StringList -> StringList -> Bool
Eq)
instance SP.ManagedPtrNewtype StringList where
toManagedPtr :: StringList -> ManagedPtr StringList
toManagedPtr (StringList ManagedPtr StringList
p) = ManagedPtr StringList
p
foreign import ccall "gtk_string_list_get_type"
c_gtk_string_list_get_type :: IO B.Types.GType
instance B.Types.TypedObject StringList where
glibType :: IO GType
glibType = IO GType
c_gtk_string_list_get_type
instance B.Types.GObject StringList
class (SP.GObject o, O.IsDescendantOf StringList o) => IsStringList o
instance (SP.GObject o, O.IsDescendantOf StringList o) => IsStringList o
instance O.HasParentTypes StringList
type instance O.ParentTypes StringList = '[GObject.Object.Object, Gio.ListModel.ListModel, Gtk.Buildable.Buildable]
toStringList :: (MIO.MonadIO m, IsStringList o) => o -> m StringList
toStringList :: forall (m :: * -> *) o.
(MonadIO m, IsStringList o) =>
o -> m StringList
toStringList = IO StringList -> m StringList
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO StringList -> m StringList)
-> (o -> IO StringList) -> o -> m StringList
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr StringList -> StringList) -> o -> IO StringList
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StringList -> StringList
StringList
instance B.GValue.IsGValue (Maybe StringList) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_string_list_get_type
gvalueSet_ :: Ptr GValue -> Maybe StringList -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StringList
P.Nothing = Ptr GValue -> Ptr StringList -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StringList
forall a. Ptr a
FP.nullPtr :: FP.Ptr StringList)
gvalueSet_ Ptr GValue
gv (P.Just StringList
obj) = StringList -> (Ptr StringList -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StringList
obj (Ptr GValue -> Ptr StringList -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe StringList)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr StringList)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StringList)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject StringList ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveStringListMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveStringListMethod "append" o = StringListAppendMethodInfo
ResolveStringListMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveStringListMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveStringListMethod "find" o = StringListFindMethodInfo
ResolveStringListMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveStringListMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveStringListMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveStringListMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveStringListMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
ResolveStringListMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveStringListMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveStringListMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveStringListMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveStringListMethod "remove" o = StringListRemoveMethodInfo
ResolveStringListMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveStringListMethod "splice" o = StringListSpliceMethodInfo
ResolveStringListMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveStringListMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveStringListMethod "take" o = StringListTakeMethodInfo
ResolveStringListMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveStringListMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveStringListMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveStringListMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
ResolveStringListMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveStringListMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
ResolveStringListMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
ResolveStringListMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
ResolveStringListMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveStringListMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveStringListMethod "getString" o = StringListGetStringMethodInfo
ResolveStringListMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveStringListMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveStringListMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveStringListMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveStringListMethod t StringList, O.OverloadedMethod info StringList p) => OL.IsLabel t (StringList -> 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 ~ ResolveStringListMethod t StringList, O.OverloadedMethod info StringList p, R.HasField t StringList p) => R.HasField t StringList p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveStringListMethod t StringList, O.OverloadedMethodInfo info StringList) => OL.IsLabel t (O.MethodProxy info StringList) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getStringListItemType :: (MonadIO m, IsStringList o) => o -> m GType
getStringListItemType :: forall (m :: * -> *) o. (MonadIO m, IsStringList o) => o -> m GType
getStringListItemType o
obj = IO GType -> m GType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO GType
forall a. GObject a => a -> String -> IO GType
B.Properties.getObjectPropertyGType o
obj String
"item-type"
#if defined(ENABLE_OVERLOADING)
data StringListItemTypePropertyInfo
instance AttrInfo StringListItemTypePropertyInfo where
type AttrAllowedOps StringListItemTypePropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint StringListItemTypePropertyInfo = IsStringList
type AttrSetTypeConstraint StringListItemTypePropertyInfo = (~) ()
type AttrTransferTypeConstraint StringListItemTypePropertyInfo = (~) ()
type AttrTransferType StringListItemTypePropertyInfo = ()
type AttrGetType StringListItemTypePropertyInfo = GType
type AttrLabel StringListItemTypePropertyInfo = "item-type"
type AttrOrigin StringListItemTypePropertyInfo = StringList
attrGet = getStringListItemType
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.itemType"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#g:attr:itemType"
})
#endif
getStringListNItems :: (MonadIO m, IsStringList o) => o -> m Word32
getStringListNItems :: forall (m :: * -> *) o.
(MonadIO m, IsStringList o) =>
o -> m Word32
getStringListNItems o
obj = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj String
"n-items"
#if defined(ENABLE_OVERLOADING)
data StringListNItemsPropertyInfo
instance AttrInfo StringListNItemsPropertyInfo where
type AttrAllowedOps StringListNItemsPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint StringListNItemsPropertyInfo = IsStringList
type AttrSetTypeConstraint StringListNItemsPropertyInfo = (~) ()
type AttrTransferTypeConstraint StringListNItemsPropertyInfo = (~) ()
type AttrTransferType StringListNItemsPropertyInfo = ()
type AttrGetType StringListNItemsPropertyInfo = Word32
type AttrLabel StringListNItemsPropertyInfo = "n-items"
type AttrOrigin StringListNItemsPropertyInfo = StringList
attrGet = getStringListNItems
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.nItems"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#g:attr:nItems"
})
#endif
constructStringListStrings :: (IsStringList o, MIO.MonadIO m) => [T.Text] -> m (GValueConstruct o)
constructStringListStrings :: forall o (m :: * -> *).
(IsStringList o, MonadIO m) =>
[Text] -> m (GValueConstruct o)
constructStringListStrings [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.constructObjectPropertyStringArray String
"strings" ([Text] -> Maybe [Text]
forall a. a -> Maybe a
P.Just [Text]
val)
#if defined(ENABLE_OVERLOADING)
data StringListStringsPropertyInfo
instance AttrInfo StringListStringsPropertyInfo where
type AttrAllowedOps StringListStringsPropertyInfo = '[ 'AttrConstruct, 'AttrClear]
type AttrBaseTypeConstraint StringListStringsPropertyInfo = IsStringList
type AttrSetTypeConstraint StringListStringsPropertyInfo = (~) [T.Text]
type AttrTransferTypeConstraint StringListStringsPropertyInfo = (~) [T.Text]
type AttrTransferType StringListStringsPropertyInfo = [T.Text]
type AttrGetType StringListStringsPropertyInfo = ()
type AttrLabel StringListStringsPropertyInfo = "strings"
type AttrOrigin StringListStringsPropertyInfo = StringList
attrGet = undefined
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructStringListStrings
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.strings"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#g:attr:strings"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StringList
type instance O.AttributeList StringList = StringListAttributeList
type StringListAttributeList = ('[ '("itemType", StringListItemTypePropertyInfo), '("nItems", StringListNItemsPropertyInfo), '("strings", StringListStringsPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
stringListItemType :: AttrLabelProxy "itemType"
stringListItemType = AttrLabelProxy
stringListNItems :: AttrLabelProxy "nItems"
stringListNItems = AttrLabelProxy
stringListStrings :: AttrLabelProxy "strings"
stringListStrings = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StringList = StringListSignalList
type StringListSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_string_list_new" gtk_string_list_new ::
Ptr CString ->
IO (Ptr StringList)
stringListNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe ([T.Text])
-> m StringList
stringListNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe [Text] -> m StringList
stringListNew Maybe [Text]
strings = IO StringList -> m StringList
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StringList -> m StringList) -> IO StringList -> m StringList
forall a b. (a -> b) -> a -> b
$ do
maybeStrings <- case Maybe [Text]
strings of
Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
FP.nullPtr
Just [Text]
jStrings -> do
jStrings' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jStrings
return jStrings'
result <- gtk_string_list_new maybeStrings
checkUnexpectedReturnNULL "stringListNew" result
result' <- (wrapObject StringList) result
mapZeroTerminatedCArray freeMem maybeStrings
freeMem maybeStrings
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_string_list_append" gtk_string_list_append ::
Ptr StringList ->
CString ->
IO ()
stringListAppend ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> T.Text
-> m ()
stringListAppend :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Text -> m ()
stringListAppend a
self Text
string = 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
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
string' <- textToCString string
gtk_string_list_append self' string'
touchManagedPtr self
freeMem string'
return ()
#if defined(ENABLE_OVERLOADING)
data StringListAppendMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListAppendMethodInfo a signature where
overloadedMethod = stringListAppend
instance O.OverloadedMethodInfo StringListAppendMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListAppend",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListAppend"
})
#endif
foreign import ccall "gtk_string_list_find" gtk_string_list_find ::
Ptr StringList ->
CString ->
IO Word32
stringListFind ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> T.Text
-> m Word32
stringListFind :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Text -> m Word32
stringListFind a
self Text
string = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
string' <- textToCString string
result <- gtk_string_list_find self' string'
touchManagedPtr self
freeMem string'
return result
#if defined(ENABLE_OVERLOADING)
data StringListFindMethodInfo
instance (signature ~ (T.Text -> m Word32), MonadIO m, IsStringList a) => O.OverloadedMethod StringListFindMethodInfo a signature where
overloadedMethod = stringListFind
instance O.OverloadedMethodInfo StringListFindMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListFind",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListFind"
})
#endif
foreign import ccall "gtk_string_list_get_string" gtk_string_list_get_string ::
Ptr StringList ->
Word32 ->
IO CString
stringListGetString ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> Word32
-> m (Maybe T.Text)
stringListGetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> m (Maybe Text)
stringListGetString a
self Word32
position = 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
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- gtk_string_list_get_string self' position
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr self
return maybeResult
#if defined(ENABLE_OVERLOADING)
data StringListGetStringMethodInfo
instance (signature ~ (Word32 -> m (Maybe T.Text)), MonadIO m, IsStringList a) => O.OverloadedMethod StringListGetStringMethodInfo a signature where
overloadedMethod = stringListGetString
instance O.OverloadedMethodInfo StringListGetStringMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListGetString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListGetString"
})
#endif
foreign import ccall "gtk_string_list_remove" gtk_string_list_remove ::
Ptr StringList ->
Word32 ->
IO ()
stringListRemove ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> Word32
-> m ()
stringListRemove :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> m ()
stringListRemove a
self Word32
position = 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
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
gtk_string_list_remove self' position
touchManagedPtr self
return ()
#if defined(ENABLE_OVERLOADING)
data StringListRemoveMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListRemoveMethodInfo a signature where
overloadedMethod = stringListRemove
instance O.OverloadedMethodInfo StringListRemoveMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListRemove",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListRemove"
})
#endif
foreign import ccall "gtk_string_list_splice" gtk_string_list_splice ::
Ptr StringList ->
Word32 ->
Word32 ->
Ptr CString ->
IO ()
stringListSplice ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> Word32
-> Word32
-> Maybe ([T.Text])
-> m ()
stringListSplice :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Word32 -> Word32 -> Maybe [Text] -> m ()
stringListSplice a
self Word32
position Word32
nRemovals Maybe [Text]
additions = 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
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
maybeAdditions <- case additions of
Maybe [Text]
Nothing -> Ptr CString -> IO (Ptr CString)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CString
forall a. Ptr a
FP.nullPtr
Just [Text]
jAdditions -> do
jAdditions' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
jAdditions
return jAdditions'
gtk_string_list_splice self' position nRemovals maybeAdditions
touchManagedPtr self
mapZeroTerminatedCArray freeMem maybeAdditions
freeMem maybeAdditions
return ()
#if defined(ENABLE_OVERLOADING)
data StringListSpliceMethodInfo
instance (signature ~ (Word32 -> Word32 -> Maybe ([T.Text]) -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListSpliceMethodInfo a signature where
overloadedMethod = stringListSplice
instance O.OverloadedMethodInfo StringListSpliceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListSplice",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListSplice"
})
#endif
foreign import ccall "gtk_string_list_take" gtk_string_list_take ::
Ptr StringList ->
CString ->
IO ()
stringListTake ::
(B.CallStack.HasCallStack, MonadIO m, IsStringList a) =>
a
-> T.Text
-> m ()
stringListTake :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStringList a) =>
a -> Text -> m ()
stringListTake a
self Text
string = 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
self' <- a -> IO (Ptr StringList)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
string' <- textToCString string
gtk_string_list_take self' string'
touchManagedPtr self
return ()
#if defined(ENABLE_OVERLOADING)
data StringListTakeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsStringList a) => O.OverloadedMethod StringListTakeMethodInfo a signature where
overloadedMethod = stringListTake
instance O.OverloadedMethodInfo StringListTakeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.StringList.stringListTake",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-StringList.html#v:stringListTake"
})
#endif