{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Handy.Objects.ValueObject
    ( 

-- * Exported types
    ValueObject(..)                         ,
    IsValueObject                           ,
    toValueObject                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [copyValue]("GI.Handy.Objects.ValueObject#g:method:copyValue"), [dupString]("GI.Handy.Objects.ValueObject#g:method:dupString"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getString]("GI.Handy.Objects.ValueObject#g:method:getString"), [getValue]("GI.Handy.Objects.ValueObject#g:method:getValue").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveValueObjectMethod                ,
#endif

-- ** copyValue #method:copyValue#

#if defined(ENABLE_OVERLOADING)
    ValueObjectCopyValueMethodInfo          ,
#endif
    valueObjectCopyValue                    ,


-- ** dupString #method:dupString#

#if defined(ENABLE_OVERLOADING)
    ValueObjectDupStringMethodInfo          ,
#endif
    valueObjectDupString                    ,


-- ** getString #method:getString#

#if defined(ENABLE_OVERLOADING)
    ValueObjectGetStringMethodInfo          ,
#endif
    valueObjectGetString                    ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    ValueObjectGetValueMethodInfo           ,
#endif
    valueObjectGetValue                     ,


-- ** new #method:new#

    valueObjectNew                          ,




 -- * Properties


-- ** value #attr:value#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ValueObjectValuePropertyInfo            ,
#endif
    constructValueObjectValue               ,
    getValueObjectValue                     ,
#if defined(ENABLE_OVERLOADING)
    valueObjectValue                        ,
#endif




    ) 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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
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 qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype ValueObject = ValueObject (SP.ManagedPtr ValueObject)
    deriving (ValueObject -> ValueObject -> Bool
(ValueObject -> ValueObject -> Bool)
-> (ValueObject -> ValueObject -> Bool) -> Eq ValueObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValueObject -> ValueObject -> Bool
$c/= :: ValueObject -> ValueObject -> Bool
== :: ValueObject -> ValueObject -> Bool
$c== :: ValueObject -> ValueObject -> Bool
Eq)

instance SP.ManagedPtrNewtype ValueObject where
    toManagedPtr :: ValueObject -> ManagedPtr ValueObject
toManagedPtr (ValueObject ManagedPtr ValueObject
p) = ManagedPtr ValueObject
p

foreign import ccall "hdy_value_object_get_type"
    c_hdy_value_object_get_type :: IO B.Types.GType

instance B.Types.TypedObject ValueObject where
    glibType :: IO GType
glibType = IO GType
c_hdy_value_object_get_type

instance B.Types.GObject ValueObject

-- | Type class for types which can be safely cast to `ValueObject`, for instance with `toValueObject`.
class (SP.GObject o, O.IsDescendantOf ValueObject o) => IsValueObject o
instance (SP.GObject o, O.IsDescendantOf ValueObject o) => IsValueObject o

instance O.HasParentTypes ValueObject
type instance O.ParentTypes ValueObject = '[GObject.Object.Object]

-- | Cast to `ValueObject`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toValueObject :: (MIO.MonadIO m, IsValueObject o) => o -> m ValueObject
toValueObject :: forall (m :: * -> *) o.
(MonadIO m, IsValueObject o) =>
o -> m ValueObject
toValueObject = IO ValueObject -> m ValueObject
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ValueObject -> m ValueObject)
-> (o -> IO ValueObject) -> o -> m ValueObject
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ValueObject -> ValueObject) -> o -> IO ValueObject
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ValueObject -> ValueObject
ValueObject

-- | Convert 'ValueObject' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe ValueObject) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_hdy_value_object_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ValueObject -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ValueObject
P.Nothing = Ptr GValue -> Ptr ValueObject -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ValueObject
forall a. Ptr a
FP.nullPtr :: FP.Ptr ValueObject)
    gvalueSet_ Ptr GValue
gv (P.Just ValueObject
obj) = ValueObject -> (Ptr ValueObject -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ValueObject
obj (Ptr GValue -> Ptr ValueObject -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ValueObject)
gvalueGet_ Ptr GValue
gv = do
        Ptr ValueObject
ptr <- Ptr GValue -> IO (Ptr ValueObject)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ValueObject)
        if Ptr ValueObject
