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 |
- Signals
- AssistantPageFunc
- BuildableParserEndElementFieldCallback
- BuildableParserErrorFieldCallback
- BuildableParserStartElementFieldCallback
- BuildableParserTextFieldCallback
- CellAllocCallback
- CellCallback
- CellLayoutDataFunc
- CustomAllocateFunc
- CustomFilterFunc
- CustomMeasureFunc
- CustomRequestModeFunc
- DrawingAreaDrawFunc
- EntryCompletionMatchFunc
- ExpressionNotify
- FlowBoxCreateWidgetFunc
- FlowBoxFilterFunc
- FlowBoxForeachFunc
- FlowBoxSortFunc
- FontFilterFunc
- IconViewForeachFunc
- ListBoxCreateWidgetFunc
- ListBoxFilterFunc
- ListBoxForeachFunc
- ListBoxSortFunc
- ListBoxUpdateHeaderFunc
- MapListModelMapFunc
- MenuButtonCreatePopupFunc
- PageSetupDoneFunc
- PrintSettingsFunc
- ScaleFormatValueFunc
- ShortcutFunc
- TextCharPredicate
- TextTagTableForeach
- TickCallback
- TreeCellDataFunc
- TreeIterCompareFunc
- TreeListModelCreateModelFunc
- TreeModelFilterModifyFunc
- TreeModelFilterVisibleFunc
- TreeModelForeachFunc
- TreeSelectionForeachFunc
- TreeSelectionFunc
- TreeViewColumnDropFunc
- TreeViewMappingFunc
- TreeViewRowSeparatorFunc
- TreeViewSearchEqualFunc
- WidgetActionActivateFunc
- WidgetClassComputeExpandFieldCallback
- WidgetClassContainsFieldCallback
- WidgetClassCssChangedFieldCallback
- WidgetClassDirectionChangedFieldCallback
- WidgetClassFocusFieldCallback
- WidgetClassGetRequestModeFieldCallback
- WidgetClassGrabFocusFieldCallback
- WidgetClassHideFieldCallback
- WidgetClassKeynavFailedFieldCallback
- WidgetClassMapFieldCallback
- WidgetClassMeasureFieldCallback
- WidgetClassMnemonicActivateFieldCallback
- WidgetClassMoveFocusFieldCallback
- WidgetClassQueryTooltipFieldCallback
- WidgetClassRealizeFieldCallback
- WidgetClassRootFieldCallback
- WidgetClassSetFocusChildFieldCallback
- WidgetClassShowFieldCallback
- WidgetClassSizeAllocateFieldCallback
- WidgetClassSnapshotFieldCallback
- WidgetClassStateFlagsChangedFieldCallback
- WidgetClassSystemSettingChangedFieldCallback
- WidgetClassUnmapFieldCallback
- WidgetClassUnrealizeFieldCallback
- WidgetClassUnrootFieldCallback
Synopsis
- type AssistantPageFunc = Int32 -> IO Int32
- type AssistantPageFunc_WithClosures = Int32 -> Ptr () -> IO Int32
- type C_AssistantPageFunc = Int32 -> Ptr () -> IO Int32
- drop_closures_AssistantPageFunc :: AssistantPageFunc -> AssistantPageFunc_WithClosures
- dynamic_AssistantPageFunc :: (HasCallStack, MonadIO m) => FunPtr C_AssistantPageFunc -> Int32 -> Ptr () -> m Int32
- genClosure_AssistantPageFunc :: MonadIO m => AssistantPageFunc -> m (GClosure C_AssistantPageFunc)
- mk_AssistantPageFunc :: C_AssistantPageFunc -> IO (FunPtr C_AssistantPageFunc)
- noAssistantPageFunc :: Maybe AssistantPageFunc
- noAssistantPageFunc_WithClosures :: Maybe AssistantPageFunc_WithClosures
- wrap_AssistantPageFunc :: Maybe (Ptr (FunPtr C_AssistantPageFunc)) -> AssistantPageFunc_WithClosures -> C_AssistantPageFunc
- type BuildableParserEndElementFieldCallback = BuildableParseContext -> Text -> IO ()
- type BuildableParserEndElementFieldCallback_WithClosures = BuildableParseContext -> Text -> Ptr () -> IO ()
- type C_BuildableParserEndElementFieldCallback = Ptr BuildableParseContext -> CString -> Ptr () -> Ptr (Ptr GError) -> IO ()
- drop_closures_BuildableParserEndElementFieldCallback :: BuildableParserEndElementFieldCallback -> BuildableParserEndElementFieldCallback_WithClosures
- dynamic_BuildableParserEndElementFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_BuildableParserEndElementFieldCallback -> BuildableParseContext -> Text -> Ptr () -> m ()
- mk_BuildableParserEndElementFieldCallback :: C_BuildableParserEndElementFieldCallback -> IO (FunPtr C_BuildableParserEndElementFieldCallback)
- noBuildableParserEndElementFieldCallback :: Maybe BuildableParserEndElementFieldCallback
- noBuildableParserEndElementFieldCallback_WithClosures :: Maybe BuildableParserEndElementFieldCallback_WithClosures
- type BuildableParserErrorFieldCallback = BuildableParseContext -> GError -> IO ()
- type BuildableParserErrorFieldCallback_WithClosures = BuildableParseContext -> GError -> Ptr () -> IO ()
- type C_BuildableParserErrorFieldCallback = Ptr BuildableParseContext -> Ptr GError -> Ptr () -> IO ()
- drop_closures_BuildableParserErrorFieldCallback :: BuildableParserErrorFieldCallback -> BuildableParserErrorFieldCallback_WithClosures
- dynamic_BuildableParserErrorFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_BuildableParserErrorFieldCallback -> BuildableParseContext -> GError -> Ptr () -> m ()
- genClosure_BuildableParserErrorFieldCallback :: MonadIO m => BuildableParserErrorFieldCallback -> m (GClosure C_BuildableParserErrorFieldCallback)
- mk_BuildableParserErrorFieldCallback :: C_BuildableParserErrorFieldCallback -> IO (FunPtr C_BuildableParserErrorFieldCallback)
- noBuildableParserErrorFieldCallback :: Maybe BuildableParserErrorFieldCallback
- noBuildableParserErrorFieldCallback_WithClosures :: Maybe BuildableParserErrorFieldCallback_WithClosures
- wrap_BuildableParserErrorFieldCallback :: Maybe (Ptr (FunPtr C_BuildableParserErrorFieldCallback)) -> BuildableParserErrorFieldCallback_WithClosures -> C_BuildableParserErrorFieldCallback
- type BuildableParserStartElementFieldCallback = BuildableParseContext -> Text -> Text -> Text -> IO ()
- type BuildableParserStartElementFieldCallback_WithClosures = BuildableParseContext -> Text -> Text -> Text -> Ptr () -> IO ()
- type C_BuildableParserStartElementFieldCallback = Ptr BuildableParseContext -> CString -> CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO ()
- drop_closures_BuildableParserStartElementFieldCallback :: BuildableParserStartElementFieldCallback -> BuildableParserStartElementFieldCallback_WithClosures
- dynamic_BuildableParserStartElementFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_BuildableParserStartElementFieldCallback -> BuildableParseContext -> Text -> Text -> Text -> Ptr () -> m ()
- mk_BuildableParserStartElementFieldCallback :: C_BuildableParserStartElementFieldCallback -> IO (FunPtr C_BuildableParserStartElementFieldCallback)
- noBuildableParserStartElementFieldCallback :: Maybe BuildableParserStartElementFieldCallback
- noBuildableParserStartElementFieldCallback_WithClosures :: Maybe BuildableParserStartElementFieldCallback_WithClosures
- type BuildableParserTextFieldCallback = BuildableParseContext -> Text -> Word64 -> IO ()
- type BuildableParserTextFieldCallback_WithClosures = BuildableParseContext -> Text -> Word64 -> Ptr () -> IO ()
- type C_BuildableParserTextFieldCallback = Ptr BuildableParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO ()
- drop_closures_BuildableParserTextFieldCallback :: BuildableParserTextFieldCallback -> BuildableParserTextFieldCallback_WithClosures
- dynamic_BuildableParserTextFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_BuildableParserTextFieldCallback -> BuildableParseContext -> Text -> Word64 -> Ptr () -> m ()
- mk_BuildableParserTextFieldCallback :: C_BuildableParserTextFieldCallback -> IO (FunPtr C_BuildableParserTextFieldCallback)
- noBuildableParserTextFieldCallback :: Maybe BuildableParserTextFieldCallback
- noBuildableParserTextFieldCallback_WithClosures :: Maybe BuildableParserTextFieldCallback_WithClosures
- type C_CellAllocCallback = Ptr CellRenderer -> Ptr Rectangle -> Ptr Rectangle -> Ptr () -> IO CInt
- type CellAllocCallback = CellRenderer -> Rectangle -> Rectangle -> IO Bool
- type CellAllocCallback_WithClosures = CellRenderer -> Rectangle -> Rectangle -> Ptr () -> IO Bool
- drop_closures_CellAllocCallback :: CellAllocCallback -> CellAllocCallback_WithClosures
- dynamic_CellAllocCallback :: (HasCallStack, MonadIO m, IsCellRenderer a) => FunPtr C_CellAllocCallback -> a -> Rectangle -> Rectangle -> Ptr () -> m Bool
- genClosure_CellAllocCallback :: MonadIO m => CellAllocCallback -> m (GClosure C_CellAllocCallback)
- mk_CellAllocCallback :: C_CellAllocCallback -> IO (FunPtr C_CellAllocCallback)
- noCellAllocCallback :: Maybe CellAllocCallback
- noCellAllocCallback_WithClosures :: Maybe CellAllocCallback_WithClosures
- wrap_CellAllocCallback :: Maybe (Ptr (FunPtr C_CellAllocCallback)) -> CellAllocCallback_WithClosures -> C_CellAllocCallback
- type C_CellCallback = Ptr CellRenderer -> Ptr () -> IO CInt
- type CellCallback = CellRenderer -> IO Bool
- type CellCallback_WithClosures = CellRenderer -> Ptr () -> IO Bool
- drop_closures_CellCallback :: CellCallback -> CellCallback_WithClosures
- dynamic_CellCallback :: (HasCallStack, MonadIO m, IsCellRenderer a) => FunPtr C_CellCallback -> a -> Ptr () -> m Bool
- genClosure_CellCallback :: MonadIO m => CellCallback -> m (GClosure C_CellCallback)
- mk_CellCallback :: C_CellCallback -> IO (FunPtr C_CellCallback)
- noCellCallback :: Maybe CellCallback
- noCellCallback_WithClosures :: Maybe CellCallback_WithClosures
- wrap_CellCallback :: Maybe (Ptr (FunPtr C_CellCallback)) -> CellCallback_WithClosures -> C_CellCallback
- type C_CellLayoutDataFunc = Ptr CellLayout -> Ptr CellRenderer -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO ()
- type CellLayoutDataFunc = CellLayout -> CellRenderer -> TreeModel -> TreeIter -> IO ()
- type CellLayoutDataFunc_WithClosures = CellLayout -> CellRenderer -> TreeModel -> TreeIter -> Ptr () -> IO ()
- drop_closures_CellLayoutDataFunc :: CellLayoutDataFunc -> CellLayoutDataFunc_WithClosures
- dynamic_CellLayoutDataFunc :: (HasCallStack, MonadIO m, IsCellLayout a, IsCellRenderer b, IsTreeModel c) => FunPtr C_CellLayoutDataFunc -> a -> b -> c -> TreeIter -> Ptr () -> m ()
- genClosure_CellLayoutDataFunc :: MonadIO m => CellLayoutDataFunc -> m (GClosure C_CellLayoutDataFunc)
- mk_CellLayoutDataFunc :: C_CellLayoutDataFunc -> IO (FunPtr C_CellLayoutDataFunc)
- noCellLayoutDataFunc :: Maybe CellLayoutDataFunc
- noCellLayoutDataFunc_WithClosures :: Maybe CellLayoutDataFunc_WithClosures
- wrap_CellLayoutDataFunc :: Maybe (Ptr (FunPtr C_CellLayoutDataFunc)) -> CellLayoutDataFunc_WithClosures -> C_CellLayoutDataFunc
- type C_CustomAllocateFunc = Ptr Widget -> Int32 -> Int32 -> Int32 -> IO ()
- type CustomAllocateFunc = Widget -> Int32 -> Int32 -> Int32 -> IO ()
- dynamic_CustomAllocateFunc :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_CustomAllocateFunc -> a -> Int32 -> Int32 -> Int32 -> m ()
- genClosure_CustomAllocateFunc :: MonadIO m => CustomAllocateFunc -> m (GClosure C_CustomAllocateFunc)
- mk_CustomAllocateFunc :: C_CustomAllocateFunc -> IO (FunPtr C_CustomAllocateFunc)
- noCustomAllocateFunc :: Maybe CustomAllocateFunc
- wrap_CustomAllocateFunc :: Maybe (Ptr (FunPtr C_CustomAllocateFunc)) -> CustomAllocateFunc -> C_CustomAllocateFunc
- type C_CustomFilterFunc = Ptr Object -> Ptr () -> IO CInt
- type CustomFilterFunc = Object -> IO Bool
- type CustomFilterFunc_WithClosures = Object -> Ptr () -> IO Bool
- drop_closures_CustomFilterFunc :: CustomFilterFunc -> CustomFilterFunc_WithClosures
- dynamic_CustomFilterFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_CustomFilterFunc -> a -> Ptr () -> m Bool
- genClosure_CustomFilterFunc :: MonadIO m => CustomFilterFunc -> m (GClosure C_CustomFilterFunc)
- mk_CustomFilterFunc :: C_CustomFilterFunc -> IO (FunPtr C_CustomFilterFunc)
- noCustomFilterFunc :: Maybe CustomFilterFunc
- noCustomFilterFunc_WithClosures :: Maybe CustomFilterFunc_WithClosures
- wrap_CustomFilterFunc :: Maybe (Ptr (FunPtr C_CustomFilterFunc)) -> CustomFilterFunc_WithClosures -> C_CustomFilterFunc
- type C_CustomMeasureFunc = Ptr Widget -> CUInt -> Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO ()
- type CustomMeasureFunc = Widget -> Orientation -> Int32 -> IO (Int32, Int32, Int32, Int32)
- dynamic_CustomMeasureFunc :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_CustomMeasureFunc -> a -> Orientation -> Int32 -> m (Int32, Int32, Int32, Int32)
- genClosure_CustomMeasureFunc :: MonadIO m => CustomMeasureFunc -> m (GClosure C_CustomMeasureFunc)
- mk_CustomMeasureFunc :: C_CustomMeasureFunc -> IO (FunPtr C_CustomMeasureFunc)
- noCustomMeasureFunc :: Maybe CustomMeasureFunc
- wrap_CustomMeasureFunc :: Maybe (Ptr (FunPtr C_CustomMeasureFunc)) -> CustomMeasureFunc -> C_CustomMeasureFunc
- type C_CustomRequestModeFunc = Ptr Widget -> IO CUInt
- type CustomRequestModeFunc = Widget -> IO SizeRequestMode
- dynamic_CustomRequestModeFunc :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_CustomRequestModeFunc -> a -> m SizeRequestMode
- genClosure_CustomRequestModeFunc :: MonadIO m => CustomRequestModeFunc -> m (GClosure C_CustomRequestModeFunc)
- mk_CustomRequestModeFunc :: C_CustomRequestModeFunc -> IO (FunPtr C_CustomRequestModeFunc)
- noCustomRequestModeFunc :: Maybe CustomRequestModeFunc
- wrap_CustomRequestModeFunc :: Maybe (Ptr (FunPtr C_CustomRequestModeFunc)) -> CustomRequestModeFunc -> C_CustomRequestModeFunc
- type C_DrawingAreaDrawFunc = Ptr DrawingArea -> Ptr Context -> Int32 -> Int32 -> Ptr () -> IO ()
- type DrawingAreaDrawFunc = DrawingArea -> Context -> Int32 -> Int32 -> IO ()
- type DrawingAreaDrawFunc_WithClosures = DrawingArea -> Context -> Int32 -> Int32 -> Ptr () -> IO ()
- drop_closures_DrawingAreaDrawFunc :: DrawingAreaDrawFunc -> DrawingAreaDrawFunc_WithClosures
- dynamic_DrawingAreaDrawFunc :: (HasCallStack, MonadIO m, IsDrawingArea a) => FunPtr C_DrawingAreaDrawFunc -> a -> Context -> Int32 -> Int32 -> Ptr () -> m ()
- genClosure_DrawingAreaDrawFunc :: MonadIO m => DrawingAreaDrawFunc -> m (GClosure C_DrawingAreaDrawFunc)
- mk_DrawingAreaDrawFunc :: C_DrawingAreaDrawFunc -> IO (FunPtr C_DrawingAreaDrawFunc)
- noDrawingAreaDrawFunc :: Maybe DrawingAreaDrawFunc
- noDrawingAreaDrawFunc_WithClosures :: Maybe DrawingAreaDrawFunc_WithClosures
- wrap_DrawingAreaDrawFunc :: Maybe (Ptr (FunPtr C_DrawingAreaDrawFunc)) -> DrawingAreaDrawFunc_WithClosures -> C_DrawingAreaDrawFunc
- type C_EntryCompletionMatchFunc = Ptr EntryCompletion -> CString -> Ptr TreeIter -> Ptr () -> IO CInt
- type EntryCompletionMatchFunc = EntryCompletion -> Text -> TreeIter -> IO Bool
- type EntryCompletionMatchFunc_WithClosures = EntryCompletion -> Text -> TreeIter -> Ptr () -> IO Bool
- drop_closures_EntryCompletionMatchFunc :: EntryCompletionMatchFunc -> EntryCompletionMatchFunc_WithClosures
- dynamic_EntryCompletionMatchFunc :: (HasCallStack, MonadIO m, IsEntryCompletion a) => FunPtr C_EntryCompletionMatchFunc -> a -> Text -> TreeIter -> Ptr () -> m Bool
- genClosure_EntryCompletionMatchFunc :: MonadIO m => EntryCompletionMatchFunc -> m (GClosure C_EntryCompletionMatchFunc)
- mk_EntryCompletionMatchFunc :: C_EntryCompletionMatchFunc -> IO (FunPtr C_EntryCompletionMatchFunc)
- noEntryCompletionMatchFunc :: Maybe EntryCompletionMatchFunc
- noEntryCompletionMatchFunc_WithClosures :: Maybe EntryCompletionMatchFunc_WithClosures
- wrap_EntryCompletionMatchFunc :: Maybe (Ptr (FunPtr C_EntryCompletionMatchFunc)) -> EntryCompletionMatchFunc_WithClosures -> C_EntryCompletionMatchFunc
- type C_ExpressionNotify = Ptr () -> IO ()
- type ExpressionNotify = IO ()
- type ExpressionNotify_WithClosures = Ptr () -> IO ()
- drop_closures_ExpressionNotify :: ExpressionNotify -> ExpressionNotify_WithClosures
- dynamic_ExpressionNotify :: (HasCallStack, MonadIO m) => FunPtr C_ExpressionNotify -> Ptr () -> m ()
- genClosure_ExpressionNotify :: MonadIO m => ExpressionNotify -> m (GClosure C_ExpressionNotify)
- mk_ExpressionNotify :: C_ExpressionNotify -> IO (FunPtr C_ExpressionNotify)
- noExpressionNotify :: Maybe ExpressionNotify
- noExpressionNotify_WithClosures :: Maybe ExpressionNotify_WithClosures
- wrap_ExpressionNotify :: Maybe (Ptr (FunPtr C_ExpressionNotify)) -> ExpressionNotify_WithClosures -> C_ExpressionNotify
- type C_FlowBoxCreateWidgetFunc = Ptr Object -> Ptr () -> IO (Ptr Widget)
- type FlowBoxCreateWidgetFunc = Object -> IO Widget
- type FlowBoxCreateWidgetFunc_WithClosures = Object -> Ptr () -> IO Widget
- drop_closures_FlowBoxCreateWidgetFunc :: FlowBoxCreateWidgetFunc -> FlowBoxCreateWidgetFunc_WithClosures
- dynamic_FlowBoxCreateWidgetFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_FlowBoxCreateWidgetFunc -> a -> Ptr () -> m Widget
- genClosure_FlowBoxCreateWidgetFunc :: MonadIO m => FlowBoxCreateWidgetFunc -> m (GClosure C_FlowBoxCreateWidgetFunc)
- mk_FlowBoxCreateWidgetFunc :: C_FlowBoxCreateWidgetFunc -> IO (FunPtr C_FlowBoxCreateWidgetFunc)
- noFlowBoxCreateWidgetFunc :: Maybe FlowBoxCreateWidgetFunc
- noFlowBoxCreateWidgetFunc_WithClosures :: Maybe FlowBoxCreateWidgetFunc_WithClosures
- wrap_FlowBoxCreateWidgetFunc :: Maybe (Ptr (FunPtr C_FlowBoxCreateWidgetFunc)) -> FlowBoxCreateWidgetFunc_WithClosures -> C_FlowBoxCreateWidgetFunc
- type C_FlowBoxFilterFunc = Ptr FlowBoxChild -> Ptr () -> IO CInt
- type FlowBoxFilterFunc = FlowBoxChild -> IO Bool
- type FlowBoxFilterFunc_WithClosures = FlowBoxChild -> Ptr () -> IO Bool
- drop_closures_FlowBoxFilterFunc :: FlowBoxFilterFunc -> FlowBoxFilterFunc_WithClosures
- dynamic_FlowBoxFilterFunc :: (HasCallStack, MonadIO m, IsFlowBoxChild a) => FunPtr C_FlowBoxFilterFunc -> a -> Ptr () -> m Bool
- genClosure_FlowBoxFilterFunc :: MonadIO m => FlowBoxFilterFunc -> m (GClosure C_FlowBoxFilterFunc)
- mk_FlowBoxFilterFunc :: C_FlowBoxFilterFunc -> IO (FunPtr C_FlowBoxFilterFunc)
- noFlowBoxFilterFunc :: Maybe FlowBoxFilterFunc
- noFlowBoxFilterFunc_WithClosures :: Maybe FlowBoxFilterFunc_WithClosures
- wrap_FlowBoxFilterFunc :: Maybe (Ptr (FunPtr C_FlowBoxFilterFunc)) -> FlowBoxFilterFunc_WithClosures -> C_FlowBoxFilterFunc
- type C_FlowBoxForeachFunc = Ptr FlowBox -> Ptr FlowBoxChild -> Ptr () -> IO ()
- type FlowBoxForeachFunc = FlowBox -> FlowBoxChild -> IO ()
- type FlowBoxForeachFunc_WithClosures = FlowBox -> FlowBoxChild -> Ptr () -> IO ()
- drop_closures_FlowBoxForeachFunc :: FlowBoxForeachFunc -> FlowBoxForeachFunc_WithClosures
- dynamic_FlowBoxForeachFunc :: (HasCallStack, MonadIO m, IsFlowBox a, IsFlowBoxChild b) => FunPtr C_FlowBoxForeachFunc -> a -> b -> Ptr () -> m ()
- genClosure_FlowBoxForeachFunc :: MonadIO m => FlowBoxForeachFunc -> m (GClosure C_FlowBoxForeachFunc)
- mk_FlowBoxForeachFunc :: C_FlowBoxForeachFunc -> IO (FunPtr C_FlowBoxForeachFunc)
- noFlowBoxForeachFunc :: Maybe FlowBoxForeachFunc
- noFlowBoxForeachFunc_WithClosures :: Maybe FlowBoxForeachFunc_WithClosures
- wrap_FlowBoxForeachFunc :: Maybe (Ptr (FunPtr C_FlowBoxForeachFunc)) -> FlowBoxForeachFunc_WithClosures -> C_FlowBoxForeachFunc
- type C_FlowBoxSortFunc = Ptr FlowBoxChild -> Ptr FlowBoxChild -> Ptr () -> IO Int32
- type FlowBoxSortFunc = FlowBoxChild -> FlowBoxChild -> IO Int32
- type FlowBoxSortFunc_WithClosures = FlowBoxChild -> FlowBoxChild -> Ptr () -> IO Int32
- drop_closures_FlowBoxSortFunc :: FlowBoxSortFunc -> FlowBoxSortFunc_WithClosures
- dynamic_FlowBoxSortFunc :: (HasCallStack, MonadIO m, IsFlowBoxChild a, IsFlowBoxChild b) => FunPtr C_FlowBoxSortFunc -> a -> b -> Ptr () -> m Int32
- genClosure_FlowBoxSortFunc :: MonadIO m => FlowBoxSortFunc -> m (GClosure C_FlowBoxSortFunc)
- mk_FlowBoxSortFunc :: C_FlowBoxSortFunc -> IO (FunPtr C_FlowBoxSortFunc)
- noFlowBoxSortFunc :: Maybe FlowBoxSortFunc
- noFlowBoxSortFunc_WithClosures :: Maybe FlowBoxSortFunc_WithClosures
- wrap_FlowBoxSortFunc :: Maybe (Ptr (FunPtr C_FlowBoxSortFunc)) -> FlowBoxSortFunc_WithClosures -> C_FlowBoxSortFunc
- type C_FontFilterFunc = Ptr FontFamily -> Ptr FontFace -> Ptr () -> IO CInt
- type FontFilterFunc = FontFamily -> FontFace -> IO Bool
- type FontFilterFunc_WithClosures = FontFamily -> FontFace -> Ptr () -> IO Bool
- drop_closures_FontFilterFunc :: FontFilterFunc -> FontFilterFunc_WithClosures
- dynamic_FontFilterFunc :: (HasCallStack, MonadIO m, IsFontFamily a, IsFontFace b) => FunPtr C_FontFilterFunc -> a -> b -> Ptr () -> m Bool
- genClosure_FontFilterFunc :: MonadIO m => FontFilterFunc -> m (GClosure C_FontFilterFunc)
- mk_FontFilterFunc :: C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc)
- noFontFilterFunc :: Maybe FontFilterFunc
- noFontFilterFunc_WithClosures :: Maybe FontFilterFunc_WithClosures
- wrap_FontFilterFunc :: Maybe (Ptr (FunPtr C_FontFilterFunc)) -> FontFilterFunc_WithClosures -> C_FontFilterFunc
- type C_IconViewForeachFunc = Ptr IconView -> Ptr TreePath -> Ptr () -> IO ()
- type IconViewForeachFunc = IconView -> TreePath -> IO ()
- type IconViewForeachFunc_WithClosures = IconView -> TreePath -> Ptr () -> IO ()
- drop_closures_IconViewForeachFunc :: IconViewForeachFunc -> IconViewForeachFunc_WithClosures
- dynamic_IconViewForeachFunc :: (HasCallStack, MonadIO m, IsIconView a) => FunPtr C_IconViewForeachFunc -> a -> TreePath -> Ptr () -> m ()
- genClosure_IconViewForeachFunc :: MonadIO m => IconViewForeachFunc -> m (GClosure C_IconViewForeachFunc)
- mk_IconViewForeachFunc :: C_IconViewForeachFunc -> IO (FunPtr C_IconViewForeachFunc)
- noIconViewForeachFunc :: Maybe IconViewForeachFunc
- noIconViewForeachFunc_WithClosures :: Maybe IconViewForeachFunc_WithClosures
- wrap_IconViewForeachFunc :: Maybe (Ptr (FunPtr C_IconViewForeachFunc)) -> IconViewForeachFunc_WithClosures -> C_IconViewForeachFunc
- type C_ListBoxCreateWidgetFunc = Ptr Object -> Ptr () -> IO (Ptr Widget)
- type ListBoxCreateWidgetFunc = Object -> IO Widget
- type ListBoxCreateWidgetFunc_WithClosures = Object -> Ptr () -> IO Widget
- drop_closures_ListBoxCreateWidgetFunc :: ListBoxCreateWidgetFunc -> ListBoxCreateWidgetFunc_WithClosures
- dynamic_ListBoxCreateWidgetFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_ListBoxCreateWidgetFunc -> a -> Ptr () -> m Widget
- genClosure_ListBoxCreateWidgetFunc :: MonadIO m => ListBoxCreateWidgetFunc -> m (GClosure C_ListBoxCreateWidgetFunc)
- mk_ListBoxCreateWidgetFunc :: C_ListBoxCreateWidgetFunc -> IO (FunPtr C_ListBoxCreateWidgetFunc)
- noListBoxCreateWidgetFunc :: Maybe ListBoxCreateWidgetFunc
- noListBoxCreateWidgetFunc_WithClosures :: Maybe ListBoxCreateWidgetFunc_WithClosures
- wrap_ListBoxCreateWidgetFunc :: Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc)) -> ListBoxCreateWidgetFunc_WithClosures -> C_ListBoxCreateWidgetFunc
- type C_ListBoxFilterFunc = Ptr ListBoxRow -> Ptr () -> IO CInt
- type ListBoxFilterFunc = ListBoxRow -> IO Bool
- type ListBoxFilterFunc_WithClosures = ListBoxRow -> Ptr () -> IO Bool
- drop_closures_ListBoxFilterFunc :: ListBoxFilterFunc -> ListBoxFilterFunc_WithClosures
- dynamic_ListBoxFilterFunc :: (HasCallStack, MonadIO m, IsListBoxRow a) => FunPtr C_ListBoxFilterFunc -> a -> Ptr () -> m Bool
- genClosure_ListBoxFilterFunc :: MonadIO m => ListBoxFilterFunc -> m (GClosure C_ListBoxFilterFunc)
- mk_ListBoxFilterFunc :: C_ListBoxFilterFunc -> IO (FunPtr C_ListBoxFilterFunc)
- noListBoxFilterFunc :: Maybe ListBoxFilterFunc
- noListBoxFilterFunc_WithClosures :: Maybe ListBoxFilterFunc_WithClosures
- wrap_ListBoxFilterFunc :: Maybe (Ptr (FunPtr C_ListBoxFilterFunc)) -> ListBoxFilterFunc_WithClosures -> C_ListBoxFilterFunc
- type C_ListBoxForeachFunc = Ptr ListBox -> Ptr ListBoxRow -> Ptr () -> IO ()
- type ListBoxForeachFunc = ListBox -> ListBoxRow -> IO ()
- type ListBoxForeachFunc_WithClosures = ListBox -> ListBoxRow -> Ptr () -> IO ()
- drop_closures_ListBoxForeachFunc :: ListBoxForeachFunc -> ListBoxForeachFunc_WithClosures
- dynamic_ListBoxForeachFunc :: (HasCallStack, MonadIO m, IsListBox a, IsListBoxRow b) => FunPtr C_ListBoxForeachFunc -> a -> b -> Ptr () -> m ()
- genClosure_ListBoxForeachFunc :: MonadIO m => ListBoxForeachFunc -> m (GClosure C_ListBoxForeachFunc)
- mk_ListBoxForeachFunc :: C_ListBoxForeachFunc -> IO (FunPtr C_ListBoxForeachFunc)
- noListBoxForeachFunc :: Maybe ListBoxForeachFunc
- noListBoxForeachFunc_WithClosures :: Maybe ListBoxForeachFunc_WithClosures
- wrap_ListBoxForeachFunc :: Maybe (Ptr (FunPtr C_ListBoxForeachFunc)) -> ListBoxForeachFunc_WithClosures -> C_ListBoxForeachFunc
- type C_ListBoxSortFunc = Ptr ListBoxRow -> Ptr ListBoxRow -> Ptr () -> IO Int32
- type ListBoxSortFunc = ListBoxRow -> ListBoxRow -> IO Int32
- type ListBoxSortFunc_WithClosures = ListBoxRow -> ListBoxRow -> Ptr () -> IO Int32
- drop_closures_ListBoxSortFunc :: ListBoxSortFunc -> ListBoxSortFunc_WithClosures
- dynamic_ListBoxSortFunc :: (HasCallStack, MonadIO m, IsListBoxRow a, IsListBoxRow b) => FunPtr C_ListBoxSortFunc -> a -> b -> Ptr () -> m Int32
- genClosure_ListBoxSortFunc :: MonadIO m => ListBoxSortFunc -> m (GClosure C_ListBoxSortFunc)
- mk_ListBoxSortFunc :: C_ListBoxSortFunc -> IO (FunPtr C_ListBoxSortFunc)
- noListBoxSortFunc :: Maybe ListBoxSortFunc
- noListBoxSortFunc_WithClosures :: Maybe ListBoxSortFunc_WithClosures
- wrap_ListBoxSortFunc :: Maybe (Ptr (FunPtr C_ListBoxSortFunc)) -> ListBoxSortFunc_WithClosures -> C_ListBoxSortFunc
- type C_ListBoxUpdateHeaderFunc = Ptr ListBoxRow -> Ptr ListBoxRow -> Ptr () -> IO ()
- type ListBoxUpdateHeaderFunc = ListBoxRow -> Maybe ListBoxRow -> IO ()
- type ListBoxUpdateHeaderFunc_WithClosures = ListBoxRow -> Maybe ListBoxRow -> Ptr () -> IO ()
- drop_closures_ListBoxUpdateHeaderFunc :: ListBoxUpdateHeaderFunc -> ListBoxUpdateHeaderFunc_WithClosures
- dynamic_ListBoxUpdateHeaderFunc :: (HasCallStack, MonadIO m, IsListBoxRow a, IsListBoxRow b) => FunPtr C_ListBoxUpdateHeaderFunc -> a -> Maybe b -> Ptr () -> m ()
- genClosure_ListBoxUpdateHeaderFunc :: MonadIO m => ListBoxUpdateHeaderFunc -> m (GClosure C_ListBoxUpdateHeaderFunc)
- mk_ListBoxUpdateHeaderFunc :: C_ListBoxUpdateHeaderFunc -> IO (FunPtr C_ListBoxUpdateHeaderFunc)
- noListBoxUpdateHeaderFunc :: Maybe ListBoxUpdateHeaderFunc
- noListBoxUpdateHeaderFunc_WithClosures :: Maybe ListBoxUpdateHeaderFunc_WithClosures
- wrap_ListBoxUpdateHeaderFunc :: Maybe (Ptr (FunPtr C_ListBoxUpdateHeaderFunc)) -> ListBoxUpdateHeaderFunc_WithClosures -> C_ListBoxUpdateHeaderFunc
- type C_MapListModelMapFunc = Ptr Object -> Ptr () -> IO (Ptr Object)
- type MapListModelMapFunc = Object -> IO Object
- type MapListModelMapFunc_WithClosures = Object -> Ptr () -> IO Object
- drop_closures_MapListModelMapFunc :: MapListModelMapFunc -> MapListModelMapFunc_WithClosures
- dynamic_MapListModelMapFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_MapListModelMapFunc -> a -> Ptr () -> m Object
- genClosure_MapListModelMapFunc :: MonadIO m => MapListModelMapFunc -> m (GClosure C_MapListModelMapFunc)
- mk_MapListModelMapFunc :: C_MapListModelMapFunc -> IO (FunPtr C_MapListModelMapFunc)
- noMapListModelMapFunc :: Maybe MapListModelMapFunc
- noMapListModelMapFunc_WithClosures :: Maybe MapListModelMapFunc_WithClosures
- wrap_MapListModelMapFunc :: Maybe (Ptr (FunPtr C_MapListModelMapFunc)) -> MapListModelMapFunc_WithClosures -> C_MapListModelMapFunc
- type C_MenuButtonCreatePopupFunc = Ptr MenuButton -> Ptr () -> IO ()
- type MenuButtonCreatePopupFunc = MenuButton -> IO ()
- type MenuButtonCreatePopupFunc_WithClosures = MenuButton -> Ptr () -> IO ()
- drop_closures_MenuButtonCreatePopupFunc :: MenuButtonCreatePopupFunc -> MenuButtonCreatePopupFunc_WithClosures
- dynamic_MenuButtonCreatePopupFunc :: (HasCallStack, MonadIO m, IsMenuButton a) => FunPtr C_MenuButtonCreatePopupFunc -> a -> Ptr () -> m ()
- genClosure_MenuButtonCreatePopupFunc :: MonadIO m => MenuButtonCreatePopupFunc -> m (GClosure C_MenuButtonCreatePopupFunc)
- mk_MenuButtonCreatePopupFunc :: C_MenuButtonCreatePopupFunc -> IO (FunPtr C_MenuButtonCreatePopupFunc)
- noMenuButtonCreatePopupFunc :: Maybe MenuButtonCreatePopupFunc
- noMenuButtonCreatePopupFunc_WithClosures :: Maybe MenuButtonCreatePopupFunc_WithClosures
- wrap_MenuButtonCreatePopupFunc :: Maybe (Ptr (FunPtr C_MenuButtonCreatePopupFunc)) -> MenuButtonCreatePopupFunc_WithClosures -> C_MenuButtonCreatePopupFunc
- type C_PageSetupDoneFunc = Ptr PageSetup -> Ptr () -> IO ()
- type PageSetupDoneFunc = PageSetup -> IO ()
- type PageSetupDoneFunc_WithClosures = PageSetup -> Ptr () -> IO ()
- drop_closures_PageSetupDoneFunc :: PageSetupDoneFunc -> PageSetupDoneFunc_WithClosures
- dynamic_PageSetupDoneFunc :: (HasCallStack, MonadIO m, IsPageSetup a) => FunPtr C_PageSetupDoneFunc -> a -> Ptr () -> m ()
- genClosure_PageSetupDoneFunc :: MonadIO m => PageSetupDoneFunc -> m (GClosure C_PageSetupDoneFunc)
- mk_PageSetupDoneFunc :: C_PageSetupDoneFunc -> IO (FunPtr C_PageSetupDoneFunc)
- noPageSetupDoneFunc :: Maybe PageSetupDoneFunc
- noPageSetupDoneFunc_WithClosures :: Maybe PageSetupDoneFunc_WithClosures
- wrap_PageSetupDoneFunc :: Maybe (Ptr (FunPtr C_PageSetupDoneFunc)) -> PageSetupDoneFunc_WithClosures -> C_PageSetupDoneFunc
- type C_PrintSettingsFunc = CString -> CString -> Ptr () -> IO ()
- type PrintSettingsFunc = Text -> Text -> IO ()
- type PrintSettingsFunc_WithClosures = Text -> Text -> Ptr () -> IO ()
- drop_closures_PrintSettingsFunc :: PrintSettingsFunc -> PrintSettingsFunc_WithClosures
- dynamic_PrintSettingsFunc :: (HasCallStack, MonadIO m) => FunPtr C_PrintSettingsFunc -> Text -> Text -> Ptr () -> m ()
- genClosure_PrintSettingsFunc :: MonadIO m => PrintSettingsFunc -> m (GClosure C_PrintSettingsFunc)
- mk_PrintSettingsFunc :: C_PrintSettingsFunc -> IO (FunPtr C_PrintSettingsFunc)
- noPrintSettingsFunc :: Maybe PrintSettingsFunc
- noPrintSettingsFunc_WithClosures :: Maybe PrintSettingsFunc_WithClosures
- wrap_PrintSettingsFunc :: Maybe (Ptr (FunPtr C_PrintSettingsFunc)) -> PrintSettingsFunc_WithClosures -> C_PrintSettingsFunc
- type C_ScaleFormatValueFunc = Ptr Scale -> CDouble -> Ptr () -> IO CString
- type ScaleFormatValueFunc = Scale -> Double -> IO Text
- type ScaleFormatValueFunc_WithClosures = Scale -> Double -> Ptr () -> IO Text
- drop_closures_ScaleFormatValueFunc :: ScaleFormatValueFunc -> ScaleFormatValueFunc_WithClosures
- dynamic_ScaleFormatValueFunc :: (HasCallStack, MonadIO m, IsScale a) => FunPtr C_ScaleFormatValueFunc -> a -> Double -> Ptr () -> m Text
- genClosure_ScaleFormatValueFunc :: MonadIO m => ScaleFormatValueFunc -> m (GClosure C_ScaleFormatValueFunc)
- mk_ScaleFormatValueFunc :: C_ScaleFormatValueFunc -> IO (FunPtr C_ScaleFormatValueFunc)
- noScaleFormatValueFunc :: Maybe ScaleFormatValueFunc
- noScaleFormatValueFunc_WithClosures :: Maybe ScaleFormatValueFunc_WithClosures
- wrap_ScaleFormatValueFunc :: Maybe (Ptr (FunPtr C_ScaleFormatValueFunc)) -> ScaleFormatValueFunc_WithClosures -> C_ScaleFormatValueFunc
- type C_ShortcutFunc = Ptr Widget -> Ptr GVariant -> Ptr () -> IO CInt
- type ShortcutFunc = Widget -> Maybe GVariant -> IO Bool
- type ShortcutFunc_WithClosures = Widget -> Maybe GVariant -> Ptr () -> IO Bool
- drop_closures_ShortcutFunc :: ShortcutFunc -> ShortcutFunc_WithClosures
- dynamic_ShortcutFunc :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_ShortcutFunc -> a -> Maybe GVariant -> Ptr () -> m Bool
- genClosure_ShortcutFunc :: MonadIO m => ShortcutFunc -> m (GClosure C_ShortcutFunc)
- mk_ShortcutFunc :: C_ShortcutFunc -> IO (FunPtr C_ShortcutFunc)
- noShortcutFunc :: Maybe ShortcutFunc
- noShortcutFunc_WithClosures :: Maybe ShortcutFunc_WithClosures
- wrap_ShortcutFunc :: Maybe (Ptr (FunPtr C_ShortcutFunc)) -> ShortcutFunc_WithClosures -> C_ShortcutFunc
- type C_TextCharPredicate = CInt -> Ptr () -> IO CInt
- type TextCharPredicate = Char -> IO Bool
- type TextCharPredicate_WithClosures = Char -> Ptr () -> IO Bool
- drop_closures_TextCharPredicate :: TextCharPredicate -> TextCharPredicate_WithClosures
- dynamic_TextCharPredicate :: (HasCallStack, MonadIO m) => FunPtr C_TextCharPredicate -> Char -> Ptr () -> m Bool
- genClosure_TextCharPredicate :: MonadIO m => TextCharPredicate -> m (GClosure C_TextCharPredicate)
- mk_TextCharPredicate :: C_TextCharPredicate -> IO (FunPtr C_TextCharPredicate)
- noTextCharPredicate :: Maybe TextCharPredicate
- noTextCharPredicate_WithClosures :: Maybe TextCharPredicate_WithClosures
- wrap_TextCharPredicate :: Maybe (Ptr (FunPtr C_TextCharPredicate)) -> TextCharPredicate_WithClosures -> C_TextCharPredicate
- type C_TextTagTableForeach = Ptr TextTag -> Ptr () -> IO ()
- type TextTagTableForeach = TextTag -> IO ()
- type TextTagTableForeach_WithClosures = TextTag -> Ptr () -> IO ()
- drop_closures_TextTagTableForeach :: TextTagTableForeach -> TextTagTableForeach_WithClosures
- dynamic_TextTagTableForeach :: (HasCallStack, MonadIO m, IsTextTag a) => FunPtr C_TextTagTableForeach -> a -> Ptr () -> m ()
- genClosure_TextTagTableForeach :: MonadIO m => TextTagTableForeach -> m (GClosure C_TextTagTableForeach)
- mk_TextTagTableForeach :: C_TextTagTableForeach -> IO (FunPtr C_TextTagTableForeach)
- noTextTagTableForeach :: Maybe TextTagTableForeach
- noTextTagTableForeach_WithClosures :: Maybe TextTagTableForeach_WithClosures
- wrap_TextTagTableForeach :: Maybe (Ptr (FunPtr C_TextTagTableForeach)) -> TextTagTableForeach_WithClosures -> C_TextTagTableForeach
- type C_TickCallback = Ptr Widget -> Ptr FrameClock -> Ptr () -> IO CInt
- type TickCallback = Widget -> FrameClock -> IO Bool
- type TickCallback_WithClosures = Widget -> FrameClock -> Ptr () -> IO Bool
- drop_closures_TickCallback :: TickCallback -> TickCallback_WithClosures
- dynamic_TickCallback :: (HasCallStack, MonadIO m, IsWidget a, IsFrameClock b) => FunPtr C_TickCallback -> a -> b -> Ptr () -> m Bool
- genClosure_TickCallback :: MonadIO m => TickCallback -> m (GClosure C_TickCallback)
- mk_TickCallback :: C_TickCallback -> IO (FunPtr C_TickCallback)
- noTickCallback :: Maybe TickCallback
- noTickCallback_WithClosures :: Maybe TickCallback_WithClosures
- wrap_TickCallback :: Maybe (Ptr (FunPtr C_TickCallback)) -> TickCallback_WithClosures -> C_TickCallback
- type C_TreeCellDataFunc = Ptr TreeViewColumn -> Ptr CellRenderer -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO ()
- type TreeCellDataFunc = TreeViewColumn -> CellRenderer -> TreeModel -> TreeIter -> IO ()
- type TreeCellDataFunc_WithClosures = TreeViewColumn -> CellRenderer -> TreeModel -> TreeIter -> Ptr () -> IO ()
- drop_closures_TreeCellDataFunc :: TreeCellDataFunc -> TreeCellDataFunc_WithClosures
- dynamic_TreeCellDataFunc :: (HasCallStack, MonadIO m, IsTreeViewColumn a, IsCellRenderer b, IsTreeModel c) => FunPtr C_TreeCellDataFunc -> a -> b -> c -> TreeIter -> Ptr () -> m ()
- genClosure_TreeCellDataFunc :: MonadIO m => TreeCellDataFunc -> m (GClosure C_TreeCellDataFunc)
- mk_TreeCellDataFunc :: C_TreeCellDataFunc -> IO (FunPtr C_TreeCellDataFunc)
- noTreeCellDataFunc :: Maybe TreeCellDataFunc
- noTreeCellDataFunc_WithClosures :: Maybe TreeCellDataFunc_WithClosures
- wrap_TreeCellDataFunc :: Maybe (Ptr (FunPtr C_TreeCellDataFunc)) -> TreeCellDataFunc_WithClosures -> C_TreeCellDataFunc
- type C_TreeIterCompareFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr TreeIter -> Ptr () -> IO Int32
- type TreeIterCompareFunc = TreeModel -> TreeIter -> TreeIter -> IO Int32
- type TreeIterCompareFunc_WithClosures = TreeModel -> TreeIter -> TreeIter -> Ptr () -> IO Int32
- drop_closures_TreeIterCompareFunc :: TreeIterCompareFunc -> TreeIterCompareFunc_WithClosures
- dynamic_TreeIterCompareFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeIterCompareFunc -> a -> TreeIter -> TreeIter -> Ptr () -> m Int32
- genClosure_TreeIterCompareFunc :: MonadIO m => TreeIterCompareFunc -> m (GClosure C_TreeIterCompareFunc)
- mk_TreeIterCompareFunc :: C_TreeIterCompareFunc -> IO (FunPtr C_TreeIterCompareFunc)
- noTreeIterCompareFunc :: Maybe TreeIterCompareFunc
- noTreeIterCompareFunc_WithClosures :: Maybe TreeIterCompareFunc_WithClosures
- wrap_TreeIterCompareFunc :: Maybe (Ptr (FunPtr C_TreeIterCompareFunc)) -> TreeIterCompareFunc_WithClosures -> C_TreeIterCompareFunc
- type C_TreeListModelCreateModelFunc = Ptr Object -> Ptr () -> IO (Ptr ListModel)
- type TreeListModelCreateModelFunc = Object -> IO (Maybe ListModel)
- type TreeListModelCreateModelFunc_WithClosures = Object -> Ptr () -> IO (Maybe ListModel)
- drop_closures_TreeListModelCreateModelFunc :: TreeListModelCreateModelFunc -> TreeListModelCreateModelFunc_WithClosures
- dynamic_TreeListModelCreateModelFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_TreeListModelCreateModelFunc -> a -> Ptr () -> m (Maybe ListModel)
- genClosure_TreeListModelCreateModelFunc :: MonadIO m => TreeListModelCreateModelFunc -> m (GClosure C_TreeListModelCreateModelFunc)
- mk_TreeListModelCreateModelFunc :: C_TreeListModelCreateModelFunc -> IO (FunPtr C_TreeListModelCreateModelFunc)
- noTreeListModelCreateModelFunc :: Maybe TreeListModelCreateModelFunc
- noTreeListModelCreateModelFunc_WithClosures :: Maybe TreeListModelCreateModelFunc_WithClosures
- wrap_TreeListModelCreateModelFunc :: Maybe (Ptr (FunPtr C_TreeListModelCreateModelFunc)) -> TreeListModelCreateModelFunc_WithClosures -> C_TreeListModelCreateModelFunc
- type C_TreeModelFilterModifyFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr GValue -> Int32 -> Ptr () -> IO ()
- type TreeModelFilterModifyFunc = TreeModel -> TreeIter -> GValue -> Int32 -> IO ()
- type TreeModelFilterModifyFunc_WithClosures = TreeModel -> TreeIter -> GValue -> Int32 -> Ptr () -> IO ()
- drop_closures_TreeModelFilterModifyFunc :: TreeModelFilterModifyFunc -> TreeModelFilterModifyFunc_WithClosures
- dynamic_TreeModelFilterModifyFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeModelFilterModifyFunc -> a -> TreeIter -> GValue -> Int32 -> Ptr () -> m ()
- genClosure_TreeModelFilterModifyFunc :: MonadIO m => TreeModelFilterModifyFunc -> m (GClosure C_TreeModelFilterModifyFunc)
- mk_TreeModelFilterModifyFunc :: C_TreeModelFilterModifyFunc -> IO (FunPtr C_TreeModelFilterModifyFunc)
- noTreeModelFilterModifyFunc :: Maybe TreeModelFilterModifyFunc
- noTreeModelFilterModifyFunc_WithClosures :: Maybe TreeModelFilterModifyFunc_WithClosures
- wrap_TreeModelFilterModifyFunc :: Maybe (Ptr (FunPtr C_TreeModelFilterModifyFunc)) -> TreeModelFilterModifyFunc_WithClosures -> C_TreeModelFilterModifyFunc
- type C_TreeModelFilterVisibleFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt
- type TreeModelFilterVisibleFunc = TreeModel -> TreeIter -> IO Bool
- type TreeModelFilterVisibleFunc_WithClosures = TreeModel -> TreeIter -> Ptr () -> IO Bool
- drop_closures_TreeModelFilterVisibleFunc :: TreeModelFilterVisibleFunc -> TreeModelFilterVisibleFunc_WithClosures
- dynamic_TreeModelFilterVisibleFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeModelFilterVisibleFunc -> a -> TreeIter -> Ptr () -> m Bool
- genClosure_TreeModelFilterVisibleFunc :: MonadIO m => TreeModelFilterVisibleFunc -> m (GClosure C_TreeModelFilterVisibleFunc)
- mk_TreeModelFilterVisibleFunc :: C_TreeModelFilterVisibleFunc -> IO (FunPtr C_TreeModelFilterVisibleFunc)
- noTreeModelFilterVisibleFunc :: Maybe TreeModelFilterVisibleFunc
- noTreeModelFilterVisibleFunc_WithClosures :: Maybe TreeModelFilterVisibleFunc_WithClosures
- wrap_TreeModelFilterVisibleFunc :: Maybe (Ptr (FunPtr C_TreeModelFilterVisibleFunc)) -> TreeModelFilterVisibleFunc_WithClosures -> C_TreeModelFilterVisibleFunc
- type C_TreeModelForeachFunc = Ptr TreeModel -> Ptr TreePath -> Ptr TreeIter -> Ptr () -> IO CInt
- type TreeModelForeachFunc = TreeModel -> TreePath -> TreeIter -> IO Bool
- type TreeModelForeachFunc_WithClosures = TreeModel -> TreePath -> TreeIter -> Ptr () -> IO Bool
- drop_closures_TreeModelForeachFunc :: TreeModelForeachFunc -> TreeModelForeachFunc_WithClosures
- dynamic_TreeModelForeachFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeModelForeachFunc -> a -> TreePath -> TreeIter -> Ptr () -> m Bool
- genClosure_TreeModelForeachFunc :: MonadIO m => TreeModelForeachFunc -> m (GClosure C_TreeModelForeachFunc)
- mk_TreeModelForeachFunc :: C_TreeModelForeachFunc -> IO (FunPtr C_TreeModelForeachFunc)
- noTreeModelForeachFunc :: Maybe TreeModelForeachFunc
- noTreeModelForeachFunc_WithClosures :: Maybe TreeModelForeachFunc_WithClosures
- wrap_TreeModelForeachFunc :: Maybe (Ptr (FunPtr C_TreeModelForeachFunc)) -> TreeModelForeachFunc_WithClosures -> C_TreeModelForeachFunc
- type C_TreeSelectionForeachFunc = Ptr TreeModel -> Ptr TreePath -> Ptr TreeIter -> Ptr () -> IO ()
- type TreeSelectionForeachFunc = TreeModel -> TreePath -> TreeIter -> IO ()
- type TreeSelectionForeachFunc_WithClosures = TreeModel -> TreePath -> TreeIter -> Ptr () -> IO ()
- drop_closures_TreeSelectionForeachFunc :: TreeSelectionForeachFunc -> TreeSelectionForeachFunc_WithClosures
- dynamic_TreeSelectionForeachFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeSelectionForeachFunc -> a -> TreePath -> TreeIter -> Ptr () -> m ()
- genClosure_TreeSelectionForeachFunc :: MonadIO m => TreeSelectionForeachFunc -> m (GClosure C_TreeSelectionForeachFunc)
- mk_TreeSelectionForeachFunc :: C_TreeSelectionForeachFunc -> IO (FunPtr C_TreeSelectionForeachFunc)
- noTreeSelectionForeachFunc :: Maybe TreeSelectionForeachFunc
- noTreeSelectionForeachFunc_WithClosures :: Maybe TreeSelectionForeachFunc_WithClosures
- wrap_TreeSelectionForeachFunc :: Maybe (Ptr (FunPtr C_TreeSelectionForeachFunc)) -> TreeSelectionForeachFunc_WithClosures -> C_TreeSelectionForeachFunc
- type C_TreeSelectionFunc = Ptr TreeSelection -> Ptr TreeModel -> Ptr TreePath -> CInt -> Ptr () -> IO CInt
- type TreeSelectionFunc = TreeSelection -> TreeModel -> TreePath -> Bool -> IO Bool
- type TreeSelectionFunc_WithClosures = TreeSelection -> TreeModel -> TreePath -> Bool -> Ptr () -> IO Bool
- drop_closures_TreeSelectionFunc :: TreeSelectionFunc -> TreeSelectionFunc_WithClosures
- dynamic_TreeSelectionFunc :: (HasCallStack, MonadIO m, IsTreeSelection a, IsTreeModel b) => FunPtr C_TreeSelectionFunc -> a -> b -> TreePath -> Bool -> Ptr () -> m Bool
- genClosure_TreeSelectionFunc :: MonadIO m => TreeSelectionFunc -> m (GClosure C_TreeSelectionFunc)
- mk_TreeSelectionFunc :: C_TreeSelectionFunc -> IO (FunPtr C_TreeSelectionFunc)
- noTreeSelectionFunc :: Maybe TreeSelectionFunc
- noTreeSelectionFunc_WithClosures :: Maybe TreeSelectionFunc_WithClosures
- wrap_TreeSelectionFunc :: Maybe (Ptr (FunPtr C_TreeSelectionFunc)) -> TreeSelectionFunc_WithClosures -> C_TreeSelectionFunc
- type C_TreeViewColumnDropFunc = Ptr TreeView -> Ptr TreeViewColumn -> Ptr TreeViewColumn -> Ptr TreeViewColumn -> Ptr () -> IO CInt
- type TreeViewColumnDropFunc = TreeView -> TreeViewColumn -> TreeViewColumn -> TreeViewColumn -> IO Bool
- type TreeViewColumnDropFunc_WithClosures = TreeView -> TreeViewColumn -> TreeViewColumn -> TreeViewColumn -> Ptr () -> IO Bool
- drop_closures_TreeViewColumnDropFunc :: TreeViewColumnDropFunc -> TreeViewColumnDropFunc_WithClosures
- dynamic_TreeViewColumnDropFunc :: (HasCallStack, MonadIO m, IsTreeView a, IsTreeViewColumn b, IsTreeViewColumn c, IsTreeViewColumn d) => FunPtr C_TreeViewColumnDropFunc -> a -> b -> c -> d -> Ptr () -> m Bool
- genClosure_TreeViewColumnDropFunc :: MonadIO m => TreeViewColumnDropFunc -> m (GClosure C_TreeViewColumnDropFunc)
- mk_TreeViewColumnDropFunc :: C_TreeViewColumnDropFunc -> IO (FunPtr C_TreeViewColumnDropFunc)
- noTreeViewColumnDropFunc :: Maybe TreeViewColumnDropFunc
- noTreeViewColumnDropFunc_WithClosures :: Maybe TreeViewColumnDropFunc_WithClosures
- wrap_TreeViewColumnDropFunc :: Maybe (Ptr (FunPtr C_TreeViewColumnDropFunc)) -> TreeViewColumnDropFunc_WithClosures -> C_TreeViewColumnDropFunc
- type C_TreeViewMappingFunc = Ptr TreeView -> Ptr TreePath -> Ptr () -> IO ()
- type TreeViewMappingFunc = TreeView -> TreePath -> IO ()
- type TreeViewMappingFunc_WithClosures = TreeView -> TreePath -> Ptr () -> IO ()
- drop_closures_TreeViewMappingFunc :: TreeViewMappingFunc -> TreeViewMappingFunc_WithClosures
- dynamic_TreeViewMappingFunc :: (HasCallStack, MonadIO m, IsTreeView a) => FunPtr C_TreeViewMappingFunc -> a -> TreePath -> Ptr () -> m ()
- genClosure_TreeViewMappingFunc :: MonadIO m => TreeViewMappingFunc -> m (GClosure C_TreeViewMappingFunc)
- mk_TreeViewMappingFunc :: C_TreeViewMappingFunc -> IO (FunPtr C_TreeViewMappingFunc)
- noTreeViewMappingFunc :: Maybe TreeViewMappingFunc
- noTreeViewMappingFunc_WithClosures :: Maybe TreeViewMappingFunc_WithClosures
- wrap_TreeViewMappingFunc :: Maybe (Ptr (FunPtr C_TreeViewMappingFunc)) -> TreeViewMappingFunc_WithClosures -> C_TreeViewMappingFunc
- type C_TreeViewRowSeparatorFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt
- type TreeViewRowSeparatorFunc = TreeModel -> TreeIter -> IO Bool
- type TreeViewRowSeparatorFunc_WithClosures = TreeModel -> TreeIter -> Ptr () -> IO Bool
- drop_closures_TreeViewRowSeparatorFunc :: TreeViewRowSeparatorFunc -> TreeViewRowSeparatorFunc_WithClosures
- dynamic_TreeViewRowSeparatorFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeViewRowSeparatorFunc -> a -> TreeIter -> Ptr () -> m Bool
- genClosure_TreeViewRowSeparatorFunc :: MonadIO m => TreeViewRowSeparatorFunc -> m (GClosure C_TreeViewRowSeparatorFunc)
- mk_TreeViewRowSeparatorFunc :: C_TreeViewRowSeparatorFunc -> IO (FunPtr C_TreeViewRowSeparatorFunc)
- noTreeViewRowSeparatorFunc :: Maybe TreeViewRowSeparatorFunc
- noTreeViewRowSeparatorFunc_WithClosures :: Maybe TreeViewRowSeparatorFunc_WithClosures
- wrap_TreeViewRowSeparatorFunc :: Maybe (Ptr (FunPtr C_TreeViewRowSeparatorFunc)) -> TreeViewRowSeparatorFunc_WithClosures -> C_TreeViewRowSeparatorFunc
- type C_TreeViewSearchEqualFunc = Ptr TreeModel -> Int32 -> CString -> Ptr TreeIter -> Ptr () -> IO CInt
- type TreeViewSearchEqualFunc = TreeModel -> Int32 -> Text -> TreeIter -> IO Bool
- type TreeViewSearchEqualFunc_WithClosures = TreeModel -> Int32 -> Text -> TreeIter -> Ptr () -> IO Bool
- drop_closures_TreeViewSearchEqualFunc :: TreeViewSearchEqualFunc -> TreeViewSearchEqualFunc_WithClosures
- dynamic_TreeViewSearchEqualFunc :: (HasCallStack, MonadIO m, IsTreeModel a) => FunPtr C_TreeViewSearchEqualFunc -> a -> Int32 -> Text -> TreeIter -> Ptr () -> m Bool
- genClosure_TreeViewSearchEqualFunc :: MonadIO m => TreeViewSearchEqualFunc -> m (GClosure C_TreeViewSearchEqualFunc)
- mk_TreeViewSearchEqualFunc :: C_TreeViewSearchEqualFunc -> IO (FunPtr C_TreeViewSearchEqualFunc)
- noTreeViewSearchEqualFunc :: Maybe TreeViewSearchEqualFunc
- noTreeViewSearchEqualFunc_WithClosures :: Maybe TreeViewSearchEqualFunc_WithClosures
- wrap_TreeViewSearchEqualFunc :: Maybe (Ptr (FunPtr C_TreeViewSearchEqualFunc)) -> TreeViewSearchEqualFunc_WithClosures -> C_TreeViewSearchEqualFunc
- type C_WidgetActionActivateFunc = Ptr Widget -> CString -> Ptr GVariant -> IO ()
- type WidgetActionActivateFunc = Widget -> Text -> GVariant -> IO ()
- dynamic_WidgetActionActivateFunc :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetActionActivateFunc -> a -> Text -> GVariant -> m ()
- genClosure_WidgetActionActivateFunc :: MonadIO m => WidgetActionActivateFunc -> m (GClosure C_WidgetActionActivateFunc)
- mk_WidgetActionActivateFunc :: C_WidgetActionActivateFunc -> IO (FunPtr C_WidgetActionActivateFunc)
- noWidgetActionActivateFunc :: Maybe WidgetActionActivateFunc
- wrap_WidgetActionActivateFunc :: Maybe (Ptr (FunPtr C_WidgetActionActivateFunc)) -> WidgetActionActivateFunc -> C_WidgetActionActivateFunc
- type C_WidgetClassComputeExpandFieldCallback = Ptr Widget -> CInt -> CInt -> IO ()
- type WidgetClassComputeExpandFieldCallback = Widget -> Bool -> Bool -> IO ()
- dynamic_WidgetClassComputeExpandFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassComputeExpandFieldCallback -> a -> Bool -> Bool -> m ()
- genClosure_WidgetClassComputeExpandFieldCallback :: MonadIO m => WidgetClassComputeExpandFieldCallback -> m (GClosure C_WidgetClassComputeExpandFieldCallback)
- mk_WidgetClassComputeExpandFieldCallback :: C_WidgetClassComputeExpandFieldCallback -> IO (FunPtr C_WidgetClassComputeExpandFieldCallback)
- noWidgetClassComputeExpandFieldCallback :: Maybe WidgetClassComputeExpandFieldCallback
- wrap_WidgetClassComputeExpandFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassComputeExpandFieldCallback)) -> WidgetClassComputeExpandFieldCallback -> C_WidgetClassComputeExpandFieldCallback
- type C_WidgetClassContainsFieldCallback = Ptr Widget -> CDouble -> CDouble -> IO CInt
- type WidgetClassContainsFieldCallback = Widget -> Double -> Double -> IO Bool
- dynamic_WidgetClassContainsFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassContainsFieldCallback -> a -> Double -> Double -> m Bool
- genClosure_WidgetClassContainsFieldCallback :: MonadIO m => WidgetClassContainsFieldCallback -> m (GClosure C_WidgetClassContainsFieldCallback)
- mk_WidgetClassContainsFieldCallback :: C_WidgetClassContainsFieldCallback -> IO (FunPtr C_WidgetClassContainsFieldCallback)
- noWidgetClassContainsFieldCallback :: Maybe WidgetClassContainsFieldCallback
- wrap_WidgetClassContainsFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassContainsFieldCallback)) -> WidgetClassContainsFieldCallback -> C_WidgetClassContainsFieldCallback
- type C_WidgetClassCssChangedFieldCallback = Ptr Widget -> Ptr CssStyleChange -> IO ()
- type WidgetClassCssChangedFieldCallback = Widget -> CssStyleChange -> IO ()
- dynamic_WidgetClassCssChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassCssChangedFieldCallback -> a -> CssStyleChange -> m ()
- genClosure_WidgetClassCssChangedFieldCallback :: MonadIO m => WidgetClassCssChangedFieldCallback -> m (GClosure C_WidgetClassCssChangedFieldCallback)
- mk_WidgetClassCssChangedFieldCallback :: C_WidgetClassCssChangedFieldCallback -> IO (FunPtr C_WidgetClassCssChangedFieldCallback)
- noWidgetClassCssChangedFieldCallback :: Maybe WidgetClassCssChangedFieldCallback
- wrap_WidgetClassCssChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassCssChangedFieldCallback)) -> WidgetClassCssChangedFieldCallback -> C_WidgetClassCssChangedFieldCallback
- type C_WidgetClassDirectionChangedFieldCallback = Ptr Widget -> CUInt -> IO ()
- type WidgetClassDirectionChangedFieldCallback = Widget -> TextDirection -> IO ()
- dynamic_WidgetClassDirectionChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassDirectionChangedFieldCallback -> a -> TextDirection -> m ()
- genClosure_WidgetClassDirectionChangedFieldCallback :: MonadIO m => WidgetClassDirectionChangedFieldCallback -> m (GClosure C_WidgetClassDirectionChangedFieldCallback)
- mk_WidgetClassDirectionChangedFieldCallback :: C_WidgetClassDirectionChangedFieldCallback -> IO (FunPtr C_WidgetClassDirectionChangedFieldCallback)
- noWidgetClassDirectionChangedFieldCallback :: Maybe WidgetClassDirectionChangedFieldCallback
- wrap_WidgetClassDirectionChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassDirectionChangedFieldCallback)) -> WidgetClassDirectionChangedFieldCallback -> C_WidgetClassDirectionChangedFieldCallback
- type C_WidgetClassFocusFieldCallback = Ptr Widget -> CUInt -> IO CInt
- type WidgetClassFocusFieldCallback = Widget -> DirectionType -> IO Bool
- dynamic_WidgetClassFocusFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassFocusFieldCallback -> a -> DirectionType -> m Bool
- genClosure_WidgetClassFocusFieldCallback :: MonadIO m => WidgetClassFocusFieldCallback -> m (GClosure C_WidgetClassFocusFieldCallback)
- mk_WidgetClassFocusFieldCallback :: C_WidgetClassFocusFieldCallback -> IO (FunPtr C_WidgetClassFocusFieldCallback)
- noWidgetClassFocusFieldCallback :: Maybe WidgetClassFocusFieldCallback
- wrap_WidgetClassFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassFocusFieldCallback)) -> WidgetClassFocusFieldCallback -> C_WidgetClassFocusFieldCallback
- type C_WidgetClassGetRequestModeFieldCallback = Ptr Widget -> IO CUInt
- type WidgetClassGetRequestModeFieldCallback = Widget -> IO SizeRequestMode
- dynamic_WidgetClassGetRequestModeFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassGetRequestModeFieldCallback -> a -> m SizeRequestMode
- genClosure_WidgetClassGetRequestModeFieldCallback :: MonadIO m => WidgetClassGetRequestModeFieldCallback -> m (GClosure C_WidgetClassGetRequestModeFieldCallback)
- mk_WidgetClassGetRequestModeFieldCallback :: C_WidgetClassGetRequestModeFieldCallback -> IO (FunPtr C_WidgetClassGetRequestModeFieldCallback)
- noWidgetClassGetRequestModeFieldCallback :: Maybe WidgetClassGetRequestModeFieldCallback
- wrap_WidgetClassGetRequestModeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassGetRequestModeFieldCallback)) -> WidgetClassGetRequestModeFieldCallback -> C_WidgetClassGetRequestModeFieldCallback
- type C_WidgetClassGrabFocusFieldCallback = Ptr Widget -> IO CInt
- type WidgetClassGrabFocusFieldCallback = Widget -> IO Bool
- dynamic_WidgetClassGrabFocusFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassGrabFocusFieldCallback -> a -> m Bool
- genClosure_WidgetClassGrabFocusFieldCallback :: MonadIO m => WidgetClassGrabFocusFieldCallback -> m (GClosure C_WidgetClassGrabFocusFieldCallback)
- mk_WidgetClassGrabFocusFieldCallback :: C_WidgetClassGrabFocusFieldCallback -> IO (FunPtr C_WidgetClassGrabFocusFieldCallback)
- noWidgetClassGrabFocusFieldCallback :: Maybe WidgetClassGrabFocusFieldCallback
- wrap_WidgetClassGrabFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassGrabFocusFieldCallback)) -> WidgetClassGrabFocusFieldCallback -> C_WidgetClassGrabFocusFieldCallback
- type C_WidgetClassHideFieldCallback = Ptr Widget -> IO ()
- type WidgetClassHideFieldCallback = Widget -> IO ()
- dynamic_WidgetClassHideFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassHideFieldCallback -> a -> m ()
- genClosure_WidgetClassHideFieldCallback :: MonadIO m => WidgetClassHideFieldCallback -> m (GClosure C_WidgetClassHideFieldCallback)
- mk_WidgetClassHideFieldCallback :: C_WidgetClassHideFieldCallback -> IO (FunPtr C_WidgetClassHideFieldCallback)
- noWidgetClassHideFieldCallback :: Maybe WidgetClassHideFieldCallback
- wrap_WidgetClassHideFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassHideFieldCallback)) -> WidgetClassHideFieldCallback -> C_WidgetClassHideFieldCallback
- type C_WidgetClassKeynavFailedFieldCallback = Ptr Widget -> CUInt -> IO CInt
- type WidgetClassKeynavFailedFieldCallback = Widget -> DirectionType -> IO Bool
- dynamic_WidgetClassKeynavFailedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassKeynavFailedFieldCallback -> a -> DirectionType -> m Bool
- genClosure_WidgetClassKeynavFailedFieldCallback :: MonadIO m => WidgetClassKeynavFailedFieldCallback -> m (GClosure C_WidgetClassKeynavFailedFieldCallback)
- mk_WidgetClassKeynavFailedFieldCallback :: C_WidgetClassKeynavFailedFieldCallback -> IO (FunPtr C_WidgetClassKeynavFailedFieldCallback)
- noWidgetClassKeynavFailedFieldCallback :: Maybe WidgetClassKeynavFailedFieldCallback
- wrap_WidgetClassKeynavFailedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassKeynavFailedFieldCallback)) -> WidgetClassKeynavFailedFieldCallback -> C_WidgetClassKeynavFailedFieldCallback
- type C_WidgetClassMapFieldCallback = Ptr Widget -> IO ()
- type WidgetClassMapFieldCallback = Widget -> IO ()
- dynamic_WidgetClassMapFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassMapFieldCallback -> a -> m ()
- genClosure_WidgetClassMapFieldCallback :: MonadIO m => WidgetClassMapFieldCallback -> m (GClosure C_WidgetClassMapFieldCallback)
- mk_WidgetClassMapFieldCallback :: C_WidgetClassMapFieldCallback -> IO (FunPtr C_WidgetClassMapFieldCallback)
- noWidgetClassMapFieldCallback :: Maybe WidgetClassMapFieldCallback
- wrap_WidgetClassMapFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMapFieldCallback)) -> WidgetClassMapFieldCallback -> C_WidgetClassMapFieldCallback
- type C_WidgetClassMeasureFieldCallback = Ptr Widget -> CUInt -> Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO ()
- type WidgetClassMeasureFieldCallback = Widget -> Orientation -> Int32 -> IO (Int32, Int32, Int32, Int32)
- dynamic_WidgetClassMeasureFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassMeasureFieldCallback -> a -> Orientation -> Int32 -> m (Int32, Int32, Int32, Int32)
- genClosure_WidgetClassMeasureFieldCallback :: MonadIO m => WidgetClassMeasureFieldCallback -> m (GClosure C_WidgetClassMeasureFieldCallback)
- mk_WidgetClassMeasureFieldCallback :: C_WidgetClassMeasureFieldCallback -> IO (FunPtr C_WidgetClassMeasureFieldCallback)
- noWidgetClassMeasureFieldCallback :: Maybe WidgetClassMeasureFieldCallback
- wrap_WidgetClassMeasureFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMeasureFieldCallback)) -> WidgetClassMeasureFieldCallback -> C_WidgetClassMeasureFieldCallback
- type C_WidgetClassMnemonicActivateFieldCallback = Ptr Widget -> CInt -> IO CInt
- type WidgetClassMnemonicActivateFieldCallback = Widget -> Bool -> IO Bool
- dynamic_WidgetClassMnemonicActivateFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassMnemonicActivateFieldCallback -> a -> Bool -> m Bool
- genClosure_WidgetClassMnemonicActivateFieldCallback :: MonadIO m => WidgetClassMnemonicActivateFieldCallback -> m (GClosure C_WidgetClassMnemonicActivateFieldCallback)
- mk_WidgetClassMnemonicActivateFieldCallback :: C_WidgetClassMnemonicActivateFieldCallback -> IO (FunPtr C_WidgetClassMnemonicActivateFieldCallback)
- noWidgetClassMnemonicActivateFieldCallback :: Maybe WidgetClassMnemonicActivateFieldCallback
- wrap_WidgetClassMnemonicActivateFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMnemonicActivateFieldCallback)) -> WidgetClassMnemonicActivateFieldCallback -> C_WidgetClassMnemonicActivateFieldCallback
- type C_WidgetClassMoveFocusFieldCallback = Ptr Widget -> CUInt -> IO ()
- type WidgetClassMoveFocusFieldCallback = Widget -> DirectionType -> IO ()
- dynamic_WidgetClassMoveFocusFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassMoveFocusFieldCallback -> a -> DirectionType -> m ()
- genClosure_WidgetClassMoveFocusFieldCallback :: MonadIO m => WidgetClassMoveFocusFieldCallback -> m (GClosure C_WidgetClassMoveFocusFieldCallback)
- mk_WidgetClassMoveFocusFieldCallback :: C_WidgetClassMoveFocusFieldCallback -> IO (FunPtr C_WidgetClassMoveFocusFieldCallback)
- noWidgetClassMoveFocusFieldCallback :: Maybe WidgetClassMoveFocusFieldCallback
- wrap_WidgetClassMoveFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMoveFocusFieldCallback)) -> WidgetClassMoveFocusFieldCallback -> C_WidgetClassMoveFocusFieldCallback
- type C_WidgetClassQueryTooltipFieldCallback = Ptr Widget -> Int32 -> Int32 -> CInt -> Ptr Tooltip -> IO CInt
- type WidgetClassQueryTooltipFieldCallback = Widget -> Int32 -> Int32 -> Bool -> Tooltip -> IO Bool
- dynamic_WidgetClassQueryTooltipFieldCallback :: (HasCallStack, MonadIO m, IsWidget a, IsTooltip b) => FunPtr C_WidgetClassQueryTooltipFieldCallback -> a -> Int32 -> Int32 -> Bool -> b -> m Bool
- genClosure_WidgetClassQueryTooltipFieldCallback :: MonadIO m => WidgetClassQueryTooltipFieldCallback -> m (GClosure C_WidgetClassQueryTooltipFieldCallback)
- mk_WidgetClassQueryTooltipFieldCallback :: C_WidgetClassQueryTooltipFieldCallback -> IO (FunPtr C_WidgetClassQueryTooltipFieldCallback)
- noWidgetClassQueryTooltipFieldCallback :: Maybe WidgetClassQueryTooltipFieldCallback
- wrap_WidgetClassQueryTooltipFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassQueryTooltipFieldCallback)) -> WidgetClassQueryTooltipFieldCallback -> C_WidgetClassQueryTooltipFieldCallback
- type C_WidgetClassRealizeFieldCallback = Ptr Widget -> IO ()
- type WidgetClassRealizeFieldCallback = Widget -> IO ()
- dynamic_WidgetClassRealizeFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassRealizeFieldCallback -> a -> m ()
- genClosure_WidgetClassRealizeFieldCallback :: MonadIO m => WidgetClassRealizeFieldCallback -> m (GClosure C_WidgetClassRealizeFieldCallback)
- mk_WidgetClassRealizeFieldCallback :: C_WidgetClassRealizeFieldCallback -> IO (FunPtr C_WidgetClassRealizeFieldCallback)
- noWidgetClassRealizeFieldCallback :: Maybe WidgetClassRealizeFieldCallback
- wrap_WidgetClassRealizeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassRealizeFieldCallback)) -> WidgetClassRealizeFieldCallback -> C_WidgetClassRealizeFieldCallback
- type C_WidgetClassRootFieldCallback = Ptr Widget -> IO ()
- type WidgetClassRootFieldCallback = Widget -> IO ()
- dynamic_WidgetClassRootFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassRootFieldCallback -> a -> m ()
- genClosure_WidgetClassRootFieldCallback :: MonadIO m => WidgetClassRootFieldCallback -> m (GClosure C_WidgetClassRootFieldCallback)
- mk_WidgetClassRootFieldCallback :: C_WidgetClassRootFieldCallback -> IO (FunPtr C_WidgetClassRootFieldCallback)
- noWidgetClassRootFieldCallback :: Maybe WidgetClassRootFieldCallback
- wrap_WidgetClassRootFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassRootFieldCallback)) -> WidgetClassRootFieldCallback -> C_WidgetClassRootFieldCallback
- type C_WidgetClassSetFocusChildFieldCallback = Ptr Widget -> Ptr Widget -> IO ()
- type WidgetClassSetFocusChildFieldCallback = Widget -> Maybe Widget -> IO ()
- dynamic_WidgetClassSetFocusChildFieldCallback :: (HasCallStack, MonadIO m, IsWidget a, IsWidget b) => FunPtr C_WidgetClassSetFocusChildFieldCallback -> a -> Maybe b -> m ()
- genClosure_WidgetClassSetFocusChildFieldCallback :: MonadIO m => WidgetClassSetFocusChildFieldCallback -> m (GClosure C_WidgetClassSetFocusChildFieldCallback)
- mk_WidgetClassSetFocusChildFieldCallback :: C_WidgetClassSetFocusChildFieldCallback -> IO (FunPtr C_WidgetClassSetFocusChildFieldCallback)
- noWidgetClassSetFocusChildFieldCallback :: Maybe WidgetClassSetFocusChildFieldCallback
- wrap_WidgetClassSetFocusChildFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSetFocusChildFieldCallback)) -> WidgetClassSetFocusChildFieldCallback -> C_WidgetClassSetFocusChildFieldCallback
- type C_WidgetClassShowFieldCallback = Ptr Widget -> IO ()
- type WidgetClassShowFieldCallback = Widget -> IO ()
- dynamic_WidgetClassShowFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassShowFieldCallback -> a -> m ()
- genClosure_WidgetClassShowFieldCallback :: MonadIO m => WidgetClassShowFieldCallback -> m (GClosure C_WidgetClassShowFieldCallback)
- mk_WidgetClassShowFieldCallback :: C_WidgetClassShowFieldCallback -> IO (FunPtr C_WidgetClassShowFieldCallback)
- noWidgetClassShowFieldCallback :: Maybe WidgetClassShowFieldCallback
- wrap_WidgetClassShowFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassShowFieldCallback)) -> WidgetClassShowFieldCallback -> C_WidgetClassShowFieldCallback
- type C_WidgetClassSizeAllocateFieldCallback = Ptr Widget -> Int32 -> Int32 -> Int32 -> IO ()
- type WidgetClassSizeAllocateFieldCallback = Widget -> Int32 -> Int32 -> Int32 -> IO ()
- dynamic_WidgetClassSizeAllocateFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassSizeAllocateFieldCallback -> a -> Int32 -> Int32 -> Int32 -> m ()
- genClosure_WidgetClassSizeAllocateFieldCallback :: MonadIO m => WidgetClassSizeAllocateFieldCallback -> m (GClosure C_WidgetClassSizeAllocateFieldCallback)
- mk_WidgetClassSizeAllocateFieldCallback :: C_WidgetClassSizeAllocateFieldCallback -> IO (FunPtr C_WidgetClassSizeAllocateFieldCallback)
- noWidgetClassSizeAllocateFieldCallback :: Maybe WidgetClassSizeAllocateFieldCallback
- wrap_WidgetClassSizeAllocateFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSizeAllocateFieldCallback)) -> WidgetClassSizeAllocateFieldCallback -> C_WidgetClassSizeAllocateFieldCallback
- type C_WidgetClassSnapshotFieldCallback = Ptr Widget -> Ptr Snapshot -> IO ()
- type WidgetClassSnapshotFieldCallback = Widget -> Snapshot -> IO ()
- dynamic_WidgetClassSnapshotFieldCallback :: (HasCallStack, MonadIO m, IsWidget a, IsSnapshot b) => FunPtr C_WidgetClassSnapshotFieldCallback -> a -> b -> m ()
- genClosure_WidgetClassSnapshotFieldCallback :: MonadIO m => WidgetClassSnapshotFieldCallback -> m (GClosure C_WidgetClassSnapshotFieldCallback)
- mk_WidgetClassSnapshotFieldCallback :: C_WidgetClassSnapshotFieldCallback -> IO (FunPtr C_WidgetClassSnapshotFieldCallback)
- noWidgetClassSnapshotFieldCallback :: Maybe WidgetClassSnapshotFieldCallback
- wrap_WidgetClassSnapshotFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSnapshotFieldCallback)) -> WidgetClassSnapshotFieldCallback -> C_WidgetClassSnapshotFieldCallback
- type C_WidgetClassStateFlagsChangedFieldCallback = Ptr Widget -> CUInt -> IO ()
- type WidgetClassStateFlagsChangedFieldCallback = Widget -> [StateFlags] -> IO ()
- dynamic_WidgetClassStateFlagsChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassStateFlagsChangedFieldCallback -> a -> [StateFlags] -> m ()
- genClosure_WidgetClassStateFlagsChangedFieldCallback :: MonadIO m => WidgetClassStateFlagsChangedFieldCallback -> m (GClosure C_WidgetClassStateFlagsChangedFieldCallback)
- mk_WidgetClassStateFlagsChangedFieldCallback :: C_WidgetClassStateFlagsChangedFieldCallback -> IO (FunPtr C_WidgetClassStateFlagsChangedFieldCallback)
- noWidgetClassStateFlagsChangedFieldCallback :: Maybe WidgetClassStateFlagsChangedFieldCallback
- wrap_WidgetClassStateFlagsChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassStateFlagsChangedFieldCallback)) -> WidgetClassStateFlagsChangedFieldCallback -> C_WidgetClassStateFlagsChangedFieldCallback
- type C_WidgetClassSystemSettingChangedFieldCallback = Ptr Widget -> CUInt -> IO ()
- type WidgetClassSystemSettingChangedFieldCallback = Widget -> SystemSetting -> IO ()
- dynamic_WidgetClassSystemSettingChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassSystemSettingChangedFieldCallback -> a -> SystemSetting -> m ()
- genClosure_WidgetClassSystemSettingChangedFieldCallback :: MonadIO m => WidgetClassSystemSettingChangedFieldCallback -> m (GClosure C_WidgetClassSystemSettingChangedFieldCallback)
- mk_WidgetClassSystemSettingChangedFieldCallback :: C_WidgetClassSystemSettingChangedFieldCallback -> IO (FunPtr C_WidgetClassSystemSettingChangedFieldCallback)
- noWidgetClassSystemSettingChangedFieldCallback :: Maybe WidgetClassSystemSettingChangedFieldCallback
- wrap_WidgetClassSystemSettingChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSystemSettingChangedFieldCallback)) -> WidgetClassSystemSettingChangedFieldCallback -> C_WidgetClassSystemSettingChangedFieldCallback
- type C_WidgetClassUnmapFieldCallback = Ptr Widget -> IO ()
- type WidgetClassUnmapFieldCallback = Widget -> IO ()
- dynamic_WidgetClassUnmapFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassUnmapFieldCallback -> a -> m ()
- genClosure_WidgetClassUnmapFieldCallback :: MonadIO m => WidgetClassUnmapFieldCallback -> m (GClosure C_WidgetClassUnmapFieldCallback)
- mk_WidgetClassUnmapFieldCallback :: C_WidgetClassUnmapFieldCallback -> IO (FunPtr C_WidgetClassUnmapFieldCallback)
- noWidgetClassUnmapFieldCallback :: Maybe WidgetClassUnmapFieldCallback
- wrap_WidgetClassUnmapFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassUnmapFieldCallback)) -> WidgetClassUnmapFieldCallback -> C_WidgetClassUnmapFieldCallback
- type C_WidgetClassUnrealizeFieldCallback = Ptr Widget -> IO ()
- type WidgetClassUnrealizeFieldCallback = Widget -> IO ()
- dynamic_WidgetClassUnrealizeFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassUnrealizeFieldCallback -> a -> m ()
- genClosure_WidgetClassUnrealizeFieldCallback :: MonadIO m => WidgetClassUnrealizeFieldCallback -> m (GClosure C_WidgetClassUnrealizeFieldCallback)
- mk_WidgetClassUnrealizeFieldCallback :: C_WidgetClassUnrealizeFieldCallback -> IO (FunPtr C_WidgetClassUnrealizeFieldCallback)
- noWidgetClassUnrealizeFieldCallback :: Maybe WidgetClassUnrealizeFieldCallback
- wrap_WidgetClassUnrealizeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassUnrealizeFieldCallback)) -> WidgetClassUnrealizeFieldCallback -> C_WidgetClassUnrealizeFieldCallback
- type C_WidgetClassUnrootFieldCallback = Ptr Widget -> IO ()
- type WidgetClassUnrootFieldCallback = Widget -> IO ()
- dynamic_WidgetClassUnrootFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassUnrootFieldCallback -> a -> m ()
- genClosure_WidgetClassUnrootFieldCallback :: MonadIO m => WidgetClassUnrootFieldCallback -> m (GClosure C_WidgetClassUnrootFieldCallback)
- mk_WidgetClassUnrootFieldCallback :: C_WidgetClassUnrootFieldCallback -> IO (FunPtr C_WidgetClassUnrootFieldCallback)
- noWidgetClassUnrootFieldCallback :: Maybe WidgetClassUnrootFieldCallback
- wrap_WidgetClassUnrootFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassUnrootFieldCallback)) -> WidgetClassUnrootFieldCallback -> C_WidgetClassUnrootFieldCallback
Signals
AssistantPageFunc
type AssistantPageFunc Source #
= Int32 |
|
-> IO Int32 | Returns: The next page number. |
A function used by assistantSetForwardPageFunc
to know which
is the next page given a current one. It’s called both for computing the
next page when the user presses the “forward” button and for handling
the behavior of the “last” button.
type AssistantPageFunc_WithClosures Source #
= Int32 |
|
-> Ptr () |
|
-> IO Int32 | Returns: The next page number. |
A function used by assistantSetForwardPageFunc
to know which
is the next page given a current one. It’s called both for computing the
next page when the user presses the “forward” button and for handling
the behavior of the “last” button.
type C_AssistantPageFunc = Int32 -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
drop_closures_AssistantPageFunc :: AssistantPageFunc -> AssistantPageFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_AssistantPageFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_AssistantPageFunc | |
-> Int32 |
|
-> Ptr () |
|
-> m Int32 | Returns: The next page number. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_AssistantPageFunc :: MonadIO m => AssistantPageFunc -> m (GClosure C_AssistantPageFunc) Source #
Wrap the callback into a GClosure
.
mk_AssistantPageFunc :: C_AssistantPageFunc -> IO (FunPtr C_AssistantPageFunc) Source #
Generate a function pointer callable from C code, from a C_AssistantPageFunc
.
noAssistantPageFunc :: Maybe AssistantPageFunc Source #
A convenience synonym for
.Nothing
:: Maybe
AssistantPageFunc
noAssistantPageFunc_WithClosures :: Maybe AssistantPageFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
AssistantPageFunc_WithClosures
wrap_AssistantPageFunc :: Maybe (Ptr (FunPtr C_AssistantPageFunc)) -> AssistantPageFunc_WithClosures -> C_AssistantPageFunc Source #
Wrap a AssistantPageFunc
into a C_AssistantPageFunc
.
BuildableParserEndElementFieldCallback
type BuildableParserEndElementFieldCallback Source #
= BuildableParseContext | |
-> Text | |
-> IO () | (Can throw |
No description available in the introspection data.
type BuildableParserEndElementFieldCallback_WithClosures Source #
= BuildableParseContext | |
-> Text | |
-> Ptr () | |
-> IO () | (Can throw |
No description available in the introspection data.
type C_BuildableParserEndElementFieldCallback = Ptr BuildableParseContext -> CString -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BuildableParserEndElementFieldCallback :: BuildableParserEndElementFieldCallback -> BuildableParserEndElementFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BuildableParserEndElementFieldCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BuildableParserEndElementFieldCallback | |
-> BuildableParseContext | |
-> Text | |
-> Ptr () | |
-> m () | (Can throw |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_BuildableParserEndElementFieldCallback :: C_BuildableParserEndElementFieldCallback -> IO (FunPtr C_BuildableParserEndElementFieldCallback) Source #
Generate a function pointer callable from C code, from a C_BuildableParserEndElementFieldCallback
.
noBuildableParserEndElementFieldCallback :: Maybe BuildableParserEndElementFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserEndElementFieldCallback
noBuildableParserEndElementFieldCallback_WithClosures :: Maybe BuildableParserEndElementFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserEndElementFieldCallback_WithClosures
BuildableParserErrorFieldCallback
type BuildableParserErrorFieldCallback = BuildableParseContext -> GError -> IO () Source #
No description available in the introspection data.
type BuildableParserErrorFieldCallback_WithClosures = BuildableParseContext -> GError -> Ptr () -> IO () Source #
No description available in the introspection data.
type C_BuildableParserErrorFieldCallback = Ptr BuildableParseContext -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BuildableParserErrorFieldCallback :: BuildableParserErrorFieldCallback -> BuildableParserErrorFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BuildableParserErrorFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_BuildableParserErrorFieldCallback -> BuildableParseContext -> GError -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BuildableParserErrorFieldCallback :: MonadIO m => BuildableParserErrorFieldCallback -> m (GClosure C_BuildableParserErrorFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_BuildableParserErrorFieldCallback :: C_BuildableParserErrorFieldCallback -> IO (FunPtr C_BuildableParserErrorFieldCallback) Source #
Generate a function pointer callable from C code, from a C_BuildableParserErrorFieldCallback
.
noBuildableParserErrorFieldCallback :: Maybe BuildableParserErrorFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserErrorFieldCallback
noBuildableParserErrorFieldCallback_WithClosures :: Maybe BuildableParserErrorFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserErrorFieldCallback_WithClosures
wrap_BuildableParserErrorFieldCallback :: Maybe (Ptr (FunPtr C_BuildableParserErrorFieldCallback)) -> BuildableParserErrorFieldCallback_WithClosures -> C_BuildableParserErrorFieldCallback Source #
BuildableParserStartElementFieldCallback
type BuildableParserStartElementFieldCallback Source #
No description available in the introspection data.
type BuildableParserStartElementFieldCallback_WithClosures Source #
No description available in the introspection data.
type C_BuildableParserStartElementFieldCallback = Ptr BuildableParseContext -> CString -> CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BuildableParserStartElementFieldCallback :: BuildableParserStartElementFieldCallback -> BuildableParserStartElementFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BuildableParserStartElementFieldCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BuildableParserStartElementFieldCallback | |
-> BuildableParseContext | |
-> Text | |
-> Text | |
-> Text | |
-> Ptr () | |
-> m () | (Can throw |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_BuildableParserStartElementFieldCallback :: C_BuildableParserStartElementFieldCallback -> IO (FunPtr C_BuildableParserStartElementFieldCallback) Source #
Generate a function pointer callable from C code, from a C_BuildableParserStartElementFieldCallback
.
noBuildableParserStartElementFieldCallback :: Maybe BuildableParserStartElementFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserStartElementFieldCallback
noBuildableParserStartElementFieldCallback_WithClosures :: Maybe BuildableParserStartElementFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserStartElementFieldCallback_WithClosures
BuildableParserTextFieldCallback
type BuildableParserTextFieldCallback Source #
= BuildableParseContext | |
-> Text | |
-> Word64 | |
-> IO () | (Can throw |
No description available in the introspection data.
type BuildableParserTextFieldCallback_WithClosures Source #
No description available in the introspection data.
type C_BuildableParserTextFieldCallback = Ptr BuildableParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BuildableParserTextFieldCallback :: BuildableParserTextFieldCallback -> BuildableParserTextFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BuildableParserTextFieldCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BuildableParserTextFieldCallback | |
-> BuildableParseContext | |
-> Text | |
-> Word64 | |
-> Ptr () | |
-> m () | (Can throw |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_BuildableParserTextFieldCallback :: C_BuildableParserTextFieldCallback -> IO (FunPtr C_BuildableParserTextFieldCallback) Source #
Generate a function pointer callable from C code, from a C_BuildableParserTextFieldCallback
.
noBuildableParserTextFieldCallback :: Maybe BuildableParserTextFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserTextFieldCallback
noBuildableParserTextFieldCallback_WithClosures :: Maybe BuildableParserTextFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BuildableParserTextFieldCallback_WithClosures
CellAllocCallback
type C_CellAllocCallback = Ptr CellRenderer -> Ptr Rectangle -> Ptr Rectangle -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CellAllocCallback Source #
= CellRenderer |
|
-> Rectangle |
|
-> Rectangle |
|
-> IO Bool | Returns: |
The type of the callback functions used for iterating over the
cell renderers and their allocated areas inside a CellArea
,
see cellAreaForeachAlloc
.
type CellAllocCallback_WithClosures Source #
= CellRenderer |
|
-> Rectangle |
|
-> Rectangle |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The type of the callback functions used for iterating over the
cell renderers and their allocated areas inside a CellArea
,
see cellAreaForeachAlloc
.
drop_closures_CellAllocCallback :: CellAllocCallback -> CellAllocCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CellAllocCallback Source #
:: (HasCallStack, MonadIO m, IsCellRenderer a) | |
=> FunPtr C_CellAllocCallback | |
-> a |
|
-> Rectangle |
|
-> Rectangle |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CellAllocCallback :: MonadIO m => CellAllocCallback -> m (GClosure C_CellAllocCallback) Source #
Wrap the callback into a GClosure
.
mk_CellAllocCallback :: C_CellAllocCallback -> IO (FunPtr C_CellAllocCallback) Source #
Generate a function pointer callable from C code, from a C_CellAllocCallback
.
noCellAllocCallback :: Maybe CellAllocCallback Source #
A convenience synonym for
.Nothing
:: Maybe
CellAllocCallback
noCellAllocCallback_WithClosures :: Maybe CellAllocCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CellAllocCallback_WithClosures
wrap_CellAllocCallback :: Maybe (Ptr (FunPtr C_CellAllocCallback)) -> CellAllocCallback_WithClosures -> C_CellAllocCallback Source #
Wrap a CellAllocCallback
into a C_CellAllocCallback
.
CellCallback
type C_CellCallback = Ptr CellRenderer -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CellCallback Source #
= CellRenderer |
|
-> IO Bool | Returns: |
The type of the callback functions used for iterating over
the cell renderers of a CellArea
, see cellAreaForeach
.
type CellCallback_WithClosures Source #
= CellRenderer |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The type of the callback functions used for iterating over
the cell renderers of a CellArea
, see cellAreaForeach
.
drop_closures_CellCallback :: CellCallback -> CellCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsCellRenderer a) | |
=> FunPtr C_CellCallback | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CellCallback :: MonadIO m => CellCallback -> m (GClosure C_CellCallback) Source #
Wrap the callback into a GClosure
.
mk_CellCallback :: C_CellCallback -> IO (FunPtr C_CellCallback) Source #
Generate a function pointer callable from C code, from a C_CellCallback
.
noCellCallback :: Maybe CellCallback Source #
A convenience synonym for
.Nothing
:: Maybe
CellCallback
noCellCallback_WithClosures :: Maybe CellCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CellCallback_WithClosures
wrap_CellCallback :: Maybe (Ptr (FunPtr C_CellCallback)) -> CellCallback_WithClosures -> C_CellCallback Source #
Wrap a CellCallback
into a C_CellCallback
.
CellLayoutDataFunc
type C_CellLayoutDataFunc = Ptr CellLayout -> Ptr CellRenderer -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type CellLayoutDataFunc Source #
= CellLayout |
|
-> CellRenderer |
|
-> TreeModel |
|
-> TreeIter |
|
-> IO () |
A function which should set the value of cellLayout
’s cell renderer(s)
as appropriate.
type CellLayoutDataFunc_WithClosures Source #
= CellLayout |
|
-> CellRenderer |
|
-> TreeModel |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO () |
A function which should set the value of cellLayout
’s cell renderer(s)
as appropriate.
drop_closures_CellLayoutDataFunc :: CellLayoutDataFunc -> CellLayoutDataFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CellLayoutDataFunc Source #
:: (HasCallStack, MonadIO m, IsCellLayout a, IsCellRenderer b, IsTreeModel c) | |
=> FunPtr C_CellLayoutDataFunc | |
-> a |
|
-> b |
|
-> c |
|
-> TreeIter |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CellLayoutDataFunc :: MonadIO m => CellLayoutDataFunc -> m (GClosure C_CellLayoutDataFunc) Source #
Wrap the callback into a GClosure
.
mk_CellLayoutDataFunc :: C_CellLayoutDataFunc -> IO (FunPtr C_CellLayoutDataFunc) Source #
Generate a function pointer callable from C code, from a C_CellLayoutDataFunc
.
noCellLayoutDataFunc :: Maybe CellLayoutDataFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CellLayoutDataFunc
noCellLayoutDataFunc_WithClosures :: Maybe CellLayoutDataFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CellLayoutDataFunc_WithClosures
wrap_CellLayoutDataFunc :: Maybe (Ptr (FunPtr C_CellLayoutDataFunc)) -> CellLayoutDataFunc_WithClosures -> C_CellLayoutDataFunc Source #
Wrap a CellLayoutDataFunc
into a C_CellLayoutDataFunc
.
CustomAllocateFunc
type C_CustomAllocateFunc = Ptr Widget -> Int32 -> Int32 -> Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type CustomAllocateFunc Source #
= Widget |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> IO () |
A function to be used by CustomLayout
to allocate a widget.
dynamic_CustomAllocateFunc Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_CustomAllocateFunc | |
-> a |
|
-> Int32 |
|
-> Int32 |
|
-> Int32 |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CustomAllocateFunc :: MonadIO m => CustomAllocateFunc -> m (GClosure C_CustomAllocateFunc) Source #
Wrap the callback into a GClosure
.
mk_CustomAllocateFunc :: C_CustomAllocateFunc -> IO (FunPtr C_CustomAllocateFunc) Source #
Generate a function pointer callable from C code, from a C_CustomAllocateFunc
.
noCustomAllocateFunc :: Maybe CustomAllocateFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CustomAllocateFunc
wrap_CustomAllocateFunc :: Maybe (Ptr (FunPtr C_CustomAllocateFunc)) -> CustomAllocateFunc -> C_CustomAllocateFunc Source #
Wrap a CustomAllocateFunc
into a C_CustomAllocateFunc
.
CustomFilterFunc
type C_CustomFilterFunc = Ptr Object -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CustomFilterFunc Source #
drop_closures_CustomFilterFunc :: CustomFilterFunc -> CustomFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CustomFilterFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_CustomFilterFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CustomFilterFunc :: MonadIO m => CustomFilterFunc -> m (GClosure C_CustomFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_CustomFilterFunc :: C_CustomFilterFunc -> IO (FunPtr C_CustomFilterFunc) Source #
Generate a function pointer callable from C code, from a C_CustomFilterFunc
.
noCustomFilterFunc :: Maybe CustomFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CustomFilterFunc
noCustomFilterFunc_WithClosures :: Maybe CustomFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CustomFilterFunc_WithClosures
wrap_CustomFilterFunc :: Maybe (Ptr (FunPtr C_CustomFilterFunc)) -> CustomFilterFunc_WithClosures -> C_CustomFilterFunc Source #
Wrap a CustomFilterFunc
into a C_CustomFilterFunc
.
CustomMeasureFunc
type C_CustomMeasureFunc = Ptr Widget -> CUInt -> Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type CustomMeasureFunc Source #
= Widget |
|
-> Orientation |
|
-> Int32 |
|
-> IO (Int32, Int32, Int32, Int32) |
A function to be used by CustomLayout
to measure a widget.
dynamic_CustomMeasureFunc Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_CustomMeasureFunc | |
-> a |
|
-> Orientation |
|
-> Int32 |
|
-> m (Int32, Int32, Int32, Int32) |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CustomMeasureFunc :: MonadIO m => CustomMeasureFunc -> m (GClosure C_CustomMeasureFunc) Source #
Wrap the callback into a GClosure
.
mk_CustomMeasureFunc :: C_CustomMeasureFunc -> IO (FunPtr C_CustomMeasureFunc) Source #
Generate a function pointer callable from C code, from a C_CustomMeasureFunc
.
noCustomMeasureFunc :: Maybe CustomMeasureFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CustomMeasureFunc
wrap_CustomMeasureFunc :: Maybe (Ptr (FunPtr C_CustomMeasureFunc)) -> CustomMeasureFunc -> C_CustomMeasureFunc Source #
Wrap a CustomMeasureFunc
into a C_CustomMeasureFunc
.
CustomRequestModeFunc
type C_CustomRequestModeFunc = Ptr Widget -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type CustomRequestModeFunc Source #
= Widget |
|
-> IO SizeRequestMode | Returns: the size request mode |
Queries a widget for its preferred size request mode.
dynamic_CustomRequestModeFunc Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_CustomRequestModeFunc | |
-> a |
|
-> m SizeRequestMode | Returns: the size request mode |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CustomRequestModeFunc :: MonadIO m => CustomRequestModeFunc -> m (GClosure C_CustomRequestModeFunc) Source #
Wrap the callback into a GClosure
.
mk_CustomRequestModeFunc :: C_CustomRequestModeFunc -> IO (FunPtr C_CustomRequestModeFunc) Source #
Generate a function pointer callable from C code, from a C_CustomRequestModeFunc
.
noCustomRequestModeFunc :: Maybe CustomRequestModeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CustomRequestModeFunc
wrap_CustomRequestModeFunc :: Maybe (Ptr (FunPtr C_CustomRequestModeFunc)) -> CustomRequestModeFunc -> C_CustomRequestModeFunc Source #
Wrap a CustomRequestModeFunc
into a C_CustomRequestModeFunc
.
DrawingAreaDrawFunc
type C_DrawingAreaDrawFunc = Ptr DrawingArea -> Ptr Context -> Int32 -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DrawingAreaDrawFunc Source #
= DrawingArea |
|
-> Context |
|
-> Int32 |
|
-> Int32 |
|
-> IO () |
Whenever drawingArea
needs to redraw, this function will be called.
This function should exclusively redraw the contents of the drawing area and must not call any widget functions that cause changes.
type DrawingAreaDrawFunc_WithClosures Source #
= DrawingArea |
|
-> Context |
|
-> Int32 |
|
-> Int32 |
|
-> Ptr () |
|
-> IO () |
Whenever drawingArea
needs to redraw, this function will be called.
This function should exclusively redraw the contents of the drawing area and must not call any widget functions that cause changes.
drop_closures_DrawingAreaDrawFunc :: DrawingAreaDrawFunc -> DrawingAreaDrawFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DrawingAreaDrawFunc Source #
:: (HasCallStack, MonadIO m, IsDrawingArea a) | |
=> FunPtr C_DrawingAreaDrawFunc | |
-> a |
|
-> Context |
|
-> Int32 |
|
-> Int32 |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DrawingAreaDrawFunc :: MonadIO m => DrawingAreaDrawFunc -> m (GClosure C_DrawingAreaDrawFunc) Source #
Wrap the callback into a GClosure
.
mk_DrawingAreaDrawFunc :: C_DrawingAreaDrawFunc -> IO (FunPtr C_DrawingAreaDrawFunc) Source #
Generate a function pointer callable from C code, from a C_DrawingAreaDrawFunc
.
noDrawingAreaDrawFunc :: Maybe DrawingAreaDrawFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DrawingAreaDrawFunc
noDrawingAreaDrawFunc_WithClosures :: Maybe DrawingAreaDrawFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DrawingAreaDrawFunc_WithClosures
wrap_DrawingAreaDrawFunc :: Maybe (Ptr (FunPtr C_DrawingAreaDrawFunc)) -> DrawingAreaDrawFunc_WithClosures -> C_DrawingAreaDrawFunc Source #
Wrap a DrawingAreaDrawFunc
into a C_DrawingAreaDrawFunc
.
EntryCompletionMatchFunc
type C_EntryCompletionMatchFunc = Ptr EntryCompletion -> CString -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type EntryCompletionMatchFunc Source #
= EntryCompletion |
|
-> Text |
|
-> TreeIter |
|
-> IO Bool | Returns: |
A function which decides whether the row indicated by iter
matches
a given key
, and should be displayed as a possible completion for key
.
Note that key
is normalized and case-folded (see utf8Normalize
and utf8Casefold
). If this is not appropriate, match functions
have access to the unmodified key via
gtk_editable_get_text (GTK_EDITABLE (gtk_entry_completion_get_entry ()))
.
type EntryCompletionMatchFunc_WithClosures Source #
= EntryCompletion |
|
-> Text |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function which decides whether the row indicated by iter
matches
a given key
, and should be displayed as a possible completion for key
.
Note that key
is normalized and case-folded (see utf8Normalize
and utf8Casefold
). If this is not appropriate, match functions
have access to the unmodified key via
gtk_editable_get_text (GTK_EDITABLE (gtk_entry_completion_get_entry ()))
.
drop_closures_EntryCompletionMatchFunc :: EntryCompletionMatchFunc -> EntryCompletionMatchFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_EntryCompletionMatchFunc Source #
:: (HasCallStack, MonadIO m, IsEntryCompletion a) | |
=> FunPtr C_EntryCompletionMatchFunc | |
-> a |
|
-> Text |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_EntryCompletionMatchFunc :: MonadIO m => EntryCompletionMatchFunc -> m (GClosure C_EntryCompletionMatchFunc) Source #
Wrap the callback into a GClosure
.
mk_EntryCompletionMatchFunc :: C_EntryCompletionMatchFunc -> IO (FunPtr C_EntryCompletionMatchFunc) Source #
Generate a function pointer callable from C code, from a C_EntryCompletionMatchFunc
.
noEntryCompletionMatchFunc :: Maybe EntryCompletionMatchFunc Source #
A convenience synonym for
.Nothing
:: Maybe
EntryCompletionMatchFunc
noEntryCompletionMatchFunc_WithClosures :: Maybe EntryCompletionMatchFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
EntryCompletionMatchFunc_WithClosures
wrap_EntryCompletionMatchFunc :: Maybe (Ptr (FunPtr C_EntryCompletionMatchFunc)) -> EntryCompletionMatchFunc_WithClosures -> C_EntryCompletionMatchFunc Source #
Wrap a EntryCompletionMatchFunc
into a C_EntryCompletionMatchFunc
.
ExpressionNotify
type C_ExpressionNotify = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ExpressionNotify = IO () Source #
Callback called by expressionWatch
when the
expression value changes.
type ExpressionNotify_WithClosures Source #
= Ptr () |
|
-> IO () |
Callback called by expressionWatch
when the
expression value changes.
drop_closures_ExpressionNotify :: ExpressionNotify -> ExpressionNotify_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ExpressionNotify Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ExpressionNotify | |
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ExpressionNotify :: MonadIO m => ExpressionNotify -> m (GClosure C_ExpressionNotify) Source #
Wrap the callback into a GClosure
.
mk_ExpressionNotify :: C_ExpressionNotify -> IO (FunPtr C_ExpressionNotify) Source #
Generate a function pointer callable from C code, from a C_ExpressionNotify
.
noExpressionNotify :: Maybe ExpressionNotify Source #
A convenience synonym for
.Nothing
:: Maybe
ExpressionNotify
noExpressionNotify_WithClosures :: Maybe ExpressionNotify_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ExpressionNotify_WithClosures
wrap_ExpressionNotify :: Maybe (Ptr (FunPtr C_ExpressionNotify)) -> ExpressionNotify_WithClosures -> C_ExpressionNotify Source #
Wrap a ExpressionNotify
into a C_ExpressionNotify
.
FlowBoxCreateWidgetFunc
type C_FlowBoxCreateWidgetFunc = Ptr Object -> Ptr () -> IO (Ptr Widget) Source #
Type for the callback on the (unwrapped) C side.
type FlowBoxCreateWidgetFunc Source #
= Object |
|
-> IO Widget | Returns: a |
Called for flow boxes that are bound to a ListModel
with
flowBoxBindModel
for each item that gets added to the model.
type FlowBoxCreateWidgetFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO Widget | Returns: a |
Called for flow boxes that are bound to a ListModel
with
flowBoxBindModel
for each item that gets added to the model.
drop_closures_FlowBoxCreateWidgetFunc :: FlowBoxCreateWidgetFunc -> FlowBoxCreateWidgetFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FlowBoxCreateWidgetFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_FlowBoxCreateWidgetFunc | |
-> a |
|
-> Ptr () |
|
-> m Widget | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FlowBoxCreateWidgetFunc :: MonadIO m => FlowBoxCreateWidgetFunc -> m (GClosure C_FlowBoxCreateWidgetFunc) Source #
Wrap the callback into a GClosure
.
mk_FlowBoxCreateWidgetFunc :: C_FlowBoxCreateWidgetFunc -> IO (FunPtr C_FlowBoxCreateWidgetFunc) Source #
Generate a function pointer callable from C code, from a C_FlowBoxCreateWidgetFunc
.
noFlowBoxCreateWidgetFunc :: Maybe FlowBoxCreateWidgetFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxCreateWidgetFunc
noFlowBoxCreateWidgetFunc_WithClosures :: Maybe FlowBoxCreateWidgetFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxCreateWidgetFunc_WithClosures
wrap_FlowBoxCreateWidgetFunc :: Maybe (Ptr (FunPtr C_FlowBoxCreateWidgetFunc)) -> FlowBoxCreateWidgetFunc_WithClosures -> C_FlowBoxCreateWidgetFunc Source #
Wrap a FlowBoxCreateWidgetFunc
into a C_FlowBoxCreateWidgetFunc
.
FlowBoxFilterFunc
type C_FlowBoxFilterFunc = Ptr FlowBoxChild -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type FlowBoxFilterFunc Source #
= FlowBoxChild |
|
-> IO Bool |
A function that will be called whenever a child changes or is added. It lets you control if the child should be visible or not.
type FlowBoxFilterFunc_WithClosures Source #
= FlowBoxChild |
|
-> Ptr () |
|
-> IO Bool |
A function that will be called whenever a child changes or is added. It lets you control if the child should be visible or not.
drop_closures_FlowBoxFilterFunc :: FlowBoxFilterFunc -> FlowBoxFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FlowBoxFilterFunc Source #
:: (HasCallStack, MonadIO m, IsFlowBoxChild a) | |
=> FunPtr C_FlowBoxFilterFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FlowBoxFilterFunc :: MonadIO m => FlowBoxFilterFunc -> m (GClosure C_FlowBoxFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_FlowBoxFilterFunc :: C_FlowBoxFilterFunc -> IO (FunPtr C_FlowBoxFilterFunc) Source #
Generate a function pointer callable from C code, from a C_FlowBoxFilterFunc
.
noFlowBoxFilterFunc :: Maybe FlowBoxFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxFilterFunc
noFlowBoxFilterFunc_WithClosures :: Maybe FlowBoxFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxFilterFunc_WithClosures
wrap_FlowBoxFilterFunc :: Maybe (Ptr (FunPtr C_FlowBoxFilterFunc)) -> FlowBoxFilterFunc_WithClosures -> C_FlowBoxFilterFunc Source #
Wrap a FlowBoxFilterFunc
into a C_FlowBoxFilterFunc
.
FlowBoxForeachFunc
type C_FlowBoxForeachFunc = Ptr FlowBox -> Ptr FlowBoxChild -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type FlowBoxForeachFunc Source #
= FlowBox |
|
-> FlowBoxChild |
|
-> IO () |
A function used by flowBoxSelectedForeach
.
It will be called on every selected child of the box
.
type FlowBoxForeachFunc_WithClosures Source #
= FlowBox |
|
-> FlowBoxChild |
|
-> Ptr () |
|
-> IO () |
A function used by flowBoxSelectedForeach
.
It will be called on every selected child of the box
.
drop_closures_FlowBoxForeachFunc :: FlowBoxForeachFunc -> FlowBoxForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FlowBoxForeachFunc Source #
:: (HasCallStack, MonadIO m, IsFlowBox a, IsFlowBoxChild b) | |
=> FunPtr C_FlowBoxForeachFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FlowBoxForeachFunc :: MonadIO m => FlowBoxForeachFunc -> m (GClosure C_FlowBoxForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_FlowBoxForeachFunc :: C_FlowBoxForeachFunc -> IO (FunPtr C_FlowBoxForeachFunc) Source #
Generate a function pointer callable from C code, from a C_FlowBoxForeachFunc
.
noFlowBoxForeachFunc :: Maybe FlowBoxForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxForeachFunc
noFlowBoxForeachFunc_WithClosures :: Maybe FlowBoxForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxForeachFunc_WithClosures
wrap_FlowBoxForeachFunc :: Maybe (Ptr (FunPtr C_FlowBoxForeachFunc)) -> FlowBoxForeachFunc_WithClosures -> C_FlowBoxForeachFunc Source #
Wrap a FlowBoxForeachFunc
into a C_FlowBoxForeachFunc
.
FlowBoxSortFunc
type C_FlowBoxSortFunc = Ptr FlowBoxChild -> Ptr FlowBoxChild -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type FlowBoxSortFunc Source #
= FlowBoxChild |
|
-> FlowBoxChild |
|
-> IO Int32 | Returns: < 0 if |
A function to compare two children to determine which should come first.
type FlowBoxSortFunc_WithClosures Source #
= FlowBoxChild |
|
-> FlowBoxChild |
|
-> Ptr () |
|
-> IO Int32 | Returns: < 0 if |
A function to compare two children to determine which should come first.
drop_closures_FlowBoxSortFunc :: FlowBoxSortFunc -> FlowBoxSortFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FlowBoxSortFunc Source #
:: (HasCallStack, MonadIO m, IsFlowBoxChild a, IsFlowBoxChild b) | |
=> FunPtr C_FlowBoxSortFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Int32 | Returns: < 0 if |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FlowBoxSortFunc :: MonadIO m => FlowBoxSortFunc -> m (GClosure C_FlowBoxSortFunc) Source #
Wrap the callback into a GClosure
.
mk_FlowBoxSortFunc :: C_FlowBoxSortFunc -> IO (FunPtr C_FlowBoxSortFunc) Source #
Generate a function pointer callable from C code, from a C_FlowBoxSortFunc
.
noFlowBoxSortFunc :: Maybe FlowBoxSortFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxSortFunc
noFlowBoxSortFunc_WithClosures :: Maybe FlowBoxSortFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FlowBoxSortFunc_WithClosures
wrap_FlowBoxSortFunc :: Maybe (Ptr (FunPtr C_FlowBoxSortFunc)) -> FlowBoxSortFunc_WithClosures -> C_FlowBoxSortFunc Source #
Wrap a FlowBoxSortFunc
into a C_FlowBoxSortFunc
.
FontFilterFunc
type C_FontFilterFunc = Ptr FontFamily -> Ptr FontFace -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type FontFilterFunc Source #
= FontFamily |
|
-> FontFace |
|
-> IO Bool | Returns: |
The type of function that is used for deciding what fonts get
shown in a FontChooser
. See fontChooserSetFilterFunc
.
type FontFilterFunc_WithClosures Source #
= FontFamily |
|
-> FontFace |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The type of function that is used for deciding what fonts get
shown in a FontChooser
. See fontChooserSetFilterFunc
.
drop_closures_FontFilterFunc :: FontFilterFunc -> FontFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FontFilterFunc Source #
:: (HasCallStack, MonadIO m, IsFontFamily a, IsFontFace b) | |
=> FunPtr C_FontFilterFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FontFilterFunc :: MonadIO m => FontFilterFunc -> m (GClosure C_FontFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_FontFilterFunc :: C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc) Source #
Generate a function pointer callable from C code, from a C_FontFilterFunc
.
noFontFilterFunc :: Maybe FontFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
FontFilterFunc
noFontFilterFunc_WithClosures :: Maybe FontFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FontFilterFunc_WithClosures
wrap_FontFilterFunc :: Maybe (Ptr (FunPtr C_FontFilterFunc)) -> FontFilterFunc_WithClosures -> C_FontFilterFunc Source #
Wrap a FontFilterFunc
into a C_FontFilterFunc
.
IconViewForeachFunc
type C_IconViewForeachFunc = Ptr IconView -> Ptr TreePath -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IconViewForeachFunc Source #
A function used by iconViewSelectedForeach
to map all
selected rows. It will be called on every selected row in the view.
type IconViewForeachFunc_WithClosures Source #
= IconView |
|
-> TreePath |
|
-> Ptr () |
|
-> IO () |
A function used by iconViewSelectedForeach
to map all
selected rows. It will be called on every selected row in the view.
drop_closures_IconViewForeachFunc :: IconViewForeachFunc -> IconViewForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_IconViewForeachFunc Source #
:: (HasCallStack, MonadIO m, IsIconView a) | |
=> FunPtr C_IconViewForeachFunc | |
-> a |
|
-> TreePath |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IconViewForeachFunc :: MonadIO m => IconViewForeachFunc -> m (GClosure C_IconViewForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_IconViewForeachFunc :: C_IconViewForeachFunc -> IO (FunPtr C_IconViewForeachFunc) Source #
Generate a function pointer callable from C code, from a C_IconViewForeachFunc
.
noIconViewForeachFunc :: Maybe IconViewForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
IconViewForeachFunc
noIconViewForeachFunc_WithClosures :: Maybe IconViewForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
IconViewForeachFunc_WithClosures
wrap_IconViewForeachFunc :: Maybe (Ptr (FunPtr C_IconViewForeachFunc)) -> IconViewForeachFunc_WithClosures -> C_IconViewForeachFunc Source #
Wrap a IconViewForeachFunc
into a C_IconViewForeachFunc
.
ListBoxCreateWidgetFunc
type C_ListBoxCreateWidgetFunc = Ptr Object -> Ptr () -> IO (Ptr Widget) Source #
Type for the callback on the (unwrapped) C side.
type ListBoxCreateWidgetFunc Source #
= Object |
|
-> IO Widget | Returns: a |
Called for list boxes that are bound to a ListModel
with
listBoxBindModel
for each item that gets added to the model.
type ListBoxCreateWidgetFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO Widget | Returns: a |
Called for list boxes that are bound to a ListModel
with
listBoxBindModel
for each item that gets added to the model.
drop_closures_ListBoxCreateWidgetFunc :: ListBoxCreateWidgetFunc -> ListBoxCreateWidgetFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ListBoxCreateWidgetFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_ListBoxCreateWidgetFunc | |
-> a |
|
-> Ptr () |
|
-> m Widget | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ListBoxCreateWidgetFunc :: MonadIO m => ListBoxCreateWidgetFunc -> m (GClosure C_ListBoxCreateWidgetFunc) Source #
Wrap the callback into a GClosure
.
mk_ListBoxCreateWidgetFunc :: C_ListBoxCreateWidgetFunc -> IO (FunPtr C_ListBoxCreateWidgetFunc) Source #
Generate a function pointer callable from C code, from a C_ListBoxCreateWidgetFunc
.
noListBoxCreateWidgetFunc :: Maybe ListBoxCreateWidgetFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxCreateWidgetFunc
noListBoxCreateWidgetFunc_WithClosures :: Maybe ListBoxCreateWidgetFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxCreateWidgetFunc_WithClosures
wrap_ListBoxCreateWidgetFunc :: Maybe (Ptr (FunPtr C_ListBoxCreateWidgetFunc)) -> ListBoxCreateWidgetFunc_WithClosures -> C_ListBoxCreateWidgetFunc Source #
Wrap a ListBoxCreateWidgetFunc
into a C_ListBoxCreateWidgetFunc
.
ListBoxFilterFunc
type C_ListBoxFilterFunc = Ptr ListBoxRow -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ListBoxFilterFunc Source #
= ListBoxRow |
|
-> IO Bool |
Will be called whenever the row changes or is added and lets you control if the row should be visible or not.
type ListBoxFilterFunc_WithClosures Source #
= ListBoxRow |
|
-> Ptr () |
|
-> IO Bool |
Will be called whenever the row changes or is added and lets you control if the row should be visible or not.
drop_closures_ListBoxFilterFunc :: ListBoxFilterFunc -> ListBoxFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ListBoxFilterFunc Source #
:: (HasCallStack, MonadIO m, IsListBoxRow a) | |
=> FunPtr C_ListBoxFilterFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ListBoxFilterFunc :: MonadIO m => ListBoxFilterFunc -> m (GClosure C_ListBoxFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_ListBoxFilterFunc :: C_ListBoxFilterFunc -> IO (FunPtr C_ListBoxFilterFunc) Source #
Generate a function pointer callable from C code, from a C_ListBoxFilterFunc
.
noListBoxFilterFunc :: Maybe ListBoxFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxFilterFunc
noListBoxFilterFunc_WithClosures :: Maybe ListBoxFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxFilterFunc_WithClosures
wrap_ListBoxFilterFunc :: Maybe (Ptr (FunPtr C_ListBoxFilterFunc)) -> ListBoxFilterFunc_WithClosures -> C_ListBoxFilterFunc Source #
Wrap a ListBoxFilterFunc
into a C_ListBoxFilterFunc
.
ListBoxForeachFunc
type C_ListBoxForeachFunc = Ptr ListBox -> Ptr ListBoxRow -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ListBoxForeachFunc Source #
= ListBox |
|
-> ListBoxRow |
|
-> IO () |
A function used by listBoxSelectedForeach
.
It will be called on every selected child of the box
.
type ListBoxForeachFunc_WithClosures Source #
= ListBox |
|
-> ListBoxRow |
|
-> Ptr () |
|
-> IO () |
A function used by listBoxSelectedForeach
.
It will be called on every selected child of the box
.
drop_closures_ListBoxForeachFunc :: ListBoxForeachFunc -> ListBoxForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ListBoxForeachFunc Source #
:: (HasCallStack, MonadIO m, IsListBox a, IsListBoxRow b) | |
=> FunPtr C_ListBoxForeachFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ListBoxForeachFunc :: MonadIO m => ListBoxForeachFunc -> m (GClosure C_ListBoxForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_ListBoxForeachFunc :: C_ListBoxForeachFunc -> IO (FunPtr C_ListBoxForeachFunc) Source #
Generate a function pointer callable from C code, from a C_ListBoxForeachFunc
.
noListBoxForeachFunc :: Maybe ListBoxForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxForeachFunc
noListBoxForeachFunc_WithClosures :: Maybe ListBoxForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxForeachFunc_WithClosures
wrap_ListBoxForeachFunc :: Maybe (Ptr (FunPtr C_ListBoxForeachFunc)) -> ListBoxForeachFunc_WithClosures -> C_ListBoxForeachFunc Source #
Wrap a ListBoxForeachFunc
into a C_ListBoxForeachFunc
.
ListBoxSortFunc
type C_ListBoxSortFunc = Ptr ListBoxRow -> Ptr ListBoxRow -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type ListBoxSortFunc Source #
= ListBoxRow |
|
-> ListBoxRow |
|
-> IO Int32 | Returns: < 0 if |
Compare two rows to determine which should be first.
type ListBoxSortFunc_WithClosures Source #
= ListBoxRow |
|
-> ListBoxRow |
|
-> Ptr () |
|
-> IO Int32 | Returns: < 0 if |
Compare two rows to determine which should be first.
drop_closures_ListBoxSortFunc :: ListBoxSortFunc -> ListBoxSortFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ListBoxSortFunc Source #
:: (HasCallStack, MonadIO m, IsListBoxRow a, IsListBoxRow b) | |
=> FunPtr C_ListBoxSortFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Int32 | Returns: < 0 if |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ListBoxSortFunc :: MonadIO m => ListBoxSortFunc -> m (GClosure C_ListBoxSortFunc) Source #
Wrap the callback into a GClosure
.
mk_ListBoxSortFunc :: C_ListBoxSortFunc -> IO (FunPtr C_ListBoxSortFunc) Source #
Generate a function pointer callable from C code, from a C_ListBoxSortFunc
.
noListBoxSortFunc :: Maybe ListBoxSortFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxSortFunc
noListBoxSortFunc_WithClosures :: Maybe ListBoxSortFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxSortFunc_WithClosures
wrap_ListBoxSortFunc :: Maybe (Ptr (FunPtr C_ListBoxSortFunc)) -> ListBoxSortFunc_WithClosures -> C_ListBoxSortFunc Source #
Wrap a ListBoxSortFunc
into a C_ListBoxSortFunc
.
ListBoxUpdateHeaderFunc
type C_ListBoxUpdateHeaderFunc = Ptr ListBoxRow -> Ptr ListBoxRow -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ListBoxUpdateHeaderFunc Source #
= ListBoxRow |
|
-> Maybe ListBoxRow |
|
-> IO () |
Whenever row
changes or which row is before row
changes this
is called, which lets you update the header on row
. You may
remove or set a new one via listBoxRowSetHeader
or
just change the state of the current header widget.
type ListBoxUpdateHeaderFunc_WithClosures Source #
= ListBoxRow |
|
-> Maybe ListBoxRow |
|
-> Ptr () |
|
-> IO () |
Whenever row
changes or which row is before row
changes this
is called, which lets you update the header on row
. You may
remove or set a new one via listBoxRowSetHeader
or
just change the state of the current header widget.
drop_closures_ListBoxUpdateHeaderFunc :: ListBoxUpdateHeaderFunc -> ListBoxUpdateHeaderFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ListBoxUpdateHeaderFunc Source #
:: (HasCallStack, MonadIO m, IsListBoxRow a, IsListBoxRow b) | |
=> FunPtr C_ListBoxUpdateHeaderFunc | |
-> a |
|
-> Maybe b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ListBoxUpdateHeaderFunc :: MonadIO m => ListBoxUpdateHeaderFunc -> m (GClosure C_ListBoxUpdateHeaderFunc) Source #
Wrap the callback into a GClosure
.
mk_ListBoxUpdateHeaderFunc :: C_ListBoxUpdateHeaderFunc -> IO (FunPtr C_ListBoxUpdateHeaderFunc) Source #
Generate a function pointer callable from C code, from a C_ListBoxUpdateHeaderFunc
.
noListBoxUpdateHeaderFunc :: Maybe ListBoxUpdateHeaderFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxUpdateHeaderFunc
noListBoxUpdateHeaderFunc_WithClosures :: Maybe ListBoxUpdateHeaderFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ListBoxUpdateHeaderFunc_WithClosures
wrap_ListBoxUpdateHeaderFunc :: Maybe (Ptr (FunPtr C_ListBoxUpdateHeaderFunc)) -> ListBoxUpdateHeaderFunc_WithClosures -> C_ListBoxUpdateHeaderFunc Source #
Wrap a ListBoxUpdateHeaderFunc
into a C_ListBoxUpdateHeaderFunc
.
MapListModelMapFunc
type C_MapListModelMapFunc = Ptr Object -> Ptr () -> IO (Ptr Object) Source #
Type for the callback on the (unwrapped) C side.
type MapListModelMapFunc Source #
= Object |
|
-> IO Object | Returns: The item to map to.
This function may not return |
User function that is called to map an item
of the original model to
an item expected by the map model.
The returned items must conform to the item type of the model they are used with.
type MapListModelMapFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO Object | Returns: The item to map to.
This function may not return |
User function that is called to map an item
of the original model to
an item expected by the map model.
The returned items must conform to the item type of the model they are used with.
drop_closures_MapListModelMapFunc :: MapListModelMapFunc -> MapListModelMapFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MapListModelMapFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_MapListModelMapFunc | |
-> a |
|
-> Ptr () |
|
-> m Object | Returns: The item to map to.
This function may not return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MapListModelMapFunc :: MonadIO m => MapListModelMapFunc -> m (GClosure C_MapListModelMapFunc) Source #
Wrap the callback into a GClosure
.
mk_MapListModelMapFunc :: C_MapListModelMapFunc -> IO (FunPtr C_MapListModelMapFunc) Source #
Generate a function pointer callable from C code, from a C_MapListModelMapFunc
.
noMapListModelMapFunc :: Maybe MapListModelMapFunc Source #
A convenience synonym for
.Nothing
:: Maybe
MapListModelMapFunc
noMapListModelMapFunc_WithClosures :: Maybe MapListModelMapFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
MapListModelMapFunc_WithClosures
wrap_MapListModelMapFunc :: Maybe (Ptr (FunPtr C_MapListModelMapFunc)) -> MapListModelMapFunc_WithClosures -> C_MapListModelMapFunc Source #
Wrap a MapListModelMapFunc
into a C_MapListModelMapFunc
.
MenuButtonCreatePopupFunc
type C_MenuButtonCreatePopupFunc = Ptr MenuButton -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MenuButtonCreatePopupFunc Source #
= MenuButton |
|
-> IO () |
User-provided callback function to create a popup for menuButton
on demand.
This function is called when the popup of menuButton
is shown, but none has
been provided via menuButtonSetPopover
or menuButtonSetMenuModel
.
type MenuButtonCreatePopupFunc_WithClosures Source #
= MenuButton |
|
-> Ptr () |
|
-> IO () |
User-provided callback function to create a popup for menuButton
on demand.
This function is called when the popup of menuButton
is shown, but none has
been provided via menuButtonSetPopover
or menuButtonSetMenuModel
.
drop_closures_MenuButtonCreatePopupFunc :: MenuButtonCreatePopupFunc -> MenuButtonCreatePopupFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MenuButtonCreatePopupFunc Source #
:: (HasCallStack, MonadIO m, IsMenuButton a) | |
=> FunPtr C_MenuButtonCreatePopupFunc | |
-> a |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MenuButtonCreatePopupFunc :: MonadIO m => MenuButtonCreatePopupFunc -> m (GClosure C_MenuButtonCreatePopupFunc) Source #
Wrap the callback into a GClosure
.
mk_MenuButtonCreatePopupFunc :: C_MenuButtonCreatePopupFunc -> IO (FunPtr C_MenuButtonCreatePopupFunc) Source #
Generate a function pointer callable from C code, from a C_MenuButtonCreatePopupFunc
.
noMenuButtonCreatePopupFunc :: Maybe MenuButtonCreatePopupFunc Source #
A convenience synonym for
.Nothing
:: Maybe
MenuButtonCreatePopupFunc
noMenuButtonCreatePopupFunc_WithClosures :: Maybe MenuButtonCreatePopupFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
MenuButtonCreatePopupFunc_WithClosures
wrap_MenuButtonCreatePopupFunc :: Maybe (Ptr (FunPtr C_MenuButtonCreatePopupFunc)) -> MenuButtonCreatePopupFunc_WithClosures -> C_MenuButtonCreatePopupFunc Source #
Wrap a MenuButtonCreatePopupFunc
into a C_MenuButtonCreatePopupFunc
.
PageSetupDoneFunc
type C_PageSetupDoneFunc = Ptr PageSetup -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PageSetupDoneFunc Source #
= PageSetup |
|
-> IO () |
The type of function that is passed to
printRunPageSetupDialogAsync
.
This function will be called when the page setup dialog
is dismissed, and also serves as destroy notify for data
.
type PageSetupDoneFunc_WithClosures Source #
= PageSetup |
|
-> Ptr () |
|
-> IO () |
The type of function that is passed to
printRunPageSetupDialogAsync
.
This function will be called when the page setup dialog
is dismissed, and also serves as destroy notify for data
.
drop_closures_PageSetupDoneFunc :: PageSetupDoneFunc -> PageSetupDoneFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PageSetupDoneFunc Source #
:: (HasCallStack, MonadIO m, IsPageSetup a) | |
=> FunPtr C_PageSetupDoneFunc | |
-> a |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PageSetupDoneFunc :: MonadIO m => PageSetupDoneFunc -> m (GClosure C_PageSetupDoneFunc) Source #
Wrap the callback into a GClosure
.
mk_PageSetupDoneFunc :: C_PageSetupDoneFunc -> IO (FunPtr C_PageSetupDoneFunc) Source #
Generate a function pointer callable from C code, from a C_PageSetupDoneFunc
.
noPageSetupDoneFunc :: Maybe PageSetupDoneFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PageSetupDoneFunc
noPageSetupDoneFunc_WithClosures :: Maybe PageSetupDoneFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PageSetupDoneFunc_WithClosures
wrap_PageSetupDoneFunc :: Maybe (Ptr (FunPtr C_PageSetupDoneFunc)) -> PageSetupDoneFunc_WithClosures -> C_PageSetupDoneFunc Source #
Wrap a PageSetupDoneFunc
into a C_PageSetupDoneFunc
.
PrintSettingsFunc
type C_PrintSettingsFunc = CString -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PrintSettingsFunc = Text -> Text -> IO () Source #
No description available in the introspection data.
type PrintSettingsFunc_WithClosures = Text -> Text -> Ptr () -> IO () Source #
No description available in the introspection data.
drop_closures_PrintSettingsFunc :: PrintSettingsFunc -> PrintSettingsFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PrintSettingsFunc :: (HasCallStack, MonadIO m) => FunPtr C_PrintSettingsFunc -> Text -> Text -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PrintSettingsFunc :: MonadIO m => PrintSettingsFunc -> m (GClosure C_PrintSettingsFunc) Source #
Wrap the callback into a GClosure
.
mk_PrintSettingsFunc :: C_PrintSettingsFunc -> IO (FunPtr C_PrintSettingsFunc) Source #
Generate a function pointer callable from C code, from a C_PrintSettingsFunc
.
noPrintSettingsFunc :: Maybe PrintSettingsFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PrintSettingsFunc
noPrintSettingsFunc_WithClosures :: Maybe PrintSettingsFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PrintSettingsFunc_WithClosures
wrap_PrintSettingsFunc :: Maybe (Ptr (FunPtr C_PrintSettingsFunc)) -> PrintSettingsFunc_WithClosures -> C_PrintSettingsFunc Source #
Wrap a PrintSettingsFunc
into a C_PrintSettingsFunc
.
ScaleFormatValueFunc
type C_ScaleFormatValueFunc = Ptr Scale -> CDouble -> Ptr () -> IO CString Source #
Type for the callback on the (unwrapped) C side.
type ScaleFormatValueFunc Source #
= Scale |
|
-> Double |
|
-> IO Text | Returns: A newly allocated string describing a textual representation of the given numerical value. |
No description available in the introspection data.
type ScaleFormatValueFunc_WithClosures Source #
= Scale |
|
-> Double |
|
-> Ptr () |
|
-> IO Text | Returns: A newly allocated string describing a textual representation of the given numerical value. |
No description available in the introspection data.
drop_closures_ScaleFormatValueFunc :: ScaleFormatValueFunc -> ScaleFormatValueFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ScaleFormatValueFunc Source #
:: (HasCallStack, MonadIO m, IsScale a) | |
=> FunPtr C_ScaleFormatValueFunc | |
-> a |
|
-> Double |
|
-> Ptr () |
|
-> m Text | Returns: A newly allocated string describing a textual representation of the given numerical value. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ScaleFormatValueFunc :: MonadIO m => ScaleFormatValueFunc -> m (GClosure C_ScaleFormatValueFunc) Source #
Wrap the callback into a GClosure
.
mk_ScaleFormatValueFunc :: C_ScaleFormatValueFunc -> IO (FunPtr C_ScaleFormatValueFunc) Source #
Generate a function pointer callable from C code, from a C_ScaleFormatValueFunc
.
noScaleFormatValueFunc :: Maybe ScaleFormatValueFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ScaleFormatValueFunc
noScaleFormatValueFunc_WithClosures :: Maybe ScaleFormatValueFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ScaleFormatValueFunc_WithClosures
wrap_ScaleFormatValueFunc :: Maybe (Ptr (FunPtr C_ScaleFormatValueFunc)) -> ScaleFormatValueFunc_WithClosures -> C_ScaleFormatValueFunc Source #
Wrap a ScaleFormatValueFunc
into a C_ScaleFormatValueFunc
.
ShortcutFunc
type C_ShortcutFunc = Ptr Widget -> Ptr GVariant -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ShortcutFunc Source #
= Widget |
|
-> Maybe GVariant |
|
-> IO Bool |
Prototype for shortcuts based on user callbacks.
type ShortcutFunc_WithClosures Source #
= Widget |
|
-> Maybe GVariant |
|
-> Ptr () |
|
-> IO Bool |
Prototype for shortcuts based on user callbacks.
drop_closures_ShortcutFunc :: ShortcutFunc -> ShortcutFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_ShortcutFunc | |
-> a |
|
-> Maybe GVariant |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ShortcutFunc :: MonadIO m => ShortcutFunc -> m (GClosure C_ShortcutFunc) Source #
Wrap the callback into a GClosure
.
mk_ShortcutFunc :: C_ShortcutFunc -> IO (FunPtr C_ShortcutFunc) Source #
Generate a function pointer callable from C code, from a C_ShortcutFunc
.
noShortcutFunc :: Maybe ShortcutFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ShortcutFunc
noShortcutFunc_WithClosures :: Maybe ShortcutFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ShortcutFunc_WithClosures
wrap_ShortcutFunc :: Maybe (Ptr (FunPtr C_ShortcutFunc)) -> ShortcutFunc_WithClosures -> C_ShortcutFunc Source #
Wrap a ShortcutFunc
into a C_ShortcutFunc
.
TextCharPredicate
type C_TextCharPredicate = CInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TextCharPredicate Source #
= Char |
|
-> IO Bool | Returns: |
The predicate function used by textIterForwardFindChar
and
textIterBackwardFindChar
.
type TextCharPredicate_WithClosures Source #
= Char |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The predicate function used by textIterForwardFindChar
and
textIterBackwardFindChar
.
drop_closures_TextCharPredicate :: TextCharPredicate -> TextCharPredicate_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TextCharPredicate Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TextCharPredicate | |
-> Char |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TextCharPredicate :: MonadIO m => TextCharPredicate -> m (GClosure C_TextCharPredicate) Source #
Wrap the callback into a GClosure
.
mk_TextCharPredicate :: C_TextCharPredicate -> IO (FunPtr C_TextCharPredicate) Source #
Generate a function pointer callable from C code, from a C_TextCharPredicate
.
noTextCharPredicate :: Maybe TextCharPredicate Source #
A convenience synonym for
.Nothing
:: Maybe
TextCharPredicate
noTextCharPredicate_WithClosures :: Maybe TextCharPredicate_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TextCharPredicate_WithClosures
wrap_TextCharPredicate :: Maybe (Ptr (FunPtr C_TextCharPredicate)) -> TextCharPredicate_WithClosures -> C_TextCharPredicate Source #
Wrap a TextCharPredicate
into a C_TextCharPredicate
.
TextTagTableForeach
type C_TextTagTableForeach = Ptr TextTag -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TextTagTableForeach Source #
A function used with textTagTableForeach
, to iterate over every
TextTag
inside a TextTagTable
.
type TextTagTableForeach_WithClosures Source #
= TextTag |
|
-> Ptr () |
|
-> IO () |
A function used with textTagTableForeach
, to iterate over every
TextTag
inside a TextTagTable
.
drop_closures_TextTagTableForeach :: TextTagTableForeach -> TextTagTableForeach_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TextTagTableForeach Source #
:: (HasCallStack, MonadIO m, IsTextTag a) | |
=> FunPtr C_TextTagTableForeach | |
-> a |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TextTagTableForeach :: MonadIO m => TextTagTableForeach -> m (GClosure C_TextTagTableForeach) Source #
Wrap the callback into a GClosure
.
mk_TextTagTableForeach :: C_TextTagTableForeach -> IO (FunPtr C_TextTagTableForeach) Source #
Generate a function pointer callable from C code, from a C_TextTagTableForeach
.
noTextTagTableForeach :: Maybe TextTagTableForeach Source #
A convenience synonym for
.Nothing
:: Maybe
TextTagTableForeach
noTextTagTableForeach_WithClosures :: Maybe TextTagTableForeach_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TextTagTableForeach_WithClosures
wrap_TextTagTableForeach :: Maybe (Ptr (FunPtr C_TextTagTableForeach)) -> TextTagTableForeach_WithClosures -> C_TextTagTableForeach Source #
Wrap a TextTagTableForeach
into a C_TextTagTableForeach
.
TickCallback
type C_TickCallback = Ptr Widget -> Ptr FrameClock -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TickCallback Source #
= Widget |
|
-> FrameClock |
|
-> IO Bool | Returns: |
Callback type for adding a function to update animations. See widgetAddTickCallback
.
type TickCallback_WithClosures Source #
= Widget |
|
-> FrameClock |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Callback type for adding a function to update animations. See widgetAddTickCallback
.
drop_closures_TickCallback :: TickCallback -> TickCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsWidget a, IsFrameClock b) | |
=> FunPtr C_TickCallback | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TickCallback :: MonadIO m => TickCallback -> m (GClosure C_TickCallback) Source #
Wrap the callback into a GClosure
.
mk_TickCallback :: C_TickCallback -> IO (FunPtr C_TickCallback) Source #
Generate a function pointer callable from C code, from a C_TickCallback
.
noTickCallback :: Maybe TickCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TickCallback
noTickCallback_WithClosures :: Maybe TickCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TickCallback_WithClosures
wrap_TickCallback :: Maybe (Ptr (FunPtr C_TickCallback)) -> TickCallback_WithClosures -> C_TickCallback Source #
Wrap a TickCallback
into a C_TickCallback
.
TreeCellDataFunc
type C_TreeCellDataFunc = Ptr TreeViewColumn -> Ptr CellRenderer -> Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TreeCellDataFunc Source #
= TreeViewColumn |
|
-> CellRenderer |
|
-> TreeModel |
|
-> TreeIter |
|
-> IO () |
A function to set the properties of a cell instead of just using the
straight mapping between the cell and the model. This is useful for
customizing the cell renderer. For example, a function might get an
integer from the treeModel
, and render it to the “text” attribute of
“cell” by converting it to its written equivalent. This is set by
calling treeViewColumnSetCellDataFunc
type TreeCellDataFunc_WithClosures Source #
= TreeViewColumn |
|
-> CellRenderer |
|
-> TreeModel |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO () |
A function to set the properties of a cell instead of just using the
straight mapping between the cell and the model. This is useful for
customizing the cell renderer. For example, a function might get an
integer from the treeModel
, and render it to the “text” attribute of
“cell” by converting it to its written equivalent. This is set by
calling treeViewColumnSetCellDataFunc
drop_closures_TreeCellDataFunc :: TreeCellDataFunc -> TreeCellDataFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeCellDataFunc Source #
:: (HasCallStack, MonadIO m, IsTreeViewColumn a, IsCellRenderer b, IsTreeModel c) | |
=> FunPtr C_TreeCellDataFunc | |
-> a |
|
-> b |
|
-> c |
|
-> TreeIter |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeCellDataFunc :: MonadIO m => TreeCellDataFunc -> m (GClosure C_TreeCellDataFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeCellDataFunc :: C_TreeCellDataFunc -> IO (FunPtr C_TreeCellDataFunc) Source #
Generate a function pointer callable from C code, from a C_TreeCellDataFunc
.
noTreeCellDataFunc :: Maybe TreeCellDataFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeCellDataFunc
noTreeCellDataFunc_WithClosures :: Maybe TreeCellDataFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeCellDataFunc_WithClosures
wrap_TreeCellDataFunc :: Maybe (Ptr (FunPtr C_TreeCellDataFunc)) -> TreeCellDataFunc_WithClosures -> C_TreeCellDataFunc Source #
Wrap a TreeCellDataFunc
into a C_TreeCellDataFunc
.
TreeIterCompareFunc
type C_TreeIterCompareFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr TreeIter -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type TreeIterCompareFunc Source #
= TreeModel |
|
-> TreeIter |
|
-> TreeIter |
|
-> IO Int32 | Returns: a negative integer, zero or a positive integer depending on whether
|
A GtkTreeIterCompareFunc should return a negative integer, zero, or a positive
integer if a
sorts before b
, a
sorts with b
, or a
sorts after b
respectively. If two iters compare as equal, their order in the sorted model
is undefined. In order to ensure that the TreeSortable
behaves as
expected, the GtkTreeIterCompareFunc must define a partial order on
the model, i.e. it must be reflexive, antisymmetric and transitive.
For example, if model
is a product catalogue, then a compare function
for the “price” column could be one which returns
price_of(@a) - price_of(@b)
.
type TreeIterCompareFunc_WithClosures Source #
= TreeModel |
|
-> TreeIter |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Int32 | Returns: a negative integer, zero or a positive integer depending on whether
|
A GtkTreeIterCompareFunc should return a negative integer, zero, or a positive
integer if a
sorts before b
, a
sorts with b
, or a
sorts after b
respectively. If two iters compare as equal, their order in the sorted model
is undefined. In order to ensure that the TreeSortable
behaves as
expected, the GtkTreeIterCompareFunc must define a partial order on
the model, i.e. it must be reflexive, antisymmetric and transitive.
For example, if model
is a product catalogue, then a compare function
for the “price” column could be one which returns
price_of(@a) - price_of(@b)
.
drop_closures_TreeIterCompareFunc :: TreeIterCompareFunc -> TreeIterCompareFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeIterCompareFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeIterCompareFunc | |
-> a |
|
-> TreeIter |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Int32 | Returns: a negative integer, zero or a positive integer depending on whether
|
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeIterCompareFunc :: MonadIO m => TreeIterCompareFunc -> m (GClosure C_TreeIterCompareFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeIterCompareFunc :: C_TreeIterCompareFunc -> IO (FunPtr C_TreeIterCompareFunc) Source #
Generate a function pointer callable from C code, from a C_TreeIterCompareFunc
.
noTreeIterCompareFunc :: Maybe TreeIterCompareFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeIterCompareFunc
noTreeIterCompareFunc_WithClosures :: Maybe TreeIterCompareFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeIterCompareFunc_WithClosures
wrap_TreeIterCompareFunc :: Maybe (Ptr (FunPtr C_TreeIterCompareFunc)) -> TreeIterCompareFunc_WithClosures -> C_TreeIterCompareFunc Source #
Wrap a TreeIterCompareFunc
into a C_TreeIterCompareFunc
.
TreeListModelCreateModelFunc
type C_TreeListModelCreateModelFunc = Ptr Object -> Ptr () -> IO (Ptr ListModel) Source #
Type for the callback on the (unwrapped) C side.
type TreeListModelCreateModelFunc Source #
= Object |
|
-> IO (Maybe ListModel) | Returns: The model tracking the children of |
Prototype of the function called to create new child models when
treeListRowSetExpanded
is called.
This function can return Nothing
to indicate that item
is guaranteed to be
a leaf node and will never have children.
If it does not have children but may get children later, it should return
an empty model that is filled once children arrive.
type TreeListModelCreateModelFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO (Maybe ListModel) | Returns: The model tracking the children of |
Prototype of the function called to create new child models when
treeListRowSetExpanded
is called.
This function can return Nothing
to indicate that item
is guaranteed to be
a leaf node and will never have children.
If it does not have children but may get children later, it should return
an empty model that is filled once children arrive.
drop_closures_TreeListModelCreateModelFunc :: TreeListModelCreateModelFunc -> TreeListModelCreateModelFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeListModelCreateModelFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_TreeListModelCreateModelFunc | |
-> a |
|
-> Ptr () |
|
-> m (Maybe ListModel) | Returns: The model tracking the children of |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeListModelCreateModelFunc :: MonadIO m => TreeListModelCreateModelFunc -> m (GClosure C_TreeListModelCreateModelFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeListModelCreateModelFunc :: C_TreeListModelCreateModelFunc -> IO (FunPtr C_TreeListModelCreateModelFunc) Source #
Generate a function pointer callable from C code, from a C_TreeListModelCreateModelFunc
.
noTreeListModelCreateModelFunc :: Maybe TreeListModelCreateModelFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeListModelCreateModelFunc
noTreeListModelCreateModelFunc_WithClosures :: Maybe TreeListModelCreateModelFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeListModelCreateModelFunc_WithClosures
wrap_TreeListModelCreateModelFunc :: Maybe (Ptr (FunPtr C_TreeListModelCreateModelFunc)) -> TreeListModelCreateModelFunc_WithClosures -> C_TreeListModelCreateModelFunc Source #
Wrap a TreeListModelCreateModelFunc
into a C_TreeListModelCreateModelFunc
.
TreeModelFilterModifyFunc
type C_TreeModelFilterModifyFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr GValue -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TreeModelFilterModifyFunc Source #
= TreeModel |
|
-> TreeIter |
|
-> GValue |
|
-> Int32 |
|
-> IO () |
A function which calculates display values from raw values in the model.
It must fill value
with the display value for the column column
in the
row indicated by iter
.
Since this function is called for each data access, it’s not a particularly efficient operation.
type TreeModelFilterModifyFunc_WithClosures Source #
= TreeModel |
|
-> TreeIter |
|
-> GValue |
|
-> Int32 |
|
-> Ptr () |
|
-> IO () |
A function which calculates display values from raw values in the model.
It must fill value
with the display value for the column column
in the
row indicated by iter
.
Since this function is called for each data access, it’s not a particularly efficient operation.
drop_closures_TreeModelFilterModifyFunc :: TreeModelFilterModifyFunc -> TreeModelFilterModifyFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeModelFilterModifyFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeModelFilterModifyFunc | |
-> a |
|
-> TreeIter |
|
-> GValue |
|
-> Int32 |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeModelFilterModifyFunc :: MonadIO m => TreeModelFilterModifyFunc -> m (GClosure C_TreeModelFilterModifyFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeModelFilterModifyFunc :: C_TreeModelFilterModifyFunc -> IO (FunPtr C_TreeModelFilterModifyFunc) Source #
Generate a function pointer callable from C code, from a C_TreeModelFilterModifyFunc
.
noTreeModelFilterModifyFunc :: Maybe TreeModelFilterModifyFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelFilterModifyFunc
noTreeModelFilterModifyFunc_WithClosures :: Maybe TreeModelFilterModifyFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelFilterModifyFunc_WithClosures
wrap_TreeModelFilterModifyFunc :: Maybe (Ptr (FunPtr C_TreeModelFilterModifyFunc)) -> TreeModelFilterModifyFunc_WithClosures -> C_TreeModelFilterModifyFunc Source #
Wrap a TreeModelFilterModifyFunc
into a C_TreeModelFilterModifyFunc
.
TreeModelFilterVisibleFunc
type C_TreeModelFilterVisibleFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeModelFilterVisibleFunc Source #
= TreeModel |
|
-> TreeIter |
|
-> IO Bool | Returns: Whether the row indicated by |
A function which decides whether the row indicated by iter
is visible.
type TreeModelFilterVisibleFunc_WithClosures Source #
= TreeModel |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Bool | Returns: Whether the row indicated by |
A function which decides whether the row indicated by iter
is visible.
drop_closures_TreeModelFilterVisibleFunc :: TreeModelFilterVisibleFunc -> TreeModelFilterVisibleFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeModelFilterVisibleFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeModelFilterVisibleFunc | |
-> a |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Bool | Returns: Whether the row indicated by |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeModelFilterVisibleFunc :: MonadIO m => TreeModelFilterVisibleFunc -> m (GClosure C_TreeModelFilterVisibleFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeModelFilterVisibleFunc :: C_TreeModelFilterVisibleFunc -> IO (FunPtr C_TreeModelFilterVisibleFunc) Source #
Generate a function pointer callable from C code, from a C_TreeModelFilterVisibleFunc
.
noTreeModelFilterVisibleFunc :: Maybe TreeModelFilterVisibleFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelFilterVisibleFunc
noTreeModelFilterVisibleFunc_WithClosures :: Maybe TreeModelFilterVisibleFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelFilterVisibleFunc_WithClosures
wrap_TreeModelFilterVisibleFunc :: Maybe (Ptr (FunPtr C_TreeModelFilterVisibleFunc)) -> TreeModelFilterVisibleFunc_WithClosures -> C_TreeModelFilterVisibleFunc Source #
Wrap a TreeModelFilterVisibleFunc
into a C_TreeModelFilterVisibleFunc
.
TreeModelForeachFunc
type C_TreeModelForeachFunc = Ptr TreeModel -> Ptr TreePath -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeModelForeachFunc Source #
= TreeModel |
|
-> TreePath |
|
-> TreeIter |
|
-> IO Bool |
Type of the callback passed to treeModelForeach
to
iterate over the rows in a tree model.
type TreeModelForeachFunc_WithClosures Source #
= TreeModel |
|
-> TreePath |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Bool |
Type of the callback passed to treeModelForeach
to
iterate over the rows in a tree model.
drop_closures_TreeModelForeachFunc :: TreeModelForeachFunc -> TreeModelForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeModelForeachFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeModelForeachFunc | |
-> a |
|
-> TreePath |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeModelForeachFunc :: MonadIO m => TreeModelForeachFunc -> m (GClosure C_TreeModelForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeModelForeachFunc :: C_TreeModelForeachFunc -> IO (FunPtr C_TreeModelForeachFunc) Source #
Generate a function pointer callable from C code, from a C_TreeModelForeachFunc
.
noTreeModelForeachFunc :: Maybe TreeModelForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelForeachFunc
noTreeModelForeachFunc_WithClosures :: Maybe TreeModelForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeModelForeachFunc_WithClosures
wrap_TreeModelForeachFunc :: Maybe (Ptr (FunPtr C_TreeModelForeachFunc)) -> TreeModelForeachFunc_WithClosures -> C_TreeModelForeachFunc Source #
Wrap a TreeModelForeachFunc
into a C_TreeModelForeachFunc
.
TreeSelectionForeachFunc
type C_TreeSelectionForeachFunc = Ptr TreeModel -> Ptr TreePath -> Ptr TreeIter -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TreeSelectionForeachFunc Source #
= TreeModel |
|
-> TreePath |
|
-> TreeIter |
|
-> IO () |
A function used by treeSelectionSelectedForeach
to map all
selected rows. It will be called on every selected row in the view.
type TreeSelectionForeachFunc_WithClosures Source #
= TreeModel |
|
-> TreePath |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO () |
A function used by treeSelectionSelectedForeach
to map all
selected rows. It will be called on every selected row in the view.
drop_closures_TreeSelectionForeachFunc :: TreeSelectionForeachFunc -> TreeSelectionForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeSelectionForeachFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeSelectionForeachFunc | |
-> a |
|
-> TreePath |
|
-> TreeIter |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeSelectionForeachFunc :: MonadIO m => TreeSelectionForeachFunc -> m (GClosure C_TreeSelectionForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeSelectionForeachFunc :: C_TreeSelectionForeachFunc -> IO (FunPtr C_TreeSelectionForeachFunc) Source #
Generate a function pointer callable from C code, from a C_TreeSelectionForeachFunc
.
noTreeSelectionForeachFunc :: Maybe TreeSelectionForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeSelectionForeachFunc
noTreeSelectionForeachFunc_WithClosures :: Maybe TreeSelectionForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeSelectionForeachFunc_WithClosures
wrap_TreeSelectionForeachFunc :: Maybe (Ptr (FunPtr C_TreeSelectionForeachFunc)) -> TreeSelectionForeachFunc_WithClosures -> C_TreeSelectionForeachFunc Source #
Wrap a TreeSelectionForeachFunc
into a C_TreeSelectionForeachFunc
.
TreeSelectionFunc
type C_TreeSelectionFunc = Ptr TreeSelection -> Ptr TreeModel -> Ptr TreePath -> CInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeSelectionFunc Source #
= TreeSelection |
|
-> TreeModel |
|
-> TreePath |
|
-> Bool |
|
-> IO Bool | Returns: |
A function used by treeSelectionSetSelectFunction
to filter
whether or not a row may be selected. It is called whenever a row's
state might change. A return value of True
indicates to selection
that it is okay to change the selection.
type TreeSelectionFunc_WithClosures Source #
= TreeSelection |
|
-> TreeModel |
|
-> TreePath |
|
-> Bool |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function used by treeSelectionSetSelectFunction
to filter
whether or not a row may be selected. It is called whenever a row's
state might change. A return value of True
indicates to selection
that it is okay to change the selection.
drop_closures_TreeSelectionFunc :: TreeSelectionFunc -> TreeSelectionFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeSelectionFunc Source #
:: (HasCallStack, MonadIO m, IsTreeSelection a, IsTreeModel b) | |
=> FunPtr C_TreeSelectionFunc | |
-> a |
|
-> b |
|
-> TreePath |
|
-> Bool |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeSelectionFunc :: MonadIO m => TreeSelectionFunc -> m (GClosure C_TreeSelectionFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeSelectionFunc :: C_TreeSelectionFunc -> IO (FunPtr C_TreeSelectionFunc) Source #
Generate a function pointer callable from C code, from a C_TreeSelectionFunc
.
noTreeSelectionFunc :: Maybe TreeSelectionFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeSelectionFunc
noTreeSelectionFunc_WithClosures :: Maybe TreeSelectionFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeSelectionFunc_WithClosures
wrap_TreeSelectionFunc :: Maybe (Ptr (FunPtr C_TreeSelectionFunc)) -> TreeSelectionFunc_WithClosures -> C_TreeSelectionFunc Source #
Wrap a TreeSelectionFunc
into a C_TreeSelectionFunc
.
TreeViewColumnDropFunc
type C_TreeViewColumnDropFunc = Ptr TreeView -> Ptr TreeViewColumn -> Ptr TreeViewColumn -> Ptr TreeViewColumn -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeViewColumnDropFunc Source #
= TreeView |
|
-> TreeViewColumn |
|
-> TreeViewColumn |
|
-> TreeViewColumn |
|
-> IO Bool | Returns: |
Function type for determining whether column
can be dropped in a
particular spot (as determined by prevColumn
and nextColumn
). In
left to right locales, prevColumn
is on the left of the potential drop
spot, and nextColumn
is on the right. In right to left mode, this is
reversed. This function should return True
if the spot is a valid drop
spot. Please note that returning True
does not actually indicate that
the column drop was made, but is meant only to indicate a possible drop
spot to the user.
type TreeViewColumnDropFunc_WithClosures Source #
= TreeView |
|
-> TreeViewColumn |
|
-> TreeViewColumn |
|
-> TreeViewColumn |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Function type for determining whether column
can be dropped in a
particular spot (as determined by prevColumn
and nextColumn
). In
left to right locales, prevColumn
is on the left of the potential drop
spot, and nextColumn
is on the right. In right to left mode, this is
reversed. This function should return True
if the spot is a valid drop
spot. Please note that returning True
does not actually indicate that
the column drop was made, but is meant only to indicate a possible drop
spot to the user.
drop_closures_TreeViewColumnDropFunc :: TreeViewColumnDropFunc -> TreeViewColumnDropFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeViewColumnDropFunc Source #
:: (HasCallStack, MonadIO m, IsTreeView a, IsTreeViewColumn b, IsTreeViewColumn c, IsTreeViewColumn d) | |
=> FunPtr C_TreeViewColumnDropFunc | |
-> a |
|
-> b |
|
-> c |
|
-> d |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeViewColumnDropFunc :: MonadIO m => TreeViewColumnDropFunc -> m (GClosure C_TreeViewColumnDropFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeViewColumnDropFunc :: C_TreeViewColumnDropFunc -> IO (FunPtr C_TreeViewColumnDropFunc) Source #
Generate a function pointer callable from C code, from a C_TreeViewColumnDropFunc
.
noTreeViewColumnDropFunc :: Maybe TreeViewColumnDropFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewColumnDropFunc
noTreeViewColumnDropFunc_WithClosures :: Maybe TreeViewColumnDropFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewColumnDropFunc_WithClosures
wrap_TreeViewColumnDropFunc :: Maybe (Ptr (FunPtr C_TreeViewColumnDropFunc)) -> TreeViewColumnDropFunc_WithClosures -> C_TreeViewColumnDropFunc Source #
Wrap a TreeViewColumnDropFunc
into a C_TreeViewColumnDropFunc
.
TreeViewMappingFunc
type C_TreeViewMappingFunc = Ptr TreeView -> Ptr TreePath -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TreeViewMappingFunc Source #
Function used for treeViewMapExpandedRows
.
type TreeViewMappingFunc_WithClosures Source #
= TreeView |
|
-> TreePath |
|
-> Ptr () |
|
-> IO () |
Function used for treeViewMapExpandedRows
.
drop_closures_TreeViewMappingFunc :: TreeViewMappingFunc -> TreeViewMappingFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeViewMappingFunc Source #
:: (HasCallStack, MonadIO m, IsTreeView a) | |
=> FunPtr C_TreeViewMappingFunc | |
-> a |
|
-> TreePath |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeViewMappingFunc :: MonadIO m => TreeViewMappingFunc -> m (GClosure C_TreeViewMappingFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeViewMappingFunc :: C_TreeViewMappingFunc -> IO (FunPtr C_TreeViewMappingFunc) Source #
Generate a function pointer callable from C code, from a C_TreeViewMappingFunc
.
noTreeViewMappingFunc :: Maybe TreeViewMappingFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewMappingFunc
noTreeViewMappingFunc_WithClosures :: Maybe TreeViewMappingFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewMappingFunc_WithClosures
wrap_TreeViewMappingFunc :: Maybe (Ptr (FunPtr C_TreeViewMappingFunc)) -> TreeViewMappingFunc_WithClosures -> C_TreeViewMappingFunc Source #
Wrap a TreeViewMappingFunc
into a C_TreeViewMappingFunc
.
TreeViewRowSeparatorFunc
type C_TreeViewRowSeparatorFunc = Ptr TreeModel -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeViewRowSeparatorFunc Source #
= TreeModel |
|
-> TreeIter |
|
-> IO Bool | Returns: |
Function type for determining whether the row pointed to by iter
should
be rendered as a separator. A common way to implement this is to have a
boolean column in the model, whose values the TreeViewRowSeparatorFunc
returns.
type TreeViewRowSeparatorFunc_WithClosures Source #
= TreeModel |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Function type for determining whether the row pointed to by iter
should
be rendered as a separator. A common way to implement this is to have a
boolean column in the model, whose values the TreeViewRowSeparatorFunc
returns.
drop_closures_TreeViewRowSeparatorFunc :: TreeViewRowSeparatorFunc -> TreeViewRowSeparatorFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeViewRowSeparatorFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeViewRowSeparatorFunc | |
-> a |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeViewRowSeparatorFunc :: MonadIO m => TreeViewRowSeparatorFunc -> m (GClosure C_TreeViewRowSeparatorFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeViewRowSeparatorFunc :: C_TreeViewRowSeparatorFunc -> IO (FunPtr C_TreeViewRowSeparatorFunc) Source #
Generate a function pointer callable from C code, from a C_TreeViewRowSeparatorFunc
.
noTreeViewRowSeparatorFunc :: Maybe TreeViewRowSeparatorFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewRowSeparatorFunc
noTreeViewRowSeparatorFunc_WithClosures :: Maybe TreeViewRowSeparatorFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewRowSeparatorFunc_WithClosures
wrap_TreeViewRowSeparatorFunc :: Maybe (Ptr (FunPtr C_TreeViewRowSeparatorFunc)) -> TreeViewRowSeparatorFunc_WithClosures -> C_TreeViewRowSeparatorFunc Source #
Wrap a TreeViewRowSeparatorFunc
into a C_TreeViewRowSeparatorFunc
.
TreeViewSearchEqualFunc
type C_TreeViewSearchEqualFunc = Ptr TreeModel -> Int32 -> CString -> Ptr TreeIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TreeViewSearchEqualFunc Source #
= TreeModel |
|
-> Int32 |
|
-> Text |
|
-> TreeIter |
|
-> IO Bool |
A function used for checking whether a row in model
matches
a search key string entered by the user. Note the return value
is reversed from what you would normally expect, though it
has some similarity to strcmp()
returning 0 for equal strings.
type TreeViewSearchEqualFunc_WithClosures Source #
= TreeModel |
|
-> Int32 |
|
-> Text |
|
-> TreeIter |
|
-> Ptr () |
|
-> IO Bool |
A function used for checking whether a row in model
matches
a search key string entered by the user. Note the return value
is reversed from what you would normally expect, though it
has some similarity to strcmp()
returning 0 for equal strings.
drop_closures_TreeViewSearchEqualFunc :: TreeViewSearchEqualFunc -> TreeViewSearchEqualFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TreeViewSearchEqualFunc Source #
:: (HasCallStack, MonadIO m, IsTreeModel a) | |
=> FunPtr C_TreeViewSearchEqualFunc | |
-> a |
|
-> Int32 |
|
-> Text |
|
-> TreeIter |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TreeViewSearchEqualFunc :: MonadIO m => TreeViewSearchEqualFunc -> m (GClosure C_TreeViewSearchEqualFunc) Source #
Wrap the callback into a GClosure
.
mk_TreeViewSearchEqualFunc :: C_TreeViewSearchEqualFunc -> IO (FunPtr C_TreeViewSearchEqualFunc) Source #
Generate a function pointer callable from C code, from a C_TreeViewSearchEqualFunc
.
noTreeViewSearchEqualFunc :: Maybe TreeViewSearchEqualFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewSearchEqualFunc
noTreeViewSearchEqualFunc_WithClosures :: Maybe TreeViewSearchEqualFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TreeViewSearchEqualFunc_WithClosures
wrap_TreeViewSearchEqualFunc :: Maybe (Ptr (FunPtr C_TreeViewSearchEqualFunc)) -> TreeViewSearchEqualFunc_WithClosures -> C_TreeViewSearchEqualFunc Source #
Wrap a TreeViewSearchEqualFunc
into a C_TreeViewSearchEqualFunc
.
WidgetActionActivateFunc
type C_WidgetActionActivateFunc = Ptr Widget -> CString -> Ptr GVariant -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetActionActivateFunc Source #
= Widget |
|
-> Text |
|
-> GVariant |
|
-> IO () |
The type of the callback functions used for activating
actions installed with widgetClassInstallAction
.
The parameter
must match the parameterType
of the action.
dynamic_WidgetActionActivateFunc Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetActionActivateFunc | |
-> a |
|
-> Text |
|
-> GVariant |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetActionActivateFunc :: MonadIO m => WidgetActionActivateFunc -> m (GClosure C_WidgetActionActivateFunc) Source #
Wrap the callback into a GClosure
.
mk_WidgetActionActivateFunc :: C_WidgetActionActivateFunc -> IO (FunPtr C_WidgetActionActivateFunc) Source #
Generate a function pointer callable from C code, from a C_WidgetActionActivateFunc
.
noWidgetActionActivateFunc :: Maybe WidgetActionActivateFunc Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetActionActivateFunc
wrap_WidgetActionActivateFunc :: Maybe (Ptr (FunPtr C_WidgetActionActivateFunc)) -> WidgetActionActivateFunc -> C_WidgetActionActivateFunc Source #
Wrap a WidgetActionActivateFunc
into a C_WidgetActionActivateFunc
.
WidgetClassComputeExpandFieldCallback
type C_WidgetClassComputeExpandFieldCallback = Ptr Widget -> CInt -> CInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassComputeExpandFieldCallback = Widget -> Bool -> Bool -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassComputeExpandFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassComputeExpandFieldCallback -> a -> Bool -> Bool -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassComputeExpandFieldCallback :: MonadIO m => WidgetClassComputeExpandFieldCallback -> m (GClosure C_WidgetClassComputeExpandFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassComputeExpandFieldCallback :: C_WidgetClassComputeExpandFieldCallback -> IO (FunPtr C_WidgetClassComputeExpandFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassComputeExpandFieldCallback
.
noWidgetClassComputeExpandFieldCallback :: Maybe WidgetClassComputeExpandFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassComputeExpandFieldCallback
wrap_WidgetClassComputeExpandFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassComputeExpandFieldCallback)) -> WidgetClassComputeExpandFieldCallback -> C_WidgetClassComputeExpandFieldCallback Source #
WidgetClassContainsFieldCallback
type C_WidgetClassContainsFieldCallback = Ptr Widget -> CDouble -> CDouble -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassContainsFieldCallback Source #
= Widget |
|
-> Double |
|
-> Double |
|
-> IO Bool | Returns: |
No description available in the introspection data.
dynamic_WidgetClassContainsFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassContainsFieldCallback | |
-> a |
|
-> Double |
|
-> Double |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassContainsFieldCallback :: MonadIO m => WidgetClassContainsFieldCallback -> m (GClosure C_WidgetClassContainsFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassContainsFieldCallback :: C_WidgetClassContainsFieldCallback -> IO (FunPtr C_WidgetClassContainsFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassContainsFieldCallback
.
noWidgetClassContainsFieldCallback :: Maybe WidgetClassContainsFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassContainsFieldCallback
wrap_WidgetClassContainsFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassContainsFieldCallback)) -> WidgetClassContainsFieldCallback -> C_WidgetClassContainsFieldCallback Source #
WidgetClassCssChangedFieldCallback
type C_WidgetClassCssChangedFieldCallback = Ptr Widget -> Ptr CssStyleChange -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassCssChangedFieldCallback = Widget -> CssStyleChange -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassCssChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassCssChangedFieldCallback -> a -> CssStyleChange -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassCssChangedFieldCallback :: MonadIO m => WidgetClassCssChangedFieldCallback -> m (GClosure C_WidgetClassCssChangedFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassCssChangedFieldCallback :: C_WidgetClassCssChangedFieldCallback -> IO (FunPtr C_WidgetClassCssChangedFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassCssChangedFieldCallback
.
noWidgetClassCssChangedFieldCallback :: Maybe WidgetClassCssChangedFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassCssChangedFieldCallback
wrap_WidgetClassCssChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassCssChangedFieldCallback)) -> WidgetClassCssChangedFieldCallback -> C_WidgetClassCssChangedFieldCallback Source #
WidgetClassDirectionChangedFieldCallback
type C_WidgetClassDirectionChangedFieldCallback = Ptr Widget -> CUInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassDirectionChangedFieldCallback = Widget -> TextDirection -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassDirectionChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassDirectionChangedFieldCallback -> a -> TextDirection -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassDirectionChangedFieldCallback :: MonadIO m => WidgetClassDirectionChangedFieldCallback -> m (GClosure C_WidgetClassDirectionChangedFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassDirectionChangedFieldCallback :: C_WidgetClassDirectionChangedFieldCallback -> IO (FunPtr C_WidgetClassDirectionChangedFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassDirectionChangedFieldCallback
.
noWidgetClassDirectionChangedFieldCallback :: Maybe WidgetClassDirectionChangedFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassDirectionChangedFieldCallback
wrap_WidgetClassDirectionChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassDirectionChangedFieldCallback)) -> WidgetClassDirectionChangedFieldCallback -> C_WidgetClassDirectionChangedFieldCallback Source #
WidgetClassFocusFieldCallback
type C_WidgetClassFocusFieldCallback = Ptr Widget -> CUInt -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassFocusFieldCallback = Widget -> DirectionType -> IO Bool Source #
No description available in the introspection data.
dynamic_WidgetClassFocusFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassFocusFieldCallback -> a -> DirectionType -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassFocusFieldCallback :: MonadIO m => WidgetClassFocusFieldCallback -> m (GClosure C_WidgetClassFocusFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassFocusFieldCallback :: C_WidgetClassFocusFieldCallback -> IO (FunPtr C_WidgetClassFocusFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassFocusFieldCallback
.
noWidgetClassFocusFieldCallback :: Maybe WidgetClassFocusFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassFocusFieldCallback
wrap_WidgetClassFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassFocusFieldCallback)) -> WidgetClassFocusFieldCallback -> C_WidgetClassFocusFieldCallback Source #
Wrap a WidgetClassFocusFieldCallback
into a C_WidgetClassFocusFieldCallback
.
WidgetClassGetRequestModeFieldCallback
type C_WidgetClassGetRequestModeFieldCallback = Ptr Widget -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassGetRequestModeFieldCallback Source #
= Widget |
|
-> IO SizeRequestMode | Returns: The |
No description available in the introspection data.
dynamic_WidgetClassGetRequestModeFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassGetRequestModeFieldCallback | |
-> a |
|
-> m SizeRequestMode | Returns: The |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassGetRequestModeFieldCallback :: MonadIO m => WidgetClassGetRequestModeFieldCallback -> m (GClosure C_WidgetClassGetRequestModeFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassGetRequestModeFieldCallback :: C_WidgetClassGetRequestModeFieldCallback -> IO (FunPtr C_WidgetClassGetRequestModeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassGetRequestModeFieldCallback
.
noWidgetClassGetRequestModeFieldCallback :: Maybe WidgetClassGetRequestModeFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassGetRequestModeFieldCallback
wrap_WidgetClassGetRequestModeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassGetRequestModeFieldCallback)) -> WidgetClassGetRequestModeFieldCallback -> C_WidgetClassGetRequestModeFieldCallback Source #
WidgetClassGrabFocusFieldCallback
type C_WidgetClassGrabFocusFieldCallback = Ptr Widget -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassGrabFocusFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassGrabFocusFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassGrabFocusFieldCallback | |
-> a |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassGrabFocusFieldCallback :: MonadIO m => WidgetClassGrabFocusFieldCallback -> m (GClosure C_WidgetClassGrabFocusFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassGrabFocusFieldCallback :: C_WidgetClassGrabFocusFieldCallback -> IO (FunPtr C_WidgetClassGrabFocusFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassGrabFocusFieldCallback
.
noWidgetClassGrabFocusFieldCallback :: Maybe WidgetClassGrabFocusFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassGrabFocusFieldCallback
wrap_WidgetClassGrabFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassGrabFocusFieldCallback)) -> WidgetClassGrabFocusFieldCallback -> C_WidgetClassGrabFocusFieldCallback Source #
WidgetClassHideFieldCallback
type C_WidgetClassHideFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassHideFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassHideFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassHideFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassHideFieldCallback :: MonadIO m => WidgetClassHideFieldCallback -> m (GClosure C_WidgetClassHideFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassHideFieldCallback :: C_WidgetClassHideFieldCallback -> IO (FunPtr C_WidgetClassHideFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassHideFieldCallback
.
noWidgetClassHideFieldCallback :: Maybe WidgetClassHideFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassHideFieldCallback
wrap_WidgetClassHideFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassHideFieldCallback)) -> WidgetClassHideFieldCallback -> C_WidgetClassHideFieldCallback Source #
Wrap a WidgetClassHideFieldCallback
into a C_WidgetClassHideFieldCallback
.
WidgetClassKeynavFailedFieldCallback
type C_WidgetClassKeynavFailedFieldCallback = Ptr Widget -> CUInt -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassKeynavFailedFieldCallback Source #
= Widget |
|
-> DirectionType |
|
-> IO Bool | Returns: |
No description available in the introspection data.
dynamic_WidgetClassKeynavFailedFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassKeynavFailedFieldCallback | |
-> a |
|
-> DirectionType |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassKeynavFailedFieldCallback :: MonadIO m => WidgetClassKeynavFailedFieldCallback -> m (GClosure C_WidgetClassKeynavFailedFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassKeynavFailedFieldCallback :: C_WidgetClassKeynavFailedFieldCallback -> IO (FunPtr C_WidgetClassKeynavFailedFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassKeynavFailedFieldCallback
.
noWidgetClassKeynavFailedFieldCallback :: Maybe WidgetClassKeynavFailedFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassKeynavFailedFieldCallback
wrap_WidgetClassKeynavFailedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassKeynavFailedFieldCallback)) -> WidgetClassKeynavFailedFieldCallback -> C_WidgetClassKeynavFailedFieldCallback Source #
WidgetClassMapFieldCallback
type C_WidgetClassMapFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassMapFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassMapFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassMapFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassMapFieldCallback :: MonadIO m => WidgetClassMapFieldCallback -> m (GClosure C_WidgetClassMapFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassMapFieldCallback :: C_WidgetClassMapFieldCallback -> IO (FunPtr C_WidgetClassMapFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassMapFieldCallback
.
noWidgetClassMapFieldCallback :: Maybe WidgetClassMapFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassMapFieldCallback
wrap_WidgetClassMapFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMapFieldCallback)) -> WidgetClassMapFieldCallback -> C_WidgetClassMapFieldCallback Source #
Wrap a WidgetClassMapFieldCallback
into a C_WidgetClassMapFieldCallback
.
WidgetClassMeasureFieldCallback
type C_WidgetClassMeasureFieldCallback = Ptr Widget -> CUInt -> Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> Ptr Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassMeasureFieldCallback Source #
= Widget |
|
-> Orientation |
|
-> Int32 |
|
-> IO (Int32, Int32, Int32, Int32) |
No description available in the introspection data.
dynamic_WidgetClassMeasureFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassMeasureFieldCallback | |
-> a |
|
-> Orientation |
|
-> Int32 |
|
-> m (Int32, Int32, Int32, Int32) |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassMeasureFieldCallback :: MonadIO m => WidgetClassMeasureFieldCallback -> m (GClosure C_WidgetClassMeasureFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassMeasureFieldCallback :: C_WidgetClassMeasureFieldCallback -> IO (FunPtr C_WidgetClassMeasureFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassMeasureFieldCallback
.
noWidgetClassMeasureFieldCallback :: Maybe WidgetClassMeasureFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassMeasureFieldCallback
wrap_WidgetClassMeasureFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMeasureFieldCallback)) -> WidgetClassMeasureFieldCallback -> C_WidgetClassMeasureFieldCallback Source #
Wrap a WidgetClassMeasureFieldCallback
into a C_WidgetClassMeasureFieldCallback
.
WidgetClassMnemonicActivateFieldCallback
type C_WidgetClassMnemonicActivateFieldCallback = Ptr Widget -> CInt -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassMnemonicActivateFieldCallback Source #
= Widget |
|
-> Bool |
|
-> IO Bool | Returns: |
No description available in the introspection data.
dynamic_WidgetClassMnemonicActivateFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassMnemonicActivateFieldCallback | |
-> a |
|
-> Bool |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassMnemonicActivateFieldCallback :: MonadIO m => WidgetClassMnemonicActivateFieldCallback -> m (GClosure C_WidgetClassMnemonicActivateFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassMnemonicActivateFieldCallback :: C_WidgetClassMnemonicActivateFieldCallback -> IO (FunPtr C_WidgetClassMnemonicActivateFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassMnemonicActivateFieldCallback
.
noWidgetClassMnemonicActivateFieldCallback :: Maybe WidgetClassMnemonicActivateFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassMnemonicActivateFieldCallback
wrap_WidgetClassMnemonicActivateFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMnemonicActivateFieldCallback)) -> WidgetClassMnemonicActivateFieldCallback -> C_WidgetClassMnemonicActivateFieldCallback Source #
WidgetClassMoveFocusFieldCallback
type C_WidgetClassMoveFocusFieldCallback = Ptr Widget -> CUInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassMoveFocusFieldCallback = Widget -> DirectionType -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassMoveFocusFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassMoveFocusFieldCallback -> a -> DirectionType -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassMoveFocusFieldCallback :: MonadIO m => WidgetClassMoveFocusFieldCallback -> m (GClosure C_WidgetClassMoveFocusFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassMoveFocusFieldCallback :: C_WidgetClassMoveFocusFieldCallback -> IO (FunPtr C_WidgetClassMoveFocusFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassMoveFocusFieldCallback
.
noWidgetClassMoveFocusFieldCallback :: Maybe WidgetClassMoveFocusFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassMoveFocusFieldCallback
wrap_WidgetClassMoveFocusFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassMoveFocusFieldCallback)) -> WidgetClassMoveFocusFieldCallback -> C_WidgetClassMoveFocusFieldCallback Source #
WidgetClassQueryTooltipFieldCallback
type C_WidgetClassQueryTooltipFieldCallback = Ptr Widget -> Int32 -> Int32 -> CInt -> Ptr Tooltip -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassQueryTooltipFieldCallback = Widget -> Int32 -> Int32 -> Bool -> Tooltip -> IO Bool Source #
No description available in the introspection data.
dynamic_WidgetClassQueryTooltipFieldCallback :: (HasCallStack, MonadIO m, IsWidget a, IsTooltip b) => FunPtr C_WidgetClassQueryTooltipFieldCallback -> a -> Int32 -> Int32 -> Bool -> b -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassQueryTooltipFieldCallback :: MonadIO m => WidgetClassQueryTooltipFieldCallback -> m (GClosure C_WidgetClassQueryTooltipFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassQueryTooltipFieldCallback :: C_WidgetClassQueryTooltipFieldCallback -> IO (FunPtr C_WidgetClassQueryTooltipFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassQueryTooltipFieldCallback
.
noWidgetClassQueryTooltipFieldCallback :: Maybe WidgetClassQueryTooltipFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassQueryTooltipFieldCallback
wrap_WidgetClassQueryTooltipFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassQueryTooltipFieldCallback)) -> WidgetClassQueryTooltipFieldCallback -> C_WidgetClassQueryTooltipFieldCallback Source #
WidgetClassRealizeFieldCallback
type C_WidgetClassRealizeFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassRealizeFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassRealizeFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassRealizeFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassRealizeFieldCallback :: MonadIO m => WidgetClassRealizeFieldCallback -> m (GClosure C_WidgetClassRealizeFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassRealizeFieldCallback :: C_WidgetClassRealizeFieldCallback -> IO (FunPtr C_WidgetClassRealizeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassRealizeFieldCallback
.
noWidgetClassRealizeFieldCallback :: Maybe WidgetClassRealizeFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassRealizeFieldCallback
wrap_WidgetClassRealizeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassRealizeFieldCallback)) -> WidgetClassRealizeFieldCallback -> C_WidgetClassRealizeFieldCallback Source #
Wrap a WidgetClassRealizeFieldCallback
into a C_WidgetClassRealizeFieldCallback
.
WidgetClassRootFieldCallback
type C_WidgetClassRootFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassRootFieldCallback = Widget -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassRootFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassRootFieldCallback -> a -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassRootFieldCallback :: MonadIO m => WidgetClassRootFieldCallback -> m (GClosure C_WidgetClassRootFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassRootFieldCallback :: C_WidgetClassRootFieldCallback -> IO (FunPtr C_WidgetClassRootFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassRootFieldCallback
.
noWidgetClassRootFieldCallback :: Maybe WidgetClassRootFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassRootFieldCallback
wrap_WidgetClassRootFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassRootFieldCallback)) -> WidgetClassRootFieldCallback -> C_WidgetClassRootFieldCallback Source #
Wrap a WidgetClassRootFieldCallback
into a C_WidgetClassRootFieldCallback
.
WidgetClassSetFocusChildFieldCallback
type C_WidgetClassSetFocusChildFieldCallback = Ptr Widget -> Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassSetFocusChildFieldCallback Source #
= Widget |
|
-> Maybe Widget |
|
-> IO () |
No description available in the introspection data.
dynamic_WidgetClassSetFocusChildFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a, IsWidget b) | |
=> FunPtr C_WidgetClassSetFocusChildFieldCallback | |
-> a |
|
-> Maybe b |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassSetFocusChildFieldCallback :: MonadIO m => WidgetClassSetFocusChildFieldCallback -> m (GClosure C_WidgetClassSetFocusChildFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassSetFocusChildFieldCallback :: C_WidgetClassSetFocusChildFieldCallback -> IO (FunPtr C_WidgetClassSetFocusChildFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassSetFocusChildFieldCallback
.
noWidgetClassSetFocusChildFieldCallback :: Maybe WidgetClassSetFocusChildFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassSetFocusChildFieldCallback
wrap_WidgetClassSetFocusChildFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSetFocusChildFieldCallback)) -> WidgetClassSetFocusChildFieldCallback -> C_WidgetClassSetFocusChildFieldCallback Source #
WidgetClassShowFieldCallback
type C_WidgetClassShowFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassShowFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassShowFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassShowFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassShowFieldCallback :: MonadIO m => WidgetClassShowFieldCallback -> m (GClosure C_WidgetClassShowFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassShowFieldCallback :: C_WidgetClassShowFieldCallback -> IO (FunPtr C_WidgetClassShowFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassShowFieldCallback
.
noWidgetClassShowFieldCallback :: Maybe WidgetClassShowFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassShowFieldCallback
wrap_WidgetClassShowFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassShowFieldCallback)) -> WidgetClassShowFieldCallback -> C_WidgetClassShowFieldCallback Source #
Wrap a WidgetClassShowFieldCallback
into a C_WidgetClassShowFieldCallback
.
WidgetClassSizeAllocateFieldCallback
type C_WidgetClassSizeAllocateFieldCallback = Ptr Widget -> Int32 -> Int32 -> Int32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassSizeAllocateFieldCallback = Widget -> Int32 -> Int32 -> Int32 -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassSizeAllocateFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassSizeAllocateFieldCallback -> a -> Int32 -> Int32 -> Int32 -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassSizeAllocateFieldCallback :: MonadIO m => WidgetClassSizeAllocateFieldCallback -> m (GClosure C_WidgetClassSizeAllocateFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassSizeAllocateFieldCallback :: C_WidgetClassSizeAllocateFieldCallback -> IO (FunPtr C_WidgetClassSizeAllocateFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassSizeAllocateFieldCallback
.
noWidgetClassSizeAllocateFieldCallback :: Maybe WidgetClassSizeAllocateFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassSizeAllocateFieldCallback
wrap_WidgetClassSizeAllocateFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSizeAllocateFieldCallback)) -> WidgetClassSizeAllocateFieldCallback -> C_WidgetClassSizeAllocateFieldCallback Source #
WidgetClassSnapshotFieldCallback
type C_WidgetClassSnapshotFieldCallback = Ptr Widget -> Ptr Snapshot -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassSnapshotFieldCallback = Widget -> Snapshot -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassSnapshotFieldCallback :: (HasCallStack, MonadIO m, IsWidget a, IsSnapshot b) => FunPtr C_WidgetClassSnapshotFieldCallback -> a -> b -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassSnapshotFieldCallback :: MonadIO m => WidgetClassSnapshotFieldCallback -> m (GClosure C_WidgetClassSnapshotFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassSnapshotFieldCallback :: C_WidgetClassSnapshotFieldCallback -> IO (FunPtr C_WidgetClassSnapshotFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassSnapshotFieldCallback
.
noWidgetClassSnapshotFieldCallback :: Maybe WidgetClassSnapshotFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassSnapshotFieldCallback
wrap_WidgetClassSnapshotFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSnapshotFieldCallback)) -> WidgetClassSnapshotFieldCallback -> C_WidgetClassSnapshotFieldCallback Source #
WidgetClassStateFlagsChangedFieldCallback
type C_WidgetClassStateFlagsChangedFieldCallback = Ptr Widget -> CUInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassStateFlagsChangedFieldCallback = Widget -> [StateFlags] -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassStateFlagsChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassStateFlagsChangedFieldCallback -> a -> [StateFlags] -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassStateFlagsChangedFieldCallback :: MonadIO m => WidgetClassStateFlagsChangedFieldCallback -> m (GClosure C_WidgetClassStateFlagsChangedFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassStateFlagsChangedFieldCallback :: C_WidgetClassStateFlagsChangedFieldCallback -> IO (FunPtr C_WidgetClassStateFlagsChangedFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassStateFlagsChangedFieldCallback
.
noWidgetClassStateFlagsChangedFieldCallback :: Maybe WidgetClassStateFlagsChangedFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassStateFlagsChangedFieldCallback
wrap_WidgetClassStateFlagsChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassStateFlagsChangedFieldCallback)) -> WidgetClassStateFlagsChangedFieldCallback -> C_WidgetClassStateFlagsChangedFieldCallback Source #
WidgetClassSystemSettingChangedFieldCallback
type C_WidgetClassSystemSettingChangedFieldCallback = Ptr Widget -> CUInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassSystemSettingChangedFieldCallback = Widget -> SystemSetting -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassSystemSettingChangedFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassSystemSettingChangedFieldCallback -> a -> SystemSetting -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassSystemSettingChangedFieldCallback :: MonadIO m => WidgetClassSystemSettingChangedFieldCallback -> m (GClosure C_WidgetClassSystemSettingChangedFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassSystemSettingChangedFieldCallback :: C_WidgetClassSystemSettingChangedFieldCallback -> IO (FunPtr C_WidgetClassSystemSettingChangedFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassSystemSettingChangedFieldCallback
.
noWidgetClassSystemSettingChangedFieldCallback :: Maybe WidgetClassSystemSettingChangedFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassSystemSettingChangedFieldCallback
wrap_WidgetClassSystemSettingChangedFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassSystemSettingChangedFieldCallback)) -> WidgetClassSystemSettingChangedFieldCallback -> C_WidgetClassSystemSettingChangedFieldCallback Source #
WidgetClassUnmapFieldCallback
type C_WidgetClassUnmapFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassUnmapFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassUnmapFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassUnmapFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassUnmapFieldCallback :: MonadIO m => WidgetClassUnmapFieldCallback -> m (GClosure C_WidgetClassUnmapFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassUnmapFieldCallback :: C_WidgetClassUnmapFieldCallback -> IO (FunPtr C_WidgetClassUnmapFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassUnmapFieldCallback
.
noWidgetClassUnmapFieldCallback :: Maybe WidgetClassUnmapFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassUnmapFieldCallback
wrap_WidgetClassUnmapFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassUnmapFieldCallback)) -> WidgetClassUnmapFieldCallback -> C_WidgetClassUnmapFieldCallback Source #
Wrap a WidgetClassUnmapFieldCallback
into a C_WidgetClassUnmapFieldCallback
.
WidgetClassUnrealizeFieldCallback
type C_WidgetClassUnrealizeFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassUnrealizeFieldCallback Source #
No description available in the introspection data.
dynamic_WidgetClassUnrealizeFieldCallback Source #
:: (HasCallStack, MonadIO m, IsWidget a) | |
=> FunPtr C_WidgetClassUnrealizeFieldCallback | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassUnrealizeFieldCallback :: MonadIO m => WidgetClassUnrealizeFieldCallback -> m (GClosure C_WidgetClassUnrealizeFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassUnrealizeFieldCallback :: C_WidgetClassUnrealizeFieldCallback -> IO (FunPtr C_WidgetClassUnrealizeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassUnrealizeFieldCallback
.
noWidgetClassUnrealizeFieldCallback :: Maybe WidgetClassUnrealizeFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassUnrealizeFieldCallback
wrap_WidgetClassUnrealizeFieldCallback :: Maybe (Ptr (FunPtr C_WidgetClassUnrealizeFieldCallback)) -> WidgetClassUnrealizeFieldCallback -> C_WidgetClassUnrealizeFieldCallback Source #
WidgetClassUnrootFieldCallback
type C_WidgetClassUnrootFieldCallback = Ptr Widget -> IO () Source #
Type for the callback on the (unwrapped) C side.
type WidgetClassUnrootFieldCallback = Widget -> IO () Source #
No description available in the introspection data.
dynamic_WidgetClassUnrootFieldCallback :: (HasCallStack, MonadIO m, IsWidget a) => FunPtr C_WidgetClassUnrootFieldCallback -> a -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_WidgetClassUnrootFieldCallback :: MonadIO m => WidgetClassUnrootFieldCallback -> m (GClosure C_WidgetClassUnrootFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_WidgetClassUnrootFieldCallback :: C_WidgetClassUnrootFieldCallback -> IO (FunPtr C_WidgetClassUnrootFieldCallback) Source #
Generate a function pointer callable from C code, from a C_WidgetClassUnrootFieldCallback
.
noWidgetClassUnrootFieldCallback :: Maybe WidgetClassUnrootFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
WidgetClassUnrootFieldCallback