{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Gui.QtahOpenGLWindow ( castQtahOpenGLWindowToQOpenGLWindow, castQOpenGLWindowToQtahOpenGLWindow, castQtahOpenGLWindowToQPaintDeviceWindow, castQPaintDeviceWindowToQtahOpenGLWindow, castQtahOpenGLWindowToQWindow, castQWindowToQtahOpenGLWindow, castQtahOpenGLWindowToQObject, castQObjectToQtahOpenGLWindow, castQtahOpenGLWindowToQSurface, castQSurfaceToQtahOpenGLWindow, castQtahOpenGLWindowToQPaintDevice, castQPaintDeviceToQtahOpenGLWindow, QtahOpenGLWindowValue (..), QtahOpenGLWindowConstPtr (..), QtahOpenGLWindowPtr (..), onInitializeGL, onPaintGL, onPaintOverGL, onPaintUnderGL, onResizeGL, QtahOpenGLWindowConst (..), castQtahOpenGLWindowToConst, QtahOpenGLWindow (..), castQtahOpenGLWindowToNonconst, new, newWithUpdateBehavior, newWithUpdateBehaviorAndParent, QtahOpenGLWindowSuper (..), QtahOpenGLWindowSuperConst (..), ) where 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.QOpenGLWindow as M302 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 qualified Graphics.UI.Qtah.Internal.Callback as M348 import Prelude (($), (.), (==), (>>=)) import qualified Prelude as HoppyP foreign import ccall "genpop__QtahOpenGLWindow_new" new' :: HoppyP.IO (HoppyF.Ptr QtahOpenGLWindow) foreign import ccall "genpop__QtahOpenGLWindow_newWithUpdateBehavior" newWithUpdateBehavior' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QtahOpenGLWindow) foreign import ccall "genpop__QtahOpenGLWindow_newWithUpdateBehaviorAndParent" newWithUpdateBehaviorAndParent' :: HoppyFC.CInt -> HoppyF.Ptr M342.QWindow -> HoppyP.IO (HoppyF.Ptr QtahOpenGLWindow) foreign import ccall "genpop__QtahOpenGLWindow_onInitializeGL" onInitializeGL' :: HoppyF.Ptr QtahOpenGLWindow -> HoppyFHR.CCallback (HoppyP.IO ()) -> HoppyP.IO () foreign import ccall "genpop__QtahOpenGLWindow_onPaintGL" onPaintGL' :: HoppyF.Ptr QtahOpenGLWindow -> HoppyFHR.CCallback (HoppyP.IO ()) -> HoppyP.IO () foreign import ccall "genpop__QtahOpenGLWindow_onPaintOverGL" onPaintOverGL' :: HoppyF.Ptr QtahOpenGLWindow -> HoppyFHR.CCallback (HoppyP.IO ()) -> HoppyP.IO () foreign import ccall "genpop__QtahOpenGLWindow_onPaintUnderGL" onPaintUnderGL' :: HoppyF.Ptr QtahOpenGLWindow -> HoppyFHR.CCallback (HoppyP.IO ()) -> HoppyP.IO () foreign import ccall "genpop__QtahOpenGLWindow_onResizeGL" onResizeGL' :: HoppyF.Ptr QtahOpenGLWindow -> HoppyFHR.CCallback (HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO ()) -> HoppyP.IO () foreign import ccall "gencast__QtahOpenGLWindow__QOpenGLWindow" castQtahOpenGLWindowToQOpenGLWindow :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M302.QOpenGLWindowConst foreign import ccall "gencast__QOpenGLWindow__QtahOpenGLWindow" castQOpenGLWindowToQtahOpenGLWindow :: HoppyF.Ptr M302.QOpenGLWindowConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gencast__QtahOpenGLWindow__QPaintDeviceWindow" castQtahOpenGLWindowToQPaintDeviceWindow :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindowConst foreign import ccall "gencast__QPaintDeviceWindow__QtahOpenGLWindow" castQPaintDeviceWindowToQtahOpenGLWindow :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gencast__QtahOpenGLWindow__QWindow" castQtahOpenGLWindowToQWindow :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M342.QWindowConst foreign import ccall "gencast__QWindow__QtahOpenGLWindow" castQWindowToQtahOpenGLWindow :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gencast__QtahOpenGLWindow__QObject" castQtahOpenGLWindowToQObject :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M94.QObjectConst foreign import ccall "gencast__QObject__QtahOpenGLWindow" castQObjectToQtahOpenGLWindow :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gencast__QtahOpenGLWindow__QSurface" castQtahOpenGLWindowToQSurface :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M334.QSurfaceConst foreign import ccall "gencast__QSurface__QtahOpenGLWindow" castQSurfaceToQtahOpenGLWindow :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gencast__QtahOpenGLWindow__QPaintDevice" castQtahOpenGLWindowToQPaintDevice :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyF.Ptr M304.QPaintDeviceConst foreign import ccall "gencast__QPaintDevice__QtahOpenGLWindow" castQPaintDeviceToQtahOpenGLWindow :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr QtahOpenGLWindowConst foreign import ccall "gendel__QtahOpenGLWindow" delete'QtahOpenGLWindow :: HoppyF.Ptr QtahOpenGLWindowConst -> HoppyP.IO () foreign import ccall "&gendel__QtahOpenGLWindow" deletePtr'QtahOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr QtahOpenGLWindowConst -> HoppyP.IO ()) class QtahOpenGLWindowValue a where withQtahOpenGLWindowPtr :: a -> (QtahOpenGLWindowConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QtahOpenGLWindowConstPtr a => QtahOpenGLWindowValue a where withQtahOpenGLWindowPtr = HoppyP.flip ($) . toQtahOpenGLWindowConst class (M302.QOpenGLWindowConstPtr this) => QtahOpenGLWindowConstPtr this where toQtahOpenGLWindowConst :: this -> QtahOpenGLWindowConst class (QtahOpenGLWindowConstPtr this, M302.QOpenGLWindowPtr this) => QtahOpenGLWindowPtr this where toQtahOpenGLWindow :: this -> QtahOpenGLWindow onInitializeGL :: (QtahOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) -> (HoppyP.IO ()) onInitializeGL arg'1 arg'2 = HoppyFHR.withCppPtr (toQtahOpenGLWindow arg'1) $ \arg'1' -> ( M348.callbackVoid_new ) arg'2 >>= \arg'2' -> (onInitializeGL' arg'1' arg'2') onPaintGL :: (QtahOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) -> (HoppyP.IO ()) onPaintGL arg'1 arg'2 = HoppyFHR.withCppPtr (toQtahOpenGLWindow arg'1) $ \arg'1' -> ( M348.callbackVoid_new ) arg'2 >>= \arg'2' -> (onPaintGL' arg'1' arg'2') onPaintOverGL :: (QtahOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) -> (HoppyP.IO ()) onPaintOverGL arg'1 arg'2 = HoppyFHR.withCppPtr (toQtahOpenGLWindow arg'1) $ \arg'1' -> ( M348.callbackVoid_new ) arg'2 >>= \arg'2' -> (onPaintOverGL' arg'1' arg'2') onPaintUnderGL :: (QtahOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) -> (HoppyP.IO ()) onPaintUnderGL arg'1 arg'2 = HoppyFHR.withCppPtr (toQtahOpenGLWindow arg'1) $ \arg'1' -> ( M348.callbackVoid_new ) arg'2 >>= \arg'2' -> (onPaintUnderGL' arg'1' arg'2') onResizeGL :: (QtahOpenGLWindowPtr this) => (this) {- ^ this -} -> (HoppyP.Int -> HoppyP.Int -> HoppyP.IO ()) -> (HoppyP.IO ()) onResizeGL arg'1 arg'2 = HoppyFHR.withCppPtr (toQtahOpenGLWindow arg'1) $ \arg'1' -> ( M348.callbackIntIntVoid_new ) arg'2 >>= \arg'2' -> (onResizeGL' arg'1' arg'2') data QtahOpenGLWindowConst = QtahOpenGLWindowConst (HoppyF.Ptr QtahOpenGLWindowConst) | QtahOpenGLWindowConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QtahOpenGLWindowConst) deriving (HoppyP.Show) instance HoppyP.Eq QtahOpenGLWindowConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QtahOpenGLWindowConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQtahOpenGLWindowToConst :: QtahOpenGLWindow -> QtahOpenGLWindowConst castQtahOpenGLWindowToConst (QtahOpenGLWindow ptr') = QtahOpenGLWindowConst $ HoppyF.castPtr ptr' castQtahOpenGLWindowToConst (QtahOpenGLWindowGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QtahOpenGLWindowConst where nullptr = QtahOpenGLWindowConst HoppyF.nullPtr withCppPtr (QtahOpenGLWindowConst ptr') f' = f' ptr' withCppPtr (QtahOpenGLWindowConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QtahOpenGLWindowConst ptr') = ptr' toPtr (QtahOpenGLWindowConstGc _ ptr') = ptr' touchCppPtr (QtahOpenGLWindowConst _) = HoppyP.return () touchCppPtr (QtahOpenGLWindowConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QtahOpenGLWindowConst where delete (QtahOpenGLWindowConst ptr') = delete'QtahOpenGLWindow ptr' delete (QtahOpenGLWindowConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QtahOpenGLWindowConst", " object."] toGc this'@(QtahOpenGLWindowConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QtahOpenGLWindowConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QtahOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QtahOpenGLWindowConstGc {}) = HoppyP.return this' instance QtahOpenGLWindowConstPtr QtahOpenGLWindowConst where toQtahOpenGLWindowConst = HoppyP.id instance M302.QOpenGLWindowConstPtr QtahOpenGLWindowConst where toQOpenGLWindowConst (QtahOpenGLWindowConst ptr') = M302.QOpenGLWindowConst $ castQtahOpenGLWindowToQOpenGLWindow ptr' toQOpenGLWindowConst (QtahOpenGLWindowConstGc fptr' ptr') = M302.QOpenGLWindowConstGc fptr' $ castQtahOpenGLWindowToQOpenGLWindow ptr' instance M306.QPaintDeviceWindowConstPtr QtahOpenGLWindowConst where toQPaintDeviceWindowConst (QtahOpenGLWindowConst ptr') = M306.QPaintDeviceWindowConst $ castQtahOpenGLWindowToQPaintDeviceWindow ptr' toQPaintDeviceWindowConst (QtahOpenGLWindowConstGc fptr' ptr') = M306.QPaintDeviceWindowConstGc fptr' $ castQtahOpenGLWindowToQPaintDeviceWindow ptr' instance M342.QWindowConstPtr QtahOpenGLWindowConst where toQWindowConst (QtahOpenGLWindowConst ptr') = M342.QWindowConst $ castQtahOpenGLWindowToQWindow ptr' toQWindowConst (QtahOpenGLWindowConstGc fptr' ptr') = M342.QWindowConstGc fptr' $ castQtahOpenGLWindowToQWindow ptr' instance M94.QObjectConstPtr QtahOpenGLWindowConst where toQObjectConst (QtahOpenGLWindowConst ptr') = M94.QObjectConst $ castQtahOpenGLWindowToQObject ptr' toQObjectConst (QtahOpenGLWindowConstGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQtahOpenGLWindowToQObject ptr' instance M334.QSurfaceConstPtr QtahOpenGLWindowConst where toQSurfaceConst (QtahOpenGLWindowConst ptr') = M334.QSurfaceConst $ castQtahOpenGLWindowToQSurface ptr' toQSurfaceConst (QtahOpenGLWindowConstGc fptr' ptr') = M334.QSurfaceConstGc fptr' $ castQtahOpenGLWindowToQSurface ptr' instance M304.QPaintDeviceConstPtr QtahOpenGLWindowConst where toQPaintDeviceConst (QtahOpenGLWindowConst ptr') = M304.QPaintDeviceConst $ castQtahOpenGLWindowToQPaintDevice ptr' toQPaintDeviceConst (QtahOpenGLWindowConstGc fptr' ptr') = M304.QPaintDeviceConstGc fptr' $ castQtahOpenGLWindowToQPaintDevice ptr' data QtahOpenGLWindow = QtahOpenGLWindow (HoppyF.Ptr QtahOpenGLWindow) | QtahOpenGLWindowGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QtahOpenGLWindow) deriving (HoppyP.Show) instance HoppyP.Eq QtahOpenGLWindow where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QtahOpenGLWindow where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQtahOpenGLWindowToNonconst :: QtahOpenGLWindowConst -> QtahOpenGLWindow castQtahOpenGLWindowToNonconst (QtahOpenGLWindowConst ptr') = QtahOpenGLWindow $ HoppyF.castPtr ptr' castQtahOpenGLWindowToNonconst (QtahOpenGLWindowConstGc fptr' ptr') = QtahOpenGLWindowGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QtahOpenGLWindow where nullptr = QtahOpenGLWindow HoppyF.nullPtr withCppPtr (QtahOpenGLWindow ptr') f' = f' ptr' withCppPtr (QtahOpenGLWindowGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QtahOpenGLWindow ptr') = ptr' toPtr (QtahOpenGLWindowGc _ ptr') = ptr' touchCppPtr (QtahOpenGLWindow _) = HoppyP.return () touchCppPtr (QtahOpenGLWindowGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QtahOpenGLWindow where delete (QtahOpenGLWindow ptr') = delete'QtahOpenGLWindow $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QtahOpenGLWindowConst) delete (QtahOpenGLWindowGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QtahOpenGLWindow", " object."] toGc this'@(QtahOpenGLWindow ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QtahOpenGLWindowGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QtahOpenGLWindow :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QtahOpenGLWindowGc {}) = HoppyP.return this' instance QtahOpenGLWindowConstPtr QtahOpenGLWindow where toQtahOpenGLWindowConst (QtahOpenGLWindow ptr') = QtahOpenGLWindowConst $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQtahOpenGLWindowConst (QtahOpenGLWindowGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance QtahOpenGLWindowPtr QtahOpenGLWindow where toQtahOpenGLWindow = HoppyP.id instance M302.QOpenGLWindowConstPtr QtahOpenGLWindow where toQOpenGLWindowConst (QtahOpenGLWindow ptr') = M302.QOpenGLWindowConst $ castQtahOpenGLWindowToQOpenGLWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQOpenGLWindowConst (QtahOpenGLWindowGc fptr' ptr') = M302.QOpenGLWindowConstGc fptr' $ castQtahOpenGLWindowToQOpenGLWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M302.QOpenGLWindowPtr QtahOpenGLWindow where toQOpenGLWindow (QtahOpenGLWindow ptr') = M302.QOpenGLWindow $ (HoppyF.castPtr :: HoppyF.Ptr M302.QOpenGLWindowConst -> HoppyF.Ptr M302.QOpenGLWindow) $ castQtahOpenGLWindowToQOpenGLWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQOpenGLWindow (QtahOpenGLWindowGc fptr' ptr') = M302.QOpenGLWindowGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M302.QOpenGLWindowConst -> HoppyF.Ptr M302.QOpenGLWindow) $ castQtahOpenGLWindowToQOpenGLWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M306.QPaintDeviceWindowConstPtr QtahOpenGLWindow where toQPaintDeviceWindowConst (QtahOpenGLWindow ptr') = M306.QPaintDeviceWindowConst $ castQtahOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQPaintDeviceWindowConst (QtahOpenGLWindowGc fptr' ptr') = M306.QPaintDeviceWindowConstGc fptr' $ castQtahOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M306.QPaintDeviceWindowPtr QtahOpenGLWindow where toQPaintDeviceWindow (QtahOpenGLWindow ptr') = M306.QPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindow) $ castQtahOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQPaintDeviceWindow (QtahOpenGLWindowGc fptr' ptr') = M306.QPaintDeviceWindowGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M306.QPaintDeviceWindowConst -> HoppyF.Ptr M306.QPaintDeviceWindow) $ castQtahOpenGLWindowToQPaintDeviceWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M342.QWindowConstPtr QtahOpenGLWindow where toQWindowConst (QtahOpenGLWindow ptr') = M342.QWindowConst $ castQtahOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQWindowConst (QtahOpenGLWindowGc fptr' ptr') = M342.QWindowConstGc fptr' $ castQtahOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M342.QWindowPtr QtahOpenGLWindow where toQWindow (QtahOpenGLWindow ptr') = M342.QWindow $ (HoppyF.castPtr :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr M342.QWindow) $ castQtahOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQWindow (QtahOpenGLWindowGc fptr' ptr') = M342.QWindowGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M342.QWindowConst -> HoppyF.Ptr M342.QWindow) $ castQtahOpenGLWindowToQWindow $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M94.QObjectConstPtr QtahOpenGLWindow where toQObjectConst (QtahOpenGLWindow ptr') = M94.QObjectConst $ castQtahOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQObjectConst (QtahOpenGLWindowGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQtahOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M94.QObjectPtr QtahOpenGLWindow where toQObject (QtahOpenGLWindow ptr') = M94.QObject $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQtahOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQObject (QtahOpenGLWindowGc fptr' ptr') = M94.QObjectGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQtahOpenGLWindowToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M334.QSurfaceConstPtr QtahOpenGLWindow where toQSurfaceConst (QtahOpenGLWindow ptr') = M334.QSurfaceConst $ castQtahOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQSurfaceConst (QtahOpenGLWindowGc fptr' ptr') = M334.QSurfaceConstGc fptr' $ castQtahOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M334.QSurfacePtr QtahOpenGLWindow where toQSurface (QtahOpenGLWindow ptr') = M334.QSurface $ (HoppyF.castPtr :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr M334.QSurface) $ castQtahOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQSurface (QtahOpenGLWindowGc fptr' ptr') = M334.QSurfaceGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M334.QSurfaceConst -> HoppyF.Ptr M334.QSurface) $ castQtahOpenGLWindowToQSurface $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M304.QPaintDeviceConstPtr QtahOpenGLWindow where toQPaintDeviceConst (QtahOpenGLWindow ptr') = M304.QPaintDeviceConst $ castQtahOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQPaintDeviceConst (QtahOpenGLWindowGc fptr' ptr') = M304.QPaintDeviceConstGc fptr' $ castQtahOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' instance M304.QPaintDevicePtr QtahOpenGLWindow where toQPaintDevice (QtahOpenGLWindow ptr') = M304.QPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr M304.QPaintDevice) $ castQtahOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' toQPaintDevice (QtahOpenGLWindowGc fptr' ptr') = M304.QPaintDeviceGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M304.QPaintDeviceConst -> HoppyF.Ptr M304.QPaintDevice) $ castQtahOpenGLWindowToQPaintDevice $ (HoppyF.castPtr :: HoppyF.Ptr QtahOpenGLWindow -> HoppyF.Ptr QtahOpenGLWindowConst) ptr' new :: (HoppyP.IO QtahOpenGLWindow) new = HoppyP.fmap QtahOpenGLWindow (new') newWithUpdateBehavior :: (M302.QOpenGLWindowUpdateBehavior) -> (HoppyP.IO QtahOpenGLWindow) newWithUpdateBehavior arg'1 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyP.fmap QtahOpenGLWindow (newWithUpdateBehavior' arg'1') newWithUpdateBehaviorAndParent :: (M342.QWindowPtr arg'2) => (M302.QOpenGLWindowUpdateBehavior) -> (arg'2) -> (HoppyP.IO QtahOpenGLWindow) newWithUpdateBehaviorAndParent arg'1 arg'2 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyFHR.withCppPtr (M342.toQWindow arg'2) $ \arg'2' -> HoppyP.fmap QtahOpenGLWindow (newWithUpdateBehaviorAndParent' arg'1' arg'2') class QtahOpenGLWindowSuper a where downToQtahOpenGLWindow :: a -> QtahOpenGLWindow instance QtahOpenGLWindowSuper M302.QOpenGLWindow where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M302.castQOpenGLWindowToConst where cast' (M302.QOpenGLWindowConst ptr') = QtahOpenGLWindowConst $ castQOpenGLWindowToQtahOpenGLWindow ptr' cast' (M302.QOpenGLWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQOpenGLWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuper M306.QPaintDeviceWindow where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M306.castQPaintDeviceWindowToConst where cast' (M306.QPaintDeviceWindowConst ptr') = QtahOpenGLWindowConst $ castQPaintDeviceWindowToQtahOpenGLWindow ptr' cast' (M306.QPaintDeviceWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQPaintDeviceWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuper M342.QWindow where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M342.castQWindowToConst where cast' (M342.QWindowConst ptr') = QtahOpenGLWindowConst $ castQWindowToQtahOpenGLWindow ptr' cast' (M342.QWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuper M94.QObject where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M94.castQObjectToConst where cast' (M94.QObjectConst ptr') = QtahOpenGLWindowConst $ castQObjectToQtahOpenGLWindow ptr' cast' (M94.QObjectConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQObjectToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuper M334.QSurface where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M334.castQSurfaceToConst where cast' (M334.QSurfaceConst ptr') = QtahOpenGLWindowConst $ castQSurfaceToQtahOpenGLWindow ptr' cast' (M334.QSurfaceConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQSurfaceToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuper M304.QPaintDevice where downToQtahOpenGLWindow = castQtahOpenGLWindowToNonconst . cast' . M304.castQPaintDeviceToConst where cast' (M304.QPaintDeviceConst ptr') = QtahOpenGLWindowConst $ castQPaintDeviceToQtahOpenGLWindow ptr' cast' (M304.QPaintDeviceConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQPaintDeviceToQtahOpenGLWindow ptr' class QtahOpenGLWindowSuperConst a where downToQtahOpenGLWindowConst :: a -> QtahOpenGLWindowConst instance QtahOpenGLWindowSuperConst M302.QOpenGLWindowConst where downToQtahOpenGLWindowConst = cast' where cast' (M302.QOpenGLWindowConst ptr') = QtahOpenGLWindowConst $ castQOpenGLWindowToQtahOpenGLWindow ptr' cast' (M302.QOpenGLWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQOpenGLWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuperConst M306.QPaintDeviceWindowConst where downToQtahOpenGLWindowConst = cast' where cast' (M306.QPaintDeviceWindowConst ptr') = QtahOpenGLWindowConst $ castQPaintDeviceWindowToQtahOpenGLWindow ptr' cast' (M306.QPaintDeviceWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQPaintDeviceWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuperConst M342.QWindowConst where downToQtahOpenGLWindowConst = cast' where cast' (M342.QWindowConst ptr') = QtahOpenGLWindowConst $ castQWindowToQtahOpenGLWindow ptr' cast' (M342.QWindowConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQWindowToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuperConst M94.QObjectConst where downToQtahOpenGLWindowConst = cast' where cast' (M94.QObjectConst ptr') = QtahOpenGLWindowConst $ castQObjectToQtahOpenGLWindow ptr' cast' (M94.QObjectConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQObjectToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuperConst M334.QSurfaceConst where downToQtahOpenGLWindowConst = cast' where cast' (M334.QSurfaceConst ptr') = QtahOpenGLWindowConst $ castQSurfaceToQtahOpenGLWindow ptr' cast' (M334.QSurfaceConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQSurfaceToQtahOpenGLWindow ptr' instance QtahOpenGLWindowSuperConst M304.QPaintDeviceConst where downToQtahOpenGLWindowConst = cast' where cast' (M304.QPaintDeviceConst ptr') = QtahOpenGLWindowConst $ castQPaintDeviceToQtahOpenGLWindow ptr' cast' (M304.QPaintDeviceConstGc fptr' ptr') = QtahOpenGLWindowConstGc fptr' $ castQPaintDeviceToQtahOpenGLWindow ptr' instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QtahOpenGLWindow)) QtahOpenGLWindow where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QtahOpenGLWindow)) QtahOpenGLWindow where decode = HoppyP.fmap QtahOpenGLWindow . HoppyF.peek