module Graphics.UI.Qtah.Generator.Interface.Internal.Callback where
import Foreign.Hoppy.Generator.Spec (
Callback,
Export (Export),
addReqIncludes,
includeStd,
makeCallback,
makeModule,
moduleAddExports,
moduleAddHaskellName,
moduleModify',
np,
toExtName,
)
import Foreign.Hoppy.Generator.Types (
boolT,
constT,
doubleT,
enumT,
intT,
objT,
ptrT,
refT,
toGcT,
voidT,
)
import Foreign.Hoppy.Generator.Version (collect, just, test)
import Graphics.UI.Qtah.Generator.Config (qtVersion)
import Graphics.UI.Qtah.Generator.Flags (flagsT)
import Graphics.UI.Qtah.Generator.Interface.Core.QAbstractItemModel (c_QAbstractItemModel)
import Graphics.UI.Qtah.Generator.Interface.Core.QDate (c_QDate)
import Graphics.UI.Qtah.Generator.Interface.Core.QEvent (c_QEvent)
import Graphics.UI.Qtah.Generator.Interface.Core.QItemSelection (c_QItemSelection)
import Graphics.UI.Qtah.Generator.Interface.Core.QModelIndex (c_QModelIndex)
import Graphics.UI.Qtah.Generator.Interface.Core.QList (c_QListQModelIndex)
import Graphics.UI.Qtah.Generator.Interface.Core.QObject (c_QObject)
import Graphics.UI.Qtah.Generator.Interface.Core.QPoint (c_QPoint)
import Graphics.UI.Qtah.Generator.Interface.Core.QSize (c_QSize)
import Graphics.UI.Qtah.Generator.Interface.Core.QVariant (c_QVariant)
import Graphics.UI.Qtah.Generator.Interface.Core.QAbstractAnimation (c_QAbstractAnimation)
import Graphics.UI.Qtah.Generator.Interface.Core.QString (c_QString)
import Graphics.UI.Qtah.Generator.Interface.Core.QAbstractAnimation (e_Direction, e_State)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Core.QProcess (e_ProcessError, e_ExitStatus, e_ProcessState)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Core.QVector (c_QVectorInt)
import Graphics.UI.Qtah.Generator.Interface.Core.Types (
e_DockWidgetArea,
fl_DockWidgetAreas,
e_Orientation,
e_ScreenOrientation,
e_ScreenOrientation_minVersion,
fl_ToolBarAreas,
e_ToolButtonStyle,
e_WindowModality,
e_WindowState,
fl_WindowStates,
qreal,
qlonglong,
)
import {-# SOURCE #-} qualified Graphics.UI.Qtah.Generator.Interface.Gui.QClipboard as QClipboard
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Gui.QIcon (c_QIcon)
import Graphics.UI.Qtah.Generator.Interface.Gui.QPaintEvent (c_QPaintEvent)
import {-# SOURCE #-} qualified Graphics.UI.Qtah.Generator.Interface.Gui.QWindow as QWindow
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QAbstractButton
(c_QAbstractButton)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QAbstractSlider (e_SliderAction)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QAction (c_QAction)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QDockWidget (
fl_DockWidgetFeatures,
)
import Graphics.UI.Qtah.Generator.Interface.Widgets.QGraphicsItem (c_QGraphicsItem)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QMdiSubWindow (c_QMdiSubWindow)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QSystemTrayIcon (
e_ActivationReason,
)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QTreeWidgetItem (c_QTreeWidgetItem)
import {-# SOURCE #-} Graphics.UI.Qtah.Generator.Interface.Widgets.QWidget (c_QWidget)
import Graphics.UI.Qtah.Generator.Module (AModule (AHoppyModule))
{-# ANN module "HLint: ignore Use camelCase" #-}
aModule :: AModule
aModule =
Module -> AModule
AHoppyModule (Module -> AModule) -> Module -> AModule
forall a b. (a -> b) -> a -> b
$
HasCallStack =>
Module -> StateT Module (Either String) () -> Module
Module -> StateT Module (Either String) () -> Module
moduleModify' (String -> String -> String -> Module
makeModule String
"callback" String
"b_callback.hpp" String
"b_callback.cpp") (StateT Module (Either String) () -> Module)
-> StateT Module (Either String) () -> Module
forall a b. (a -> b) -> a -> b
$ do
[String] -> StateT Module (Either String) ()
forall (m :: * -> *).
(MonadError String m, MonadState Module m) =>
[String] -> m ()
moduleAddHaskellName [String
"Internal", String
"Callback"]
[Export] -> StateT Module (Either String) ()
forall (m :: * -> *).
(MonadError String m, MonadState Module m) =>
[Export] -> m ()
moduleAddExports ([Export] -> StateT Module (Either String) ())
-> [Export] -> StateT Module (Either String) ()
forall a b. (a -> b) -> a -> b
$ [Filtered Export] -> [Export]
forall a. [Filtered a] -> [a]
collect
[ Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_BoolVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_DockWidgetAreaVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_DockWidgetAreasVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_DoubleVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_IntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_IntBoolVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_IntIntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_OrientationVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_OrientationIntIntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQAbstractButtonVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQAbstractButtonBoolVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQAbstractItemModelVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQActionVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQGraphicsItemPtrQEventBool
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQMdiSubWindowVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQObjectPtrQEventBool
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQObjectVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQPaintEventVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_RefConstQModelIndexVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_RefConstQListQModelIndexVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQTreeWidgetItemVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQTreeWidgetItemIntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQTreeWidgetItemPtrQTreeWidgetItemVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_PtrQWidgetPtrQWidgetVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QAbstractSliderActionVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QClipboardModeVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QDateVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QDockWidgetFeaturesVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QModelIndexVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QModelIndexIntIntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QModelIndexIntIntQModelIndexIntVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QModelIndexQModelIndexVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QModelIndexQModelIndexQVectorIntVoid
, Bool -> Export -> Filtered Export
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= Version
QWindow.minVersion) (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QWindowVisibilityVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QPointVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QrealVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QSizeVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QStringVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QSystemTrayIconActivationReasonVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_RefConstQIconVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_RefConstQItemSelectionRefConstQItemSelectionVoid
, Bool -> Export -> Filtered Export
forall a. Bool -> a -> Filtered a
test (Version
qtVersion Version -> Version -> Bool
forall a. Ord a => a -> a -> Bool
>= Version
e_ScreenOrientation_minVersion) (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_ScreenOrientationVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_ToolBarAreasVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_ToolButtonStyleVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_WindowModalityVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_WindowStateVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_WindowStatesWindowStatesVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QlonglongVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_IntQlonglongVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_ProcessErrorVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_IntExitStatusVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_ProcessStateVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_StateStateVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_DirectionVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_RefConstQVariantVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_QAbstractAnimationVoid
, Export -> Filtered Export
forall a. a -> Filtered a
just (Export -> Filtered Export) -> Export -> Filtered Export
forall a b. (a -> b) -> a -> b
$ Callback -> Export
forall a. Exportable a => a -> Export
Export Callback
cb_Void
]
cb_BoolVoid :: Callback
cb_BoolVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackBoolVoid")
[Type
boolT] Type
voidT
cb_DockWidgetAreaVoid :: Callback
cb_DockWidgetAreaVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackDockWidgetAreaVoid")
[CppEnum -> Type
enumT CppEnum
e_DockWidgetArea] Type
voidT
cb_DockWidgetAreasVoid :: Callback
cb_DockWidgetAreasVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackDockWidgetAreasVoid")
[Flags -> Type
flagsT Flags
fl_DockWidgetAreas] Type
voidT
cb_DoubleVoid :: Callback
cb_DoubleVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackDoubleVoid")
[Type
doubleT] Type
voidT
cb_IntVoid :: Callback
cb_IntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackIntVoid")
[Type
intT] Type
voidT
cb_IntBoolVoid :: Callback
cb_IntBoolVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackIntBoolVoid")
[Type
intT, Type
boolT] Type
voidT
cb_IntIntVoid :: Callback
cb_IntIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackIntIntVoid")
[Type
intT, Type
intT] Type
voidT
cb_OrientationVoid :: Callback
cb_OrientationVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackOrientationVoid")
[CppEnum -> Type
enumT CppEnum
e_Orientation] Type
voidT
cb_OrientationIntIntVoid :: Callback
cb_OrientationIntIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackOrientationIntIntVoid")
[CppEnum -> Type
enumT CppEnum
e_Orientation, Type
intT, Type
intT] Type
voidT
cb_PtrQAbstractButtonVoid :: Callback
cb_PtrQAbstractButtonVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQAbstractButtonVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QAbstractButton] Type
voidT
cb_PtrQAbstractButtonBoolVoid :: Callback
cb_PtrQAbstractButtonBoolVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQAbstractButtonBoolVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QAbstractButton, Type
boolT] Type
voidT
cb_PtrQAbstractItemModelVoid :: Callback
cb_PtrQAbstractItemModelVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQAbstractItemModelVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QAbstractItemModel] Type
voidT
cb_PtrQActionVoid :: Callback
cb_PtrQActionVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQActionVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QAction] Type
voidT
cb_PtrQGraphicsItemPtrQEventBool :: Callback
cb_PtrQGraphicsItemPtrQEventBool =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQGraphicsItemPtrQEventBool")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QGraphicsItem, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QEvent] Type
boolT
cb_PtrQMdiSubWindowVoid :: Callback
cb_PtrQMdiSubWindowVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQMdiSubWindowVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QMdiSubWindow] Type
voidT
cb_PtrQObjectPtrQEventBool :: Callback
cb_PtrQObjectPtrQEventBool =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQObjectPtrQEventBool")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QObject, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QEvent] Type
boolT
cb_PtrQObjectVoid :: Callback
cb_PtrQObjectVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQObjectVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QObject] Type
voidT
cb_PtrQPaintEventVoid :: Callback
cb_PtrQPaintEventVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQPaintEventVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QPaintEvent] Type
voidT
cb_RefConstQModelIndexVoid :: Callback
cb_RefConstQModelIndexVoid :: Callback
cb_RefConstQModelIndexVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackRefConstQModelIndexVoid")
[Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QModelIndex] Type
voidT
cb_RefConstQListQModelIndexVoid :: Callback
cb_RefConstQListQModelIndexVoid :: Callback
cb_RefConstQListQModelIndexVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackRefConstQListQModelIndexVoid")
[Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QListQModelIndex] Type
voidT
cb_PtrQTreeWidgetItemVoid :: Callback
cb_PtrQTreeWidgetItemVoid :: Callback
cb_PtrQTreeWidgetItemVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQTreeWidgetItemVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTreeWidgetItem] Type
voidT
cb_PtrQTreeWidgetItemIntVoid :: Callback
cb_PtrQTreeWidgetItemIntVoid :: Callback
cb_PtrQTreeWidgetItemIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQTreeWidgetItemIntVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTreeWidgetItem, Type
intT] Type
voidT
cb_PtrQTreeWidgetItemPtrQTreeWidgetItemVoid :: Callback
cb_PtrQTreeWidgetItemPtrQTreeWidgetItemVoid :: Callback
cb_PtrQTreeWidgetItemPtrQTreeWidgetItemVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQTreeWidgetItemPtrQTreeWidgetItemVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTreeWidgetItem, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QTreeWidgetItem] Type
voidT
cb_PtrQWidgetPtrQWidgetVoid :: Callback
cb_PtrQWidgetPtrQWidgetVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackPtrQWidgetPtrQWidgetVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QWidget, Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QWidget] Type
voidT
cb_QAbstractSliderActionVoid :: Callback
cb_QAbstractSliderActionVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQAbstractSliderActionVoid")
[CppEnum -> Type
enumT CppEnum
e_SliderAction] Type
voidT
cb_QClipboardModeVoid :: Callback
cb_QClipboardModeVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQClipboardModeVoid")
[CppEnum -> Type
enumT CppEnum
QClipboard.e_Mode] Type
voidT
cb_QDateVoid :: Callback
cb_QDateVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQDateVoid")
[Class -> Type
objT Class
c_QDate] Type
voidT
cb_QDockWidgetFeaturesVoid :: Callback
cb_QDockWidgetFeaturesVoid =
[Include] -> Callback -> Callback
forall a. HasReqs a => [Include] -> a -> a
addReqIncludes [String -> Include
includeStd String
"QDockWidget"] (Callback -> Callback) -> Callback -> Callback
forall a b. (a -> b) -> a -> b
$
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQDockWidgetFeaturesVoid")
[Flags -> Type
flagsT Flags
fl_DockWidgetFeatures] Type
voidT
cb_QModelIndexVoid :: Callback
cb_QModelIndexVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQModelIndexVoid")
[Class -> Type
objT Class
c_QModelIndex] Type
voidT
cb_QModelIndexIntIntVoid :: Callback
cb_QModelIndexIntIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQModelIndexIntIntVoid")
[Class -> Type
objT Class
c_QModelIndex, Type
intT, Type
intT] Type
voidT
cb_QModelIndexIntIntQModelIndexIntVoid :: Callback
cb_QModelIndexIntIntQModelIndexIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQModelIndexIntIntQModelIndexIntVoid")
[Class -> Type
objT Class
c_QModelIndex, Type
intT, Type
intT, Class -> Type
objT Class
c_QModelIndex, Type
intT] Type
voidT
cb_QModelIndexQModelIndexVoid :: Callback
cb_QModelIndexQModelIndexVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQModelIndexQModelIndexVoid")
[Class -> Type
objT Class
c_QModelIndex, Class -> Type
objT Class
c_QModelIndex] Type
voidT
cb_QModelIndexQModelIndexQVectorIntVoid :: Callback
cb_QModelIndexQModelIndexQVectorIntVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQModelIndexQModelIndexQVectorIntVoid")
[Class -> Type
objT Class
c_QModelIndex, Class -> Type
objT Class
c_QModelIndex, Type -> Type
toGcT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QVectorInt] Type
voidT
cb_QWindowVisibilityVoid :: Callback
cb_QWindowVisibilityVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQWindowVisibilityVoid")
[CppEnum -> Type
enumT CppEnum
QWindow.e_Visibility] Type
voidT
cb_QPointVoid :: Callback
cb_QPointVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQPointVoid")
[Class -> Type
objT Class
c_QPoint] Type
voidT
cb_QrealVoid :: Callback
cb_QrealVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQrealVoid")
[Type
qreal] Type
voidT
cb_QSizeVoid :: Callback
cb_QSizeVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQSizeVoid")
[Class -> Type
objT Class
c_QSize] Type
voidT
cb_QStringVoid :: Callback
cb_QStringVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQStringVoid")
[Class -> Type
objT Class
c_QString] Type
voidT
cb_QSystemTrayIconActivationReasonVoid :: Callback
cb_QSystemTrayIconActivationReasonVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQSystemTrayIconActivationReasonVoid")
[CppEnum -> Type
enumT CppEnum
e_ActivationReason] Type
voidT
cb_RefConstQIconVoid :: Callback
cb_RefConstQIconVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackRefConstQIconVoid")
[Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QIcon] Type
voidT
cb_RefConstQItemSelectionRefConstQItemSelectionVoid :: Callback
cb_RefConstQItemSelectionRefConstQItemSelectionVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackRefConstQItemSelectionRefConstQItemSelectionVoid")
[Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QItemSelection, Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QItemSelection] Type
voidT
cb_ScreenOrientationVoid :: Callback
cb_ScreenOrientationVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackScreenOrientationVoid")
[CppEnum -> Type
enumT CppEnum
e_ScreenOrientation] Type
voidT
cb_ToolBarAreasVoid :: Callback
cb_ToolBarAreasVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackToolBarAreasVoid")
[Flags -> Type
flagsT Flags
fl_ToolBarAreas] Type
voidT
cb_ToolButtonStyleVoid :: Callback
cb_ToolButtonStyleVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackToolButtonStyleVoid")
[CppEnum -> Type
enumT CppEnum
e_ToolButtonStyle] Type
voidT
cb_WindowModalityVoid :: Callback
cb_WindowModalityVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackWindowModalityVoid")
[CppEnum -> Type
enumT CppEnum
e_WindowModality] Type
voidT
cb_WindowStateVoid :: Callback
cb_WindowStateVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackWindowStateVoid")
[CppEnum -> Type
enumT CppEnum
e_WindowState] Type
voidT
cb_WindowStatesWindowStatesVoid :: Callback
cb_WindowStatesWindowStatesVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackWindowStatesWindowStatesVoid")
[Flags -> Type
flagsT Flags
fl_WindowStates, Flags -> Type
flagsT Flags
fl_WindowStates] Type
voidT
cb_QlonglongVoid :: Callback
cb_QlonglongVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQlonglongVoid")
[Type
qlonglong] Type
voidT
cb_IntQlonglongVoid :: Callback
cb_IntQlonglongVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackIntQlonglongVoid")
[Type
intT, Type
qlonglong] Type
voidT
cb_ProcessErrorVoid :: Callback
cb_ProcessErrorVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackProcessErrorVoid")
[CppEnum -> Type
enumT CppEnum
e_ProcessError] Type
voidT
cb_IntExitStatusVoid :: Callback
cb_IntExitStatusVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackIntExitStatusVoid")
[Type
intT, CppEnum -> Type
enumT CppEnum
e_ExitStatus] Type
voidT
cb_ProcessStateVoid :: Callback
cb_ProcessStateVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackProcessStateVoid")
[CppEnum -> Type
enumT CppEnum
e_ProcessState] Type
voidT
cb_DirectionVoid :: Callback
cb_DirectionVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackDirectionVoid")
[CppEnum -> Type
enumT CppEnum
e_Direction] Type
voidT
cb_StateStateVoid :: Callback
cb_StateStateVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackStateStateVoid")
[CppEnum -> Type
enumT CppEnum
e_State, CppEnum -> Type
enumT CppEnum
e_State] Type
voidT
cb_RefConstQVariantVoid :: Callback
cb_RefConstQVariantVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackRefConstQVariantVoid")
[Type -> Type
refT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Type -> Type
constT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QVariant] Type
voidT
cb_QAbstractAnimationVoid :: Callback
cb_QAbstractAnimationVoid =
ExtName -> [Type] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackQAbstractAnimationVoid")
[Type -> Type
ptrT (Type -> Type) -> Type -> Type
forall a b. (a -> b) -> a -> b
$ Class -> Type
objT Class
c_QAbstractAnimation] Type
voidT
cb_Void :: Callback
cb_Void =
ExtName -> [Parameter] -> Type -> Callback
forall p. IsParameter p => ExtName -> [p] -> Type -> Callback
makeCallback (HasCallStack => String -> ExtName
String -> ExtName
toExtName String
"CallbackVoid")
[Parameter]
np Type
voidT