{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QFileSelector ( castQFileSelectorToQObject, castQObjectToQFileSelector, QFileSelectorValue (..), QFileSelectorConstPtr (..), allSelectors, extraSelectors, select, QFileSelectorPtr (..), setExtraSelectors, QFileSelectorConst (..), castQFileSelectorToConst, QFileSelector (..), castQFileSelectorToNonconst, new, newWithParent, QFileSelectorSuper (..), QFileSelectorSuperConst (..), ) where import qualified Foreign as HoppyF import qualified Foreign.Hoppy.Runtime as HoppyFHR import qualified Graphics.UI.Qtah.Generated.Core.QObject as M94 import qualified Graphics.UI.Qtah.Generated.Core.QString as M142 import qualified Graphics.UI.Qtah.Generated.Core.QStringList as M144 import Prelude (($), (.), (=<<), (==)) import qualified Prelude as HoppyP import qualified Prelude as QtahP foreign import ccall "genpop__QFileSelector_new" new' :: HoppyP.IO (HoppyF.Ptr QFileSelector) foreign import ccall "genpop__QFileSelector_newWithParent" newWithParent' :: HoppyF.Ptr M94.QObject -> HoppyP.IO (HoppyF.Ptr QFileSelector) foreign import ccall "genpop__QFileSelector_allSelectors" allSelectors' :: HoppyF.Ptr QFileSelectorConst -> HoppyP.IO (HoppyF.Ptr M144.QStringListConst) foreign import ccall "genpop__QFileSelector_extraSelectors" extraSelectors' :: HoppyF.Ptr QFileSelectorConst -> HoppyP.IO (HoppyF.Ptr M144.QStringListConst) foreign import ccall "genpop__QFileSelector_select" select' :: HoppyF.Ptr QFileSelectorConst -> HoppyF.Ptr M142.QStringConst -> HoppyP.IO (HoppyF.Ptr M142.QStringConst) foreign import ccall "genpop__QFileSelector_setExtraSelectors" setExtraSelectors' :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr M144.QStringListConst -> HoppyP.IO () foreign import ccall "gencast__QFileSelector__QObject" castQFileSelectorToQObject :: HoppyF.Ptr QFileSelectorConst -> HoppyF.Ptr M94.QObjectConst foreign import ccall "gencast__QObject__QFileSelector" castQObjectToQFileSelector :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr QFileSelectorConst foreign import ccall "gendel__QFileSelector" delete'QFileSelector :: HoppyF.Ptr QFileSelectorConst -> HoppyP.IO () foreign import ccall "&gendel__QFileSelector" deletePtr'QFileSelector :: HoppyF.FunPtr (HoppyF.Ptr QFileSelectorConst -> HoppyP.IO ()) class QFileSelectorValue a where withQFileSelectorPtr :: a -> (QFileSelectorConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QFileSelectorConstPtr a => QFileSelectorValue a where withQFileSelectorPtr = HoppyP.flip ($) . toQFileSelectorConst class (M94.QObjectConstPtr this) => QFileSelectorConstPtr this where toQFileSelectorConst :: this -> QFileSelectorConst allSelectors :: (QFileSelectorValue this) => (this) {- ^ this -} -> (HoppyP.IO [QtahP.String]) allSelectors arg'1 = withQFileSelectorPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M144.QStringListConst) =<< (allSelectors' arg'1') extraSelectors :: (QFileSelectorValue this) => (this) {- ^ this -} -> (HoppyP.IO [QtahP.String]) extraSelectors arg'1 = withQFileSelectorPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M144.QStringListConst) =<< (extraSelectors' arg'1') select :: (QFileSelectorValue this, M142.QStringValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QtahP.String) select arg'1 arg'2 = withQFileSelectorPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M142.withQStringPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (HoppyFHR.decodeAndDelete . M142.QStringConst) =<< (select' arg'1' arg'2') class (QFileSelectorConstPtr this, M94.QObjectPtr this) => QFileSelectorPtr this where toQFileSelector :: this -> QFileSelector setExtraSelectors :: (QFileSelectorPtr this, M144.QStringListValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setExtraSelectors arg'1 arg'2 = HoppyFHR.withCppPtr (toQFileSelector arg'1) $ \arg'1' -> M144.withQStringListPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setExtraSelectors' arg'1' arg'2') data QFileSelectorConst = QFileSelectorConst (HoppyF.Ptr QFileSelectorConst) | QFileSelectorConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QFileSelectorConst) deriving (HoppyP.Show) instance HoppyP.Eq QFileSelectorConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QFileSelectorConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQFileSelectorToConst :: QFileSelector -> QFileSelectorConst castQFileSelectorToConst (QFileSelector ptr') = QFileSelectorConst $ HoppyF.castPtr ptr' castQFileSelectorToConst (QFileSelectorGc fptr' ptr') = QFileSelectorConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QFileSelectorConst where nullptr = QFileSelectorConst HoppyF.nullPtr withCppPtr (QFileSelectorConst ptr') f' = f' ptr' withCppPtr (QFileSelectorConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QFileSelectorConst ptr') = ptr' toPtr (QFileSelectorConstGc _ ptr') = ptr' touchCppPtr (QFileSelectorConst _) = HoppyP.return () touchCppPtr (QFileSelectorConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QFileSelectorConst where delete (QFileSelectorConst ptr') = delete'QFileSelector ptr' delete (QFileSelectorConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QFileSelectorConst", " object."] toGc this'@(QFileSelectorConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QFileSelectorConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QFileSelector :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QFileSelectorConstGc {}) = HoppyP.return this' instance QFileSelectorConstPtr QFileSelectorConst where toQFileSelectorConst = HoppyP.id instance M94.QObjectConstPtr QFileSelectorConst where toQObjectConst (QFileSelectorConst ptr') = M94.QObjectConst $ castQFileSelectorToQObject ptr' toQObjectConst (QFileSelectorConstGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQFileSelectorToQObject ptr' data QFileSelector = QFileSelector (HoppyF.Ptr QFileSelector) | QFileSelectorGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QFileSelector) deriving (HoppyP.Show) instance HoppyP.Eq QFileSelector where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QFileSelector where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQFileSelectorToNonconst :: QFileSelectorConst -> QFileSelector castQFileSelectorToNonconst (QFileSelectorConst ptr') = QFileSelector $ HoppyF.castPtr ptr' castQFileSelectorToNonconst (QFileSelectorConstGc fptr' ptr') = QFileSelectorGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QFileSelector where nullptr = QFileSelector HoppyF.nullPtr withCppPtr (QFileSelector ptr') f' = f' ptr' withCppPtr (QFileSelectorGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QFileSelector ptr') = ptr' toPtr (QFileSelectorGc _ ptr') = ptr' touchCppPtr (QFileSelector _) = HoppyP.return () touchCppPtr (QFileSelectorGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QFileSelector where delete (QFileSelector ptr') = delete'QFileSelector $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QFileSelectorConst) delete (QFileSelectorGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QFileSelector", " object."] toGc this'@(QFileSelector ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QFileSelectorGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QFileSelector :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QFileSelectorGc {}) = HoppyP.return this' instance QFileSelectorConstPtr QFileSelector where toQFileSelectorConst (QFileSelector ptr') = QFileSelectorConst $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' toQFileSelectorConst (QFileSelectorGc fptr' ptr') = QFileSelectorConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' instance QFileSelectorPtr QFileSelector where toQFileSelector = HoppyP.id instance M94.QObjectConstPtr QFileSelector where toQObjectConst (QFileSelector ptr') = M94.QObjectConst $ castQFileSelectorToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' toQObjectConst (QFileSelectorGc fptr' ptr') = M94.QObjectConstGc fptr' $ castQFileSelectorToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' instance M94.QObjectPtr QFileSelector where toQObject (QFileSelector ptr') = M94.QObject $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQFileSelectorToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' toQObject (QFileSelectorGc fptr' ptr') = M94.QObjectGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr M94.QObjectConst -> HoppyF.Ptr M94.QObject) $ castQFileSelectorToQObject $ (HoppyF.castPtr :: HoppyF.Ptr QFileSelector -> HoppyF.Ptr QFileSelectorConst) ptr' new :: (HoppyP.IO QFileSelector) new = HoppyP.fmap QFileSelector (new') newWithParent :: (M94.QObjectPtr arg'1) => (arg'1) -> (HoppyP.IO QFileSelector) newWithParent arg'1 = HoppyFHR.withCppPtr (M94.toQObject arg'1) $ \arg'1' -> HoppyP.fmap QFileSelector (newWithParent' arg'1') class QFileSelectorSuper a where downToQFileSelector :: a -> QFileSelector instance QFileSelectorSuper M94.QObject where downToQFileSelector = castQFileSelectorToNonconst . cast' . M94.castQObjectToConst where cast' (M94.QObjectConst ptr') = QFileSelectorConst $ castQObjectToQFileSelector ptr' cast' (M94.QObjectConstGc fptr' ptr') = QFileSelectorConstGc fptr' $ castQObjectToQFileSelector ptr' class QFileSelectorSuperConst a where downToQFileSelectorConst :: a -> QFileSelectorConst instance QFileSelectorSuperConst M94.QObjectConst where downToQFileSelectorConst = cast' where cast' (M94.QObjectConst ptr') = QFileSelectorConst $ castQObjectToQFileSelector ptr' cast' (M94.QObjectConstGc fptr' ptr') = QFileSelectorConstGc fptr' $ castQObjectToQFileSelector ptr' instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QFileSelector)) QFileSelector where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QFileSelector)) QFileSelector where decode = HoppyP.fmap QFileSelector . HoppyF.peek