{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Gui.QOpenGLWindow ( castQOpenGLWindowToQPaintDeviceWindow, castQPaintDeviceWindowToQOpenGLWindow, castQOpenGLWindowToQWindow, castQWindowToQOpenGLWindow, castQOpenGLWindowToQObject, castQObjectToQOpenGLWindow, castQOpenGLWindowToQSurface, castQSurfaceToQOpenGLWindow, castQOpenGLWindowToQPaintDevice, castQPaintDeviceToQOpenGLWindow, QOpenGLWindowValue (..), QOpenGLWindowConstPtr (..), defaultFramebufferObject, isValid, updateBehavior, QOpenGLWindowPtr (..), doneCurrent, grabFramebuffer, makeCurrent, emitFrameSwapped, QOpenGLWindowConst (..), castQOpenGLWindowToConst, QOpenGLWindow (..), castQOpenGLWindowToNonconst, new, newWithUpdateBehavior, newWithUpdateBehaviorAndParent, QOpenGLWindowSuper (..), QOpenGLWindowSuperConst (..), QOpenGLWindowUpdateBehavior (..), ) where import qualified Data.Word as HoppyDW import qualified Foreign as HoppyF import qualified Foreign.C as HoppyFC import qualified Foreign.Hoppy.Runtime as HoppyFHR import qualified Graphics.UI.Qtah.Generated.Core.QObject as M94 import qualified Graphics.UI.Qtah.Generated.Gui.QImage as M292 import qualified Graphics.UI.Qtah.Generated.Gui.QPaintDevice as M304 import qualified Graphics.UI.Qtah.Generated.Gui.QPaintDeviceWindow as M306 import qualified Graphics.UI.Qtah.Generated.Gui.QSurface as M334 import qualified Graphics.UI.Qtah.Generated.Gui.QWindow as M342 import Prelude (($), (.), (/=), (=<<), (==), (>>=)) import qualified Prelude as HoppyP foreign import ccall "genpop__QOpenGLWindow_new" new' :: HoppyP.IO (HoppyF.Ptr QOpenGLWindow) foreign import ccall "genpop__QOpenGLWindow_newWithUpdateBehavior" newWithUpdateBehavior' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QOpenGLWindow) foreign import ccall "genpop__QOpenGLWindow_newWithUpdateBehaviorAndParent" newWithUpdateBehaviorAndParent' :: HoppyFC.CInt -> HoppyF.Ptr M342.QWindow -> HoppyP.IO (HoppyF.Ptr QOpenGLWindow) foreign import ccall "genpop__QOpenGLWindow_defaultFramebufferObject" defaultFramebufferObject' :: HoppyF.Ptr QOpenGLWindowConst -> HoppyP.IO HoppyDW.Word32 foreign import ccall "genpop__QOpenGLWindow_doneCurrent" doneCurrent' :: HoppyF.Ptr QOpenGLWindow -> HoppyP.IO () foreign import ccall "genpop__QOpenGLWindow_grabFramebuffer" grabFramebuffer' :: HoppyF.Ptr QOpenGLWindow -> HoppyP.IO (HoppyF.Ptr M292.QImageConst) foreign import ccall "genpop__QOpenGLWindow_isValid" isValid' :: HoppyF.Ptr QOpenGLWindowConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QOpenGLWindow_makeCurrent" makeCurrent' :: HoppyF.Ptr QOpenGLWindow -> HoppyP.IO () foreign import ccall "genpop__QOpenGLWindow_updateBehavior" updateBehavior' :: HoppyF.Ptr QOpenGLWindowConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QOpenGLWindow_emitFrameSwapped" emitFrameSwapped' :: HoppyF.Ptr QOpenGLWindow -> HoppyP.IO () foreign import ccall "gencast__QOpenGLWindow__QPaintDeviceWindow" castQOpenGLWindowToQPaintDeviceWindow :: HoppyF.Ptr QOpenGLWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindowConst foreign import ccall "gencast__QPaintDeviceWindow__QOpenGLWindow" castQPaintDeviceWindowToQOpenGLWindow :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr QOpenGLWindowConst foreign import ccall "gencast__QOpenGLWindow__QWindow" castQOpenGLWindowToQWindow :: HoppyF.Ptr QOpenGLWindowConst -> HoppyF.Ptr M342.QWindowConst foreign import ccall "gencast__QWindow__QOpenGLWindow" castQWindowToQOpenGLWindow :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr QOpenGLWindowConst foreign import ccall "gencast__QOpenGLWindow__QObject" castQOpenGLWindowToQObject :: HoppyF.Ptr QOpenGLWindowConst -> HoppyF.Ptr M94.QObjectConst foreign import ccall "gencast__QObject__QOpenGLWindow" castQObjectToQOpenGLWindow :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr QOpenGLWindowConst foreign import ccall "gencast__QOpenGLWindow__QSurface" castQOpenGLWindowToQSurface :: HoppyF.Ptr QOpenGLWindowConst -> HoppyF.Ptr M334.QSurfaceConst foreign import ccall "gencast__QSurface__QOpenGLWindow" castQSurfaceToQOpenGLWindow :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr QOpenGLWindowConst foreign import ccall "gencast__QOpenGLWindow__QPaintDevice" castQOpenGLWindowToQPaintDevice :: HoppyF.Ptr QOpenGLWindowConst -> HoppyF.Ptr M304.QPaintDeviceConst foreign import ccall "gencast__QPaintDevice__QOpenGLWindow" castQPaintDeviceToQOpenGLWindow :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr QOpenGLWindowConst foreign import ccall "gendel__QOpenGLWindow" delete'QOpenGLWindow :: HoppyF.Ptr QOpenGLWindowConst -> HoppyP.IO () foreign import ccall "&gendel__QOpenGLWindow" deletePtr'QOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr QOpenGLWindowConst -> HoppyP.IO ()) class QOpenGLWindowValue a where withQOpenGLWindowPtr :: a -> (QOpenGLWindowConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QOpenGLWindowConstPtr a => QOpenGLWindowValue a where withQOpenGLWindowPtr = HoppyP.flip ($) . toQOpenGLWindowConst class (M306.QPaintDeviceWindowConstPtr this) => QOpenGLWindowConstPtr this where toQOpenGLWindowConst :: this -> QOpenGLWindowConst defaultFramebufferObject :: (QOpenGLWindowValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyDW.Word32) defaultFramebufferObject arg'1 = withQOpenGLWindowPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (defaultFramebufferObject' arg'1') isValid :: (QOpenGLWindowValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) isValid arg'1 = withQOpenGLWindowPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (isValid' arg'1') updateBehavior :: (QOpenGLWindowValue this) => (this) {- ^ this -} -> (HoppyP.IO QOpenGLWindowUpdateBehavior) updateBehavior arg'1 = withQOpenGLWindowPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.toCppEnum ) =<< (updateBehavior' arg'1') class (QOpenGLWindowConstPtr this, M306.QPaintDeviceWindowPtr this) => QOpenGLWindowPtr this where toQOpenGLWindow :: this -> QOpenGLWindow doneCurrent :: (QOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) doneCurrent arg'1 = HoppyFHR.withCppPtr (toQOpenGLWindow arg'1) $ \arg'1' -> (doneCurrent' arg'1') grabFramebuffer :: (QOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO M292.QImage) grabFramebuffer arg'1 = HoppyFHR.withCppPtr (toQOpenGLWindow arg'1) $ \arg'1' -> (HoppyFHR.decodeAndDelete . M292.QImageConst) =<< (grabFramebuffer' arg'1') makeCurrent :: (QOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) makeCurrent arg'1 = HoppyFHR.withCppPtr (toQOpenGLWindow arg'1) $ \arg'1' -> (makeCurrent' arg'1') emitFrameSwapped :: (QOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) emitFrameSwapped arg'1 = HoppyFHR.withCppPtr (toQOpenGLWindow arg'1) $ \arg'1' -> (emitFrameSwapped' arg'1') data QOpenGLWindowConst = QOpenGLWindowConst (HoppyF.Ptr QOpenGLWindowConst) | QOpenGLWindowConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QOpenGLWindowConst) deriving (HoppyP.Show) instance HoppyP.Eq QOpenGLWindowConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QOpenGLWindowConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQOpenGLWindowToConst :: QOpenGLWindow -> QOpenGLWindowConst castQOpenGLWindowToConst (QOpenGLWindow ptr') = QOpenGLWindowConst $ HoppyF.castPtr ptr' castQOpenGLWindowToConst (QOpenGLWindowGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QOpenGLWindowConst where nullptr = QOpenGLWindowConst HoppyF.nullPtr withCppPtr (QOpenGLWindowConst ptr') f' = f' ptr' withCppPtr (QOpenGLWindowConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QOpenGLWindowConst ptr') = ptr' toPtr (QOpenGLWindowConstGc _ ptr') = ptr' touchCppPtr (QOpenGLWindowConst _) = HoppyP.return () touchCppPtr (QOpenGLWindowConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QOpenGLWindowConst where delete (QOpenGLWindowConst ptr') = delete'QOpenGLWindow ptr' delete (QOpenGLWindowConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QOpenGLWindowConst", " object."] toGc this'@(QOpenGLWindowConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QOpenGLWindowConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QOpenGLWindowConstGc {}) = HoppyP.return this' instance QOpenGLWindowConstPtr QOpenGLWindowConst where toQOpenGLWindowConst = HoppyP.id instance M306.QPaintDeviceWindowConstPtr QOpenGLWindowConst where toQPaintDeviceWindowConst (QOpenGLWindowConst ptr') = M306.QPaintDeviceWindowConst $ castQOpenGLWindowToQPaintDeviceWindow ptr' toQPaintDeviceWindowConst (QOpenGLWindowConstGc fptr' ptr') = M306.QPaintDeviceWindowConstGc fptr' $ castQOpenGLWindowToQPaintDeviceWindow ptr' instance M342.QWindowConstPtr QOpenGLWindowConst where toQWindowConst (QOpenGLWindowConst ptr') = M342.QWindowConst $ castQOpenGLWindowToQWindow ptr' toQWindowConst (QOpenGLWindowConstGc fptr' ptr') = M342.QWindowConstGc fptr' $ castQOpenGLWindowToQWindow ptr' instance M94.QObjectConstPtr QOpenGLWindowConst where toQObjectConst (QOpenGLWindowConst ptr') = M94.QObjectConst $ castQOpenGLWindowToQObject ptr' toQObjectConst (QOpenGLWindowConstGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQOpenGLWindowToQObject ptr' instance M334.QSurfaceConstPtr QOpenGLWindowConst where toQSurfaceConst (QOpenGLWindowConst ptr') = M334.QSurfaceConst $ castQOpenGLWindowToQSurface ptr' toQSurfaceConst (QOpenGLWindowConstGc fptr' ptr') = M334.QSurfaceConstGc fptr' $ castQOpenGLWindowToQSurface ptr' instance M304.QPaintDeviceConstPtr QOpenGLWindowConst where toQPaintDeviceConst (QOpenGLWindowConst ptr') = M304.QPaintDeviceConst $ castQOpenGLWindowToQPaintDevice ptr' toQPaintDeviceConst (QOpenGLWindowConstGc fptr' ptr') = M304.QPaintDeviceConstGc fptr' $ castQOpenGLWindowToQPaintDevice ptr' data QOpenGLWindow = QOpenGLWindow (HoppyF.Ptr QOpenGLWindow) | QOpenGLWindowGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QOpenGLWindow) deriving (HoppyP.Show) instance HoppyP.Eq QOpenGLWindow where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QOpenGLWindow where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQOpenGLWindowToNonconst :: QOpenGLWindowConst -> QOpenGLWindow castQOpenGLWindowToNonconst (QOpenGLWindowConst ptr') = QOpenGLWindow $ HoppyF.castPtr ptr' castQOpenGLWindowToNonconst (QOpenGLWindowConstGc fptr' ptr') = QOpenGLWindowGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QOpenGLWindow where nullptr = QOpenGLWindow HoppyF.nullPtr withCppPtr (QOpenGLWindow ptr') f' = f' ptr' withCppPtr (QOpenGLWindowGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QOpenGLWindow ptr') = ptr' toPtr (QOpenGLWindowGc _ ptr') = ptr' touchCppPtr (QOpenGLWindow _) = HoppyP.return () touchCppPtr (QOpenGLWindowGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QOpenGLWindow where delete (QOpenGLWindow ptr') = delete'QOpenGLWindow $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QOpenGLWindowConst) delete (QOpenGLWindowGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QOpenGLWindow", " object."] toGc this'@(QOpenGLWindow ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QOpenGLWindowGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QOpenGLWindowGc {}) = HoppyP.return this' instance QOpenGLWindowConstPtr QOpenGLWindow where toQOpenGLWindowConst (QOpenGLWindow ptr') = QOpenGLWindowConst $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQOpenGLWindowConst (QOpenGLWindowGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance QOpenGLWindowPtr QOpenGLWindow where toQOpenGLWindow = HoppyP.id instance M306.QPaintDeviceWindowConstPtr QOpenGLWindow where toQPaintDeviceWindowConst (QOpenGLWindow ptr') = M306.QPaintDeviceWindowConst $ castQOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQPaintDeviceWindowConst (QOpenGLWindowGc fptr' ptr') = M306.QPaintDeviceWindowConstGc fptr' $ castQOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M306.QPaintDeviceWindowPtr QOpenGLWindow where toQPaintDeviceWindow (QOpenGLWindow ptr') = M306.QPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindow) $ castQOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQPaintDeviceWindow (QOpenGLWindowGc fptr' ptr') = M306.QPaintDeviceWindowGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindow) $ castQOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M342.QWindowConstPtr QOpenGLWindow where toQWindowConst (QOpenGLWindow ptr') = M342.QWindowConst $ castQOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQWindowConst (QOpenGLWindowGc fptr' ptr') = M342.QWindowConstGc fptr' $ castQOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M342.QWindowPtr QOpenGLWindow where toQWindow (QOpenGLWindow ptr') = M342.QWindow $ (HoppyF.castPtr :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr M342.QWindow) $ castQOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQWindow (QOpenGLWindowGc fptr' ptr') = M342.QWindowGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr M342.QWindow) $ castQOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M94.QObjectConstPtr QOpenGLWindow where toQObjectConst (QOpenGLWindow ptr') = M94.QObjectConst $ castQOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQObjectConst (QOpenGLWindowGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M94.QObjectPtr QOpenGLWindow where toQObject (QOpenGLWindow ptr') = M94.QObject $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQObject (QOpenGLWindowGc fptr' ptr') = M94.QObjectGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M334.QSurfaceConstPtr QOpenGLWindow where toQSurfaceConst (QOpenGLWindow ptr') = M334.QSurfaceConst $ castQOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQSurfaceConst (QOpenGLWindowGc fptr' ptr') = M334.QSurfaceConstGc fptr' $ castQOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M334.QSurfacePtr QOpenGLWindow where toQSurface (QOpenGLWindow ptr') = M334.QSurface $ (HoppyF.castPtr :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr M334.QSurface) $ castQOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQSurface (QOpenGLWindowGc fptr' ptr') = M334.QSurfaceGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr M334.QSurface) $ castQOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M304.QPaintDeviceConstPtr QOpenGLWindow where toQPaintDeviceConst (QOpenGLWindow ptr') = M304.QPaintDeviceConst $ castQOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQPaintDeviceConst (QOpenGLWindowGc fptr' ptr') = M304.QPaintDeviceConstGc fptr' $ castQOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' instance M304.QPaintDevicePtr QOpenGLWindow where toQPaintDevice (QOpenGLWindow ptr') = M304.QPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr M304.QPaintDevice) $ castQOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' toQPaintDevice (QOpenGLWindowGc fptr' ptr') = M304.QPaintDeviceGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr M304.QPaintDevice) $ castQOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QOpenGLWindow -> HoppyF.Ptr QOpenGLWindowConst) ptr' new :: (HoppyP.IO QOpenGLWindow) new = HoppyP.fmap QOpenGLWindow (new') newWithUpdateBehavior :: (QOpenGLWindowUpdateBehavior) -> (HoppyP.IO QOpenGLWindow) newWithUpdateBehavior arg'1 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyP.fmap QOpenGLWindow (newWithUpdateBehavior' arg'1') newWithUpdateBehaviorAndParent :: (M342.QWindowPtr arg'2) => (QOpenGLWindowUpdateBehavior) -> (arg'2) -> (HoppyP.IO QOpenGLWindow) newWithUpdateBehaviorAndParent arg'1 arg'2 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyFHR.withCppPtr (M342.toQWindow arg'2) $ \arg'2' -> HoppyP.fmap QOpenGLWindow (newWithUpdateBehaviorAndParent' arg'1' arg'2') class QOpenGLWindowSuper a where downToQOpenGLWindow :: a -> QOpenGLWindow instance QOpenGLWindowSuper M306.QPaintDeviceWindow where downToQOpenGLWindow = castQOpenGLWindowToNonconst . cast' . M306.castQPaintDeviceWindowToConst where cast' (M306.QPaintDeviceWindowConst ptr') = QOpenGLWindowConst $ castQPaintDeviceWindowToQOpenGLWindow ptr' cast' (M306.QPaintDeviceWindowConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQPaintDeviceWindowToQOpenGLWindow ptr' instance QOpenGLWindowSuper M342.QWindow where downToQOpenGLWindow = castQOpenGLWindowToNonconst . cast' . M342.castQWindowToConst where cast' (M342.QWindowConst ptr') = QOpenGLWindowConst $ castQWindowToQOpenGLWindow ptr' cast' (M342.QWindowConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQWindowToQOpenGLWindow ptr' instance QOpenGLWindowSuper M94.QObject where downToQOpenGLWindow = castQOpenGLWindowToNonconst . cast' . M94.castQObjectToConst where cast' (M94.QObjectConst ptr') = QOpenGLWindowConst $ castQObjectToQOpenGLWindow ptr' cast' (M94.QObjectConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQObjectToQOpenGLWindow ptr' instance QOpenGLWindowSuper M334.QSurface where downToQOpenGLWindow = castQOpenGLWindowToNonconst . cast' . M334.castQSurfaceToConst where cast' (M334.QSurfaceConst ptr') = QOpenGLWindowConst $ castQSurfaceToQOpenGLWindow ptr' cast' (M334.QSurfaceConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQSurfaceToQOpenGLWindow ptr' instance QOpenGLWindowSuper M304.QPaintDevice where downToQOpenGLWindow = castQOpenGLWindowToNonconst . cast' . M304.castQPaintDeviceToConst where cast' (M304.QPaintDeviceConst ptr') = QOpenGLWindowConst $ castQPaintDeviceToQOpenGLWindow ptr' cast' (M304.QPaintDeviceConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQPaintDeviceToQOpenGLWindow ptr' class QOpenGLWindowSuperConst a where downToQOpenGLWindowConst :: a -> QOpenGLWindowConst instance QOpenGLWindowSuperConst M306.QPaintDeviceWindowConst where downToQOpenGLWindowConst = cast' where cast' (M306.QPaintDeviceWindowConst ptr') = QOpenGLWindowConst $ castQPaintDeviceWindowToQOpenGLWindow ptr' cast' (M306.QPaintDeviceWindowConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQPaintDeviceWindowToQOpenGLWindow ptr' instance QOpenGLWindowSuperConst M342.QWindowConst where downToQOpenGLWindowConst = cast' where cast' (M342.QWindowConst ptr') = QOpenGLWindowConst $ castQWindowToQOpenGLWindow ptr' cast' (M342.QWindowConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQWindowToQOpenGLWindow ptr' instance QOpenGLWindowSuperConst M94.QObjectConst where downToQOpenGLWindowConst = cast' where cast' (M94.QObjectConst ptr') = QOpenGLWindowConst $ castQObjectToQOpenGLWindow ptr' cast' (M94.QObjectConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQObjectToQOpenGLWindow ptr' instance QOpenGLWindowSuperConst M334.QSurfaceConst where downToQOpenGLWindowConst = cast' where cast' (M334.QSurfaceConst ptr') = QOpenGLWindowConst $ castQSurfaceToQOpenGLWindow ptr' cast' (M334.QSurfaceConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQSurfaceToQOpenGLWindow ptr' instance QOpenGLWindowSuperConst M304.QPaintDeviceConst where downToQOpenGLWindowConst = cast' where cast' (M304.QPaintDeviceConst ptr') = QOpenGLWindowConst $ castQPaintDeviceToQOpenGLWindow ptr' cast' (M304.QPaintDeviceConstGc fptr' ptr') = QOpenGLWindowConstGc fptr' $ castQPaintDeviceToQOpenGLWindow ptr' instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QOpenGLWindow)) QOpenGLWindow where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QOpenGLWindow)) QOpenGLWindow where decode = HoppyP.fmap QOpenGLWindow . HoppyF.peek data QOpenGLWindowUpdateBehavior = NoPartialUpdate | PartialUpdateBlit | PartialUpdateBlend | UnknownQOpenGlWindowUpdateBehavior (HoppyFC.CInt) deriving (HoppyP.Show) instance HoppyFHR.CppEnum (HoppyFC.CInt) QOpenGLWindowUpdateBehavior where fromCppEnum NoPartialUpdate = 0 fromCppEnum PartialUpdateBlit = 1 fromCppEnum PartialUpdateBlend = 2 fromCppEnum (UnknownQOpenGlWindowUpdateBehavior n) = n toCppEnum (0) = NoPartialUpdate toCppEnum (1) = PartialUpdateBlit toCppEnum (2) = PartialUpdateBlend toCppEnum n = UnknownQOpenGlWindowUpdateBehavior n instance HoppyP.Eq QOpenGLWindowUpdateBehavior where x == y = HoppyFHR.fromCppEnum x == HoppyFHR.fromCppEnum y instance HoppyP.Ord QOpenGLWindowUpdateBehavior where compare x y = HoppyP.compare (HoppyFHR.fromCppEnum x) (HoppyFHR.fromCppEnum y)