module Qtc.Enums.Gui.QStyleOptionSpinBox (
QStyleOptionSpinBoxStyleOptionType
, QStyleOptionSpinBoxStyleOptionVersion
)
where
import Foreign.C.Types
import Qtc.Classes.Base
import Qtc.ClassTypes.Core (QObject, TQObject, qObjectFromPtr)
import Qtc.Core.Base (Qcs, connectSlot, qtc_connectSlot_int, wrapSlotHandler_int)
import Qtc.Enums.Base
import Qtc.Enums.Classes.Core
data CQStyleOptionSpinBoxStyleOptionType a = CQStyleOptionSpinBoxStyleOptionType a
type QStyleOptionSpinBoxStyleOptionType = QEnum(CQStyleOptionSpinBoxStyleOptionType Int)
ieQStyleOptionSpinBoxStyleOptionType :: Int -> QStyleOptionSpinBoxStyleOptionType
ieQStyleOptionSpinBoxStyleOptionType x = QEnum (CQStyleOptionSpinBoxStyleOptionType x)
instance QEnumC (CQStyleOptionSpinBoxStyleOptionType Int) where
qEnum_toInt (QEnum (CQStyleOptionSpinBoxStyleOptionType x)) = x
qEnum_fromInt x = QEnum (CQStyleOptionSpinBoxStyleOptionType x)
withQEnumResult x
= do
ti <- x
return $ qEnum_fromInt $ fromIntegral ti
withQEnumListResult x
= do
til <- x
return $ map qEnum_fromInt til
instance Qcs (QObject c -> QStyleOptionSpinBoxStyleOptionType -> IO ()) where
connectSlot _qsig_obj _qsig_nam _qslt_obj _qslt_nam _handler
= do
funptr <- wrapSlotHandler_int slotHandlerWrapper_int
stptr <- newStablePtr (Wrap _handler)
withObjectPtr _qsig_obj $ \cobj_sig ->
withCWString _qsig_nam $ \cstr_sig ->
withObjectPtr _qslt_obj $ \cobj_slt ->
withCWString _qslt_nam $ \cstr_slt ->
qtc_connectSlot_int cobj_sig cstr_sig cobj_slt cstr_slt (toCFunPtr funptr) (castStablePtrToPtr stptr)
return ()
where
slotHandlerWrapper_int :: Ptr fun -> Ptr () -> Ptr (TQObject c) -> CInt -> IO ()
slotHandlerWrapper_int funptr stptr qobjptr cint
= do qobj <- qObjectFromPtr qobjptr
let hint = fromCInt cint
if (objectIsNull qobj)
then do when (stptr/=ptrNull)
(freeStablePtr (castPtrToStablePtr stptr))
when (funptr/=ptrNull)
(freeHaskellFunPtr (castPtrToFunPtr funptr))
else _handler qobj (qEnum_fromInt hint)
return ()
instance QeType QStyleOptionSpinBoxStyleOptionType where
eType
= ieQStyleOptionSpinBoxStyleOptionType $ 983042
data CQStyleOptionSpinBoxStyleOptionVersion a = CQStyleOptionSpinBoxStyleOptionVersion a
type QStyleOptionSpinBoxStyleOptionVersion = QEnum(CQStyleOptionSpinBoxStyleOptionVersion Int)
ieQStyleOptionSpinBoxStyleOptionVersion :: Int -> QStyleOptionSpinBoxStyleOptionVersion
ieQStyleOptionSpinBoxStyleOptionVersion x = QEnum (CQStyleOptionSpinBoxStyleOptionVersion x)
instance QEnumC (CQStyleOptionSpinBoxStyleOptionVersion Int) where
qEnum_toInt (QEnum (CQStyleOptionSpinBoxStyleOptionVersion x)) = x
qEnum_fromInt x = QEnum (CQStyleOptionSpinBoxStyleOptionVersion x)
withQEnumResult x
= do
ti <- x
return $ qEnum_fromInt $ fromIntegral ti
withQEnumListResult x
= do
til <- x
return $ map qEnum_fromInt til
instance Qcs (QObject c -> QStyleOptionSpinBoxStyleOptionVersion -> IO ()) where
connectSlot _qsig_obj _qsig_nam _qslt_obj _qslt_nam _handler
= do
funptr <- wrapSlotHandler_int slotHandlerWrapper_int
stptr <- newStablePtr (Wrap _handler)
withObjectPtr _qsig_obj $ \cobj_sig ->
withCWString _qsig_nam $ \cstr_sig ->
withObjectPtr _qslt_obj $ \cobj_slt ->
withCWString _qslt_nam $ \cstr_slt ->
qtc_connectSlot_int cobj_sig cstr_sig cobj_slt cstr_slt (toCFunPtr funptr) (castStablePtrToPtr stptr)
return ()
where
slotHandlerWrapper_int :: Ptr fun -> Ptr () -> Ptr (TQObject c) -> CInt -> IO ()
slotHandlerWrapper_int funptr stptr qobjptr cint
= do qobj <- qObjectFromPtr qobjptr
let hint = fromCInt cint
if (objectIsNull qobj)
then do when (stptr/=ptrNull)
(freeStablePtr (castPtrToStablePtr stptr))
when (funptr/=ptrNull)
(freeHaskellFunPtr (castPtrToFunPtr funptr))
else _handler qobj (qEnum_fromInt hint)
return ()
instance QeVersion QStyleOptionSpinBoxStyleOptionVersion where
eVersion
= ieQStyleOptionSpinBoxStyleOptionVersion $ 1