{-# LANGUAGE FlexibleContexts, FlexibleInstances, ForeignFunctionInterface, MonoLocalBinds, MultiParamTypeClasses, ScopedTypeVariables, TypeSynonymInstances, UndecidableInstances #-} ---------- GENERATED FILE, EDITS WILL BE LOST ---------- module Graphics.UI.Qtah.Generated.Core.QTime ( QTimeValue (..), QTimeConstPtr (..), addMSecs, addSecs, elapsed, hour, isNull, isValid, minute, msec, msecsSinceStartOfDay, msecsTo, second, secsTo, toString, toStringWithDateFormat, toStringWithStringFormat, eQ, nE, lT, lE, gT, gE, QTimePtr (..), isValidStatic, isValidStaticWithMs, restart, setHMS, setHMSWithMs, start, currentTime, fromMSecsSinceStartOfDay, fromString, fromStringWithDateFormat, fromStringWithStringFormat, QTimeConst (..), castQTimeToConst, QTime (..), castQTimeToNonconst, new, newWithHM, newWithHMS, newWithHMSMs, newCopy, QTimeSuper (..), QTimeSuperConst (..), ) 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.QString as M142 import qualified Graphics.UI.Qtah.Generated.Core.Types as M190 import Prelude (($), (.), (/=), (=<<), (==), (>>=)) import qualified Prelude as HoppyP import qualified Prelude as QtahP foreign import ccall "genpop__QTime_new" new' :: HoppyP.IO (HoppyF.Ptr QTime) foreign import ccall "genpop__QTime_newWithHM" newWithHM' :: HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTime) foreign import ccall "genpop__QTime_newWithHMS" newWithHMS' :: HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTime) foreign import ccall "genpop__QTime_newWithHMSMs" newWithHMSMs' :: HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTime) foreign import ccall "genpop__QTime_newCopy" newCopy' :: HoppyF.Ptr QTimeConst -> HoppyP.IO (HoppyF.Ptr QTime) foreign import ccall "genpop__QTime_addMSecs" addMSecs' :: HoppyF.Ptr QTimeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_addSecs" addSecs' :: HoppyF.Ptr QTimeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_currentTime" currentTime' :: HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_elapsed" elapsed' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_fromMSecsSinceStartOfDay" fromMSecsSinceStartOfDay' :: HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_fromString" fromString' :: HoppyF.Ptr M142.QStringConst -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_fromStringWithDateFormat" fromStringWithDateFormat' :: HoppyF.Ptr M142.QStringConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_fromStringWithStringFormat" fromStringWithStringFormat' :: HoppyF.Ptr M142.QStringConst -> HoppyF.Ptr M142.QStringConst -> HoppyP.IO (HoppyF.Ptr QTimeConst) foreign import ccall "genpop__QTime_hour" hour' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_isNull" isNull' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_isValid" isValid' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_isValidStatic" isValidStatic' :: HoppyF.Ptr QTime -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_isValidStaticWithMs" isValidStaticWithMs' :: HoppyF.Ptr QTime -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_minute" minute' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_msec" msec' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_msecsSinceStartOfDay" msecsSinceStartOfDay' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_msecsTo" msecsTo' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_restart" restart' :: HoppyF.Ptr QTime -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_second" second' :: HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_secsTo" secsTo' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CInt foreign import ccall "genpop__QTime_setHMS" setHMS' :: HoppyF.Ptr QTime -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_setHMSWithMs" setHMSWithMs' :: HoppyF.Ptr QTime -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyFC.CInt -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_start" start' :: HoppyF.Ptr QTime -> HoppyP.IO () foreign import ccall "genpop__QTime_toString" toString' :: HoppyF.Ptr QTimeConst -> HoppyP.IO (HoppyF.Ptr M142.QStringConst) foreign import ccall "genpop__QTime_toStringWithDateFormat" toStringWithDateFormat' :: HoppyF.Ptr QTimeConst -> HoppyFC.CInt -> HoppyP.IO (HoppyF.Ptr M142.QStringConst) foreign import ccall "genpop__QTime_toStringWithStringFormat" toStringWithStringFormat' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr M142.QStringConst -> HoppyP.IO (HoppyF.Ptr M142.QStringConst) foreign import ccall "genpop__QTime_EQ" eQ' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_NE" nE' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_LT" lT' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_LE" lE' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_GT" gT' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "genpop__QTime_GE" gE' :: HoppyF.Ptr QTimeConst -> HoppyF.Ptr QTimeConst -> HoppyP.IO HoppyFC.CBool foreign import ccall "gendel__QTime" delete'QTime :: HoppyF.Ptr QTimeConst -> HoppyP.IO () foreign import ccall "&gendel__QTime" deletePtr'QTime :: HoppyF.FunPtr (HoppyF.Ptr QTimeConst -> HoppyP.IO ()) class QTimeValue a where withQTimePtr :: a -> (QTimeConst -> HoppyP.IO b) -> HoppyP.IO b instance {-# OVERLAPPABLE #-} QTimeConstPtr a => QTimeValue a where withQTimePtr = HoppyP.flip ($) . toQTimeConst class (HoppyFHR.CppPtr this) => QTimeConstPtr this where toQTimeConst :: this -> QTimeConst addMSecs :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO QTime) addMSecs arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (addMSecs' arg'1' arg'2') addSecs :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.IO QTime) addSecs arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (addSecs' arg'1' arg'2') elapsed :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) elapsed arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (elapsed' arg'1') hour :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) hour arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (hour' arg'1') isNull :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) isNull arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (isNull' arg'1') isValid :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Bool) isValid arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( (HoppyP.return . (/= 0)) ) =<< (isValid' arg'1') minute :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) minute arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (minute' arg'1') msec :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) msec arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (msec' arg'1') msecsSinceStartOfDay :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) msecsSinceStartOfDay arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (msecsSinceStartOfDay' arg'1') msecsTo :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) msecsTo arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (msecsTo' arg'1' arg'2') second :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) second arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (second' arg'1') secsTo :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Int) secsTo arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (secsTo' arg'1' arg'2') toString :: (QTimeValue this) => (this) {- ^ this -} -> (HoppyP.IO QtahP.String) toString arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . M142.QStringConst) =<< (toString' arg'1') toStringWithDateFormat :: (QTimeValue this) => (this) {- ^ this -} -> (M190.QtDateFormat) -> (HoppyP.IO QtahP.String) toStringWithDateFormat arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . M142.QStringConst) =<< (toStringWithDateFormat' arg'1' arg'2') toStringWithStringFormat :: (QTimeValue this, M142.QStringValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO QtahP.String) toStringWithStringFormat arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M142.withQStringPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (HoppyFHR.decodeAndDelete . M142.QStringConst) =<< (toStringWithStringFormat' arg'1' arg'2') eQ :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) eQ arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (eQ' arg'1' arg'2') nE :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) nE arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (nE' arg'1' arg'2') lT :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) lT arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (lT' arg'1' arg'2') lE :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) lE arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (lE' arg'1' arg'2') gT :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) gT arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (gT' arg'1' arg'2') gE :: (QTimeValue this, QTimeValue arg'2) => (this) {- ^ this -} -> (arg'2) -> (HoppyP.IO HoppyP.Bool) gE arg'1 arg'2 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> withQTimePtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> ( (HoppyP.return . (/= 0)) ) =<< (gE' arg'1' arg'2') class (QTimeConstPtr this) => QTimePtr this where toQTime :: this -> QTime isValidStatic :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Bool) isValidStatic arg'1 arg'2 arg'3 arg'4 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'4 >>= \arg'4' -> ( (HoppyP.return . (/= 0)) ) =<< (isValidStatic' arg'1' arg'2' arg'3' arg'4') isValidStaticWithMs :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Bool) isValidStaticWithMs arg'1 arg'2 arg'3 arg'4 arg'5 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'4 >>= \arg'4' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'5 >>= \arg'5' -> ( (HoppyP.return . (/= 0)) ) =<< (isValidStaticWithMs' arg'1' arg'2' arg'3' arg'4' arg'5') restart :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.IO HoppyP.Int) restart arg'1 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) =<< (restart' arg'1') setHMS :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Bool) setHMS arg'1 arg'2 arg'3 arg'4 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'4 >>= \arg'4' -> ( (HoppyP.return . (/= 0)) ) =<< (setHMS' arg'1' arg'2' arg'3' arg'4') setHMSWithMs :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO HoppyP.Bool) setHMSWithMs arg'1 arg'2 arg'3 arg'4 arg'5 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'4 >>= \arg'4' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'5 >>= \arg'5' -> ( (HoppyP.return . (/= 0)) ) =<< (setHMSWithMs' arg'1' arg'2' arg'3' arg'4' arg'5') start :: (QTimePtr this) => (this) {- ^ this -} -> (HoppyP.IO ()) start arg'1 = HoppyFHR.withCppPtr (toQTime arg'1) $ \arg'1' -> (start' arg'1') currentTime :: (HoppyP.IO QTime) currentTime = (HoppyFHR.decodeAndDelete . QTimeConst) =<< (currentTime') fromMSecsSinceStartOfDay :: (HoppyP.Int) -> (HoppyP.IO QTime) fromMSecsSinceStartOfDay arg'1 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (fromMSecsSinceStartOfDay' arg'1') fromString :: (M142.QStringValue arg'1) => (arg'1) -> (HoppyP.IO QTime) fromString arg'1 = M142.withQStringPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (fromString' arg'1') fromStringWithDateFormat :: (M142.QStringValue arg'1) => (arg'1) -> (M190.QtDateFormat) -> (HoppyP.IO QTime) fromStringWithDateFormat arg'1 arg'2 = M142.withQStringPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> ( HoppyP.return . HoppyFHR.fromCppEnum ) arg'2 >>= \arg'2' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (fromStringWithDateFormat' arg'1' arg'2') fromStringWithStringFormat :: (M142.QStringValue arg'1, M142.QStringValue arg'2) => (arg'1) -> (arg'2) -> (HoppyP.IO QTime) fromStringWithStringFormat arg'1 arg'2 = M142.withQStringPtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> M142.withQStringPtr arg'2 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'2' -> (HoppyFHR.decodeAndDelete . QTimeConst) =<< (fromStringWithStringFormat' arg'1' arg'2') data QTimeConst = QTimeConst (HoppyF.Ptr QTimeConst) | QTimeConstGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QTimeConst) deriving (HoppyP.Show) instance HoppyP.Eq QTimeConst where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QTimeConst where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQTimeToConst :: QTime -> QTimeConst castQTimeToConst (QTime ptr') = QTimeConst $ HoppyF.castPtr ptr' castQTimeToConst (QTimeGc fptr' ptr') = QTimeConstGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QTimeConst where nullptr = QTimeConst HoppyF.nullPtr withCppPtr (QTimeConst ptr') f' = f' ptr' withCppPtr (QTimeConstGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QTimeConst ptr') = ptr' toPtr (QTimeConstGc _ ptr') = ptr' touchCppPtr (QTimeConst _) = HoppyP.return () touchCppPtr (QTimeConstGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QTimeConst where delete (QTimeConst ptr') = delete'QTime ptr' delete (QTimeConstGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QTimeConst", " object."] toGc this'@(QTimeConst ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QTimeConstGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QTime :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QTimeConstGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QTimeConst QTime where copy = newCopy instance QTimeConstPtr QTimeConst where toQTimeConst = HoppyP.id data QTime = QTime (HoppyF.Ptr QTime) | QTimeGc (HoppyF.ForeignPtr ()) (HoppyF.Ptr QTime) deriving (HoppyP.Show) instance HoppyP.Eq QTime where x == y = HoppyFHR.toPtr x == HoppyFHR.toPtr y instance HoppyP.Ord QTime where compare x y = HoppyP.compare (HoppyFHR.toPtr x) (HoppyFHR.toPtr y) castQTimeToNonconst :: QTimeConst -> QTime castQTimeToNonconst (QTimeConst ptr') = QTime $ HoppyF.castPtr ptr' castQTimeToNonconst (QTimeConstGc fptr' ptr') = QTimeGc fptr' $ HoppyF.castPtr ptr' instance HoppyFHR.CppPtr QTime where nullptr = QTime HoppyF.nullPtr withCppPtr (QTime ptr') f' = f' ptr' withCppPtr (QTimeGc fptr' ptr') f' = HoppyF.withForeignPtr fptr' $ \_ -> f' ptr' toPtr (QTime ptr') = ptr' toPtr (QTimeGc _ ptr') = ptr' touchCppPtr (QTime _) = HoppyP.return () touchCppPtr (QTimeGc fptr' _) = HoppyF.touchForeignPtr fptr' instance HoppyFHR.Deletable QTime where delete (QTime ptr') = delete'QTime $ (HoppyF.castPtr ptr' :: HoppyF.Ptr QTimeConst) delete (QTimeGc _ _) = HoppyP.fail $ HoppyP.concat ["Deletable.delete: Asked to delete a GC-managed ", "QTime", " object."] toGc this'@(QTime ptr') = if ptr' == HoppyF.nullPtr then HoppyP.return this' else HoppyP.fmap (HoppyP.flip QTimeGc ptr') $ HoppyF.newForeignPtr (HoppyF.castFunPtr deletePtr'QTime :: HoppyF.FunPtr (HoppyF.Ptr () -> HoppyP.IO ())) (HoppyF.castPtr ptr' :: HoppyF.Ptr ()) toGc this'@(QTimeGc {}) = HoppyP.return this' instance HoppyFHR.Copyable QTime QTime where copy = newCopy instance QTimeConstPtr QTime where toQTimeConst (QTime ptr') = QTimeConst $ (HoppyF.castPtr :: HoppyF.Ptr QTime -> HoppyF.Ptr QTimeConst) ptr' toQTimeConst (QTimeGc fptr' ptr') = QTimeConstGc fptr' $ (HoppyF.castPtr :: HoppyF.Ptr QTime -> HoppyF.Ptr QTimeConst) ptr' instance QTimePtr QTime where toQTime = HoppyP.id new :: (HoppyP.IO QTime) new = HoppyP.fmap QTime (new') newWithHM :: (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO QTime) newWithHM arg'1 arg'2 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> HoppyP.fmap QTime (newWithHM' arg'1' arg'2') newWithHMS :: (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO QTime) newWithHMS arg'1 arg'2 arg'3 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> HoppyP.fmap QTime (newWithHMS' arg'1' arg'2' arg'3') newWithHMSMs :: (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.Int) -> (HoppyP.IO QTime) newWithHMSMs arg'1 arg'2 arg'3 arg'4 = ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'1 >>= \arg'1' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'2 >>= \arg'2' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'3 >>= \arg'3' -> ( HoppyP.return . HoppyFHR.coerceIntegral ) arg'4 >>= \arg'4' -> HoppyP.fmap QTime (newWithHMSMs' arg'1' arg'2' arg'3' arg'4') newCopy :: (QTimeValue arg'1) => (arg'1) -> (HoppyP.IO QTime) newCopy arg'1 = withQTimePtr arg'1 $ HoppyP.flip HoppyFHR.withCppPtr $ \arg'1' -> HoppyP.fmap QTime (newCopy' arg'1') class QTimeSuper a where downToQTime :: a -> QTime class QTimeSuperConst a where downToQTimeConst :: a -> QTimeConst instance HoppyFHR.Assignable (HoppyF.Ptr (HoppyF.Ptr QTime)) QTime where assign ptr' value' = HoppyF.poke ptr' $ HoppyFHR.toPtr value' instance HoppyFHR.Decodable (HoppyF.Ptr (HoppyF.Ptr QTime)) QTime where decode = HoppyP.fmap QTime . HoppyF.peek instance HoppyFHR.Decodable QTime (QTime) where decode = HoppyFHR.decode . toQTimeConst instance HoppyFHR.Decodable QTimeConst (QTime) where decode = HoppyFHR.copy >=> HoppyFHR.toGc