{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QPropertyAnimation ( castQPropertyAnimationToQVariantAnimation, castQVariantAnimationToQPropertyAnimation, castQPropertyAnimationToQAbstractAnimation, castQAbstractAnimationToQPropertyAnimation, castQPropertyAnimationToQObject, castQObjectToQPropertyAnimation, QPropertyAnimationValue (..), QPropertyAnimationConstPtr (..), propertyName, targetObject, QPropertyAnimationPtr (..), setPropertyName, setTargetObject, QPropertyAnimationConst (..), castQPropertyAnimationToConst, QPropertyAnimation (..), castQPropertyAnimationToNonconst, QPropertyAnimationSuper (..), QPropertyAnimationSuperConst (..), ) where import qualified Data.ByteString as QtahDBS import qualified Foreign as HoppyF import qualified Foreign.Hoppy.Runtime as HoppyFHR import qualified Graphics.UI.Qtah.Generated.Core.QAbstractAnimation as M2 import qualified Graphics.UI.Qtah.Generated.Core.QByteArray as M12 import qualified Graphics.UI.Qtah.Generated.Core.QObject as M94 import qualified Graphics.UI.Qtah.Generated.Core.QVariantAnimation as M170 import Prelude (($), (.), (=<<), (==)) import qualified Prelude as HoppyP foreign import ccall "genpop__QPropertyAnimation_propertyName" propertyName' :: HoppyF.Ptr QPropertyAnimationConst -> HoppyP.IO (HoppyF.Ptr M12.QByteArrayConst) foreign import ccall "genpop__QPropertyAnimation_setPropertyName" setPropertyName' :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr M12.QByteArrayConst -> HoppyP.IO () foreign import ccall "genpop__QPropertyAnimation_targetObject" targetObject' :: HoppyF.Ptr QPropertyAnimationConst -> HoppyP.IO (HoppyF.Ptr M94.QObject) foreign import ccall "genpop__QPropertyAnimation_setTargetObject" setTargetObject' :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr M94.QObject -> HoppyP.IO () foreign import ccall "gencast__QPropertyAnimation__QVariantAnimation" castQPropertyAnimationToQVariantAnimation :: HoppyF.Ptr QPropertyAnimationConst -> HoppyF.Ptr M170.QVariantAnimationConst foreign import ccall "gencast__QVariantAnimation__QPropertyAnimation" castQVariantAnimationToQPropertyAnimation :: HoppyF.Ptr M170.QVariantAnimationConst -> HoppyF.Ptr QPropertyAnimationConst foreign import ccall "gencast__QPropertyAnimation__QAbstractAnimation" castQPropertyAnimationToQAbstractAnimation :: HoppyF.Ptr QPropertyAnimationConst -> HoppyF.Ptr M2.QAbstractAnimationConst foreign import ccall "gencast__QAbstractAnimation__QPropertyAnimation" castQAbstractAnimationToQPropertyAnimation :: HoppyF.Ptr M2.QAbstractAnimationConst -> HoppyF.Ptr QPropertyAnimationConst foreign import ccall "gencast__QPropertyAnimation__QObject" castQPropertyAnimationToQObject :: HoppyF.Ptr QPropertyAnimationConst -> HoppyF.Ptr M94.QObjectConst foreign import ccall "gencast__QObject__QPropertyAnimation" castQObjectToQPropertyAnimation :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr QPropertyAnimationConst foreign import ccall "gendel__QPropertyAnimation" delete'QPropertyAnimation :: HoppyF.Ptr QPropertyAnimationConst -> HoppyP.IO () foreign import ccall "&gendel__QPropertyAnimation" deletePtr'QPropertyAnimation :: HoppyF.FunPtr (HoppyF.Ptr QPropertyAnimationConst -> HoppyP.IO ()) class QPropertyAnimationValue a where withQPropertyAnimationPtr :: a -> (QPropertyAnimationConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QPropertyAnimationConstPtr a => QPropertyAnimationValue a where withQPropertyAnimationPtr = HoppyP.flip ($) . toQPropertyAnimationConst class (M170.QVariantAnimationConstPtr this) => QPropertyAnimationConstPtr this where toQPropertyAnimationConst :: this -> QPropertyAnimationConst propertyName :: (QPropertyAnimationValue this) => (this) {- ^ this -} -> (HoppyP.IO QtahDBS.ByteString) propertyName arg'1 = withQPropertyAnimationPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M12.QByteArrayConst) =<< (propertyName' arg'1') targetObject :: (QPropertyAnimationValue this) => (this) {- ^ this -} -> (HoppyP.IO M94.QObject) targetObject arg'1 = withQPropertyAnimationPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap M94.QObject (targetObject' arg'1') class (QPropertyAnimationConstPtr this, M170.QVariantAnimationPtr this) => QPropertyAnimationPtr this where toQPropertyAnimation :: this -> QPropertyAnimation setPropertyName :: (QPropertyAnimationPtr this, M12.QByteArrayValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setPropertyName arg'1 arg'2 = HoppyFHR.withCppPtr (toQPropertyAnimation arg'1) $ \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setPropertyName' arg'1' arg'2') setTargetObject :: (QPropertyAnimationPtr this, M94.QObjectPtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setTargetObject arg'1 arg'2 = HoppyFHR.withCppPtr (toQPropertyAnimation arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (M94.toQObject arg'2) $ \arg'2' -> (setTargetObject' arg'1' arg'2') data QPropertyAnimationConst = QPropertyAnimationConst (HoppyF.Ptr QPropertyAnimationConst) | QPropertyAnimationConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QPropertyAnimationConst) deriving (HoppyP.Show) instance HoppyP.Eq QPropertyAnimationConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QPropertyAnimationConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQPropertyAnimationToConst :: QPropertyAnimation -> QPropertyAnimationConst castQPropertyAnimationToConst (QPropertyAnimation ptr') = QPropertyAnimationConst $ HoppyF.castPtr ptr' castQPropertyAnimationToConst (QPropertyAnimationGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QPropertyAnimationConst where nullptr = QPropertyAnimationConst HoppyF.nullPtr withCppPtr (QPropertyAnimationConst ptr') f' = f' ptr' withCppPtr (QPropertyAnimationConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QPropertyAnimationConst ptr') = ptr' toPtr (QPropertyAnimationConstGc _ ptr') = ptr' touchCppPtr (QPropertyAnimationConst _) = HoppyP.return () touchCppPtr (QPropertyAnimationConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QPropertyAnimationConst where delete (QPropertyAnimationConst ptr') = delete'QPropertyAnimation ptr' delete (QPropertyAnimationConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QPropertyAnimationConst", " object."] toGc this'@(QPropertyAnimationConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QPropertyAnimationConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QPropertyAnimation :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QPropertyAnimationConstGc {}) = HoppyP.return this' instance QPropertyAnimationConstPtr QPropertyAnimationConst where toQPropertyAnimationConst = HoppyP.id instance M170.QVariantAnimationConstPtr QPropertyAnimationConst where toQVariantAnimationConst (QPropertyAnimationConst ptr') = M170.QVariantAnimationConst $ castQPropertyAnimationToQVariantAnimation ptr' toQVariantAnimationConst (QPropertyAnimationConstGc fptr' ptr') = M170.QVariantAnimationConstGc fptr' $ castQPropertyAnimationToQVariantAnimation ptr' instance M2.QAbstractAnimationConstPtr QPropertyAnimationConst where toQAbstractAnimationConst (QPropertyAnimationConst ptr') = M2.QAbstractAnimationConst $ castQPropertyAnimationToQAbstractAnimation ptr' toQAbstractAnimationConst (QPropertyAnimationConstGc fptr' ptr') = M2.QAbstractAnimationConstGc fptr' $ castQPropertyAnimationToQAbstractAnimation ptr' instance M94.QObjectConstPtr QPropertyAnimationConst where toQObjectConst (QPropertyAnimationConst ptr') = M94.QObjectConst $ castQPropertyAnimationToQObject ptr' toQObjectConst (QPropertyAnimationConstGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQPropertyAnimationToQObject ptr' data QPropertyAnimation = QPropertyAnimation (HoppyF.Ptr QPropertyAnimation) | QPropertyAnimationGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QPropertyAnimation) deriving (HoppyP.Show) instance HoppyP.Eq QPropertyAnimation where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QPropertyAnimation where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQPropertyAnimationToNonconst :: QPropertyAnimationConst -> QPropertyAnimation castQPropertyAnimationToNonconst (QPropertyAnimationConst ptr') = QPropertyAnimation $ HoppyF.castPtr ptr' castQPropertyAnimationToNonconst (QPropertyAnimationConstGc fptr' ptr') = QPropertyAnimationGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QPropertyAnimation where nullptr = QPropertyAnimation HoppyF.nullPtr withCppPtr (QPropertyAnimation ptr') f' = f' ptr' withCppPtr (QPropertyAnimationGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QPropertyAnimation ptr') = ptr' toPtr (QPropertyAnimationGc _ ptr') = ptr' touchCppPtr (QPropertyAnimation _) = HoppyP.return () touchCppPtr (QPropertyAnimationGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QPropertyAnimation where delete (QPropertyAnimation ptr') = delete'QPropertyAnimation $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QPropertyAnimationConst) delete (QPropertyAnimationGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QPropertyAnimation", " object."] toGc this'@(QPropertyAnimation ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QPropertyAnimationGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QPropertyAnimation :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QPropertyAnimationGc {}) = HoppyP.return this' instance QPropertyAnimationConstPtr QPropertyAnimation where toQPropertyAnimationConst (QPropertyAnimation ptr') = QPropertyAnimationConst $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQPropertyAnimationConst (QPropertyAnimationGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance QPropertyAnimationPtr QPropertyAnimation where toQPropertyAnimation = HoppyP.id instance M170.QVariantAnimationConstPtr QPropertyAnimation where toQVariantAnimationConst (QPropertyAnimation ptr') = M170.QVariantAnimationConst $ castQPropertyAnimationToQVariantAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQVariantAnimationConst (QPropertyAnimationGc fptr' ptr') = M170.QVariantAnimationConstGc fptr' $ castQPropertyAnimationToQVariantAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance M170.QVariantAnimationPtr QPropertyAnimation where toQVariantAnimation (QPropertyAnimation ptr') = M170.QVariantAnimation $ (HoppyF.castPtr :: HoppyF.Ptr M170.QVariantAnimationConst -> HoppyF.Ptr M170.QVariantAnimation) $ castQPropertyAnimationToQVariantAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQVariantAnimation (QPropertyAnimationGc fptr' ptr') = M170.QVariantAnimationGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M170.QVariantAnimationConst -> HoppyF.Ptr M170.QVariantAnimation) $ castQPropertyAnimationToQVariantAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance M2.QAbstractAnimationConstPtr QPropertyAnimation where toQAbstractAnimationConst (QPropertyAnimation ptr') = M2.QAbstractAnimationConst $ castQPropertyAnimationToQAbstractAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQAbstractAnimationConst (QPropertyAnimationGc fptr' ptr') = M2.QAbstractAnimationConstGc fptr' $ castQPropertyAnimationToQAbstractAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance M2.QAbstractAnimationPtr QPropertyAnimation where toQAbstractAnimation (QPropertyAnimation ptr') = M2.QAbstractAnimation $ (HoppyF.castPtr :: HoppyF.Ptr M2.QAbstractAnimationConst -> HoppyF.Ptr M2.QAbstractAnimation) $ castQPropertyAnimationToQAbstractAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQAbstractAnimation (QPropertyAnimationGc fptr' ptr') = M2.QAbstractAnimationGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M2.QAbstractAnimationConst -> HoppyF.Ptr M2.QAbstractAnimation) $ castQPropertyAnimationToQAbstractAnimation $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance M94.QObjectConstPtr QPropertyAnimation where toQObjectConst (QPropertyAnimation ptr') = M94.QObjectConst $ castQPropertyAnimationToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQObjectConst (QPropertyAnimationGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQPropertyAnimationToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' instance M94.QObjectPtr QPropertyAnimation where toQObject (QPropertyAnimation ptr') = M94.QObject $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQPropertyAnimationToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' toQObject (QPropertyAnimationGc fptr' ptr') = M94.QObjectGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQPropertyAnimationToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QPropertyAnimation -> HoppyF.Ptr QPropertyAnimationConst) ptr' class QPropertyAnimationSuper a where downToQPropertyAnimation :: a -> QPropertyAnimation instance QPropertyAnimationSuper M170.QVariantAnimation where downToQPropertyAnimation = castQPropertyAnimationToNonconst . cast' . M170.castQVariantAnimationToConst where cast' (M170.QVariantAnimationConst ptr') = QPropertyAnimationConst $ castQVariantAnimationToQPropertyAnimation ptr' cast' (M170.QVariantAnimationConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQVariantAnimationToQPropertyAnimation ptr' instance QPropertyAnimationSuper M2.QAbstractAnimation where downToQPropertyAnimation = castQPropertyAnimationToNonconst . cast' . M2.castQAbstractAnimationToConst where cast' (M2.QAbstractAnimationConst ptr') = QPropertyAnimationConst $ castQAbstractAnimationToQPropertyAnimation ptr' cast' (M2.QAbstractAnimationConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQAbstractAnimationToQPropertyAnimation ptr' instance QPropertyAnimationSuper M94.QObject where downToQPropertyAnimation = castQPropertyAnimationToNonconst . cast' . M94.castQObjectToConst where cast' (M94.QObjectConst ptr') = QPropertyAnimationConst $ castQObjectToQPropertyAnimation ptr' cast' (M94.QObjectConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQObjectToQPropertyAnimation ptr' class QPropertyAnimationSuperConst a where downToQPropertyAnimationConst :: a -> QPropertyAnimationConst instance QPropertyAnimationSuperConst M170.QVariantAnimationConst where downToQPropertyAnimationConst = cast' where cast' (M170.QVariantAnimationConst ptr') = QPropertyAnimationConst $ castQVariantAnimationToQPropertyAnimation ptr' cast' (M170.QVariantAnimationConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQVariantAnimationToQPropertyAnimation ptr' instance QPropertyAnimationSuperConst M2.QAbstractAnimationConst where downToQPropertyAnimationConst = cast' where cast' (M2.QAbstractAnimationConst ptr') = QPropertyAnimationConst $ castQAbstractAnimationToQPropertyAnimation ptr' cast' (M2.QAbstractAnimationConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQAbstractAnimationToQPropertyAnimation ptr' instance QPropertyAnimationSuperConst M94.QObjectConst where downToQPropertyAnimationConst = cast' where cast' (M94.QObjectConst ptr') = QPropertyAnimationConst $ castQObjectToQPropertyAnimation ptr' cast' (M94.QObjectConstGc fptr' ptr') = QPropertyAnimationConstGc fptr' $ castQObjectToQPropertyAnimation ptr' instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QPropertyAnimation)) QPropertyAnimation where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QPropertyAnimation)) QPropertyAnimation where decode = HoppyP.fmap QPropertyAnimation . HoppyF.peek