{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QMessageAuthenticationCode ( QMessageAuthenticationCodeValue (..), QMessageAuthenticationCodeConstPtr (..), result, QMessageAuthenticationCodePtr (..), addDataRaw, addDataByteArray, addDataDevice, reset, setKey, hash, QMessageAuthenticationCodeConst (..), castQMessageAuthenticationCodeToConst, QMessageAuthenticationCode (..), castQMessageAuthenticationCodeToNonconst, new, newWithKey, QMessageAuthenticationCodeSuper (..), QMessageAuthenticationCodeSuperConst (..), ) where import qualified Data.ByteString as QtahDBS 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.QCryptographicHash as M46 import qualified Graphics.UI.Qtah.Generated.Core.QIODevice as M48 import Prelude (($), (.), (/=), (=<<), (==), (>>=)) import qualified Prelude as HoppyP foreign import ccall "genpop__QMessageAuthenticationCode_new" new' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QMessageAuthenticationCode) foreign import ccall "genpop__QMessageAuthenticationCode_newWithKey" newWithKey' :: HoppyFC.CInt -> HoppyF.Ptr M12.QByteArrayConst -> HoppyP.IO (HoppyF.Ptr QMessageAuthenticationCode) foreign import ccall "genpop__QMessageAuthenticationCode_addDataRaw" addDataRaw' :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr HoppyFC.CChar -> HoppyFC.CInt -> HoppyP.IO () foreign import ccall "genpop__QMessageAuthenticationCode_addDataByteArray" addDataByteArray' :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr M12.QByteArrayConst -> HoppyP.IO () foreign import ccall "genpop__QMessageAuthenticationCode_addDataDevice" addDataDevice' :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr M48.QIODevice -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QMessageAuthenticationCode_hash" hash' :: HoppyF.Ptr M12.QByteArrayConst -> HoppyF.Ptr M12.QByteArrayConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M12.QByteArrayConst) foreign import ccall "genpop__QMessageAuthenticationCode_reset" reset' :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyP.IO () foreign import ccall "genpop__QMessageAuthenticationCode_result" result' :: HoppyF.Ptr QMessageAuthenticationCodeConst -> HoppyP.IO (HoppyF.Ptr M12.QByteArrayConst) foreign import ccall "genpop__QMessageAuthenticationCode_setKey" setKey' :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr M12.QByteArrayConst -> HoppyP.IO () foreign import ccall "gendel__QMessageAuthenticationCode" delete'QMessageAuthenticationCode :: HoppyF.Ptr QMessageAuthenticationCodeConst -> HoppyP.IO () foreign import ccall "&gendel__QMessageAuthenticationCode" deletePtr'QMessageAuthenticationCode :: HoppyF.FunPtr (HoppyF.Ptr QMessageAuthenticationCodeConst -> HoppyP.IO ()) class QMessageAuthenticationCodeValue a where withQMessageAuthenticationCodePtr :: a -> (QMessageAuthenticationCodeConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QMessageAuthenticationCodeConstPtr a => QMessageAuthenticationCodeValue a where withQMessageAuthenticationCodePtr = HoppyP.flip ($) . toQMessageAuthenticationCodeConst class (HoppyFHR.CppPtr this) => QMessageAuthenticationCodeConstPtr this where toQMessageAuthenticationCodeConst :: this -> QMessageAuthenticationCodeConst result :: (QMessageAuthenticationCodeValue this) => (this) {- ^ this -} -> (HoppyP.IO QtahDBS.ByteString) result arg'1 = withQMessageAuthenticationCodePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M12.QByteArrayConst) =<< (result' arg'1') class (QMessageAuthenticationCodeConstPtr this) => QMessageAuthenticationCodePtr this where toQMessageAuthenticationCode :: this -> QMessageAuthenticationCode addDataRaw :: (QMessageAuthenticationCodePtr this) => (this) {- ^ this -} -> (HoppyF.Ptr HoppyFC.CChar) -> (HoppyP.Int) -> (HoppyP.IO ()) addDataRaw arg'1 arg'2 arg'3 = HoppyFHR.withCppPtr (toQMessageAuthenticationCode arg'1) $ \arg'1' -> let arg'2' = arg'2 in ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> (addDataRaw' arg'1' arg'2' arg'3') addDataByteArray :: (QMessageAuthenticationCodePtr this, M12.QByteArrayValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) addDataByteArray arg'1 arg'2 = HoppyFHR.withCppPtr (toQMessageAuthenticationCode arg'1) $ \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (addDataByteArray' arg'1' arg'2') addDataDevice :: (QMessageAuthenticationCodePtr this, M48.QIODevicePtr arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) addDataDevice arg'1 arg'2 = HoppyFHR.withCppPtr (toQMessageAuthenticationCode arg'1) $ \arg'1' -> HoppyFHR.withCppPtr (M48.toQIODevice arg'2) $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (addDataDevice' arg'1' arg'2') reset :: (QMessageAuthenticationCodePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) reset arg'1 = HoppyFHR.withCppPtr (toQMessageAuthenticationCode arg'1) $ \arg'1' -> (reset' arg'1') setKey :: (QMessageAuthenticationCodePtr this, M12.QByteArrayValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO ()) setKey arg'1 arg'2 = HoppyFHR.withCppPtr (toQMessageAuthenticationCode arg'1) $ \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (setKey' arg'1' arg'2') hash :: (M12.QByteArrayValue arg'1, M12.QByteArrayValue arg'2) => (arg'1) -> (arg'2) -> (M46.QCryptographicHashAlgorithm) -> (HoppyP.IO QtahDBS.ByteString) hash arg'1 arg'2 arg'3 = M12.withQByteArrayPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'3 >>= \arg'3' -> (HoppyFHR.decodeAndDelete . M12.QByteArrayConst) =<< (hash' arg'1' arg'2' arg'3') data QMessageAuthenticationCodeConst = QMessageAuthenticationCodeConst (HoppyF.Ptr QMessageAuthenticationCodeConst) | QMessageAuthenticationCodeConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QMessageAuthenticationCodeConst) deriving (HoppyP.Show) instance HoppyP.Eq QMessageAuthenticationCodeConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QMessageAuthenticationCodeConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQMessageAuthenticationCodeToConst :: QMessageAuthenticationCode -> QMessageAuthenticationCodeConst castQMessageAuthenticationCodeToConst (QMessageAuthenticationCode ptr') = QMessageAuthenticationCodeConst $ HoppyF.castPtr ptr' castQMessageAuthenticationCodeToConst (QMessageAuthenticationCodeGc fptr' ptr') = QMessageAuthenticationCodeConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QMessageAuthenticationCodeConst where nullptr = QMessageAuthenticationCodeConst HoppyF.nullPtr withCppPtr (QMessageAuthenticationCodeConst ptr') f' = f' ptr' withCppPtr (QMessageAuthenticationCodeConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QMessageAuthenticationCodeConst ptr') = ptr' toPtr (QMessageAuthenticationCodeConstGc _ ptr') = ptr' touchCppPtr (QMessageAuthenticationCodeConst _) = HoppyP.return () touchCppPtr (QMessageAuthenticationCodeConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QMessageAuthenticationCodeConst where delete (QMessageAuthenticationCodeConst ptr') = delete'QMessageAuthenticationCode ptr' delete (QMessageAuthenticationCodeConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QMessageAuthenticationCodeConst", " object."] toGc this'@(QMessageAuthenticationCodeConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QMessageAuthenticationCodeConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QMessageAuthenticationCode :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QMessageAuthenticationCodeConstGc {}) = HoppyP.return this' instance QMessageAuthenticationCodeConstPtr QMessageAuthenticationCodeConst where toQMessageAuthenticationCodeConst = HoppyP.id data QMessageAuthenticationCode = QMessageAuthenticationCode (HoppyF.Ptr QMessageAuthenticationCode) | QMessageAuthenticationCodeGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QMessageAuthenticationCode) deriving (HoppyP.Show) instance HoppyP.Eq QMessageAuthenticationCode where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QMessageAuthenticationCode where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQMessageAuthenticationCodeToNonconst :: QMessageAuthenticationCodeConst -> QMessageAuthenticationCode castQMessageAuthenticationCodeToNonconst (QMessageAuthenticationCodeConst ptr') = QMessageAuthenticationCode $ HoppyF.castPtr ptr' castQMessageAuthenticationCodeToNonconst (QMessageAuthenticationCodeConstGc fptr' ptr') = QMessageAuthenticationCodeGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QMessageAuthenticationCode where nullptr = QMessageAuthenticationCode HoppyF.nullPtr withCppPtr (QMessageAuthenticationCode ptr') f' = f' ptr' withCppPtr (QMessageAuthenticationCodeGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QMessageAuthenticationCode ptr') = ptr' toPtr (QMessageAuthenticationCodeGc _ ptr') = ptr' touchCppPtr (QMessageAuthenticationCode _) = HoppyP.return () touchCppPtr (QMessageAuthenticationCodeGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QMessageAuthenticationCode where delete (QMessageAuthenticationCode ptr') = delete'QMessageAuthenticationCode $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QMessageAuthenticationCodeConst) delete (QMessageAuthenticationCodeGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QMessageAuthenticationCode", " object."] toGc this'@(QMessageAuthenticationCode ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QMessageAuthenticationCodeGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QMessageAuthenticationCode :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QMessageAuthenticationCodeGc {}) = HoppyP.return this' instance QMessageAuthenticationCodeConstPtr QMessageAuthenticationCode where toQMessageAuthenticationCodeConst (QMessageAuthenticationCode ptr') = QMessageAuthenticationCodeConst $ (HoppyF.castPtr :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr QMessageAuthenticationCodeConst) ptr' toQMessageAuthenticationCodeConst (QMessageAuthenticationCodeGc fptr' ptr') = QMessageAuthenticationCodeConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QMessageAuthenticationCode -> HoppyF.Ptr QMessageAuthenticationCodeConst) ptr' instance QMessageAuthenticationCodePtr QMessageAuthenticationCode where toQMessageAuthenticationCode = HoppyP.id new :: (M46.QCryptographicHashAlgorithm) -> (HoppyP.IO QMessageAuthenticationCode) new arg'1 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> HoppyP.fmap QMessageAuthenticationCode (new' arg'1') newWithKey :: (M12.QByteArrayValue arg'2) => (M46.QCryptographicHashAlgorithm) -> (arg'2) -> (HoppyP.IO QMessageAuthenticationCode) newWithKey arg'1 arg'2 = ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'1 >>= \arg'1' -> M12.withQByteArrayPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> HoppyP.fmap QMessageAuthenticationCode (newWithKey' arg'1' arg'2') class QMessageAuthenticationCodeSuper a where downToQMessageAuthenticationCode :: a -> QMessageAuthenticationCode class QMessageAuthenticationCodeSuperConst a where downToQMessageAuthenticationCodeConst :: a -> QMessageAuthenticationCodeConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QMessageAuthenticationCode)) QMessageAuthenticationCode where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QMessageAuthenticationCode)) QMessageAuthenticationCode where decode = HoppyP.fmap QMessageAuthenticationCode . HoppyF.peek