ptr Ptr ValueObject -> Ptr ValueObject -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ValueObject
forall a. Ptr a
FP.nullPtr
        then ValueObject -> Maybe ValueObject
forall a. a -> Maybe a
P.Just (ValueObject -> Maybe ValueObject)
-> IO ValueObject -> IO (Maybe ValueObject)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ValueObject -> ValueObject)
-> Ptr ValueObject -> IO ValueObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ValueObject -> ValueObject
ValueObject Ptr ValueObject
ptr
        else Maybe ValueObject -> IO (Maybe ValueObject)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ValueObject
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveValueObjectMethod (t :: Symbol) (o :: *) :: * where
    ResolveValueObjectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveValueObjectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveValueObjectMethod "copyValue" o = ValueObjectCopyValueMethodInfo
    ResolveValueObjectMethod "dupString" o = ValueObjectDupStringMethodInfo
    ResolveValueObjectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveValueObjectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveValueObjectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveValueObjectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveValueObjectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveValueObjectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveValueObjectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveValueObjectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveValueObjectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveValueObjectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveValueObjectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveValueObjectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveValueObjectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveValueObjectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveValueObjectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveValueObjectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveValueObjectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveValueObjectMethod "getString" o = ValueObjectGetStringMethodInfo
    ResolveValueObjectMethod "getValue" o = ValueObjectGetValueMethodInfo
    ResolveValueObjectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveValueObjectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveValueObjectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveValueObjectMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveValueObjectMethod t ValueObject, O.OverloadedMethod info ValueObject p) => OL.IsLabel t (ValueObject -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveValueObjectMethod t ValueObject, O.OverloadedMethod info ValueObject p, R.HasField t ValueObject p) => R.HasField t ValueObject p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveValueObjectMethod t ValueObject, O.OverloadedMethodInfo info ValueObject) => OL.IsLabel t (O.MethodProxy info ValueObject) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "value"
   -- Type: TGValue
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' valueObject #value
-- @
getValueObjectValue :: (MonadIO m, IsValueObject o) => o -> m GValue
getValueObjectValue :: forall (m :: * -> *) o.
(MonadIO m, IsValueObject o) =>
o -> m GValue
getValueObjectValue o
obj = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe GValue) -> IO GValue
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getValueObjectValue" (IO (Maybe GValue) -> IO GValue) -> IO (Maybe GValue) -> IO GValue
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe GValue)
forall a. GObject a => a -> String -> IO (Maybe GValue)
B.Properties.getObjectPropertyGValue o
obj String
"value"

-- | Construct a `GValueConstruct` with valid value for the “@value@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructValueObjectValue :: (IsValueObject o, MIO.MonadIO m) => GValue -> m (GValueConstruct o)
constructValueObjectValue :: forall o (m :: * -> *).
(IsValueObject o, MonadIO m) =>
GValue -> m (GValueConstruct o)
constructValueObjectValue GValue
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe GValue -> IO (GValueConstruct o)
forall o. String -> Maybe GValue -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyGValue String
"value" (GValue -> Maybe GValue
forall a. a -> Maybe a
P.Just GValue
val)

#if defined(ENABLE_OVERLOADING)
data ValueObjectValuePropertyInfo
instance AttrInfo ValueObjectValuePropertyInfo where
    type AttrAllowedOps ValueObjectValuePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ValueObjectValuePropertyInfo = IsValueObject
    type AttrSetTypeConstraint ValueObjectValuePropertyInfo = (~) GValue
    type AttrTransferTypeConstraint ValueObjectValuePropertyInfo = (~) GValue
    type AttrTransferType ValueObjectValuePropertyInfo = GValue
    type AttrGetType ValueObjectValuePropertyInfo = GValue
    type AttrLabel ValueObjectValuePropertyInfo = "value"
    type AttrOrigin ValueObjectValuePropertyInfo = ValueObject
    attrGet = getValueObjectValue
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructValueObjectValue
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ValueObject.value"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-ValueObject.html#g:attr:value"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ValueObject
type instance O.AttributeList ValueObject = ValueObjectAttributeList
type ValueObjectAttributeList = ('[ '("value", ValueObjectValuePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
valueObjectValue :: AttrLabelProxy "value"
valueObjectValue = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ValueObject = ValueObjectSignalList
type ValueObjectSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method ValueObject::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "value"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GValue to store"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Handy" , name = "ValueObject" })
-- throws : False
-- Skip return : False

foreign import ccall "hdy_value_object_new" hdy_value_object_new :: 
    Ptr GValue ->                           -- value : TGValue
    IO (Ptr ValueObject)

-- | Create a new t'GI.Handy.Objects.ValueObject.ValueObject'.
-- 
-- /Since: 0.0.8/
valueObjectNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GValue
    -- ^ /@value@/: the t'GI.GObject.Structs.Value.Value' to store
    -> m ValueObject
    -- ^ __Returns:__ a new t'GI.Handy.Objects.ValueObject.ValueObject'
valueObjectNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GValue -> m ValueObject
valueObjectNew GValue
value = IO ValueObject -> m ValueObject
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ValueObject -> m ValueObject)
-> IO ValueObject -> m ValueObject
forall a b. (a -> b) -> a -> b
$ do
    Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
    Ptr ValueObject
result <- Ptr GValue -> IO (Ptr ValueObject)
hdy_value_object_new Ptr GValue
value'
    Text -> Ptr ValueObject -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"valueObjectNew" Ptr ValueObject
result
    ValueObject
result' <- ((ManagedPtr ValueObject -> ValueObject)
-> Ptr ValueObject -> IO ValueObject
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ValueObject -> ValueObject
ValueObject) Ptr ValueObject
result
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
    ValueObject -> IO ValueObject
forall (m :: * -> *) a. Monad m => a -> m a
return ValueObject
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ValueObject::copy_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ValueObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #HdyValueObject"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType = TGValue
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GValue with correct type to copy into"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "hdy_value_object_copy_value" hdy_value_object_copy_value :: 
    Ptr ValueObject ->                      -- value : TInterface (Name {namespace = "Handy", name = "ValueObject"})
    Ptr GValue ->                           -- dest : TGValue
    IO ()

-- | Copy data from the contained t'GI.GObject.Structs.Value.Value' into /@dest@/.
-- 
-- /Since: 0.0.8/
valueObjectCopyValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsValueObject a) =>
    a
    -- ^ /@value@/: the t'GI.Handy.Objects.ValueObject.ValueObject'
    -> GValue
    -- ^ /@dest@/: t'GI.GObject.Structs.Value.Value' with correct type to copy into
    -> m ()
valueObjectCopyValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsValueObject a) =>
a -> GValue -> m ()
valueObjectCopyValue a
value GValue
dest = 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 ValueObject
value' <- a -> IO (Ptr ValueObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    Ptr GValue
dest' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
dest
    Ptr ValueObject -> Ptr GValue -> IO ()
hdy_value_object_copy_value Ptr ValueObject
value' Ptr GValue
dest'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
dest
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ValueObjectCopyValueMethodInfo
instance (signature ~ (GValue -> m ()), MonadIO m, IsValueObject a) => O.OverloadedMethod ValueObjectCopyValueMethodInfo a signature where
    overloadedMethod = valueObjectCopyValue

instance O.OverloadedMethodInfo ValueObjectCopyValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ValueObject.valueObjectCopyValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-ValueObject.html#v:valueObjectCopyValue"
        })


#endif

-- method ValueObject::dup_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ValueObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #HdyValueObject"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "hdy_value_object_dup_string" hdy_value_object_dup_string :: 
    Ptr ValueObject ->                      -- value : TInterface (Name {namespace = "Handy", name = "ValueObject"})
    IO CString

-- | Returns a copy of the contained string if the value is of type
-- @/G_TYPE_STRING/@.
-- 
-- /Since: 0.0.8/
valueObjectDupString ::
    (B.CallStack.HasCallStack, MonadIO m, IsValueObject a) =>
    a
    -- ^ /@value@/: the t'GI.Handy.Objects.ValueObject.ValueObject'
    -> m T.Text
    -- ^ __Returns:__ a copy of the contained string
