{-# LANGUAGE CPP, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} #if !MIN_VERSION_base(4,8,0) {-# LANGUAGE OverlappingInstances #-} #endif ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Widgets.QHBoxLayout ( castQHBoxLayoutToQBoxLayout, castQBoxLayoutToQHBoxLayout, castQHBoxLayoutToQLayout, castQLayoutToQHBoxLayout, castQHBoxLayoutToQObject, castQObjectToQHBoxLayout, castQHBoxLayoutToQLayoutItem, castQLayoutItemToQHBoxLayout, QHBoxLayoutValue (..), QHBoxLayoutConstPtr (..), QHBoxLayoutPtr (..), QHBoxLayoutConst (..), castQHBoxLayoutToConst, QHBoxLayout (..), castQHBoxLayoutToNonconst, new, newWithParent, QHBoxLayoutSuper (..), QHBoxLayoutSuperConst (..), ) where import qualified Foreign as HoppyF import qualified Foreign.Hoppy.Runtime as HoppyFHR import qualified Graphics.UI.Qtah.Generated.Core.QObject as M30 import qualified Graphics.UI.Qtah.Generated.Widgets.QBoxLayout as M180 import qualified Graphics.UI.Qtah.Generated.Widgets.QLayout as M228 import qualified Graphics.UI.Qtah.Generated.Widgets.QLayoutItem as M230 import qualified Graphics.UI.Qtah.Generated.Widgets.QWidget as M280 import Prelude (($), (.), (==)) import qualified Prelude as HoppyP foreign import ccall "genpop__QHBoxLayout_new" new' :: HoppyP.IO (HoppyF.Ptr QHBoxLayout) foreign import ccall "genpop__QHBoxLayout_newWithParent" newWithParent' :: HoppyF.Ptr M280.QWidget -> HoppyP.IO (HoppyF.Ptr QHBoxLayout) foreign import ccall "gencast__QHBoxLayout__QBoxLayout" castQHBoxLayoutToQBoxLayout :: HoppyF.Ptr QHBoxLayoutConst -> HoppyF.Ptr M180.QBoxLayoutConst foreign import ccall "gencast__QBoxLayout__QHBoxLayout" castQBoxLayoutToQHBoxLayout :: HoppyF.Ptr M180.QBoxLayoutConst -> HoppyF.Ptr QHBoxLayoutConst foreign import ccall "gencast__QHBoxLayout__QLayout" castQHBoxLayoutToQLayout :: HoppyF.Ptr QHBoxLayoutConst -> HoppyF.Ptr M228.QLayoutConst foreign import ccall "gencast__QLayout__QHBoxLayout" castQLayoutToQHBoxLayout :: HoppyF.Ptr M228.QLayoutConst -> HoppyF.Ptr QHBoxLayoutConst foreign import ccall "gencast__QHBoxLayout__QObject" castQHBoxLayoutToQObject :: HoppyF.Ptr QHBoxLayoutConst -> HoppyF.Ptr M30.QObjectConst foreign import ccall "gencast__QObject__QHBoxLayout" castQObjectToQHBoxLayout :: HoppyF.Ptr M30.QObjectConst -> HoppyF.Ptr QHBoxLayoutConst foreign import ccall "gencast__QHBoxLayout__QLayoutItem" castQHBoxLayoutToQLayoutItem :: HoppyF.Ptr QHBoxLayoutConst -> HoppyF.Ptr M230.QLayoutItemConst foreign import ccall "gencast__QLayoutItem__QHBoxLayout" castQLayoutItemToQHBoxLayout :: HoppyF.Ptr M230.QLayoutItemConst -> HoppyF.Ptr QHBoxLayoutConst foreign import ccall "gendel__QHBoxLayout" delete'QHBoxLayout :: HoppyF.Ptr QHBoxLayoutConst -> HoppyP.IO () foreign import ccall "&gendel__QHBoxLayout" deletePtr'QHBoxLayout :: HoppyF.FunPtr (HoppyF.Ptr QHBoxLayoutConst -> HoppyP.IO ()) class QHBoxLayoutValue a where withQHBoxLayoutPtr :: a -> (QHBoxLayoutConst -> HoppyP.IO b) -> HoppyP.IO b #if MIN_VERSION_base(4,8,0) instance {-# OVERLAPPABLE #-} QHBoxLayoutConstPtr a => QHBoxLayoutValue a where #else instance QHBoxLayoutConstPtr a => QHBoxLayoutValue a where #endif withQHBoxLayoutPtr = HoppyP.flip ($) . toQHBoxLayoutConst class (M180.QBoxLayoutConstPtr this) => QHBoxLayoutConstPtr this where toQHBoxLayoutConst :: this -> QHBoxLayoutConst class (QHBoxLayoutConstPtr this, M180.QBoxLayoutPtr this) => QHBoxLayoutPtr this where toQHBoxLayout :: this -> QHBoxLayout data QHBoxLayoutConst = QHBoxLayoutConst (HoppyF.Ptr QHBoxLayoutConst) | QHBoxLayoutConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QHBoxLayoutConst) deriving (HoppyP.Show) instance HoppyP.Eq QHBoxLayoutConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QHBoxLayoutConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQHBoxLayoutToConst :: QHBoxLayout -> QHBoxLayoutConst castQHBoxLayoutToConst (QHBoxLayout ptr') = QHBoxLayoutConst $ HoppyF.castPtr ptr' castQHBoxLayoutToConst (QHBoxLayoutGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QHBoxLayoutConst where nullptr = QHBoxLayoutConst HoppyF.nullPtr withCppPtr (QHBoxLayoutConst ptr') f' = f' ptr' withCppPtr (QHBoxLayoutConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QHBoxLayoutConst ptr') = ptr' toPtr (QHBoxLayoutConstGc _ ptr') = ptr' touchCppPtr (QHBoxLayoutConst _) = HoppyP.return () touchCppPtr (QHBoxLayoutConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QHBoxLayoutConst where delete (QHBoxLayoutConst ptr') = delete'QHBoxLayout ptr' delete (QHBoxLayoutConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QHBoxLayoutConst", " object."] toGc this'@(QHBoxLayoutConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QHBoxLayoutConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QHBoxLayout :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QHBoxLayoutConstGc {}) = HoppyP.return this' instance QHBoxLayoutConstPtr QHBoxLayoutConst where toQHBoxLayoutConst = HoppyP.id instance M180.QBoxLayoutConstPtr QHBoxLayoutConst where toQBoxLayoutConst (QHBoxLayoutConst ptr') = M180.QBoxLayoutConst $ castQHBoxLayoutToQBoxLayout ptr' toQBoxLayoutConst (QHBoxLayoutConstGc fptr' ptr') = M180.QBoxLayoutConstGc fptr' $ castQHBoxLayoutToQBoxLayout ptr' instance M228.QLayoutConstPtr QHBoxLayoutConst where toQLayoutConst (QHBoxLayoutConst ptr') = M228.QLayoutConst $ castQHBoxLayoutToQLayout ptr' toQLayoutConst (QHBoxLayoutConstGc fptr' ptr') = M228.QLayoutConstGc fptr' $ castQHBoxLayoutToQLayout ptr' instance M30.QObjectConstPtr QHBoxLayoutConst where toQObjectConst (QHBoxLayoutConst ptr') = M30.QObjectConst $ castQHBoxLayoutToQObject ptr' toQObjectConst (QHBoxLayoutConstGc fptr' ptr') = M30.QObjectConstGc fptr' $ castQHBoxLayoutToQObject ptr' instance M230.QLayoutItemConstPtr QHBoxLayoutConst where toQLayoutItemConst (QHBoxLayoutConst ptr') = M230.QLayoutItemConst $ castQHBoxLayoutToQLayoutItem ptr' toQLayoutItemConst (QHBoxLayoutConstGc fptr' ptr') = M230.QLayoutItemConstGc fptr' $ castQHBoxLayoutToQLayoutItem ptr' data QHBoxLayout = QHBoxLayout (HoppyF.Ptr QHBoxLayout) | QHBoxLayoutGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QHBoxLayout) deriving (HoppyP.Show) instance HoppyP.Eq QHBoxLayout where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QHBoxLayout where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQHBoxLayoutToNonconst :: QHBoxLayoutConst -> QHBoxLayout castQHBoxLayoutToNonconst (QHBoxLayoutConst ptr') = QHBoxLayout $ HoppyF.castPtr ptr' castQHBoxLayoutToNonconst (QHBoxLayoutConstGc fptr' ptr') = QHBoxLayoutGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QHBoxLayout where nullptr = QHBoxLayout HoppyF.nullPtr withCppPtr (QHBoxLayout ptr') f' = f' ptr' withCppPtr (QHBoxLayoutGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QHBoxLayout ptr') = ptr' toPtr (QHBoxLayoutGc _ ptr') = ptr' touchCppPtr (QHBoxLayout _) = HoppyP.return () touchCppPtr (QHBoxLayoutGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QHBoxLayout where delete (QHBoxLayout ptr') = delete'QHBoxLayout $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QHBoxLayoutConst) delete (QHBoxLayoutGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QHBoxLayout", " object."] toGc this'@(QHBoxLayout ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QHBoxLayoutGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QHBoxLayout :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QHBoxLayoutGc {}) = HoppyP.return this' instance QHBoxLayoutConstPtr QHBoxLayout where toQHBoxLayoutConst (QHBoxLayout ptr') = QHBoxLayoutConst $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQHBoxLayoutConst (QHBoxLayoutGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance QHBoxLayoutPtr QHBoxLayout where toQHBoxLayout = HoppyP.id instance M180.QBoxLayoutConstPtr QHBoxLayout where toQBoxLayoutConst (QHBoxLayout ptr') = M180.QBoxLayoutConst $ castQHBoxLayoutToQBoxLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQBoxLayoutConst (QHBoxLayoutGc fptr' ptr') = M180.QBoxLayoutConstGc fptr' $ castQHBoxLayoutToQBoxLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M180.QBoxLayoutPtr QHBoxLayout where toQBoxLayout (QHBoxLayout ptr') = M180.QBoxLayout $ (HoppyF.castPtr :: HoppyF.Ptr M180.QBoxLayoutConst -> HoppyF.Ptr M180.QBoxLayout) $ castQHBoxLayoutToQBoxLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQBoxLayout (QHBoxLayoutGc fptr' ptr') = M180.QBoxLayoutGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M180.QBoxLayoutConst -> HoppyF.Ptr M180.QBoxLayout) $ castQHBoxLayoutToQBoxLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M228.QLayoutConstPtr QHBoxLayout where toQLayoutConst (QHBoxLayout ptr') = M228.QLayoutConst $ castQHBoxLayoutToQLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQLayoutConst (QHBoxLayoutGc fptr' ptr') = M228.QLayoutConstGc fptr' $ castQHBoxLayoutToQLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M228.QLayoutPtr QHBoxLayout where toQLayout (QHBoxLayout ptr') = M228.QLayout $ (HoppyF.castPtr :: HoppyF.Ptr M228.QLayoutConst -> HoppyF.Ptr M228.QLayout) $ castQHBoxLayoutToQLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQLayout (QHBoxLayoutGc fptr' ptr') = M228.QLayoutGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M228.QLayoutConst -> HoppyF.Ptr M228.QLayout) $ castQHBoxLayoutToQLayout $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M30.QObjectConstPtr QHBoxLayout where toQObjectConst (QHBoxLayout ptr') = M30.QObjectConst $ castQHBoxLayoutToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQObjectConst (QHBoxLayoutGc fptr' ptr') = M30.QObjectConstGc fptr' $ castQHBoxLayoutToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M30.QObjectPtr QHBoxLayout where toQObject (QHBoxLayout ptr') = M30.QObject $ (HoppyF.castPtr :: HoppyF.Ptr M30.QObjectConst -> HoppyF.Ptr M30.QObject) $ castQHBoxLayoutToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQObject (QHBoxLayoutGc fptr' ptr') = M30.QObjectGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M30.QObjectConst -> HoppyF.Ptr M30.QObject) $ castQHBoxLayoutToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M230.QLayoutItemConstPtr QHBoxLayout where toQLayoutItemConst (QHBoxLayout ptr') = M230.QLayoutItemConst $ castQHBoxLayoutToQLayoutItem $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQLayoutItemConst (QHBoxLayoutGc fptr' ptr') = M230.QLayoutItemConstGc fptr' $ castQHBoxLayoutToQLayoutItem $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' instance M230.QLayoutItemPtr QHBoxLayout where toQLayoutItem (QHBoxLayout ptr') = M230.QLayoutItem $ (HoppyF.castPtr :: HoppyF.Ptr M230.QLayoutItemConst -> HoppyF.Ptr M230.QLayoutItem) $ castQHBoxLayoutToQLayoutItem $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' toQLayoutItem (QHBoxLayoutGc fptr' ptr') = M230.QLayoutItemGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M230.QLayoutItemConst -> HoppyF.Ptr M230.QLayoutItem) $ castQHBoxLayoutToQLayoutItem $ (HoppyF.castPtr :: HoppyF.Ptr QHBoxLayout -> HoppyF.Ptr QHBoxLayoutConst) ptr' new :: HoppyP.IO QHBoxLayout new = HoppyP.fmap QHBoxLayout (new') newWithParent :: (M280.QWidgetPtr arg'1) => arg'1 -> HoppyP.IO QHBoxLayout newWithParent arg'1 = HoppyFHR.withCppPtr (M280.toQWidget arg'1) $ \arg'1' -> HoppyP.fmap QHBoxLayout (newWithParent' arg'1') class QHBoxLayoutSuper a where downToQHBoxLayout :: a -> QHBoxLayout instance QHBoxLayoutSuper M180.QBoxLayout where downToQHBoxLayout = castQHBoxLayoutToNonconst . cast' . M180.castQBoxLayoutToConst where cast' (M180.QBoxLayoutConst ptr') = QHBoxLayoutConst $ castQBoxLayoutToQHBoxLayout ptr' cast' (M180.QBoxLayoutConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQBoxLayoutToQHBoxLayout ptr' instance QHBoxLayoutSuper M228.QLayout where downToQHBoxLayout = castQHBoxLayoutToNonconst . cast' . M228.castQLayoutToConst where cast' (M228.QLayoutConst ptr') = QHBoxLayoutConst $ castQLayoutToQHBoxLayout ptr' cast' (M228.QLayoutConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQLayoutToQHBoxLayout ptr' instance QHBoxLayoutSuper M30.QObject where downToQHBoxLayout = castQHBoxLayoutToNonconst . cast' . M30.castQObjectToConst where cast' (M30.QObjectConst ptr') = QHBoxLayoutConst $ castQObjectToQHBoxLayout ptr' cast' (M30.QObjectConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQObjectToQHBoxLayout ptr' instance QHBoxLayoutSuper M230.QLayoutItem where downToQHBoxLayout = castQHBoxLayoutToNonconst . cast' . M230.castQLayoutItemToConst where cast' (M230.QLayoutItemConst ptr') = QHBoxLayoutConst $ castQLayoutItemToQHBoxLayout ptr' cast' (M230.QLayoutItemConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQLayoutItemToQHBoxLayout ptr' class QHBoxLayoutSuperConst a where downToQHBoxLayoutConst :: a -> QHBoxLayoutConst instance QHBoxLayoutSuperConst M180.QBoxLayoutConst where downToQHBoxLayoutConst = cast' where cast' (M180.QBoxLayoutConst ptr') = QHBoxLayoutConst $ castQBoxLayoutToQHBoxLayout ptr' cast' (M180.QBoxLayoutConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQBoxLayoutToQHBoxLayout ptr' instance QHBoxLayoutSuperConst M228.QLayoutConst where downToQHBoxLayoutConst = cast' where cast' (M228.QLayoutConst ptr') = QHBoxLayoutConst $ castQLayoutToQHBoxLayout ptr' cast' (M228.QLayoutConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQLayoutToQHBoxLayout ptr' instance QHBoxLayoutSuperConst M30.QObjectConst where downToQHBoxLayoutConst = cast' where cast' (M30.QObjectConst ptr') = QHBoxLayoutConst $ castQObjectToQHBoxLayout ptr' cast' (M30.QObjectConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQObjectToQHBoxLayout ptr' instance QHBoxLayoutSuperConst M230.QLayoutItemConst where downToQHBoxLayoutConst = cast' where cast' (M230.QLayoutItemConst ptr') = QHBoxLayoutConst $ castQLayoutItemToQHBoxLayout ptr' cast' (M230.QLayoutItemConstGc fptr' ptr') = QHBoxLayoutConstGc fptr' $ castQLayoutItemToQHBoxLayout ptr' instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QHBoxLayout)) QHBoxLayout where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QHBoxLayout)) QHBoxLayout where decode = HoppyP.fmap QHBoxLayout . HoppyF.peek