| Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte | 
|---|---|
| License | LGPL-2.1 | 
| Maintainer | Iñaki García Etxebarria | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
GI.Gtk.Objects.EntryCompletion
Contents
- Exported types
- Methods- complete
- computePrefix
- getCompletionPrefix
- getEntry
- getInlineCompletion
- getInlineSelection
- getMinimumKeyLength
- getModel
- getPopupCompletion
- getPopupSetWidth
- getPopupSingleMatch
- getTextColumn
- insertPrefix
- new
- newWithArea
- setInlineCompletion
- setInlineSelection
- setMatchFunc
- setMinimumKeyLength
- setModel
- setPopupCompletion
- setPopupSetWidth
- setPopupSingleMatch
- setTextColumn
 
- Properties
- Signals
Description
EntryCompletion is an auxiliary object to be used in conjunction with
 Entry to provide the completion functionality. It implements the
 CellLayout interface, to allow the user to add extra cells to the
 TreeView with completion matches.
“Completion functionality” means that when the user modifies the text
 in the entry, EntryCompletion checks which rows in the model match
 the current content of the entry, and displays a list of matches.
 By default, the matching is done by comparing the entry text
 case-insensitively against the text column of the model (see
 entryCompletionSetTextColumn), but this can be overridden
 with a custom match function (see entryCompletionSetMatchFunc).
When the user selects a completion, the content of the entry is
 updated. By default, the content of the entry is replaced by the
 text column of the model, but this can be overridden by connecting
 to the matchSelected signal and updating the
 entry in the signal handler. Note that you should return True from
 the signal handler to suppress the default behaviour.
To add completion functionality to an entry, use entrySetCompletion.
GtkEntryCompletion uses a TreeModelFilter model to represent the
 subset of the entire model that is currently matching. While the
 GtkEntryCompletion signals matchSelected and
 cursorOnMatch take the original model and an
 iter pointing to that model as arguments, other callbacks and signals
 (such as GtkCellLayoutDataFuncs or applyAttributes)
 will generally take the filter model as argument. As long as you are
 only calling gtk_tree_model_get(), this will make no difference to
 you. If for some reason, you need the original model, use
 treeModelFilterGetModel. Don’t forget to use
 treeModelFilterConvertIterToChildIter to obtain a
 matching iter.
