{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QDebug ( QDebugValue (..), QDebugConstPtr (..), autoInsertSpaces, verbosity, QDebugPtr (..), maybeQuote, maybeQuoteWithChar, maybeSpace, noquote, nospace, quote, resetFormat, setAutoInsertSpaces, setVerbosity, space, swap, verbosityWithLevel, sHLQChar, sHLBool, sHLChar, sHLShort, sHLUshort, sHLInt, sHLUint, sHLLong, sHLUlong, sHLQlonglong, sHLQulonglong, sHLFloat, sHLDouble, sHLPtrConstChar, sHLString, sHLByteArray, sHLPtrVoid, aSSIGN, QDebugConst (..), castQDebugToConst, QDebug (..), castQDebugToNonconst, newWithMsgType, newWithString, newWithIODevice, newCopy, QDebugSuper (..), QDebugSuperConst (..), ) where import Control.Monad ((>=>)) import qualified Data.Int as HoppyDI 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.QByteArray as M12 import qualified Graphics.UI.Qtah.Generated.Core.QChar as M16 import qualified Graphics.UI.Qtah.Generated.Core.QIODevice as M48 import qualified Graphics.UI.Qtah.Generated.Core.QString as M142 import qualified Graphics.UI.Qtah.Generated.Core.Types as M190 import Prelude (($), (.), (/=), (=<<), (==), (>>), (>>=)) import qualified Prelude as HoppyP foreign import ccall "genpop__QDebug_newWithMsgType" newWithMsgType' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_newWithString" newWithString' :: HoppyF.Ptr M142.QString -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_newWithIODevice" newWithIODevice' :: HoppyF.Ptr M48.QIODevice -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_newCopy" newCopy' :: HoppyF.Ptr QDebugConst -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_autoInsertSpaces" autoInsertSpaces' :: HoppyF.Ptr QDebugConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QDebug_maybeQuote" maybeQuote' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_maybeQuoteWithChar" maybeQuoteWithChar' :: HoppyF.Ptr QDebug -> HoppyFC.CChar -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_maybeSpace" maybeSpace' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_noquote" noquote' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_nospace" nospace' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_quote" quote' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_resetFormat" resetFormat' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_setAutoInsertSpaces" setAutoInsertSpaces' :: HoppyF.Ptr QDebug -> HoppyFC.CBool -> HoppyP.IO () foreign import ccall "genpop__QDebug_setVerbosity" setVerbosity' :: HoppyF.Ptr QDebug -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QDebug_space" space' :: HoppyF.Ptr QDebug -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_swap" swap' :: HoppyF.Ptr QDebug -> HoppyF.Ptr QDebug -> HoppyP.IO () foreign import ccall "genpop__QDebug_verbosityWithLevel" verbosityWithLevel' :: HoppyF.Ptr QDebug -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_verbosity" verbosity' :: HoppyF.Ptr QDebugConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QDebug_SHLQChar" sHLQChar' :: HoppyF.Ptr QDebug -> HoppyF.Ptr M16.QCharConst -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLBool" sHLBool' :: HoppyF.Ptr QDebug -> HoppyFC.CBool -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLChar" sHLChar' :: HoppyF.Ptr QDebug -> HoppyFC.CChar -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLShort" sHLShort' :: HoppyF.Ptr QDebug -> HoppyFC.CShort -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLUshort" sHLUshort' :: HoppyF.Ptr QDebug -> HoppyFC.CUShort -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLInt" sHLInt' :: HoppyF.Ptr QDebug -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLUint" sHLUint' :: HoppyF.Ptr QDebug -> HoppyFC.CUInt -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLLong" sHLLong' :: HoppyF.Ptr QDebug -> HoppyFC.CLong -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLUlong" sHLUlong' :: HoppyF.Ptr QDebug -> HoppyFC.CULong -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLQlonglong" sHLQlonglong' :: HoppyF.Ptr QDebug -> HoppyDI.Int64 -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLQulonglong" sHLQulonglong' :: HoppyF.Ptr QDebug -> HoppyDW.Word64 -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLFloat" sHLFloat' :: HoppyF.Ptr QDebug -> HoppyFC.CFloat -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLDouble" sHLDouble' :: HoppyF.Ptr QDebug -> HoppyFC.CDouble -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLPtrConstChar" sHLPtrConstChar' :: HoppyF.Ptr QDebug -> HoppyF.Ptr HoppyFC.CChar -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLString" sHLString' :: HoppyF.Ptr QDebug -> HoppyF.Ptr M142.QStringConst -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLByteArray" sHLByteArray' :: HoppyF.Ptr QDebug -> HoppyF.Ptr M12.QByteArrayConst -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_SHLPtrVoid" sHLPtrVoid' :: HoppyF.Ptr QDebug -> HoppyF.Ptr () -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "genpop__QDebug_ASSIGN" aSSIGN' :: HoppyF.Ptr QDebug -> HoppyF.Ptr QDebugConst -> HoppyP.IO (HoppyF.Ptr QDebug) foreign import ccall "gendel__QDebug" delete'QDebug :: HoppyF.Ptr QDebugConst -> HoppyP.IO () foreign import ccall "&gendel__QDebug" deletePtr'QDebug :: HoppyF.FunPtr (HoppyF.Ptr QDebugConst -> HoppyP.IO ()) class QDebugValue a where withQDebugPtr :: a -> (QDebugConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QDebugConstPtr a => QDebugValue a where withQDebugPtr = HoppyP.flip ($) . toQDebugConst class (HoppyFHR.CppPtr this) => QDebugConstPtr this where toQDebugConst :: this -> QDebugConst autoInsertSpaces :: (QDebugValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) autoInsertSpaces arg'1 = withQDebugPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (autoInsertSpaces' arg'1') verbosity :: (QDebugValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) verbosity arg'1 = withQDebugPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (verbosity' arg'1') class (QDebugConstPtr this) => QDebugPtr this where toQDebug :: this -> QDebug maybeQuote :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) maybeQuote arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (maybeQuote' arg'1') maybeQuoteWithChar :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CChar) -> (HoppyP.IO QDebug) maybeQuoteWithChar arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (maybeQuoteWithChar' arg'1' arg'2') maybeSpace :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) maybeSpace arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (maybeSpace' arg'1') noquote :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) noquote arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (noquote' arg'1') nospace :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) nospace arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (nospace' arg'1') quote :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) quote arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (quote' arg'1') resetFormat :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) resetFormat arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (resetFormat' arg'1') setAutoInsertSpaces :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Bool) -> (HoppyP.IO ()) setAutoInsertSpaces arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( \x -> HoppyP.return $ if x then 1 else 0 ) arg'2 >>= \arg'2' -> (setAutoInsertSpaces' arg'1' arg'2') setVerbosity :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO ()) setVerbosity arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (setVerbosity' arg'1' arg'2') space :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.IO QDebug) space arg'1 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyP.fmap QDebug (space' arg'1') swap :: (QDebugPtr this, QDebugPtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) swap arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (toQDebug arg'2) $ \arg'2' -> (swap' arg'1' arg'2') verbosityWithLevel :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO QDebug) verbosityWithLevel arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyP.fmap QDebug (verbosityWithLevel' arg'1' arg'2') sHLQChar :: (QDebugPtr this, M16.QCharValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QDebug) sHLQChar arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> M16.withQCharPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QDebug (sHLQChar' arg'1' arg'2') sHLBool :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Bool) -> (HoppyP.IO QDebug) sHLBool arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( \x -> HoppyP.return $ if x then 1 else 0 ) arg'2 >>= \arg'2' -> HoppyP.fmap QDebug (sHLBool' arg'1' arg'2') sHLChar :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CChar) -> (HoppyP.IO QDebug) sHLChar arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLChar' arg'1' arg'2') sHLShort :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CShort) -> (HoppyP.IO QDebug) sHLShort arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLShort' arg'1' arg'2') sHLUshort :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CUShort) -> (HoppyP.IO QDebug) sHLUshort arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLUshort' arg'1' arg'2') sHLInt :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO QDebug) sHLInt arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyP.fmap QDebug (sHLInt' arg'1' arg'2') sHLUint :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CUInt) -> (HoppyP.IO QDebug) sHLUint arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLUint' arg'1' arg'2') sHLLong :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CLong) -> (HoppyP.IO QDebug) sHLLong arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLLong' arg'1' arg'2') sHLUlong :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyFC.CULong) -> (HoppyP.IO QDebug) sHLUlong arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLUlong' arg'1' arg'2') sHLQlonglong :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyDI.Int64) -> (HoppyP.IO QDebug) sHLQlonglong arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLQlonglong' arg'1' arg'2') sHLQulonglong :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyDW.Word64) -> (HoppyP.IO QDebug) sHLQulonglong arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLQulonglong' arg'1' arg'2') sHLFloat :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Float) -> (HoppyP.IO QDebug) sHLFloat arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( HoppyP.return . HoppyP.realToFrac ) arg'2 >>= \arg'2' -> HoppyP.fmap QDebug (sHLFloat' arg'1' arg'2') sHLDouble :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyP.Double) -> (HoppyP.IO QDebug) sHLDouble arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> ( HoppyP.return . HoppyP.realToFrac ) arg'2 >>= \arg'2' -> HoppyP.fmap QDebug (sHLDouble' arg'1' arg'2') sHLPtrConstChar :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyF.Ptr HoppyFC.CChar) -> (HoppyP.IO QDebug) sHLPtrConstChar arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLPtrConstChar' arg'1' arg'2') sHLString :: (QDebugPtr this, M142.QStringValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QDebug) sHLString arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> M142.withQStringPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QDebug (sHLString' arg'1' arg'2') sHLByteArray :: (QDebugPtr this, M12.QByteArrayValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QDebug) sHLByteArray arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QDebug (sHLByteArray' arg'1' arg'2') sHLPtrVoid :: (QDebugPtr this) => (this) {- ^ this -} -> (HoppyF.Ptr ()) -> (HoppyP.IO QDebug) sHLPtrVoid arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> let arg'2' = arg'2 in HoppyP.fmap QDebug (sHLPtrVoid' arg'1' arg'2') aSSIGN :: (QDebugPtr this, QDebugValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QDebug) aSSIGN arg'1 arg'2 = HoppyFHR.withCppPtr (toQDebug arg'1) $ \arg'1' -> withQDebugPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QDebug (aSSIGN' arg'1' arg'2') data QDebugConst = QDebugConst (HoppyF.Ptr QDebugConst) | QDebugConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QDebugConst) deriving (HoppyP.Show) instance HoppyP.Eq QDebugConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QDebugConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQDebugToConst :: QDebug -> QDebugConst castQDebugToConst (QDebug ptr') = QDebugConst $ HoppyF.castPtr ptr' castQDebugToConst (QDebugGc fptr' ptr') = QDebugConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QDebugConst where nullptr = QDebugConst HoppyF.nullPtr withCppPtr (QDebugConst ptr') f' = f' ptr' withCppPtr (QDebugConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QDebugConst ptr') = ptr' toPtr (QDebugConstGc _ ptr') = ptr' touchCppPtr (QDebugConst _) = HoppyP.return () touchCppPtr (QDebugConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QDebugConst where delete (QDebugConst ptr') = delete'QDebug ptr' delete (QDebugConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QDebugConst", " object."] toGc this'@(QDebugConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QDebugConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QDebug :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QDebugConstGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QDebugConst QDebug where copy = newCopy instance QDebugConstPtr QDebugConst where toQDebugConst = HoppyP.id data QDebug = QDebug (HoppyF.Ptr QDebug) | QDebugGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QDebug) deriving (HoppyP.Show) instance HoppyP.Eq QDebug where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QDebug where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQDebugToNonconst :: QDebugConst -> QDebug castQDebugToNonconst (QDebugConst ptr') = QDebug $ HoppyF.castPtr ptr' castQDebugToNonconst (QDebugConstGc fptr' ptr') = QDebugGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QDebug where nullptr = QDebug HoppyF.nullPtr withCppPtr (QDebug ptr') f' = f' ptr' withCppPtr (QDebugGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QDebug ptr') = ptr' toPtr (QDebugGc _ ptr') = ptr' touchCppPtr (QDebug _) = HoppyP.return () touchCppPtr (QDebugGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QDebug where delete (QDebug ptr') = delete'QDebug $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QDebugConst) delete (QDebugGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QDebug", " object."] toGc this'@(QDebug ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QDebugGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QDebug :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QDebugGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QDebug QDebug where copy = newCopy instance QDebugConstPtr QDebug where toQDebugConst (QDebug ptr') = QDebugConst $ (HoppyF.castPtr :: HoppyF.Ptr QDebug -> HoppyF.Ptr QDebugConst) ptr' toQDebugConst (QDebugGc fptr' ptr') = QDebugConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QDebug -> HoppyF.Ptr QDebugConst) ptr' instance QDebugPtr QDebug where toQDebug = HoppyP.id newWithMsgType :: (M190.QtMsgType) -> (HoppyP.IO QDebug) newWithMsgType arg'1 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyP.fmap QDebug (newWithMsgType' arg'1') newWithString :: (M142.QStringPtr arg'1) => (arg'1) -> (HoppyP.IO QDebug) newWithString arg'1 = HoppyFHR.withCppPtr (M142.toQString arg'1) $ \arg'1' -> HoppyP.fmap QDebug (newWithString' arg'1') newWithIODevice :: (M48.QIODevicePtr arg'1) => (arg'1) -> (HoppyP.IO QDebug) newWithIODevice arg'1 = HoppyFHR.withCppPtr (M48.toQIODevice arg'1) $ \arg'1' -> HoppyP.fmap QDebug (newWithIODevice' arg'1') newCopy :: (QDebugValue arg'1) => (arg'1) -> (HoppyP.IO QDebug) newCopy arg'1 = withQDebugPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QDebug (newCopy' arg'1') class QDebugSuper a where downToQDebug :: a -> QDebug class QDebugSuperConst a where downToQDebugConst :: a -> QDebugConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QDebug)) QDebug where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance QDebugValue a => HoppyFHR.Assignable QDebug a where assign x' y' = aSSIGN x' y' >> HoppyP.return () instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QDebug)) QDebug where decode = HoppyP.fmap QDebug . HoppyF.peek instance HoppyFHR.Decodable QDebug (QDebug) where decode = HoppyFHR.decode . toQDebugConst instance HoppyFHR.Decodable QDebugConst (QDebug) where decode = HoppyFHR.copy >=> HoppyFHR.toGc