Safe Haskell | None |
---|---|
Language | Haskell98 |
Qtc.Core.Attributes
Description
Documentation
signalString :: Qsignal x f -> String Source
slotString :: Qslot x f -> String Source
signalStringf :: Qsignalf f -> String Source
signalObjectf :: Qsignalf f -> QObject () Source
Constructors
forall a . (Attr w a) := a infixr 0 | |
forall a . (Attr w a) :~ (a -> a) infixr 0 | |
forall a . (Attr w a) ::= (w -> a) infixr 0 | |
forall a . (Attr w a) ::~ (w -> a -> a) infixr 0 | |
forall a . (WriteAttr w a) :- a infixr 0 | |
forall a . (WriteAttr w a) ::- (w -> a) infixr 0 | |
forall a . (Attr w a) :< (IO a) infixr 0 | |
forall a . (WriteAttr w a) :<- (IO a) infixr 0 | |
(SigConf w w) :=< (Qsignalf w) infixr 0 | |
forall a . (SigConf w a) :-< (Qsignalf a) infixr 0 | |
forall a . (SltCon w a ()) :~> String | |
forall a . (SltConf w a) :=> (Qslot w a, a) infixr 0 | |
forall a . (SltConf w a) :-> (Qslot w a, a) infixr 0 |
Instances
Qst a => QsaSignalRowsRemoved_nt_f SigConf a (QStandardItemModel b) (IO ()) | |
Qst a => QsaSignalItemChanged_nt_f SigConf a (QStandardItemModel b) (IO ()) |
Instances
Qst a => QsaSignalItemChanged_nt_f SltConf a (QStandardItemModel b) (a -> QStandardItem () -> IO ()) |
class QsigClicked p | -> p where Source
Instances
QsigClicked (QModelIndex () -> IO ()) |
st_sltConf_nt_p :: (Qst a, Qst d, Qcsn (b -> IO c)) => a -> Qsig (b -> IO c) -> SltConf d (d -> b -> IO c) Source
on_sltConf_nt_p :: Qcsn (b -> IO c) => Qsig (b -> IO c) -> SltConf (QObject d) (QObject d -> b -> IO c) Source
sltConf_nt_p :: Qcsn (b -> IO c) => QObject a -> Qsig (b -> IO c) -> SltConf (QObject d) (QObject d -> b -> IO c) Source
sortFilterProxyModel' :: QqSortFilterProxyModel x1 => x1 -> [Prop (QSortFilterProxyModel ())] -> IO (QSortFilterProxyModel ()) Source
vBoxLayout' :: QqVBoxLayout x1 => x1 -> [Prop (QVBoxLayout ())] -> IO (QVBoxLayout ()) Source
hBoxLayout' :: [Prop (QHBoxLayout ())] -> IO (QHBoxLayout ()) Source
standardItem_nf' :: QqStandardItem_nf x1 => x1 -> [Prop (QStandardItem ())] -> IO (QStandardItem ()) Source
class QsaSignalValueChanged_nt_f w x f where Source
Methods
signalValueChanged', valueChanged' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalValueChanged_nt_f a (QAbstractSlider b) (a -> Int -> IO ()) |
class QsaSignalTriggered_nt_f w x f where Source
Methods
signalTriggered', triggered' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalTriggered_nt_f a (QMenu b) (a -> QAction () -> IO ()) | |
Qst a => QsaSignalTriggered_nt_f a (QAction b) (a -> IO ()) |
class QsaSignalToggled_nt_f w x f where Source
Methods
signalToggled', toggled' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalToggled_nt_f a (QAction b) (a -> Bool -> IO ()) |
class QsaSignalExpanded_nt_f w x f where Source
Methods
signalExpanded', expanded' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalExpanded_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) |
class QsaSignalCollapsed_nt_f w x f where Source
Methods
signalCollapsed', collapsed' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalCollapsed_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) |
class QsaSignalActivated_nt_f w x f where Source
Methods
signalActivated', activated' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalActivated_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) |
class QsaSignalDoubleClicked_nt_f w x f where Source
Methods
signalDoubleClicked', doubleClicked' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalDoubleClicked_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) |
class QsaSignalCurrentChanged_nt_f w x f where Source
Methods
signalCurrentChanged', currentChanged' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalCurrentChanged_nt_f a (QItemSelectionModel b) (a -> QModelIndex () -> IO ()) |
class QsaSignalCustomContextMenuRequested_nt_f w x f where Source
Methods
signalCustomContextMenuRequested', customContextMenuRequested' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalCustomContextMenuRequested_nt_f a (QWidget b) (a -> QPoint () -> IO ()) |
class QsaSignalCurrentIndexChanged_nt_f w x f where Source
Methods
signalCurrentIndexChanged', currentIndexChanged' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalCurrentIndexChanged_nt_f a (QComboBox b) (a -> String -> IO ()) |
class QsaSignalItemChanged_nt_f r w x f where Source
Methods
signalItemChanged', itemChanged' :: x -> r w f Source
Instances
Qst a => QsaSignalItemChanged_nt_f SigConf a (QStandardItemModel b) (IO ()) | |
Qst a => QsaSignalItemChanged_nt_f SltConf a (QStandardItemModel b) (a -> QStandardItem () -> IO ()) |
class QsaSignalRowsRemoved_nt_f r w x f where Source
Methods
signalRowsRemoved', rowsRemoved' :: x -> r w f Source
Instances
Qst a => QsaSignalRowsRemoved_nt_f SigConf a (QStandardItemModel b) (IO ()) |
class QsaSignalTextChanged_nt_f w x f where Source
Methods
signalTextChanged', textChanged' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalTextChanged_nt_f a (QLineEdit b) (a -> IO ()) | |
Qst a => QsaSignalTextChanged_nt_f a (QLineEdit b) (a -> String -> IO ()) |
class QsaSignalClicked_nt_f w x f where Source
Methods
signalClicked', clicked' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalClicked_nt_f a (QTreeView ()) (a -> QModelIndex () -> IO ()) | |
Qst a => QsaSignalClicked_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) | |
Qst a => QsaSignalClicked_nt_f a (QAbstractButton b) (a -> IO ()) |
class QsaSlotReject w where Source
Methods
slotReject', reject' :: (Qslot w (w -> ()), w -> ()) Source
Instances
Qstt a (QDialogSc b) => QsaSlotReject a |
class QsaSignalRejected_nt_f w x f where Source
Methods
signalRejected', rejected' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalRejected_nt_f a (QDialogButtonBox b) (a -> ()) |
class QsaSignalAccepted_nt_f w x f where Source
Methods
signalAccepted', accepted' :: x -> SltConf w f Source
Instances
Qst a => QsaSignalAccepted_nt_f a (QDialogButtonBox b) (a -> IO ()) |
class QsaOnSignalClicked_nt_f w where Source
Methods
onSignalClicked', onClicked' :: SigConf w (IO ()) Source
Instances
class QsaOnSignalRejected_nt_f w where Source
Methods
onSignalRejected' :: SigConf w (IO ()) Source
Instances
(Qst a, Qstt a (QDialogSc b)) => QsaOnSignalRejected_nt_f a |
class QsaConnectSlot_nt_f w x f where Source
Instances
Qst a => QsaConnectSlot_nt_f a (QAbstractButton b) (a -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QWidget b) (a -> QPoint () -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QTreeViewSc b) (a -> QModelIndex () -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QDialogButtonBox b) (a -> ()) | |
Qst a => QsaConnectSlot_nt_f a (QDialogButtonBox b) (a -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QLineEdit b) (a -> String -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QStandardItemModel b) (a -> QStandardItem () -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QComboBox b) (a -> String -> IO ()) | |
Qst a => QsaConnectSlot_nt_f a (QItemSelectionModel b) (a -> QModelIndex () -> IO ()) |
class QsaConnectSignal w x where Source
Instances
QsaConnectSignal (QObject a) (QObject b) |
class QsaConnectSlot w x f where Source
Instances
QsaConnectSlot (QObject a) (QObject b) () | |
QsaConnectSlot (QObject a) (QObject b) (QObject a -> Object c -> IO ()) | |
QsaConnectSlot (QObject a) (QObject b) (QObject a -> String -> IO ()) | |
QsaConnectSlot (QObject a) (QObject b) (QObject a -> IO ()) |
class QsaConnectSlot_nt w x f where Source
Instances
QsaConnectSlot_nt (QObject a) (QObject b) () | |
QsaConnectSlot_nt (QObject a) (QObject b) (IO ()) | |
QsaConnectSlot_nt (QObject a) (QObject b) (Object c -> IO ()) | |
QsaConnectSlot_nt (QObject a) (QObject b) (String -> IO ()) | |
QsaConnectSlot_nt (QObject a) (QObject b) (() -> IO ()) |
Instances
QaIcon (QStandardItem a) | |
QaIcon (QAbstractButton a) |
class QaSourceModel w where Source
Methods
sourceModel' :: Attr w (QAbstractItemModel a) Source
Instances
Methods
model' :: Attr w (QAbstractItemModel a) Source
Instances
QaModel (QTreeViewSc a) | |
QaModel (QTreeView ()) | |
QaModel (QAbstractItemView ()) |
class QaAcceptDrops w where Source
Methods
acceptDrops' :: Attr w Bool Source
Instances
QaAcceptDrops (QWidget a) |
class QaEditable w where Source
Instances
class QwaOnEventFilter w x where Source
Methods
onEventFilter' :: WriteAttr w x Source
class QwaOnFocusInEvent w x where Source
Methods
onFocusInEvent' :: WriteAttr w x Source
Instances
Qstt w (QWidgetSc a) => QwaOnFocusInEvent w (w -> QWidget b -> QFocusEvent t -> IO ()) |
class QaValue w x where Source
Instances
QaValue (QProgressDialog a) Int | |
QaValue (QSettings ()) (String, IO (QByteArray ())) |
class QwaAddWidget w where Source
Methods
addWidget' :: WriteAttr w (QWidget a) Source
Instances
QwaAddWidget (QVBoxLayout ()) |
class QwaAddItem w where Source
Methods
addItem' :: WriteAttr w (QLayoutItem a) Source
Instances
QwaAddItem (QHBoxLayout ()) |
class QwaAddItems w x where Source
Instances
QwaAddItems (QComboBox a) [String] |
getSettingsValue :: QSettings () -> String -> IO (Maybe (QByteArray ())) Source
displayRole :: Int -> Int Source
class QdataRole x where Source
Instances
QdataRole (QModelIndex ()) | |
QdataRole (QStandardItem ()) |
class QdataUserRole x where Source
Methods
dataUserS :: x -> IO String Source
dataUserRoleS :: x -> Int -> IO String Source
dataUserB :: x -> IO Bool Source
dataUserRoleB :: x -> Int -> IO Bool Source
dataUserI :: x -> IO Int Source
dataUserRoleI :: x -> Int -> IO Int Source
Instances
QdataUserRole (QModelIndex ()) | |
QdataUserRole (QStandardItem ()) |
class QdataDisplayRole x where Source
Methods
dataDisplayS :: x -> IO String Source
dataDisplayRoleS :: x -> Int -> IO String Source
dataDisplayB :: x -> IO Bool Source
dataDisplayRoleB :: x -> Int -> IO Bool Source
Instances
class QsetDataUserRole a b where Source
Methods
setDataUserRole :: a -> b -> Int -> IO () Source
Instances