Synopsis
- newtype EntryCompletion = EntryCompletion (ManagedPtr EntryCompletion)
- class (GObject o, IsDescendantOf EntryCompletion o) => IsEntryCompletion o
- toEntryCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m EntryCompletion
- entryCompletionComplete :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m ()
- entryCompletionComputePrefix :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Text -> m (Maybe Text)
- entryCompletionGetCompletionPrefix :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m (Maybe Text)
- entryCompletionGetEntry :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Widget
- entryCompletionGetInlineCompletion :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Bool
- entryCompletionGetInlineSelection :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Bool
- entryCompletionGetMinimumKeyLength :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Int32
- entryCompletionGetModel :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m (Maybe TreeModel)
- entryCompletionGetPopupCompletion :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Bool
- entryCompletionGetPopupSetWidth :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Bool
- entryCompletionGetPopupSingleMatch :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Bool
- entryCompletionGetTextColumn :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m Int32
- entryCompletionInsertPrefix :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> m ()
- entryCompletionNew :: (HasCallStack, MonadIO m) => m EntryCompletion
- entryCompletionNewWithArea :: (HasCallStack, MonadIO m, IsCellArea a) => a -> m EntryCompletion
- entryCompletionSetInlineCompletion :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Bool -> m ()
- entryCompletionSetInlineSelection :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Bool -> m ()
- entryCompletionSetMatchFunc :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> EntryCompletionMatchFunc -> m ()
- entryCompletionSetMinimumKeyLength :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Int32 -> m ()
- entryCompletionSetModel :: (HasCallStack, MonadIO m, IsEntryCompletion a, IsTreeModel b) => a -> Maybe b -> m ()
- entryCompletionSetPopupCompletion :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Bool -> m ()
- entryCompletionSetPopupSetWidth :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Bool -> m ()
- entryCompletionSetPopupSingleMatch :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Bool -> m ()
- entryCompletionSetTextColumn :: (HasCallStack, MonadIO m, IsEntryCompletion a) => a -> Int32 -> m ()
- constructEntryCompletionCellArea :: (IsEntryCompletion o, MonadIO m, IsCellArea a) => a -> m (GValueConstruct o)
- getEntryCompletionCellArea :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe CellArea)
- constructEntryCompletionInlineCompletion :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o)
- getEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
- setEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
- constructEntryCompletionInlineSelection :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o)
- getEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
- setEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
- constructEntryCompletionMinimumKeyLength :: (IsEntryCompletion o, MonadIO m) => Int32 -> m (GValueConstruct o)
- getEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> m Int32
- setEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m ()
- clearEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m ()
- constructEntryCompletionModel :: (IsEntryCompletion o, MonadIO m, IsTreeModel a) => a -> m (GValueConstruct o)
- getEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe TreeModel)
- setEntryCompletionModel :: (MonadIO m, IsEntryCompletion o, IsTreeModel a) => o -> a -> m ()
- constructEntryCompletionPopupCompletion :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o)
- getEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
- setEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
- constructEntryCompletionPopupSetWidth :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o)
- getEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
- setEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
- constructEntryCompletionPopupSingleMatch :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o)
- getEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> m Bool
- setEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m ()
- constructEntryCompletionTextColumn :: (IsEntryCompletion o, MonadIO m) => Int32 -> m (GValueConstruct o)
- getEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> m Int32
- setEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m ()
- type C_EntryCompletionCursorOnMatchCallback = Ptr () -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt
- type EntryCompletionCursorOnMatchCallback = TreeModel -> TreeIter -> IO Bool
- afterEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionCursorOnMatchCallback -> m SignalHandlerId
- genClosure_EntryCompletionCursorOnMatch :: MonadIO m => EntryCompletionCursorOnMatchCallback -> m (GClosure C_EntryCompletionCursorOnMatchCallback)
- mk_EntryCompletionCursorOnMatchCallback :: C_EntryCompletionCursorOnMatchCallback -> IO (FunPtr C_EntryCompletionCursorOnMatchCallback)
- noEntryCompletionCursorOnMatchCallback :: Maybe EntryCompletionCursorOnMatchCallback
- onEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionCursorOnMatchCallback -> m SignalHandlerId
- wrap_EntryCompletionCursorOnMatchCallback :: EntryCompletionCursorOnMatchCallback -> C_EntryCompletionCursorOnMatchCallback
- type C_EntryCompletionInsertPrefixCallback = Ptr () -> CString -> Ptr () -> IO CInt
- type EntryCompletionInsertPrefixCallback = Text -> IO Bool
- afterEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionInsertPrefixCallback -> m SignalHandlerId
- genClosure_EntryCompletionInsertPrefix :: MonadIO m => EntryCompletionInsertPrefixCallback -> m (GClosure C_EntryCompletionInsertPrefixCallback)
- mk_EntryCompletionInsertPrefixCallback :: C_EntryCompletionInsertPrefixCallback -> IO (FunPtr C_EntryCompletionInsertPrefixCallback)
- noEntryCompletionInsertPrefixCallback :: Maybe EntryCompletionInsertPrefixCallback
- onEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionInsertPrefixCallback -> m SignalHandlerId
- wrap_EntryCompletionInsertPrefixCallback :: EntryCompletionInsertPrefixCallback -> C_EntryCompletionInsertPrefixCallback
- type C_EntryCompletionMatchSelectedCallback = Ptr () -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt
- type EntryCompletionMatchSelectedCallback = TreeModel -> TreeIter -> IO Bool
- afterEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionMatchSelectedCallback -> m SignalHandlerId
- genClosure_EntryCompletionMatchSelected :: MonadIO m => EntryCompletionMatchSelectedCallback -> m (GClosure C_EntryCompletionMatchSelectedCallback)
- mk_EntryCompletionMatchSelectedCallback :: C_EntryCompletionMatchSelectedCallback -> IO (FunPtr C_EntryCompletionMatchSelectedCallback)
- noEntryCompletionMatchSelectedCallback :: Maybe EntryCompletionMatchSelectedCallback
- onEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionMatchSelectedCallback -> m SignalHandlerId
- wrap_EntryCompletionMatchSelectedCallback :: EntryCompletionMatchSelectedCallback -> C_EntryCompletionMatchSelectedCallback
- type C_EntryCompletionNoMatchesCallback = Ptr () -> Ptr () -> IO ()
- type EntryCompletionNoMatchesCallback = IO ()
- afterEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionNoMatchesCallback -> m SignalHandlerId
- genClosure_EntryCompletionNoMatches :: MonadIO m => EntryCompletionNoMatchesCallback -> m (GClosure C_EntryCompletionNoMatchesCallback)
- mk_EntryCompletionNoMatchesCallback :: C_EntryCompletionNoMatchesCallback -> IO (FunPtr C_EntryCompletionNoMatchesCallback)
- noEntryCompletionNoMatchesCallback :: Maybe EntryCompletionNoMatchesCallback
- onEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionNoMatchesCallback -> m SignalHandlerId
- wrap_EntryCompletionNoMatchesCallback :: EntryCompletionNoMatchesCallback -> C_EntryCompletionNoMatchesCallback
Exported types
newtype EntryCompletion Source #
Memory-managed wrapper type.
Constructors
| EntryCompletion (ManagedPtr EntryCompletion) | 
Instances
| Eq EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion Methods (==) :: EntryCompletion -> EntryCompletion -> Bool # (/=) :: EntryCompletion -> EntryCompletion -> Bool # | |
| GObject EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion | |
| ManagedPtrNewtype EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion Methods toManagedPtr :: EntryCompletion -> ManagedPtr EntryCompletion | |
| TypedObject EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion | |
| HasParentTypes EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion | |
| IsGValue (Maybe EntryCompletion) Source # | Convert  | 
| Defined in GI.Gtk.Objects.EntryCompletion Methods gvalueGType_ :: IO GType gvalueSet_ :: Ptr GValue -> Maybe EntryCompletion -> IO () gvalueGet_ :: Ptr GValue -> IO (Maybe EntryCompletion) | |
| type ParentTypes EntryCompletion Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion | |
class (GObject o, IsDescendantOf EntryCompletion o) => IsEntryCompletion o Source #
Type class for types which can be safely cast to EntryCompletion, for instance with toEntryCompletion.
Instances
| (GObject o, IsDescendantOf EntryCompletion o) => IsEntryCompletion o Source # | |
| Defined in GI.Gtk.Objects.EntryCompletion | |
toEntryCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m EntryCompletion Source #
Cast to EntryCompletion, for types for which this is known to be safe. For general casts, use castTo.
Methods
Click to display all available methods, including inherited ones
Methods
addAttribute, bindProperty, bindPropertyFull, clear, clearAttributes, complete, computePrefix, forceFloating, freezeNotify, getv, insertPrefix, isFloating, notify, notifyByPspec, packEnd, packStart, ref, refSink, reorder, runDispose, stealData, stealQdata, thawNotify, unref, watchClosure.
Getters
getArea, getBuildableId, getCells, getCompletionPrefix, getData, getEntry, getInlineCompletion, getInlineSelection, getMinimumKeyLength, getModel, getPopupCompletion, getPopupSetWidth, getPopupSingleMatch, getProperty, getQdata, getTextColumn.
Setters
setCellDataFunc, setData, setDataFull, setInlineCompletion, setInlineSelection, setMatchFunc, setMinimumKeyLength, setModel, setPopupCompletion, setPopupSetWidth, setPopupSingleMatch, setProperty, setTextColumn.
complete
entryCompletionComplete Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m () | 
Requests a completion operation, or in other words a refiltering of the current list with completions, using the current key. The completion list view will be updated accordingly.
computePrefix
entryCompletionComputePrefix Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Text | 
 | 
| -> m (Maybe Text) | Returns: The common prefix all rows starting with
    | 
Computes the common prefix that is shared by all rows in completion
 that start with key. If no row matches key, Nothing will be returned.
 Note that a text column must have been set for this function to work,
 see entryCompletionSetTextColumn for details.
getCompletionPrefix
entryCompletionGetCompletionPrefix Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m (Maybe Text) | Returns: the prefix for the current completion | 
Get the original text entered by the user that triggered
 the completion or Nothing if there’s no completion ongoing.
getEntry
entryCompletionGetEntry Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Widget | Returns: The entry  | 
Gets the entry completion has been attached to.
getInlineCompletion
entryCompletionGetInlineCompletion Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Bool | Returns:  | 
Returns whether the common prefix of the possible completions should be automatically inserted in the entry.
getInlineSelection
entryCompletionGetInlineSelection Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Bool | Returns:  | 
Returns True if inline-selection mode is turned on.
getMinimumKeyLength
entryCompletionGetMinimumKeyLength Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Int32 | Returns: The currently used minimum key length | 
Returns the minimum key length as set for completion.
getModel
entryCompletionGetModel Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m (Maybe TreeModel) | Returns: A  | 
Returns the model the EntryCompletion is using as data source.
 Returns Nothing if the model is unset.
getPopupCompletion
entryCompletionGetPopupCompletion Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Bool | Returns:  | 
Returns whether the completions should be presented in a popup window.
getPopupSetWidth
entryCompletionGetPopupSetWidth Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Bool | Returns:  | 
Returns whether the completion popup window will be resized to the width of the entry.
getPopupSingleMatch
entryCompletionGetPopupSingleMatch Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Bool | Returns:  | 
Returns whether the completion popup window will appear even if there is only a single match.
getTextColumn
entryCompletionGetTextColumn Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m Int32 | Returns: the column containing the strings | 
Returns the column in the model of completion to get strings from.
insertPrefix
entryCompletionInsertPrefix Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> m () | 
Requests a prefix insertion.
new
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m EntryCompletion | Returns: A newly created  | 
Creates a new EntryCompletion object.
newWithArea
entryCompletionNewWithArea Source #
Arguments
| :: (HasCallStack, MonadIO m, IsCellArea a) | |
| => a | 
 | 
| -> m EntryCompletion | Returns: A newly created  | 
Creates a new EntryCompletion object using the
 specified area to layout cells in the underlying
 TreeViewColumn for the drop-down menu.
setInlineCompletion
entryCompletionSetInlineCompletion Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Bool | 
 | 
| -> m () | 
Sets whether the common prefix of the possible completions should be automatically inserted in the entry.
setInlineSelection
entryCompletionSetInlineSelection Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Bool | 
 | 
| -> m () | 
Sets whether it is possible to cycle through the possible completions inside the entry.
setMatchFunc
entryCompletionSetMatchFunc Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> EntryCompletionMatchFunc | 
 | 
| -> m () | 
Sets the match function for completion to be func. The match function
 is used to determine if a row should or should not be in the completion
 list.
setMinimumKeyLength
entryCompletionSetMinimumKeyLength Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Int32 | 
 | 
| -> m () | 
Requires the length of the search key for completion to be at least
 length. This is useful for long lists, where completing using a small
 key takes a lot of time and will come up with meaningless results anyway
 (ie, a too large dataset).
setModel
entryCompletionSetModel Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a, IsTreeModel b) | |
| => a | 
 | 
| -> Maybe b | 
 | 
| -> m () | 
Sets the model for a EntryCompletion. If completion already has
 a model set, it will remove it before setting the new model.
 If model is Nothing, then it will unset the model.
setPopupCompletion
entryCompletionSetPopupCompletion Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Bool | 
 | 
| -> m () | 
Sets whether the completions should be presented in a popup window.
setPopupSetWidth
entryCompletionSetPopupSetWidth Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Bool | 
 | 
| -> m () | 
Sets whether the completion popup window will be resized to be the same width as the entry.
setPopupSingleMatch
entryCompletionSetPopupSingleMatch Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Bool | 
 | 
| -> m () | 
Sets whether the completion popup window will appear even if there is
 only a single match. You may want to set this to False if you
 are using [inline completion][GtkEntryCompletion--inline-completion].
setTextColumn
entryCompletionSetTextColumn Source #
Arguments
| :: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
| => a | 
 | 
| -> Int32 | 
 | 
| -> m () | 
Convenience function for setting up the most used case of this code: a
 completion list with just strings. This function will set up completion
 to have a list displaying all (and just) strings in the completion list,
 and to get those strings from column in the model of completion.
This functions creates and adds a CellRendererText for the selected
 column. If you need to set the text column, but don't want the cell
 renderer, use g_object_set() to set the EntryCompletion:text-column
 property directly.
Properties
cellArea
The CellArea used to layout cell renderers in the treeview column.
If no area is specified when creating the entry completion with
 entryCompletionNewWithArea a horizontally oriented
 CellAreaBox will be used.
constructEntryCompletionCellArea :: (IsEntryCompletion o, MonadIO m, IsCellArea a) => a -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “cell-area” property. This is rarely needed directly, but it is used by new.
getEntryCompletionCellArea :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe CellArea) Source #
Get the value of the “cell-area” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #cellArea
inlineCompletion
Determines whether the common prefix of the possible completions should be inserted automatically in the entry. Note that this requires text-column to be set, even if you are using a custom match function.
constructEntryCompletionInlineCompletion :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “inline-completion” property. This is rarely needed directly, but it is used by new.
getEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool Source #
Get the value of the “inline-completion” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #inlineCompletion
setEntryCompletionInlineCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m () Source #
Set the value of the “inline-completion” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #inlineCompletion:=value ]
inlineSelection
Determines whether the possible completions on the popup will appear in the entry as you navigate through them.
constructEntryCompletionInlineSelection :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “inline-selection” property. This is rarely needed directly, but it is used by new.
getEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> m Bool Source #
Get the value of the “inline-selection” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #inlineSelection
setEntryCompletionInlineSelection :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m () Source #
Set the value of the “inline-selection” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #inlineSelection:=value ]
minimumKeyLength
No description available in the introspection data.
constructEntryCompletionMinimumKeyLength :: (IsEntryCompletion o, MonadIO m) => Int32 -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “minimum-key-length” property. This is rarely needed directly, but it is used by new.
getEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> m Int32 Source #
Get the value of the “minimum-key-length” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #minimumKeyLength
setEntryCompletionMinimumKeyLength :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m () Source #
Set the value of the “minimum-key-length” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #minimumKeyLength:=value ]
model
No description available in the introspection data.
clearEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m () Source #
Set the value of the “model” property to Nothing.
 When overloading is enabled, this is equivalent to
clear #model
constructEntryCompletionModel :: (IsEntryCompletion o, MonadIO m, IsTreeModel a) => a -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “model” property. This is rarely needed directly, but it is used by new.
getEntryCompletionModel :: (MonadIO m, IsEntryCompletion o) => o -> m (Maybe TreeModel) Source #
Get the value of the “model” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #model
setEntryCompletionModel :: (MonadIO m, IsEntryCompletion o, IsTreeModel a) => o -> a -> m () Source #
Set the value of the “model” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #model:=value ]
popupCompletion
Determines whether the possible completions should be shown in a popup window.
constructEntryCompletionPopupCompletion :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “popup-completion” property. This is rarely needed directly, but it is used by new.
getEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> m Bool Source #
Get the value of the “popup-completion” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #popupCompletion
setEntryCompletionPopupCompletion :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m () Source #
Set the value of the “popup-completion” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #popupCompletion:=value ]
popupSetWidth
Determines whether the completions popup window will be resized to the width of the entry.
constructEntryCompletionPopupSetWidth :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “popup-set-width” property. This is rarely needed directly, but it is used by new.
getEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> m Bool Source #
Get the value of the “popup-set-width” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #popupSetWidth
setEntryCompletionPopupSetWidth :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m () Source #
Set the value of the “popup-set-width” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #popupSetWidth:=value ]
popupSingleMatch
Determines whether the completions popup window will shown
 for a single possible completion. You probably want to set
 this to False if you are using
 [inline completion][GtkEntryCompletion--inline-completion].
constructEntryCompletionPopupSingleMatch :: (IsEntryCompletion o, MonadIO m) => Bool -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “popup-single-match” property. This is rarely needed directly, but it is used by new.
getEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> m Bool Source #
Get the value of the “popup-single-match” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #popupSingleMatch
setEntryCompletionPopupSingleMatch :: (MonadIO m, IsEntryCompletion o) => o -> Bool -> m () Source #
Set the value of the “popup-single-match” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #popupSingleMatch:=value ]
textColumn
The column of the model containing the strings. Note that the strings must be UTF-8.
constructEntryCompletionTextColumn :: (IsEntryCompletion o, MonadIO m) => Int32 -> m (GValueConstruct o) Source #
Construct a GValueConstruct with valid value for the “text-column” property. This is rarely needed directly, but it is used by new.
getEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> m Int32 Source #
Get the value of the “text-column” property.
 When overloading is enabled, this is equivalent to
get entryCompletion #textColumn
setEntryCompletionTextColumn :: (MonadIO m, IsEntryCompletion o) => o -> Int32 -> m () Source #
Set the value of the “text-column” property.
 When overloading is enabled, this is equivalent to
setentryCompletion [ #textColumn:=value ]
Signals
cursorOnMatch
type C_EntryCompletionCursorOnMatchCallback = Ptr () -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type EntryCompletionCursorOnMatchCallback Source #
Arguments
| = TreeModel | 
 | 
| -> TreeIter | 
 | 
| -> IO Bool | Returns:  | 
Gets emitted when a match from the cursor is on a match
 of the list. The default behaviour is to replace the contents
 of the entry with the contents of the text column in the row
 pointed to by iter.
Note that model is the model that was passed to
 entryCompletionSetModel.
afterEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionCursorOnMatchCallback -> m SignalHandlerId Source #
Connect a signal handler for the cursorOnMatch signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after entryCompletion #cursorOnMatch callback
genClosure_EntryCompletionCursorOnMatch :: MonadIO m => EntryCompletionCursorOnMatchCallback -> m (GClosure C_EntryCompletionCursorOnMatchCallback) Source #
Wrap the callback into a GClosure.
mk_EntryCompletionCursorOnMatchCallback :: C_EntryCompletionCursorOnMatchCallback -> IO (FunPtr C_EntryCompletionCursorOnMatchCallback) Source #
Generate a function pointer callable from C code, from a C_EntryCompletionCursorOnMatchCallback.
noEntryCompletionCursorOnMatchCallback :: Maybe EntryCompletionCursorOnMatchCallback Source #
A convenience synonym for Nothing :: Maybe EntryCompletionCursorOnMatchCallback
onEntryCompletionCursorOnMatch :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionCursorOnMatchCallback -> m SignalHandlerId Source #
Connect a signal handler for the cursorOnMatch signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on entryCompletion #cursorOnMatch callback
wrap_EntryCompletionCursorOnMatchCallback :: EntryCompletionCursorOnMatchCallback -> C_EntryCompletionCursorOnMatchCallback Source #
insertPrefix
type C_EntryCompletionInsertPrefixCallback = Ptr () -> CString -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type EntryCompletionInsertPrefixCallback Source #
Arguments
| = Text | 
 | 
| -> IO Bool | Returns:  | 
Gets emitted when the inline autocompletion is triggered. The default behaviour is to make the entry display the whole prefix and select the newly inserted part.
Applications may connect to this signal in order to insert only a
 smaller part of the prefix into the entry - e.g. the entry used in
 the FileChooser inserts only the part of the prefix up to the
 next '/'.
afterEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionInsertPrefixCallback -> m SignalHandlerId Source #
Connect a signal handler for the insertPrefix signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after entryCompletion #insertPrefix callback
genClosure_EntryCompletionInsertPrefix :: MonadIO m => EntryCompletionInsertPrefixCallback -> m (GClosure C_EntryCompletionInsertPrefixCallback) Source #
Wrap the callback into a GClosure.
mk_EntryCompletionInsertPrefixCallback :: C_EntryCompletionInsertPrefixCallback -> IO (FunPtr C_EntryCompletionInsertPrefixCallback) Source #
Generate a function pointer callable from C code, from a C_EntryCompletionInsertPrefixCallback.
noEntryCompletionInsertPrefixCallback :: Maybe EntryCompletionInsertPrefixCallback Source #
A convenience synonym for Nothing :: Maybe EntryCompletionInsertPrefixCallback
onEntryCompletionInsertPrefix :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionInsertPrefixCallback -> m SignalHandlerId Source #
Connect a signal handler for the insertPrefix signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on entryCompletion #insertPrefix callback
wrap_EntryCompletionInsertPrefixCallback :: EntryCompletionInsertPrefixCallback -> C_EntryCompletionInsertPrefixCallback Source #
matchSelected
type C_EntryCompletionMatchSelectedCallback = Ptr () -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type EntryCompletionMatchSelectedCallback Source #
Arguments
| = TreeModel | 
 | 
| -> TreeIter | 
 | 
| -> IO Bool | Returns:  | 
Gets emitted when a match from the list is selected.
 The default behaviour is to replace the contents of the
 entry with the contents of the text column in the row
 pointed to by iter.
Note that model is the model that was passed to
 entryCompletionSetModel.
afterEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionMatchSelectedCallback -> m SignalHandlerId Source #
Connect a signal handler for the matchSelected signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after entryCompletion #matchSelected callback
genClosure_EntryCompletionMatchSelected :: MonadIO m => EntryCompletionMatchSelectedCallback -> m (GClosure C_EntryCompletionMatchSelectedCallback) Source #
Wrap the callback into a GClosure.
mk_EntryCompletionMatchSelectedCallback :: C_EntryCompletionMatchSelectedCallback -> IO (FunPtr C_EntryCompletionMatchSelectedCallback) Source #
Generate a function pointer callable from C code, from a C_EntryCompletionMatchSelectedCallback.
noEntryCompletionMatchSelectedCallback :: Maybe EntryCompletionMatchSelectedCallback Source #
A convenience synonym for Nothing :: Maybe EntryCompletionMatchSelectedCallback
onEntryCompletionMatchSelected :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionMatchSelectedCallback -> m SignalHandlerId Source #
Connect a signal handler for the matchSelected signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on entryCompletion #matchSelected callback
wrap_EntryCompletionMatchSelectedCallback :: EntryCompletionMatchSelectedCallback -> C_EntryCompletionMatchSelectedCallback Source #
noMatches
type C_EntryCompletionNoMatchesCallback = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type EntryCompletionNoMatchesCallback = IO () Source #
Gets emitted when the filter model has zero number of rows in completion_complete method. (In other words when GtkEntryCompletion is out of suggestions)
afterEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionNoMatchesCallback -> m SignalHandlerId Source #
Connect a signal handler for the noMatches signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after entryCompletion #noMatches callback
genClosure_EntryCompletionNoMatches :: MonadIO m => EntryCompletionNoMatchesCallback -> m (GClosure C_EntryCompletionNoMatchesCallback) Source #
Wrap the callback into a GClosure.
mk_EntryCompletionNoMatchesCallback :: C_EntryCompletionNoMatchesCallback -> IO (FunPtr C_EntryCompletionNoMatchesCallback) Source #
Generate a function pointer callable from C code, from a C_EntryCompletionNoMatchesCallback.
noEntryCompletionNoMatchesCallback :: Maybe EntryCompletionNoMatchesCallback Source #
A convenience synonym for Nothing :: Maybe EntryCompletionNoMatchesCallback
onEntryCompletionNoMatches :: (IsEntryCompletion a, MonadIO m) => a -> EntryCompletionNoMatchesCallback -> m SignalHandlerId Source #
Connect a signal handler for the noMatches signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on entryCompletion #noMatches callback