{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.SettingsValue
(
SettingsValue(..) ,
newZeroSettingsValue ,
#if defined(ENABLE_OVERLOADING)
ResolveSettingsValueMethod ,
#endif
clearSettingsValueOrigin ,
getSettingsValueOrigin ,
setSettingsValueOrigin ,
#if defined(ENABLE_OVERLOADING)
settingsValue_origin ,
#endif
clearSettingsValueValue ,
getSettingsValueValue ,
setSettingsValueValue ,
#if defined(ENABLE_OVERLOADING)
settingsValue_value ,
#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.GHashTable as B.GHT
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.Kind as DK
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
newtype SettingsValue = SettingsValue (SP.ManagedPtr SettingsValue)
deriving (SettingsValue -> SettingsValue -> Bool
(SettingsValue -> SettingsValue -> Bool)
-> (SettingsValue -> SettingsValue -> Bool) -> Eq SettingsValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SettingsValue -> SettingsValue -> Bool
== :: SettingsValue -> SettingsValue -> Bool
$c/= :: SettingsValue -> SettingsValue -> Bool
/= :: SettingsValue -> SettingsValue -> Bool
Eq)
instance SP.ManagedPtrNewtype SettingsValue where
toManagedPtr :: SettingsValue -> ManagedPtr SettingsValue
toManagedPtr (SettingsValue ManagedPtr SettingsValue
p) = ManagedPtr SettingsValue
p
instance BoxedPtr SettingsValue where
boxedPtrCopy :: SettingsValue -> IO SettingsValue
boxedPtrCopy = \SettingsValue
p -> SettingsValue
-> (Ptr SettingsValue -> IO SettingsValue) -> IO SettingsValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsValue
p (Int -> Ptr SettingsValue -> IO (Ptr SettingsValue)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr SettingsValue -> IO (Ptr SettingsValue))
-> (Ptr SettingsValue -> IO SettingsValue)
-> Ptr SettingsValue
-> IO SettingsValue
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr SettingsValue -> SettingsValue)
-> Ptr SettingsValue -> IO SettingsValue
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr SettingsValue -> SettingsValue
SettingsValue)
boxedPtrFree :: SettingsValue -> IO ()
boxedPtrFree = \SettingsValue
x -> SettingsValue -> (Ptr SettingsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr SettingsValue
x Ptr SettingsValue -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr SettingsValue where
boxedPtrCalloc :: IO (Ptr SettingsValue)
boxedPtrCalloc = Int -> IO (Ptr SettingsValue)
forall a. Int -> IO (Ptr a)
callocBytes Int
32
newZeroSettingsValue :: MonadIO m => m SettingsValue
newZeroSettingsValue :: forall (m :: * -> *). MonadIO m => m SettingsValue
newZeroSettingsValue = IO SettingsValue -> m SettingsValue
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsValue -> m SettingsValue)
-> IO SettingsValue -> m SettingsValue
forall a b. (a -> b) -> a -> b
$ IO (Ptr SettingsValue)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr SettingsValue)
-> (Ptr SettingsValue -> IO SettingsValue) -> IO SettingsValue
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr SettingsValue -> SettingsValue)
-> Ptr SettingsValue -> IO SettingsValue
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr SettingsValue -> SettingsValue
SettingsValue
instance tag ~ 'AttrSet => Constructible SettingsValue tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr SettingsValue -> SettingsValue)
-> [AttrOp SettingsValue tag] -> m SettingsValue
new ManagedPtr SettingsValue -> SettingsValue
_ [AttrOp SettingsValue tag]
attrs = do
SettingsValue
o <- m SettingsValue
forall (m :: * -> *). MonadIO m => m SettingsValue
newZeroSettingsValue
SettingsValue -> [AttrOp SettingsValue 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set SettingsValue
o [AttrOp SettingsValue tag]
[AttrOp SettingsValue 'AttrSet]
attrs
SettingsValue -> m SettingsValue
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsValue
o
getSettingsValueOrigin :: MonadIO m => SettingsValue -> m (Maybe T.Text)
getSettingsValueOrigin :: forall (m :: * -> *). MonadIO m => SettingsValue -> m (Maybe Text)
getSettingsValueOrigin SettingsValue
s = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ SettingsValue
-> (Ptr SettingsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr SettingsValue -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CString
Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
val' -> do
Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setSettingsValueOrigin :: MonadIO m => SettingsValue -> CString -> m ()
setSettingsValueOrigin :: forall (m :: * -> *). MonadIO m => SettingsValue -> CString -> m ()
setSettingsValueOrigin SettingsValue
s CString
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ SettingsValue -> (Ptr SettingsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO ()) -> IO ())
-> (Ptr SettingsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
val :: CString)
clearSettingsValueOrigin :: MonadIO m => SettingsValue -> m ()
clearSettingsValueOrigin :: forall (m :: * -> *). MonadIO m => SettingsValue -> m ()
clearSettingsValueOrigin SettingsValue
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ SettingsValue -> (Ptr SettingsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO ()) -> IO ())
-> (Ptr SettingsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
forall a. Ptr a
FP.nullPtr :: CString)
#if defined(ENABLE_OVERLOADING)
data SettingsValueOriginFieldInfo
instance AttrInfo SettingsValueOriginFieldInfo where
type AttrBaseTypeConstraint SettingsValueOriginFieldInfo = (~) SettingsValue
type AttrAllowedOps SettingsValueOriginFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint SettingsValueOriginFieldInfo = (~) CString
type AttrTransferTypeConstraint SettingsValueOriginFieldInfo = (~)CString
type AttrTransferType SettingsValueOriginFieldInfo = CString
type AttrGetType SettingsValueOriginFieldInfo = Maybe T.Text
type AttrLabel SettingsValueOriginFieldInfo = "origin"
type AttrOrigin SettingsValueOriginFieldInfo = SettingsValue
attrGet = getSettingsValueOrigin
attrSet = setSettingsValueOrigin
attrConstruct = undefined
attrClear = clearSettingsValueOrigin
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.SettingsValue.origin"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-SettingsValue.html#g:attr:origin"
})
settingsValue_origin :: AttrLabelProxy "origin"
settingsValue_origin = AttrLabelProxy
#endif
getSettingsValueValue :: MonadIO m => SettingsValue -> m (Maybe GValue)
getSettingsValueValue :: forall (m :: * -> *).
MonadIO m =>
SettingsValue -> m (Maybe GValue)
getSettingsValueValue SettingsValue
s = IO (Maybe GValue) -> m (Maybe GValue)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GValue) -> m (Maybe GValue))
-> IO (Maybe GValue) -> m (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ SettingsValue
-> (Ptr SettingsValue -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO (Maybe GValue)) -> IO (Maybe GValue))
-> (Ptr SettingsValue -> IO (Maybe GValue)) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
Ptr GValue
val <- Ptr (Ptr GValue) -> IO (Ptr GValue)
forall a. Storable a => Ptr a -> IO a
peek (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr GValue)
Maybe GValue
result <- Ptr GValue -> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GValue
val ((Ptr GValue -> IO GValue) -> IO (Maybe GValue))
-> (Ptr GValue -> IO GValue) -> IO (Maybe GValue)
forall a b. (a -> b) -> a -> b
$ \Ptr GValue
val' -> do
GValue
val'' <- Ptr GValue -> IO GValue
B.GValue.newGValueFromPtr Ptr GValue
val'
GValue -> IO GValue
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
val''
Maybe GValue -> IO (Maybe GValue)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GValue
result
setSettingsValueValue :: MonadIO m => SettingsValue -> Ptr GValue -> m ()
setSettingsValueValue :: forall (m :: * -> *).
MonadIO m =>
SettingsValue -> Ptr GValue -> m ()
setSettingsValueValue SettingsValue
s Ptr GValue
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ SettingsValue -> (Ptr SettingsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO ()) -> IO ())
-> (Ptr SettingsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GValue
val :: Ptr GValue)
clearSettingsValueValue :: MonadIO m => SettingsValue -> m ()
clearSettingsValueValue :: forall (m :: * -> *). MonadIO m => SettingsValue -> m ()
clearSettingsValueValue SettingsValue
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ SettingsValue -> (Ptr SettingsValue -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr SettingsValue
s ((Ptr SettingsValue -> IO ()) -> IO ())
-> (Ptr SettingsValue -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsValue
ptr -> do
Ptr (Ptr GValue) -> Ptr GValue -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr SettingsValue
ptr Ptr SettingsValue -> Int -> Ptr (Ptr GValue)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GValue
forall a. Ptr a
FP.nullPtr :: Ptr GValue)
#if defined(ENABLE_OVERLOADING)
data SettingsValueValueFieldInfo
instance AttrInfo SettingsValueValueFieldInfo where
type AttrBaseTypeConstraint SettingsValueValueFieldInfo = (~) SettingsValue
type AttrAllowedOps SettingsValueValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint SettingsValueValueFieldInfo = (~) (Ptr GValue)
type AttrTransferTypeConstraint SettingsValueValueFieldInfo = (~)(Ptr GValue)
type AttrTransferType SettingsValueValueFieldInfo = (Ptr GValue)
type AttrGetType SettingsValueValueFieldInfo = Maybe GValue
type AttrLabel SettingsValueValueFieldInfo = "value"
type AttrOrigin SettingsValueValueFieldInfo = SettingsValue
attrGet = getSettingsValueValue
attrSet = setSettingsValueValue
attrConstruct = undefined
attrClear = clearSettingsValueValue
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.SettingsValue.value"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-3.0.41/docs/GI-Gtk-Structs-SettingsValue.html#g:attr:value"
})
settingsValue_value :: AttrLabelProxy "value"
settingsValue_value = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsValue
type instance O.AttributeList SettingsValue = SettingsValueAttributeList
type SettingsValueAttributeList = ('[ '("origin", SettingsValueOriginFieldInfo), '("value", SettingsValueValueFieldInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsValueMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSettingsValueMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSettingsValueMethod t SettingsValue, O.OverloadedMethod info SettingsValue p) => OL.IsLabel t (SettingsValue -> 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 ~ ResolveSettingsValueMethod t SettingsValue, O.OverloadedMethod info SettingsValue p, R.HasField t SettingsValue p) => R.HasField t SettingsValue p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSettingsValueMethod t SettingsValue, O.OverloadedMethodInfo info SettingsValue) => OL.IsLabel t (O.MethodProxy info SettingsValue) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif