{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Interfaces.Value
(
Value(..) ,
noValue ,
IsValue ,
toValue ,
#if defined(ENABLE_OVERLOADING)
ResolveValueMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ValueGetCurrentValueMethodInfo ,
#endif
valueGetCurrentValue ,
#if defined(ENABLE_OVERLOADING)
ValueGetIncrementMethodInfo ,
#endif
valueGetIncrement ,
#if defined(ENABLE_OVERLOADING)
ValueGetMaximumValueMethodInfo ,
#endif
valueGetMaximumValue ,
#if defined(ENABLE_OVERLOADING)
ValueGetMinimumIncrementMethodInfo ,
#endif
valueGetMinimumIncrement ,
#if defined(ENABLE_OVERLOADING)
ValueGetMinimumValueMethodInfo ,
#endif
valueGetMinimumValue ,
#if defined(ENABLE_OVERLOADING)
ValueGetRangeMethodInfo ,
#endif
valueGetRange ,
#if defined(ENABLE_OVERLOADING)
ValueGetSubRangesMethodInfo ,
#endif
valueGetSubRanges ,
#if defined(ENABLE_OVERLOADING)
ValueGetValueAndTextMethodInfo ,
#endif
valueGetValueAndText ,
#if defined(ENABLE_OVERLOADING)
ValueSetCurrentValueMethodInfo ,
#endif
valueSetCurrentValue ,
#if defined(ENABLE_OVERLOADING)
ValueSetValueMethodInfo ,
#endif
valueSetValue ,
C_ValueValueChangedCallback ,
ValueValueChangedCallback ,
#if defined(ENABLE_OVERLOADING)
ValueValueChangedSignalInfo ,
#endif
afterValueValueChanged ,
genClosure_ValueValueChanged ,
mk_ValueValueChangedCallback ,
noValueValueChangedCallback ,
onValueValueChanged ,
wrap_ValueValueChangedCallback ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.Atk.Structs.Range as Atk.Range
import qualified GI.GObject.Objects.Object as GObject.Object
newtype Value = Value (ManagedPtr Value)
deriving (Value -> Value -> Bool
(Value -> Value -> Bool) -> (Value -> Value -> Bool) -> Eq Value
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c== :: Value -> Value -> Bool
Eq)
noValue :: Maybe Value
noValue :: Maybe Value
noValue = Maybe Value
forall a. Maybe a
Nothing
type ValueValueChangedCallback =
Double
-> T.Text
-> IO ()
noValueValueChangedCallback :: Maybe ValueValueChangedCallback
noValueValueChangedCallback :: Maybe ValueValueChangedCallback
noValueValueChangedCallback = Maybe ValueValueChangedCallback
forall a. Maybe a
Nothing
type C_ValueValueChangedCallback =
Ptr () ->
CDouble ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ValueValueChangedCallback :: C_ValueValueChangedCallback -> IO (FunPtr C_ValueValueChangedCallback)
genClosure_ValueValueChanged :: MonadIO m => ValueValueChangedCallback -> m (GClosure C_ValueValueChangedCallback)
genClosure_ValueValueChanged :: ValueValueChangedCallback
-> m (GClosure C_ValueValueChangedCallback)
genClosure_ValueValueChanged cb :: ValueValueChangedCallback
cb = IO (GClosure C_ValueValueChangedCallback)
-> m (GClosure C_ValueValueChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ValueValueChangedCallback)
-> m (GClosure C_ValueValueChangedCallback))
-> IO (GClosure C_ValueValueChangedCallback)
-> m (GClosure C_ValueValueChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ValueValueChangedCallback
cb' = ValueValueChangedCallback -> C_ValueValueChangedCallback
wrap_ValueValueChangedCallback ValueValueChangedCallback
cb
C_ValueValueChangedCallback
-> IO (FunPtr C_ValueValueChangedCallback)
mk_ValueValueChangedCallback C_ValueValueChangedCallback
cb' IO (FunPtr C_ValueValueChangedCallback)
-> (FunPtr C_ValueValueChangedCallback
-> IO (GClosure C_ValueValueChangedCallback))
-> IO (GClosure C_ValueValueChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ValueValueChangedCallback
-> IO (GClosure C_ValueValueChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_ValueValueChangedCallback ::
ValueValueChangedCallback ->
C_ValueValueChangedCallback
wrap_ValueValueChangedCallback :: ValueValueChangedCallback -> C_ValueValueChangedCallback
wrap_ValueValueChangedCallback _cb :: ValueValueChangedCallback
_cb _ value :: CDouble
value text :: CString
text _ = do
let value' :: Double
value' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
value
Text
text' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
text
ValueValueChangedCallback
_cb Double
value' Text
text'
onValueValueChanged :: (IsValue a, MonadIO m) => a -> ValueValueChangedCallback -> m SignalHandlerId
onValueValueChanged :: a -> ValueValueChangedCallback -> m SignalHandlerId
onValueValueChanged obj :: a
obj cb :: ValueValueChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ValueValueChangedCallback
cb' = ValueValueChangedCallback -> C_ValueValueChangedCallback
wrap_ValueValueChangedCallback ValueValueChangedCallback
cb
FunPtr C_ValueValueChangedCallback
cb'' <- C_ValueValueChangedCallback
-> IO (FunPtr C_ValueValueChangedCallback)
mk_ValueValueChangedCallback C_ValueValueChangedCallback
cb'
a
-> Text
-> FunPtr C_ValueValueChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "value-changed" FunPtr C_ValueValueChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterValueValueChanged :: (IsValue a, MonadIO m) => a -> ValueValueChangedCallback -> m SignalHandlerId
afterValueValueChanged :: a -> ValueValueChangedCallback -> m SignalHandlerId
afterValueValueChanged obj :: a
obj cb :: ValueValueChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let cb' :: C_ValueValueChangedCallback
cb' = ValueValueChangedCallback -> C_ValueValueChangedCallback
wrap_ValueValueChangedCallback ValueValueChangedCallback
cb
FunPtr C_ValueValueChangedCallback
cb'' <- C_ValueValueChangedCallback
-> IO (FunPtr C_ValueValueChangedCallback)
mk_ValueValueChangedCallback C_ValueValueChangedCallback
cb'
a
-> Text
-> FunPtr C_ValueValueChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "value-changed" FunPtr C_ValueValueChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data ValueValueChangedSignalInfo
instance SignalInfo ValueValueChangedSignalInfo where
type HaskellCallbackType ValueValueChangedSignalInfo = ValueValueChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ValueValueChangedCallback cb
cb'' <- mk_ValueValueChangedCallback cb'
connectSignalFunPtr obj "value-changed" cb'' connectMode detail
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Value = ValueSignalList
type ValueSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("valueChanged", ValueValueChangedSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_value_get_type"
c_atk_value_get_type :: IO GType
instance GObject Value where
gobjectType :: IO GType
gobjectType = IO GType
c_atk_value_get_type
instance B.GValue.IsGValue Value where
toGValue :: Value -> IO GValue
toGValue o :: Value
o = do
GType
gtype <- IO GType
c_atk_value_get_type
Value -> (Ptr Value -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Value
o (GType -> (GValue -> Ptr Value -> IO ()) -> Ptr Value -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Value -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Value
fromGValue gv :: GValue
gv = do
Ptr Value
ptr <- GValue -> IO (Ptr Value)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Value)
(ManagedPtr Value -> Value) -> Ptr Value -> IO Value
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Value -> Value
Value Ptr Value
ptr
class (GObject o, O.IsDescendantOf Value o) => IsValue o
instance (GObject o, O.IsDescendantOf Value o) => IsValue o
instance O.HasParentTypes Value
type instance O.ParentTypes Value = '[GObject.Object.Object]
toValue :: (MonadIO m, IsValue o) => o -> m Value
toValue :: o -> m Value
toValue = IO Value -> m Value
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Value -> m Value) -> (o -> IO Value) -> o -> m Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Value -> Value) -> o -> IO Value
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Value -> Value
Value
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Value
type instance O.AttributeList Value = ValueAttributeList
type ValueAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveValueMethod (t :: Symbol) (o :: *) :: * where
ResolveValueMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveValueMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveValueMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveValueMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveValueMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveValueMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveValueMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveValueMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveValueMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveValueMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveValueMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveValueMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveValueMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveValueMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveValueMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveValueMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveValueMethod "getCurrentValue" o = ValueGetCurrentValueMethodInfo
ResolveValueMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveValueMethod "getIncrement" o = ValueGetIncrementMethodInfo
ResolveValueMethod "getMaximumValue" o = ValueGetMaximumValueMethodInfo
ResolveValueMethod "getMinimumIncrement" o = ValueGetMinimumIncrementMethodInfo
ResolveValueMethod "getMinimumValue" o = ValueGetMinimumValueMethodInfo
ResolveValueMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveValueMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveValueMethod "getRange" o = ValueGetRangeMethodInfo
ResolveValueMethod "getSubRanges" o = ValueGetSubRangesMethodInfo
ResolveValueMethod "getValueAndText" o = ValueGetValueAndTextMethodInfo
ResolveValueMethod "setCurrentValue" o = ValueSetCurrentValueMethodInfo
ResolveValueMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveValueMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveValueMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveValueMethod "setValue" o = ValueSetValueMethodInfo
ResolveValueMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveValueMethod t Value, O.MethodInfo info Value p) => OL.IsLabel t (Value -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "atk_value_get_current_value" atk_value_get_current_value ::
Ptr Value ->
Ptr GValue ->
IO ()
{-# DEPRECATED valueGetCurrentValue ["Since 2.12. Use 'GI.Atk.Interfaces.Value.valueGetValueAndText'","instead."] #-}
valueGetCurrentValue ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m (GValue)
valueGetCurrentValue :: a -> m GValue
valueGetCurrentValue obj :: a
obj = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
Ptr Value -> Ptr GValue -> IO ()
atk_value_get_current_value Ptr Value
obj' Ptr GValue
value
GValue
value' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
#if defined(ENABLE_OVERLOADING)
data ValueGetCurrentValueMethodInfo
instance (signature ~ (m (GValue)), MonadIO m, IsValue a) => O.MethodInfo ValueGetCurrentValueMethodInfo a signature where
overloadedMethod = valueGetCurrentValue
#endif
foreign import ccall "atk_value_get_increment" atk_value_get_increment ::
Ptr Value ->
IO CDouble
valueGetIncrement ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m Double
valueGetIncrement :: a -> m Double
valueGetIncrement obj :: a
obj = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
CDouble
result <- Ptr Value -> IO CDouble
atk_value_get_increment Ptr Value
obj'
let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data ValueGetIncrementMethodInfo
instance (signature ~ (m Double), MonadIO m, IsValue a) => O.MethodInfo ValueGetIncrementMethodInfo a signature where
overloadedMethod = valueGetIncrement
#endif
foreign import ccall "atk_value_get_maximum_value" atk_value_get_maximum_value ::
Ptr Value ->
Ptr GValue ->
IO ()
{-# DEPRECATED valueGetMaximumValue ["Since 2.12. Use 'GI.Atk.Interfaces.Value.valueGetRange' instead."] #-}
valueGetMaximumValue ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m (GValue)
valueGetMaximumValue :: a -> m GValue
valueGetMaximumValue obj :: a
obj = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
Ptr Value -> Ptr GValue -> IO ()
atk_value_get_maximum_value Ptr Value
obj' Ptr GValue
value
GValue
value' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
#if defined(ENABLE_OVERLOADING)
data ValueGetMaximumValueMethodInfo
instance (signature ~ (m (GValue)), MonadIO m, IsValue a) => O.MethodInfo ValueGetMaximumValueMethodInfo a signature where
overloadedMethod = valueGetMaximumValue
#endif
foreign import ccall "atk_value_get_minimum_increment" atk_value_get_minimum_increment ::
Ptr Value ->
Ptr GValue ->
IO ()
{-# DEPRECATED valueGetMinimumIncrement ["Since 2.12. Use 'GI.Atk.Interfaces.Value.valueGetIncrement' instead."] #-}
valueGetMinimumIncrement ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m (GValue)
valueGetMinimumIncrement :: a -> m GValue
valueGetMinimumIncrement obj :: a
obj = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
Ptr Value -> Ptr GValue -> IO ()
atk_value_get_minimum_increment Ptr Value
obj' Ptr GValue
value
GValue
value' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
#if defined(ENABLE_OVERLOADING)
data ValueGetMinimumIncrementMethodInfo
instance (signature ~ (m (GValue)), MonadIO m, IsValue a) => O.MethodInfo ValueGetMinimumIncrementMethodInfo a signature where
overloadedMethod = valueGetMinimumIncrement
#endif
foreign import ccall "atk_value_get_minimum_value" atk_value_get_minimum_value ::
Ptr Value ->
Ptr GValue ->
IO ()
{-# DEPRECATED valueGetMinimumValue ["Since 2.12. Use 'GI.Atk.Interfaces.Value.valueGetRange' instead."] #-}
valueGetMinimumValue ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m (GValue)
valueGetMinimumValue :: a -> m GValue
valueGetMinimumValue obj :: a
obj = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr GValue
value <- Int -> IO (Ptr GValue)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 24 :: IO (Ptr GValue)
Ptr Value -> Ptr GValue -> IO ()
atk_value_get_minimum_value Ptr Value
obj' Ptr GValue
value
GValue
value' <- ((ManagedPtr GValue -> GValue) -> Ptr GValue -> IO GValue
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GValue -> GValue
GValue) Ptr GValue
value
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
value'
#if defined(ENABLE_OVERLOADING)
data ValueGetMinimumValueMethodInfo
instance (signature ~ (m (GValue)), MonadIO m, IsValue a) => O.MethodInfo ValueGetMinimumValueMethodInfo a signature where
overloadedMethod = valueGetMinimumValue
#endif
foreign import ccall "atk_value_get_range" atk_value_get_range ::
Ptr Value ->
IO (Ptr Atk.Range.Range)
valueGetRange ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m (Maybe Atk.Range.Range)
valueGetRange :: a -> m (Maybe Range)
valueGetRange obj :: a
obj = IO (Maybe Range) -> m (Maybe Range)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Range) -> m (Maybe Range))
-> IO (Maybe Range) -> m (Maybe Range)
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr Range
result <- Ptr Value -> IO (Ptr Range)
atk_value_get_range Ptr Value
obj'
Maybe Range
maybeResult <- Ptr Range -> (Ptr Range -> IO Range) -> IO (Maybe Range)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Range
result ((Ptr Range -> IO Range) -> IO (Maybe Range))
-> (Ptr Range -> IO Range) -> IO (Maybe Range)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Range
result' -> do
Range
result'' <- ((ManagedPtr Range -> Range) -> Ptr Range -> IO Range
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Range -> Range
Atk.Range.Range) Ptr Range
result'
Range -> IO Range
forall (m :: * -> *) a. Monad m => a -> m a
return Range
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
Maybe Range -> IO (Maybe Range)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Range
maybeResult
#if defined(ENABLE_OVERLOADING)
data ValueGetRangeMethodInfo
instance (signature ~ (m (Maybe Atk.Range.Range)), MonadIO m, IsValue a) => O.MethodInfo ValueGetRangeMethodInfo a signature where
overloadedMethod = valueGetRange
#endif
foreign import ccall "atk_value_get_sub_ranges" atk_value_get_sub_ranges ::
Ptr Value ->
IO (Ptr (GSList (Ptr Atk.Range.Range)))
valueGetSubRanges ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m [Atk.Range.Range]
valueGetSubRanges :: a -> m [Range]
valueGetSubRanges obj :: a
obj = IO [Range] -> m [Range]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Range] -> m [Range]) -> IO [Range] -> m [Range]
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr (GSList (Ptr Range))
result <- Ptr Value -> IO (Ptr (GSList (Ptr Range)))
atk_value_get_sub_ranges Ptr Value
obj'
[Ptr Range]
result' <- Ptr (GSList (Ptr Range)) -> IO [Ptr Range]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Range))
result
[Range]
result'' <- (Ptr Range -> IO Range) -> [Ptr Range] -> IO [Range]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Range -> Range) -> Ptr Range -> IO Range
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Range -> Range
Atk.Range.Range) [Ptr Range]
result'
Ptr (GSList (Ptr Range)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Range))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
[Range] -> IO [Range]
forall (m :: * -> *) a. Monad m => a -> m a
return [Range]
result''
#if defined(ENABLE_OVERLOADING)
data ValueGetSubRangesMethodInfo
instance (signature ~ (m [Atk.Range.Range]), MonadIO m, IsValue a) => O.MethodInfo ValueGetSubRangesMethodInfo a signature where
overloadedMethod = valueGetSubRanges
#endif
foreign import ccall "atk_value_get_value_and_text" atk_value_get_value_and_text ::
Ptr Value ->
Ptr CDouble ->
Ptr CString ->
IO ()
valueGetValueAndText ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> m ((Double, T.Text))
valueGetValueAndText :: a -> m (Double, Text)
valueGetValueAndText obj :: a
obj = IO (Double, Text) -> m (Double, Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Text) -> m (Double, Text))
-> IO (Double, Text) -> m (Double, Text)
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr CDouble
value <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
Ptr CString
text <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CString)
Ptr Value -> Ptr CDouble -> Ptr CString -> IO ()
atk_value_get_value_and_text Ptr Value
obj' Ptr CDouble
value Ptr CString
text
CDouble
value' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
value
let value'' :: Double
value'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
value'
CString
text' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
text
Text
text'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
text'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
value
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
text
(Double, Text) -> IO (Double, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
value'', Text
text'')
#if defined(ENABLE_OVERLOADING)
data ValueGetValueAndTextMethodInfo
instance (signature ~ (m ((Double, T.Text))), MonadIO m, IsValue a) => O.MethodInfo ValueGetValueAndTextMethodInfo a signature where
overloadedMethod = valueGetValueAndText
#endif
foreign import ccall "atk_value_set_current_value" atk_value_set_current_value ::
Ptr Value ->
Ptr GValue ->
IO CInt
{-# DEPRECATED valueSetCurrentValue ["Since 2.12. Use 'GI.Atk.Interfaces.Value.valueSetValue' instead."] #-}
valueSetCurrentValue ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> GValue
-> m Bool
valueSetCurrentValue :: a -> GValue -> m Bool
valueSetCurrentValue obj :: a
obj value :: GValue
value = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
CInt
result <- Ptr Value -> Ptr GValue -> IO CInt
atk_value_set_current_value Ptr Value
obj' Ptr GValue
value'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ValueSetCurrentValueMethodInfo
instance (signature ~ (GValue -> m Bool), MonadIO m, IsValue a) => O.MethodInfo ValueSetCurrentValueMethodInfo a signature where
overloadedMethod = valueSetCurrentValue
#endif
foreign import ccall "atk_value_set_value" atk_value_set_value ::
Ptr Value ->
CDouble ->
IO ()
valueSetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsValue a) =>
a
-> Double
-> m ()
valueSetValue :: a -> Double -> m ()
valueSetValue obj :: a
obj newValue :: Double
newValue = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr Value
obj' <- a -> IO (Ptr Value)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
let newValue' :: CDouble
newValue' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
newValue
Ptr Value -> CDouble -> IO ()
atk_value_set_value Ptr Value
obj' CDouble
newValue'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ValueSetValueMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsValue a) => O.MethodInfo ValueSetValueMethodInfo a signature where
overloadedMethod = valueSetValue
#endif