{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QVector.QXmlStreamAttribute ( QVectorQXmlStreamAttributeValue (..), QVectorQXmlStreamAttributeConstPtr (..), atConst, capacity, contains, count, arrayConst, endsWith, firstConst, get, indexOf, indexOfFrom, isEmpty, lastConst, lastIndexOf, lastIndexOfFrom, mid, midLength, size, startsWith, value, valueOr, aDD, QVectorQXmlStreamAttributePtr (..), append, appendVector, at, clear, array, fill, fillResize, first, insert, insertMany, last, prepend, remove, removeMany, removeAll, removeFirst, removeLast, removeOne, replace, reserve, resize, squeeze, swap, takeAt, takeFirst, takeLast, aSSIGN, QVectorQXmlStreamAttributeConst (..), castQVectorQXmlStreamAttributeToConst, QVectorQXmlStreamAttribute (..), castQVectorQXmlStreamAttributeToNonconst, new, newWithSize, newWithSizeAndValue, newCopy, QVectorQXmlStreamAttributeSuper (..), QVectorQXmlStreamAttributeSuperConst (..), ) where import Control.Monad ((<=<)) import qualified Foreign as HoppyF import qualified Foreign.C as HoppyFC import qualified Foreign.Hoppy.Runtime as HoppyFHR import qualified Foreign.Hoppy.Runtime as QtahFHR import qualified Graphics.UI.Qtah.Generated.Core.QXmlStreamAttribute as M174 import Prelude (($), (-), (.), (/=), (=<<), (==), (>>), (>>=)) import qualified Prelude as HoppyP import qualified Prelude as QtahP foreign import ccall "genpop__QVectorQXmlStreamAttribute_new" new' :: HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_newWithSize" newWithSize' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_newWithSizeAndValue" newWithSizeAndValue' :: HoppyFC.CInt -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_newCopy" newCopy' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_append" append' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_appendVector" appendVector' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_at" at' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_atConst" atConst' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_capacity" capacity' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_clear" clear' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_contains" contains' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QVectorQXmlStreamAttribute_count" count' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_array" array' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_arrayConst" arrayConst' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_endsWith" endsWith' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QVectorQXmlStreamAttribute_fill" fill' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_fillResize" fillResize' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_first" first' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_firstConst" firstConst' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_get" get' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_indexOf" indexOf' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_indexOfFrom" indexOfFrom' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_insert" insert' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_insertMany" insertMany' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_isEmpty" isEmpty' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QVectorQXmlStreamAttribute_last" last' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_lastConst" lastConst' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_lastIndexOf" lastIndexOf' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_lastIndexOfFrom" lastIndexOfFrom' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_mid" mid' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_midLength" midLength' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_prepend" prepend' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_remove" remove' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_removeMany" removeMany' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_removeAll" removeAll' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_removeFirst" removeFirst' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_removeLast" removeLast' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_removeOne" removeOne' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QVectorQXmlStreamAttribute_replace" replace' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_reserve" reserve' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_resize" resize' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_size" size' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QVectorQXmlStreamAttribute_squeeze" squeeze' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_startsWith" startsWith' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QVectorQXmlStreamAttribute_swap" swap' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO () foreign import ccall "genpop__QVectorQXmlStreamAttribute_takeAt" takeAt' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_takeFirst" takeFirst' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_takeLast" takeLast' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_value" value' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_valueOr" valueOr' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyFC.CInt -> HoppyF.Ptr M174.QXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr M174.QXmlStreamAttributeConst) foreign import ccall "genpop__QVectorQXmlStreamAttribute_ADD" aDD' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "genpop__QVectorQXmlStreamAttribute_ASSIGN" aSSIGN' :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO (HoppyF.Ptr QVectorQXmlStreamAttribute) foreign import ccall "gendel__QVectorQXmlStreamAttribute" delete'QVectorQXmlStreamAttribute :: HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO () foreign import ccall "&gendel__QVectorQXmlStreamAttribute" deletePtr'QVectorQXmlStreamAttribute :: HoppyF.FunPtr (HoppyF.Ptr QVectorQXmlStreamAttributeConst -> HoppyP.IO ()) class QVectorQXmlStreamAttributeValue a where withQVectorQXmlStreamAttributePtr :: a -> (QVectorQXmlStreamAttributeConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QVectorQXmlStreamAttributeConstPtr a => QVectorQXmlStreamAttributeValue a where withQVectorQXmlStreamAttributePtr = HoppyP.flip ($) . toQVectorQXmlStreamAttributeConst class (HoppyFHR.CppPtr this) => QVectorQXmlStreamAttributeConstPtr this where toQVectorQXmlStreamAttributeConst :: this -> QVectorQXmlStreamAttributeConst atConst :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO M174.QXmlStreamAttributeConst) atConst arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyP.fmap M174.QXmlStreamAttributeConst (atConst' arg'1' arg'2') capacity :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) capacity arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (capacity' arg'1') contains :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) contains arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (contains' arg'1' arg'2') count :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) count arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (count' arg'1' arg'2') arrayConst :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttributeConst) arrayConst arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttributeConst (arrayConst' arg'1') endsWith :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) endsWith arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (endsWith' arg'1' arg'2') firstConst :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttributeConst) firstConst arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttributeConst (firstConst' arg'1') get :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO M174.QXmlStreamAttribute) get arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (get' arg'1' arg'2') indexOf :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) indexOf arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (indexOf' arg'1' arg'2') indexOfFrom :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Int) indexOfFrom arg'1 arg'2 arg'3 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (indexOfFrom' arg'1' arg'2' arg'3') isEmpty :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) isEmpty arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (isEmpty' arg'1') lastConst :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttributeConst) lastConst arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttributeConst (lastConst' arg'1') lastIndexOf :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) lastIndexOf arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (lastIndexOf' arg'1' arg'2') lastIndexOfFrom :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Int) lastIndexOfFrom arg'1 arg'2 arg'3 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (lastIndexOfFrom' arg'1' arg'2' arg'3') mid :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO QVectorQXmlStreamAttribute) mid arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyFHR.toGc =<< HoppyP.fmap QVectorQXmlStreamAttribute (mid' arg'1' arg'2') midLength :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO QVectorQXmlStreamAttribute) midLength arg'1 arg'2 arg'3 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> HoppyFHR.toGc =<< HoppyP.fmap QVectorQXmlStreamAttribute (midLength' arg'1' arg'2' arg'3') size :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) size arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (size' arg'1') startsWith :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) startsWith arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (startsWith' arg'1' arg'2') value :: (QVectorQXmlStreamAttributeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO M174.QXmlStreamAttribute) value arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (value' arg'1' arg'2') valueOr :: (QVectorQXmlStreamAttributeValue this, M174.QXmlStreamAttributeValue arg'3) => (this) {- ^ this -} -> (HoppyP.Int) -> (arg'3) -> (HoppyP.IO M174.QXmlStreamAttribute) valueOr arg'1 arg'2 arg'3 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> M174.withQXmlStreamAttributePtr arg'3 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'3' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (valueOr' arg'1' arg'2' arg'3') aDD :: (QVectorQXmlStreamAttributeValue this, QVectorQXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QVectorQXmlStreamAttribute) aDD arg'1 arg'2 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQVectorQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyFHR.toGc =<< HoppyP.fmap QVectorQXmlStreamAttribute (aDD' arg'1' arg'2') class (QVectorQXmlStreamAttributeConstPtr this) => QVectorQXmlStreamAttributePtr this where toQVectorQXmlStreamAttribute :: this -> QVectorQXmlStreamAttribute append :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) append arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (append' arg'1' arg'2') appendVector :: (QVectorQXmlStreamAttributePtr this, QVectorQXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) appendVector arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> withQVectorQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (appendVector' arg'1' arg'2') at :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO M174.QXmlStreamAttribute) at arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyP.fmap M174.QXmlStreamAttribute (at' arg'1' arg'2') clear :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) clear arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (clear' arg'1') array :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttribute) array arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttribute (array' arg'1') fill :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) fill arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (fill' arg'1' arg'2') fillResize :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.Int) -> (HoppyP.IO ()) fillResize arg'1 arg'2 arg'3 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> (fillResize' arg'1' arg'2' arg'3') first :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttribute) first arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttribute (first' arg'1') insert :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'3) => (this) {- ^ this -} -> (HoppyP.Int) -> (arg'3) -> (HoppyP.IO ()) insert arg'1 arg'2 arg'3 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> M174.withQXmlStreamAttributePtr arg'3 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'3' -> (insert' arg'1' arg'2' arg'3') insertMany :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'4) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (arg'4) -> (HoppyP.IO ()) insertMany arg'1 arg'2 arg'3 arg'4 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> M174.withQXmlStreamAttributePtr arg'4 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'4' -> (insertMany' arg'1' arg'2' arg'3' arg'4') last :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttribute) last arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> HoppyP.fmap M174.QXmlStreamAttribute (last' arg'1') prepend :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) prepend arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (prepend' arg'1' arg'2') remove :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO ()) remove arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (remove' arg'1' arg'2') removeMany :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO ()) removeMany arg'1 arg'2 arg'3 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> (removeMany' arg'1' arg'2' arg'3') removeAll :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) removeAll arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (removeAll' arg'1' arg'2') removeFirst :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) removeFirst arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (removeFirst' arg'1') removeLast :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) removeLast arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (removeLast' arg'1') removeOne :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) removeOne arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (removeOne' arg'1' arg'2') replace :: (QVectorQXmlStreamAttributePtr this, M174.QXmlStreamAttributeValue arg'3) => (this) {- ^ this -} -> (HoppyP.Int) -> (arg'3) -> (HoppyP.IO ()) replace arg'1 arg'2 arg'3 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> M174.withQXmlStreamAttributePtr arg'3 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'3' -> (replace' arg'1' arg'2' arg'3') reserve :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO ()) reserve arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (reserve' arg'1' arg'2') resize :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO ()) resize arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (resize' arg'1' arg'2') squeeze :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) squeeze arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (squeeze' arg'1') swap :: (QVectorQXmlStreamAttributePtr this, QVectorQXmlStreamAttributePtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) swap arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'2) $ \arg'2' -> (swap' arg'1' arg'2') takeAt :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO M174.QXmlStreamAttribute) takeAt arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (takeAt' arg'1' arg'2') takeFirst :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttribute) takeFirst arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (takeFirst' arg'1') takeLast :: (QVectorQXmlStreamAttributePtr this) => (this) {- ^ this -} -> (HoppyP.IO M174.QXmlStreamAttribute) takeLast arg'1 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> (HoppyFHR.decodeAndDelete . M174.QXmlStreamAttributeConst) =<< (takeLast' arg'1') aSSIGN :: (QVectorQXmlStreamAttributePtr this, QVectorQXmlStreamAttributeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QVectorQXmlStreamAttribute) aSSIGN arg'1 arg'2 = HoppyFHR.withCppPtr (toQVectorQXmlStreamAttribute arg'1) $ \arg'1' -> withQVectorQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QVectorQXmlStreamAttribute (aSSIGN' arg'1' arg'2') data QVectorQXmlStreamAttributeConst = QVectorQXmlStreamAttributeConst (HoppyF.Ptr QVectorQXmlStreamAttributeConst) | QVectorQXmlStreamAttributeConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QVectorQXmlStreamAttributeConst) deriving (HoppyP.Show) instance HoppyP.Eq QVectorQXmlStreamAttributeConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QVectorQXmlStreamAttributeConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQVectorQXmlStreamAttributeToConst :: QVectorQXmlStreamAttribute -> QVectorQXmlStreamAttributeConst castQVectorQXmlStreamAttributeToConst (QVectorQXmlStreamAttribute ptr') = QVectorQXmlStreamAttributeConst $ HoppyF.castPtr ptr' castQVectorQXmlStreamAttributeToConst (QVectorQXmlStreamAttributeGc fptr' ptr') = QVectorQXmlStreamAttributeConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QVectorQXmlStreamAttributeConst where nullptr = QVectorQXmlStreamAttributeConst HoppyF.nullPtr withCppPtr (QVectorQXmlStreamAttributeConst ptr') f' = f' ptr' withCppPtr (QVectorQXmlStreamAttributeConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QVectorQXmlStreamAttributeConst ptr') = ptr' toPtr (QVectorQXmlStreamAttributeConstGc _ ptr') = ptr' touchCppPtr (QVectorQXmlStreamAttributeConst _) = HoppyP.return () touchCppPtr (QVectorQXmlStreamAttributeConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QVectorQXmlStreamAttributeConst where delete (QVectorQXmlStreamAttributeConst ptr') = delete'QVectorQXmlStreamAttribute ptr' delete (QVectorQXmlStreamAttributeConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QVectorQXmlStreamAttributeConst", " object."] toGc this'@(QVectorQXmlStreamAttributeConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QVectorQXmlStreamAttributeConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QVectorQXmlStreamAttribute :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QVectorQXmlStreamAttributeConstGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QVectorQXmlStreamAttributeConst QVectorQXmlStreamAttribute where copy = newCopy instance QVectorQXmlStreamAttributeConstPtr QVectorQXmlStreamAttributeConst where toQVectorQXmlStreamAttributeConst = HoppyP.id data QVectorQXmlStreamAttribute = QVectorQXmlStreamAttribute (HoppyF.Ptr QVectorQXmlStreamAttribute) | QVectorQXmlStreamAttributeGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QVectorQXmlStreamAttribute) deriving (HoppyP.Show) instance HoppyP.Eq QVectorQXmlStreamAttribute where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QVectorQXmlStreamAttribute where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQVectorQXmlStreamAttributeToNonconst :: QVectorQXmlStreamAttributeConst -> QVectorQXmlStreamAttribute castQVectorQXmlStreamAttributeToNonconst (QVectorQXmlStreamAttributeConst ptr') = QVectorQXmlStreamAttribute $ HoppyF.castPtr ptr' castQVectorQXmlStreamAttributeToNonconst (QVectorQXmlStreamAttributeConstGc fptr' ptr') = QVectorQXmlStreamAttributeGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QVectorQXmlStreamAttribute where nullptr = QVectorQXmlStreamAttribute HoppyF.nullPtr withCppPtr (QVectorQXmlStreamAttribute ptr') f' = f' ptr' withCppPtr (QVectorQXmlStreamAttributeGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QVectorQXmlStreamAttribute ptr') = ptr' toPtr (QVectorQXmlStreamAttributeGc _ ptr') = ptr' touchCppPtr (QVectorQXmlStreamAttribute _) = HoppyP.return () touchCppPtr (QVectorQXmlStreamAttributeGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QVectorQXmlStreamAttribute where delete (QVectorQXmlStreamAttribute ptr') = delete'QVectorQXmlStreamAttribute $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QVectorQXmlStreamAttributeConst) delete (QVectorQXmlStreamAttributeGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QVectorQXmlStreamAttribute", " object."] toGc this'@(QVectorQXmlStreamAttribute ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QVectorQXmlStreamAttributeGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QVectorQXmlStreamAttribute :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QVectorQXmlStreamAttributeGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QVectorQXmlStreamAttribute QVectorQXmlStreamAttribute where copy = newCopy instance QVectorQXmlStreamAttributeConstPtr QVectorQXmlStreamAttribute where toQVectorQXmlStreamAttributeConst (QVectorQXmlStreamAttribute ptr') = QVectorQXmlStreamAttributeConst $ (HoppyF.castPtr :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr QVectorQXmlStreamAttributeConst) ptr' toQVectorQXmlStreamAttributeConst (QVectorQXmlStreamAttributeGc fptr' ptr') = QVectorQXmlStreamAttributeConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QVectorQXmlStreamAttribute -> HoppyF.Ptr QVectorQXmlStreamAttributeConst) ptr' instance QVectorQXmlStreamAttributePtr QVectorQXmlStreamAttribute where toQVectorQXmlStreamAttribute = HoppyP.id new :: (HoppyP.IO QVectorQXmlStreamAttribute) new = HoppyP.fmap QVectorQXmlStreamAttribute (new') newWithSize :: (HoppyP.Int) -> (HoppyP.IO QVectorQXmlStreamAttribute) newWithSize arg'1 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> HoppyP.fmap QVectorQXmlStreamAttribute (newWithSize' arg'1') newWithSizeAndValue :: (M174.QXmlStreamAttributeValue arg'2) => (HoppyP.Int) -> (arg'2) -> (HoppyP.IO QVectorQXmlStreamAttribute) newWithSizeAndValue arg'1 arg'2 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> M174.withQXmlStreamAttributePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QVectorQXmlStreamAttribute (newWithSizeAndValue' arg'1' arg'2') newCopy :: (QVectorQXmlStreamAttributeValue arg'1) => (arg'1) -> (HoppyP.IO QVectorQXmlStreamAttribute) newCopy arg'1 = withQVectorQXmlStreamAttributePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QVectorQXmlStreamAttribute (newCopy' arg'1') class QVectorQXmlStreamAttributeSuper a where downToQVectorQXmlStreamAttribute :: a -> QVectorQXmlStreamAttribute class QVectorQXmlStreamAttributeSuperConst a where downToQVectorQXmlStreamAttributeConst :: a -> QVectorQXmlStreamAttributeConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QVectorQXmlStreamAttribute)) QVectorQXmlStreamAttribute where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance QVectorQXmlStreamAttributeValue a => HoppyFHR.Assignable QVectorQXmlStreamAttribute a where assign x' y' = aSSIGN x' y' >> HoppyP.return () instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QVectorQXmlStreamAttribute)) QVectorQXmlStreamAttribute where decode = HoppyP.fmap QVectorQXmlStreamAttribute . HoppyF.peek instance QtahFHR.HasContents QVectorQXmlStreamAttributeConst (M174.QXmlStreamAttribute) where toContents this' = do size' <- size this' QtahP.mapM (QtahFHR.decode <=< atConst this') [0..size'-1] instance QtahFHR.HasContents QVectorQXmlStreamAttribute (M174.QXmlStreamAttribute) where toContents this' = do size' <- size this' QtahP.mapM (QtahFHR.decode <=< at this') [0..size'-1] instance QtahFHR.FromContents QVectorQXmlStreamAttribute (M174.QXmlStreamAttribute) where fromContents values' = do vector' <- new reserve vector' $ QtahFHR.coerceIntegral $ QtahP.length values' QtahP.mapM_ (append vector') values' QtahP.return vector'