{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.SelectionModel
(
SelectionModel(..) ,
IsSelectionModel ,
toSelectionModel ,
#if defined(ENABLE_OVERLOADING)
ResolveSelectionModelMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SelectionModelGetSelectionMethodInfo ,
#endif
selectionModelGetSelection ,
#if defined(ENABLE_OVERLOADING)
SelectionModelGetSelectionInRangeMethodInfo,
#endif
selectionModelGetSelectionInRange ,
#if defined(ENABLE_OVERLOADING)
SelectionModelIsSelectedMethodInfo ,
#endif
selectionModelIsSelected ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSelectAllMethodInfo ,
#endif
selectionModelSelectAll ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSelectItemMethodInfo ,
#endif
selectionModelSelectItem ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSelectRangeMethodInfo ,
#endif
selectionModelSelectRange ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSelectionChangedMethodInfo,
#endif
selectionModelSelectionChanged ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSetSelectionMethodInfo ,
#endif
selectionModelSetSelection ,
#if defined(ENABLE_OVERLOADING)
SelectionModelUnselectAllMethodInfo ,
#endif
selectionModelUnselectAll ,
#if defined(ENABLE_OVERLOADING)
SelectionModelUnselectItemMethodInfo ,
#endif
selectionModelUnselectItem ,
#if defined(ENABLE_OVERLOADING)
SelectionModelUnselectRangeMethodInfo ,
#endif
selectionModelUnselectRange ,
SelectionModelSelectionChangedCallback ,
#if defined(ENABLE_OVERLOADING)
SelectionModelSelectionChangedSignalInfo,
#endif
afterSelectionModelSelectionChanged ,
onSelectionModelSelectionChanged ,
) 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.Structs.Bitset as Gtk.Bitset
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import {-# SOURCE #-} qualified GI.Gtk.Structs.Bitset as Gtk.Bitset
#endif
newtype SelectionModel = SelectionModel (SP.ManagedPtr SelectionModel)
deriving (SelectionModel -> SelectionModel -> Bool
(SelectionModel -> SelectionModel -> Bool)
-> (SelectionModel -> SelectionModel -> Bool) -> Eq SelectionModel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SelectionModel -> SelectionModel -> Bool
== :: SelectionModel -> SelectionModel -> Bool
$c/= :: SelectionModel -> SelectionModel -> Bool
/= :: SelectionModel -> SelectionModel -> Bool
Eq)
instance SP.ManagedPtrNewtype SelectionModel where
toManagedPtr :: SelectionModel -> ManagedPtr SelectionModel
toManagedPtr (SelectionModel ManagedPtr SelectionModel
p) = ManagedPtr SelectionModel
p
foreign import ccall "gtk_selection_model_get_type"
c_gtk_selection_model_get_type :: IO B.Types.GType
instance B.Types.TypedObject SelectionModel where
glibType :: IO GType
glibType = IO GType
c_gtk_selection_model_get_type
instance B.Types.GObject SelectionModel
class (SP.GObject o, O.IsDescendantOf SelectionModel o) => IsSelectionModel o
instance (SP.GObject o, O.IsDescendantOf SelectionModel o) => IsSelectionModel o
instance O.HasParentTypes SelectionModel
type instance O.ParentTypes SelectionModel = '[Gio.ListModel.ListModel, GObject.Object.Object]
toSelectionModel :: (MIO.MonadIO m, IsSelectionModel o) => o -> m SelectionModel
toSelectionModel :: forall (m :: * -> *) o.
(MonadIO m, IsSelectionModel o) =>
o -> m SelectionModel
toSelectionModel = IO SelectionModel -> m SelectionModel
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SelectionModel -> m SelectionModel)
-> (o -> IO SelectionModel) -> o -> m SelectionModel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SelectionModel -> SelectionModel)
-> o -> IO SelectionModel
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SelectionModel -> SelectionModel
SelectionModel
instance B.GValue.IsGValue (Maybe SelectionModel) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_selection_model_get_type
gvalueSet_ :: Ptr GValue -> Maybe SelectionModel -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SelectionModel
P.Nothing = Ptr GValue -> Ptr SelectionModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SelectionModel
forall a. Ptr a
FP.nullPtr :: FP.Ptr SelectionModel)
gvalueSet_ Ptr GValue
gv (P.Just SelectionModel
obj) = SelectionModel -> (Ptr SelectionModel -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SelectionModel
obj (Ptr GValue -> Ptr SelectionModel -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SelectionModel)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr SelectionModel)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SelectionModel)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject SelectionModel ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SelectionModel
type instance O.AttributeList SelectionModel = SelectionModelAttributeList
type SelectionModelAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSelectionModelMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSelectionModelMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSelectionModelMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSelectionModelMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSelectionModelMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSelectionModelMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSelectionModelMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSelectionModelMethod "isSelected" o = SelectionModelIsSelectedMethodInfo
ResolveSelectionModelMethod "itemsChanged" o = Gio.ListModel.ListModelItemsChangedMethodInfo
ResolveSelectionModelMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSelectionModelMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSelectionModelMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSelectionModelMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSelectionModelMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSelectionModelMethod "selectAll" o = SelectionModelSelectAllMethodInfo
ResolveSelectionModelMethod "selectItem" o = SelectionModelSelectItemMethodInfo
ResolveSelectionModelMethod "selectRange" o = SelectionModelSelectRangeMethodInfo
ResolveSelectionModelMethod "selectionChanged" o = SelectionModelSelectionChangedMethodInfo
ResolveSelectionModelMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSelectionModelMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSelectionModelMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSelectionModelMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSelectionModelMethod "unselectAll" o = SelectionModelUnselectAllMethodInfo
ResolveSelectionModelMethod "unselectItem" o = SelectionModelUnselectItemMethodInfo
ResolveSelectionModelMethod "unselectRange" o = SelectionModelUnselectRangeMethodInfo
ResolveSelectionModelMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSelectionModelMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSelectionModelMethod "getItem" o = Gio.ListModel.ListModelGetItemMethodInfo
ResolveSelectionModelMethod "getItemType" o = Gio.ListModel.ListModelGetItemTypeMethodInfo
ResolveSelectionModelMethod "getNItems" o = Gio.ListModel.ListModelGetNItemsMethodInfo
ResolveSelectionModelMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSelectionModelMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSelectionModelMethod "getSelection" o = SelectionModelGetSelectionMethodInfo
ResolveSelectionModelMethod "getSelectionInRange" o = SelectionModelGetSelectionInRangeMethodInfo
ResolveSelectionModelMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSelectionModelMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSelectionModelMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSelectionModelMethod "setSelection" o = SelectionModelSetSelectionMethodInfo
ResolveSelectionModelMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSelectionModelMethod t SelectionModel, O.OverloadedMethod info SelectionModel p) => OL.IsLabel t (SelectionModel -> 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 ~ ResolveSelectionModelMethod t SelectionModel, O.OverloadedMethod info SelectionModel p, R.HasField t SelectionModel p) => R.HasField t SelectionModel p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSelectionModelMethod t SelectionModel, O.OverloadedMethodInfo info SelectionModel) => OL.IsLabel t (O.MethodProxy info SelectionModel) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gtk_selection_model_get_selection" gtk_selection_model_get_selection ::
Ptr SelectionModel ->
IO (Ptr Gtk.Bitset.Bitset)
selectionModelGetSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> m Gtk.Bitset.Bitset
selectionModelGetSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> m Bitset
selectionModelGetSelection a
model = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_get_selection model'
checkUnexpectedReturnNULL "selectionModelGetSelection" result
result' <- (wrapBoxed Gtk.Bitset.Bitset) result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelGetSelectionMethodInfo
instance (signature ~ (m Gtk.Bitset.Bitset), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelGetSelectionMethodInfo a signature where
overloadedMethod = selectionModelGetSelection
instance O.OverloadedMethodInfo SelectionModelGetSelectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelGetSelection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelGetSelection"
})
#endif
foreign import ccall "gtk_selection_model_get_selection_in_range" gtk_selection_model_get_selection_in_range ::
Ptr SelectionModel ->
Word32 ->
Word32 ->
IO (Ptr Gtk.Bitset.Bitset)
selectionModelGetSelectionInRange ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> Word32
-> m Gtk.Bitset.Bitset
selectionModelGetSelectionInRange :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> Word32 -> m Bitset
selectionModelGetSelectionInRange a
model Word32
position Word32
nItems = IO Bitset -> m Bitset
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bitset -> m Bitset) -> IO Bitset -> m Bitset
forall a b. (a -> b) -> a -> b
$ do
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_get_selection_in_range model' position nItems
checkUnexpectedReturnNULL "selectionModelGetSelectionInRange" result
result' <- (wrapBoxed Gtk.Bitset.Bitset) result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelGetSelectionInRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> m Gtk.Bitset.Bitset), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelGetSelectionInRangeMethodInfo a signature where
overloadedMethod = selectionModelGetSelectionInRange
instance O.OverloadedMethodInfo SelectionModelGetSelectionInRangeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelGetSelectionInRange",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelGetSelectionInRange"
})
#endif
foreign import ccall "gtk_selection_model_is_selected" gtk_selection_model_is_selected ::
Ptr SelectionModel ->
Word32 ->
IO CInt
selectionModelIsSelected ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> m Bool
selectionModelIsSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> m Bool
selectionModelIsSelected a
model Word32
position = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_is_selected model' position
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelIsSelectedMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelIsSelectedMethodInfo a signature where
overloadedMethod = selectionModelIsSelected
instance O.OverloadedMethodInfo SelectionModelIsSelectedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelIsSelected",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelIsSelected"
})
#endif
foreign import ccall "gtk_selection_model_select_all" gtk_selection_model_select_all ::
Ptr SelectionModel ->
IO CInt
selectionModelSelectAll ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> m Bool
selectionModelSelectAll :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> m Bool
selectionModelSelectAll a
model = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_select_all model'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelSelectAllMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelSelectAllMethodInfo a signature where
overloadedMethod = selectionModelSelectAll
instance O.OverloadedMethodInfo SelectionModelSelectAllMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelSelectAll",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelSelectAll"
})
#endif
foreign import ccall "gtk_selection_model_select_item" gtk_selection_model_select_item ::
Ptr SelectionModel ->
Word32 ->
CInt ->
IO CInt
selectionModelSelectItem ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> Bool
-> m Bool
selectionModelSelectItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> Bool -> m Bool
selectionModelSelectItem a
model Word32
position Bool
unselectRest = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
let unselectRest' = (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
unselectRest
result <- gtk_selection_model_select_item model' position unselectRest'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelSelectItemMethodInfo
instance (signature ~ (Word32 -> Bool -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelSelectItemMethodInfo a signature where
overloadedMethod = selectionModelSelectItem
instance O.OverloadedMethodInfo SelectionModelSelectItemMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelSelectItem",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelSelectItem"
})
#endif
foreign import ccall "gtk_selection_model_select_range" gtk_selection_model_select_range ::
Ptr SelectionModel ->
Word32 ->
Word32 ->
CInt ->
IO CInt
selectionModelSelectRange ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> Word32
-> Bool
-> m Bool
selectionModelSelectRange :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> Word32 -> Bool -> m Bool
selectionModelSelectRange a
model Word32
position Word32
nItems Bool
unselectRest = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
let unselectRest' = (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
unselectRest
result <- gtk_selection_model_select_range model' position nItems unselectRest'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelSelectRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> Bool -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelSelectRangeMethodInfo a signature where
overloadedMethod = selectionModelSelectRange
instance O.OverloadedMethodInfo SelectionModelSelectRangeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelSelectRange",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelSelectRange"
})
#endif
foreign import ccall "gtk_selection_model_selection_changed" gtk_selection_model_selection_changed ::
Ptr SelectionModel ->
Word32 ->
Word32 ->
IO ()
selectionModelSelectionChanged ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> Word32
-> m ()
selectionModelSelectionChanged :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> Word32 -> m ()
selectionModelSelectionChanged a
model Word32
position Word32
nItems = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
gtk_selection_model_selection_changed model' position nItems
touchManagedPtr model
return ()
#if defined(ENABLE_OVERLOADING)
data SelectionModelSelectionChangedMethodInfo
instance (signature ~ (Word32 -> Word32 -> m ()), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelSelectionChangedMethodInfo a signature where
overloadedMethod = selectionModelSelectionChanged
instance O.OverloadedMethodInfo SelectionModelSelectionChangedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelSelectionChanged",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelSelectionChanged"
})
#endif
foreign import ccall "gtk_selection_model_set_selection" gtk_selection_model_set_selection ::
Ptr SelectionModel ->
Ptr Gtk.Bitset.Bitset ->
Ptr Gtk.Bitset.Bitset ->
IO CInt
selectionModelSetSelection ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Gtk.Bitset.Bitset
-> Gtk.Bitset.Bitset
-> m Bool
selectionModelSetSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Bitset -> Bitset -> m Bool
selectionModelSetSelection a
model Bitset
selected Bitset
mask = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
selected' <- unsafeManagedPtrGetPtr selected
mask' <- unsafeManagedPtrGetPtr mask
result <- gtk_selection_model_set_selection model' selected' mask'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
touchManagedPtr selected
touchManagedPtr mask
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelSetSelectionMethodInfo
instance (signature ~ (Gtk.Bitset.Bitset -> Gtk.Bitset.Bitset -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelSetSelectionMethodInfo a signature where
overloadedMethod = selectionModelSetSelection
instance O.OverloadedMethodInfo SelectionModelSetSelectionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelSetSelection",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelSetSelection"
})
#endif
foreign import ccall "gtk_selection_model_unselect_all" gtk_selection_model_unselect_all ::
Ptr SelectionModel ->
IO CInt
selectionModelUnselectAll ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> m Bool
selectionModelUnselectAll :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> m Bool
selectionModelUnselectAll a
model = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_unselect_all model'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelUnselectAllMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelUnselectAllMethodInfo a signature where
overloadedMethod = selectionModelUnselectAll
instance O.OverloadedMethodInfo SelectionModelUnselectAllMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelUnselectAll",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelUnselectAll"
})
#endif
foreign import ccall "gtk_selection_model_unselect_item" gtk_selection_model_unselect_item ::
Ptr SelectionModel ->
Word32 ->
IO CInt
selectionModelUnselectItem ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> m Bool
selectionModelUnselectItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> m Bool
selectionModelUnselectItem a
model Word32
position = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_unselect_item model' position
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelUnselectItemMethodInfo
instance (signature ~ (Word32 -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelUnselectItemMethodInfo a signature where
overloadedMethod = selectionModelUnselectItem
instance O.OverloadedMethodInfo SelectionModelUnselectItemMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelUnselectItem",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelUnselectItem"
})
#endif
foreign import ccall "gtk_selection_model_unselect_range" gtk_selection_model_unselect_range ::
Ptr SelectionModel ->
Word32 ->
Word32 ->
IO CInt
selectionModelUnselectRange ::
(B.CallStack.HasCallStack, MonadIO m, IsSelectionModel a) =>
a
-> Word32
-> Word32
-> m Bool
selectionModelUnselectRange :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSelectionModel a) =>
a -> Word32 -> Word32 -> m Bool
selectionModelUnselectRange a
model Word32
position Word32
nItems = 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
model' <- a -> IO (Ptr SelectionModel)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
model
result <- gtk_selection_model_unselect_range model' position nItems
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr model
return result'
#if defined(ENABLE_OVERLOADING)
data SelectionModelUnselectRangeMethodInfo
instance (signature ~ (Word32 -> Word32 -> m Bool), MonadIO m, IsSelectionModel a) => O.OverloadedMethod SelectionModelUnselectRangeMethodInfo a signature where
overloadedMethod = selectionModelUnselectRange
instance O.OverloadedMethodInfo SelectionModelUnselectRangeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel.selectionModelUnselectRange",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#v:selectionModelUnselectRange"
})
#endif
type SelectionModelSelectionChangedCallback =
Word32
-> Word32
-> IO ()
type C_SelectionModelSelectionChangedCallback =
Ptr SelectionModel ->
Word32 ->
Word32 ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_SelectionModelSelectionChangedCallback :: C_SelectionModelSelectionChangedCallback -> IO (FunPtr C_SelectionModelSelectionChangedCallback)
wrap_SelectionModelSelectionChangedCallback ::
GObject a => (a -> SelectionModelSelectionChangedCallback) ->
C_SelectionModelSelectionChangedCallback
wrap_SelectionModelSelectionChangedCallback :: forall a.
GObject a =>
(a -> Word32 -> Word32 -> IO ())
-> C_SelectionModelSelectionChangedCallback
wrap_SelectionModelSelectionChangedCallback a -> Word32 -> Word32 -> IO ()
gi'cb Ptr SelectionModel
gi'selfPtr Word32
position Word32
nItems Ptr ()
_ = do
Ptr SelectionModel -> (SelectionModel -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr SelectionModel
gi'selfPtr ((SelectionModel -> IO ()) -> IO ())
-> (SelectionModel -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \SelectionModel
gi'self -> a -> Word32 -> Word32 -> IO ()
gi'cb (SelectionModel -> a
forall a b. Coercible a b => a -> b
Coerce.coerce SelectionModel
gi'self) Word32
position Word32
nItems
onSelectionModelSelectionChanged :: (IsSelectionModel a, MonadIO m) => a -> ((?self :: a) => SelectionModelSelectionChangedCallback) -> m SignalHandlerId
onSelectionModelSelectionChanged :: forall a (m :: * -> *).
(IsSelectionModel a, MonadIO m) =>
a -> ((?self::a) => Word32 -> Word32 -> IO ()) -> m SignalHandlerId
onSelectionModelSelectionChanged a
obj (?self::a) => Word32 -> Word32 -> IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> Word32 -> Word32 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => Word32 -> Word32 -> IO ()
Word32 -> Word32 -> IO ()
cb
let wrapped' :: C_SelectionModelSelectionChangedCallback
wrapped' = (a -> Word32 -> Word32 -> IO ())
-> C_SelectionModelSelectionChangedCallback
forall a.
GObject a =>
(a -> Word32 -> Word32 -> IO ())
-> C_SelectionModelSelectionChangedCallback
wrap_SelectionModelSelectionChangedCallback a -> Word32 -> Word32 -> IO ()
wrapped
wrapped'' <- C_SelectionModelSelectionChangedCallback
-> IO (FunPtr C_SelectionModelSelectionChangedCallback)
mk_SelectionModelSelectionChangedCallback C_SelectionModelSelectionChangedCallback
wrapped'
connectSignalFunPtr obj "selection-changed" wrapped'' SignalConnectBefore Nothing
afterSelectionModelSelectionChanged :: (IsSelectionModel a, MonadIO m) => a -> ((?self :: a) => SelectionModelSelectionChangedCallback) -> m SignalHandlerId
afterSelectionModelSelectionChanged :: forall a (m :: * -> *).
(IsSelectionModel a, MonadIO m) =>
a -> ((?self::a) => Word32 -> Word32 -> IO ()) -> m SignalHandlerId
afterSelectionModelSelectionChanged a
obj (?self::a) => Word32 -> Word32 -> IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> Word32 -> Word32 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => Word32 -> Word32 -> IO ()
Word32 -> Word32 -> IO ()
cb
let wrapped' :: C_SelectionModelSelectionChangedCallback
wrapped' = (a -> Word32 -> Word32 -> IO ())
-> C_SelectionModelSelectionChangedCallback
forall a.
GObject a =>
(a -> Word32 -> Word32 -> IO ())
-> C_SelectionModelSelectionChangedCallback
wrap_SelectionModelSelectionChangedCallback a -> Word32 -> Word32 -> IO ()
wrapped
wrapped'' <- C_SelectionModelSelectionChangedCallback
-> IO (FunPtr C_SelectionModelSelectionChangedCallback)
mk_SelectionModelSelectionChangedCallback C_SelectionModelSelectionChangedCallback
wrapped'
connectSignalFunPtr obj "selection-changed" wrapped'' SignalConnectAfter Nothing
#if defined(ENABLE_OVERLOADING)
data SelectionModelSelectionChangedSignalInfo
instance SignalInfo SelectionModelSelectionChangedSignalInfo where
type HaskellCallbackType SelectionModelSelectionChangedSignalInfo = SelectionModelSelectionChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_SelectionModelSelectionChangedCallback cb
cb'' <- mk_SelectionModelSelectionChangedCallback cb'
connectSignalFunPtr obj "selection-changed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.SelectionModel::selection-changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-SelectionModel.html#g:signal:selectionChanged"})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SelectionModel = SelectionModelSignalList
type SelectionModelSignalList = ('[ '("itemsChanged", Gio.ListModel.ListModelItemsChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("selectionChanged", SelectionModelSelectionChangedSignalInfo)] :: [(Symbol, DK.Type)])
#endif