valueObjectDupString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsValueObject a) =>
a -> m Text
valueObjectDupString a
value = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ValueObject
value' <- a -> IO (Ptr ValueObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    CString
result <- Ptr ValueObject -> IO CString
hdy_value_object_dup_string Ptr ValueObject
value'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"valueObjectDupString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ValueObjectDupStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsValueObject a) => O.OverloadedMethod ValueObjectDupStringMethodInfo a signature where
    overloadedMethod = valueObjectDupString

instance O.OverloadedMethodInfo ValueObjectDupStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ValueObject.valueObjectDupString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-ValueObject.html#v:valueObjectDupString"
        })


#endif

-- method ValueObject::get_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ValueObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #HdyValueObject"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "hdy_value_object_get_string" hdy_value_object_get_string :: 
    Ptr ValueObject ->                      -- value : TInterface (Name {namespace = "Handy", name = "ValueObject"})
    IO CString

-- | Returns the contained string if the value is of type @/G_TYPE_STRING/@.
-- 
-- /Since: 0.0.8/
valueObjectGetString ::
    (B.CallStack.HasCallStack, MonadIO m, IsValueObject a) =>
    a
    -- ^ /@value@/: the t'GI.Handy.Objects.ValueObject.ValueObject'
    -> m T.Text
    -- ^ __Returns:__ the contained string
valueObjectGetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsValueObject a) =>
a -> m Text
valueObjectGetString a
value = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ValueObject
value' <- a -> IO (Ptr ValueObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    CString
result <- Ptr ValueObject -> IO CString
hdy_value_object_get_string Ptr ValueObject
value'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"valueObjectGetString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ValueObjectGetStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsValueObject a) => O.OverloadedMethod ValueObjectGetStringMethodInfo a signature where
    overloadedMethod = valueObjectGetString

instance O.OverloadedMethodInfo ValueObjectGetStringMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ValueObject.valueObjectGetString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-ValueObject.html#v:valueObjectGetString"
        })


#endif

-- method ValueObject::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "value"
--           , argType =
--               TInterface Name { namespace = "Handy" , name = "ValueObject" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #HdyValueObject"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just TGValue
-- throws : False
-- Skip return : False

foreign import ccall "hdy_value_object_get_value" hdy_value_object_get_value :: 
    Ptr ValueObject ->                      -- value : TInterface (Name {namespace = "Handy", name = "ValueObject"})
    IO (Ptr GValue)

-- | Return the contained value.
-- 
-- /Since: 0.0.8/
valueObjectGetValue ::
    (B.CallStack.HasCallStack, MonadIO m, IsValueObject a) =>
    a
    -- ^ /@value@/: the t'GI.Handy.Objects.ValueObject.ValueObject'
    -> m GValue
    -- ^ __Returns:__ the contained t'GI.GObject.Structs.Value.Value'
valueObjectGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsValueObject a) =>
a -> m GValue
valueObjectGetValue a
value = 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 ValueObject
value' <- a -> IO (Ptr ValueObject)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
value
    Ptr GValue
result <- Ptr ValueObject -> IO (Ptr GValue)
hdy_value_object_get_value Ptr ValueObject
value'
    Text -> Ptr GValue -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"valueObjectGetValue" Ptr GValue
result
    GValue
result' <- Ptr GValue -> IO GValue
B.GValue.newGValueFromPtr Ptr GValue
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
value
    GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
result'

#if defined(ENABLE_OVERLOADING)
data ValueObjectGetValueMethodInfo
instance (signature ~ (m GValue), MonadIO m, IsValueObject a) => O.OverloadedMethod ValueObjectGetValueMethodInfo a signature where
    overloadedMethod = valueObjectGetValue

instance O.OverloadedMethodInfo ValueObjectGetValueMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Handy.Objects.ValueObject.valueObjectGetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-handy-1.0.1/docs/GI-Handy-Objects-ValueObject.html#v:valueObjectGetValue"
        })


#endif