{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Gui.QBrush ( QBrushValue (..), QBrushConstPtr (..), color, isOpaque, style, texture, textureImage, transform, eQ, nE, QBrushPtr (..), setColor, setGlobalColor, setStyle, swap, setTexture, setTextureImage, setTransform, aSSIGN, QBrushConst (..), castQBrushToConst, QBrush (..), castQBrushToNonconst, new, newWithColor, newCopy, QBrushSuper (..), QBrushSuperConst (..), ) where import Control.Monad ((>=>)) 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.Types as M190 import qualified Graphics.UI.Qtah.Generated.Gui.QColor as M252 import {-# SOURCE #-} qualified Graphics.UI.Qtah.Generated.Gui.QImage as M292 import {-# SOURCE #-} qualified Graphics.UI.Qtah.Generated.Gui.QPixmap as M316 import qualified Graphics.UI.Qtah.Generated.Gui.QTransform as M336 import qualified Graphics.UI.Qtah.Gui.HColor as HColor import Prelude (($), (.), (/=), (=<<), (==), (>>), (>>=)) import qualified Prelude as HoppyP foreign import ccall "genpop__QBrush_new" new' :: HoppyP.IO (HoppyF.Ptr QBrush) foreign import ccall "genpop__QBrush_newWithColor" newWithColor' :: HoppyF.Ptr M252.QColorConst -> HoppyP.IO (HoppyF.Ptr QBrush) foreign import ccall "genpop__QBrush_newCopy" newCopy' :: HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr QBrush) foreign import ccall "genpop__QBrush_color" color' :: HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr M252.QColorConst) foreign import ccall "genpop__QBrush_setColor" setColor' :: HoppyF.Ptr QBrush -> HoppyF.Ptr M252.QColorConst -> HoppyP.IO () foreign import ccall "genpop__QBrush_isOpaque" isOpaque' :: HoppyF.Ptr QBrushConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QBrush_setGlobalColor" setGlobalColor' :: HoppyF.Ptr QBrush -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QBrush_style" style' :: HoppyF.Ptr QBrushConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QBrush_setStyle" setStyle' :: HoppyF.Ptr QBrush -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QBrush_swap" swap' :: HoppyF.Ptr QBrush -> HoppyF.Ptr QBrush -> HoppyP.IO () foreign import ccall "genpop__QBrush_texture" texture' :: HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr M316.QPixmapConst) foreign import ccall "genpop__QBrush_setTexture" setTexture' :: HoppyF.Ptr QBrush -> HoppyF.Ptr M316.QPixmapConst -> HoppyP.IO () foreign import ccall "genpop__QBrush_textureImage" textureImage' :: HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr M292.QImageConst) foreign import ccall "genpop__QBrush_setTextureImage" setTextureImage' :: HoppyF.Ptr QBrush -> HoppyF.Ptr M292.QImageConst -> HoppyP.IO () foreign import ccall "genpop__QBrush_transform" transform' :: HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr M336.QTransformConst) foreign import ccall "genpop__QBrush_setTransform" setTransform' :: HoppyF.Ptr QBrush -> HoppyF.Ptr M336.QTransformConst -> HoppyP.IO () foreign import ccall "genpop__QBrush_EQ" eQ' :: HoppyF.Ptr QBrushConst -> HoppyF.Ptr QBrushConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QBrush_NE" nE' :: HoppyF.Ptr QBrushConst -> HoppyF.Ptr QBrushConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QBrush_ASSIGN" aSSIGN' :: HoppyF.Ptr QBrush -> HoppyF.Ptr QBrushConst -> HoppyP.IO (HoppyF.Ptr QBrush) foreign import ccall "gendel__QBrush" delete'QBrush :: HoppyF.Ptr QBrushConst -> HoppyP.IO () foreign import ccall "&gendel__QBrush" deletePtr'QBrush :: HoppyF.FunPtr (HoppyF.Ptr QBrushConst -> HoppyP.IO ()) class QBrushValue a where withQBrushPtr :: a -> (QBrushConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QBrushConstPtr a => QBrushValue a where withQBrushPtr = HoppyP.flip ($) . toQBrushConst class (HoppyFHR.CppPtr this) => QBrushConstPtr this where toQBrushConst :: this -> QBrushConst color :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO HColor.HColor) color arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M252.QColorConst) =<< (color' arg'1') isOpaque :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) isOpaque arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (isOpaque' arg'1') style :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO M190.QtBrushStyle) style arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.toCppEnum ) =<< (style' arg'1') texture :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO M316.QPixmap) texture arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M316.QPixmapConst) =<< (texture' arg'1') textureImage :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO M292.QImage) textureImage arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M292.QImageConst) =<< (textureImage' arg'1') transform :: (QBrushValue this) => (this) {- ^ this -} -> (HoppyP.IO M336.QTransform) transform arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M336.QTransformConst) =<< (transform' arg'1') eQ :: (QBrushValue this, QBrushValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) eQ arg'1 arg'2 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQBrushPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (eQ' arg'1' arg'2') nE :: (QBrushValue this, QBrushValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) nE arg'1 arg'2 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQBrushPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (nE' arg'1' arg'2') class (QBrushConstPtr this) => QBrushPtr this where toQBrush :: this -> QBrush setColor :: (QBrushPtr this, M252.QColorValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setColor arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> M252.withQColorPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setColor' arg'1' arg'2') setGlobalColor :: (QBrushPtr this) => (this) {- ^ this -} -> (M190.QtGlobalColor) -> (HoppyP.IO ()) setGlobalColor arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'2 >>= \arg'2' -> (setGlobalColor' arg'1' arg'2') setStyle :: (QBrushPtr this) => (this) {- ^ this -} -> (M190.QtBrushStyle) -> (HoppyP.IO ()) setStyle arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'2 >>= \arg'2' -> (setStyle' arg'1' arg'2') swap :: (QBrushPtr this, QBrushPtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) swap arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (toQBrush arg'2) $ \arg'2' -> (swap' arg'1' arg'2') setTexture :: (QBrushPtr this, M316.QPixmapValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setTexture arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> M316.withQPixmapPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setTexture' arg'1' arg'2') setTextureImage :: (QBrushPtr this, M292.QImageValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setTextureImage arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> M292.withQImagePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setTextureImage' arg'1' arg'2') setTransform :: (QBrushPtr this, M336.QTransformValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setTransform arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> M336.withQTransformPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setTransform' arg'1' arg'2') aSSIGN :: (QBrushPtr this, QBrushValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QBrush) aSSIGN arg'1 arg'2 = HoppyFHR.withCppPtr (toQBrush arg'1) $ \arg'1' -> withQBrushPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QBrush (aSSIGN' arg'1' arg'2') data QBrushConst = QBrushConst (HoppyF.Ptr QBrushConst) | QBrushConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QBrushConst) deriving (HoppyP.Show) instance HoppyP.Eq QBrushConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QBrushConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQBrushToConst :: QBrush -> QBrushConst castQBrushToConst (QBrush ptr') = QBrushConst $ HoppyF.castPtr ptr' castQBrushToConst (QBrushGc fptr' ptr') = QBrushConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QBrushConst where nullptr = QBrushConst HoppyF.nullPtr withCppPtr (QBrushConst ptr') f' = f' ptr' withCppPtr (QBrushConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QBrushConst ptr') = ptr' toPtr (QBrushConstGc _ ptr') = ptr' touchCppPtr (QBrushConst _) = HoppyP.return () touchCppPtr (QBrushConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QBrushConst where delete (QBrushConst ptr') = delete'QBrush ptr' delete (QBrushConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QBrushConst", " object."] toGc this'@(QBrushConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QBrushConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QBrush :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QBrushConstGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QBrushConst QBrush where copy = newCopy instance QBrushConstPtr QBrushConst where toQBrushConst = HoppyP.id data QBrush = QBrush (HoppyF.Ptr QBrush) | QBrushGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QBrush) deriving (HoppyP.Show) instance HoppyP.Eq QBrush where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QBrush where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQBrushToNonconst :: QBrushConst -> QBrush castQBrushToNonconst (QBrushConst ptr') = QBrush $ HoppyF.castPtr ptr' castQBrushToNonconst (QBrushConstGc fptr' ptr') = QBrushGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QBrush where nullptr = QBrush HoppyF.nullPtr withCppPtr (QBrush ptr') f' = f' ptr' withCppPtr (QBrushGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QBrush ptr') = ptr' toPtr (QBrushGc _ ptr') = ptr' touchCppPtr (QBrush _) = HoppyP.return () touchCppPtr (QBrushGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QBrush where delete (QBrush ptr') = delete'QBrush $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QBrushConst) delete (QBrushGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QBrush", " object."] toGc this'@(QBrush ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QBrushGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QBrush :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QBrushGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QBrush QBrush where copy = newCopy instance QBrushConstPtr QBrush where toQBrushConst (QBrush ptr') = QBrushConst $ (HoppyF.castPtr :: HoppyF.Ptr QBrush -> HoppyF.Ptr QBrushConst) ptr' toQBrushConst (QBrushGc fptr' ptr') = QBrushConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QBrush -> HoppyF.Ptr QBrushConst) ptr' instance QBrushPtr QBrush where toQBrush = HoppyP.id new :: (HoppyP.IO QBrush) new = HoppyP.fmap QBrush (new') newWithColor :: (M252.QColorValue arg'1) => (arg'1) -> (HoppyP.IO QBrush) newWithColor arg'1 = M252.withQColorPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QBrush (newWithColor' arg'1') newCopy :: (QBrushValue arg'1) => (arg'1) -> (HoppyP.IO QBrush) newCopy arg'1 = withQBrushPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QBrush (newCopy' arg'1') class QBrushSuper a where downToQBrush :: a -> QBrush class QBrushSuperConst a where downToQBrushConst :: a -> QBrushConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QBrush)) QBrush where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance QBrushValue a => HoppyFHR.Assignable QBrush a where assign x' y' = aSSIGN x' y' >> HoppyP.return () instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QBrush)) QBrush where decode = HoppyP.fmap QBrush . HoppyF.peek instance HoppyFHR.Decodable QBrush (QBrush) where decode = HoppyFHR.decode . toQBrushConst instance HoppyFHR.Decodable QBrushConst (QBrush) where decode = HoppyFHR.copy >=> HoppyFHR.toGc