{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QPair.IntInt ( QPairIntIntValue (..), QPairIntIntConstPtr (..), QPairIntIntPtr (..), swap, aSSIGN, QPairIntIntConst (..), castQPairIntIntToConst, QPairIntInt (..), castQPairIntIntToNonconst, new, newWithValues, newCopy, QPairIntIntSuper (..), QPairIntIntSuperConst (..), ) where import qualified Foreign as HoppyF import qualified Foreign.C as HoppyFC import qualified Foreign.Hoppy.Runtime as HoppyFHR import Prelude (($), (.), (==), (>>)) import qualified Prelude as HoppyP foreign import ccall "genpop__QPairIntInt_new" new' :: HoppyP.IO (HoppyF.Ptr QPairIntInt) foreign import ccall "genpop__QPairIntInt_newWithValues" newWithValues' :: HoppyF.Ptr HoppyFC.CInt -> HoppyF.Ptr HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QPairIntInt) foreign import ccall "genpop__QPairIntInt_newCopy" newCopy' :: HoppyF.Ptr QPairIntIntConst -> HoppyP.IO (HoppyF.Ptr QPairIntInt) foreign import ccall "genpop__QPairIntInt_swap" swap' :: HoppyF.Ptr QPairIntInt -> HoppyF.Ptr QPairIntInt -> HoppyP.IO () foreign import ccall "genpop__QPairIntInt_ASSIGN" aSSIGN' :: HoppyF.Ptr QPairIntInt -> HoppyF.Ptr QPairIntIntConst -> HoppyP.IO (HoppyF.Ptr QPairIntInt) foreign import ccall "gendel__QPairIntInt" delete'QPairIntInt :: HoppyF.Ptr QPairIntIntConst -> HoppyP.IO () foreign import ccall "&gendel__QPairIntInt" deletePtr'QPairIntInt :: HoppyF.FunPtr (HoppyF.Ptr QPairIntIntConst -> HoppyP.IO ()) class QPairIntIntValue a where withQPairIntIntPtr :: a -> (QPairIntIntConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QPairIntIntConstPtr a => QPairIntIntValue a where withQPairIntIntPtr = HoppyP.flip ($) . toQPairIntIntConst class (HoppyFHR.CppPtr this) => QPairIntIntConstPtr this where toQPairIntIntConst :: this -> QPairIntIntConst class (QPairIntIntConstPtr this) => QPairIntIntPtr this where toQPairIntInt :: this -> QPairIntInt swap :: (QPairIntIntPtr this, QPairIntIntPtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) swap arg'1 arg'2 = HoppyFHR.withCppPtr (toQPairIntInt arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (toQPairIntInt arg'2) $ \arg'2' -> (swap' arg'1' arg'2') aSSIGN :: (QPairIntIntPtr this, QPairIntIntValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QPairIntInt) aSSIGN arg'1 arg'2 = HoppyFHR.withCppPtr (toQPairIntInt arg'1) $ \arg'1' -> withQPairIntIntPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QPairIntInt (aSSIGN' arg'1' arg'2') data QPairIntIntConst = QPairIntIntConst (HoppyF.Ptr QPairIntIntConst) | QPairIntIntConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QPairIntIntConst) deriving (HoppyP.Show) instance HoppyP.Eq QPairIntIntConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QPairIntIntConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQPairIntIntToConst :: QPairIntInt -> QPairIntIntConst castQPairIntIntToConst (QPairIntInt ptr') = QPairIntIntConst $ HoppyF.castPtr ptr' castQPairIntIntToConst (QPairIntIntGc fptr' ptr') = QPairIntIntConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QPairIntIntConst where nullptr = QPairIntIntConst HoppyF.nullPtr withCppPtr (QPairIntIntConst ptr') f' = f' ptr' withCppPtr (QPairIntIntConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QPairIntIntConst ptr') = ptr' toPtr (QPairIntIntConstGc _ ptr') = ptr' touchCppPtr (QPairIntIntConst _) = HoppyP.return () touchCppPtr (QPairIntIntConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QPairIntIntConst where delete (QPairIntIntConst ptr') = delete'QPairIntInt ptr' delete (QPairIntIntConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QPairIntIntConst", " object."] toGc this'@(QPairIntIntConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QPairIntIntConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QPairIntInt :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QPairIntIntConstGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QPairIntIntConst QPairIntInt where copy = newCopy instance QPairIntIntConstPtr QPairIntIntConst where toQPairIntIntConst = HoppyP.id data QPairIntInt = QPairIntInt (HoppyF.Ptr QPairIntInt) | QPairIntIntGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QPairIntInt) deriving (HoppyP.Show) instance HoppyP.Eq QPairIntInt where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QPairIntInt where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQPairIntIntToNonconst :: QPairIntIntConst -> QPairIntInt castQPairIntIntToNonconst (QPairIntIntConst ptr') = QPairIntInt $ HoppyF.castPtr ptr' castQPairIntIntToNonconst (QPairIntIntConstGc fptr' ptr') = QPairIntIntGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QPairIntInt where nullptr = QPairIntInt HoppyF.nullPtr withCppPtr (QPairIntInt ptr') f' = f' ptr' withCppPtr (QPairIntIntGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QPairIntInt ptr') = ptr' toPtr (QPairIntIntGc _ ptr') = ptr' touchCppPtr (QPairIntInt _) = HoppyP.return () touchCppPtr (QPairIntIntGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QPairIntInt where delete (QPairIntInt ptr') = delete'QPairIntInt $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QPairIntIntConst) delete (QPairIntIntGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QPairIntInt", " object."] toGc this'@(QPairIntInt ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QPairIntIntGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QPairIntInt :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QPairIntIntGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QPairIntInt QPairIntInt where copy = newCopy instance QPairIntIntConstPtr QPairIntInt where toQPairIntIntConst (QPairIntInt ptr') = QPairIntIntConst $ (HoppyF.castPtr :: HoppyF.Ptr QPairIntInt -> HoppyF.Ptr QPairIntIntConst) ptr' toQPairIntIntConst (QPairIntIntGc fptr' ptr') = QPairIntIntConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QPairIntInt -> HoppyF.Ptr QPairIntIntConst) ptr' instance QPairIntIntPtr QPairIntInt where toQPairIntInt = HoppyP.id new :: (HoppyP.IO QPairIntInt) new = HoppyP.fmap QPairIntInt (new') newWithValues :: (HoppyF.Ptr HoppyFC.CInt) -> (HoppyF.Ptr HoppyFC.CInt) -> (HoppyP.IO QPairIntInt) newWithValues arg'1 arg'2 = let arg'1' = arg'1 in let arg'2' = arg'2 in HoppyP.fmap QPairIntInt (newWithValues' arg'1' arg'2') newCopy :: (QPairIntIntValue arg'1) => (arg'1) -> (HoppyP.IO QPairIntInt) newCopy arg'1 = withQPairIntIntPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QPairIntInt (newCopy' arg'1') class QPairIntIntSuper a where downToQPairIntInt :: a -> QPairIntInt class QPairIntIntSuperConst a where downToQPairIntIntConst :: a -> QPairIntIntConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QPairIntInt)) QPairIntInt where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance QPairIntIntValue a => HoppyFHR.Assignable QPairIntInt a where assign x' y' = aSSIGN x' y' >> HoppyP.return () instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QPairIntInt)) QPairIntInt where decode = HoppyP.fmap QPairIntInt . HoppyF.peek