{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.LogField
(
LogField(..) ,
newZeroLogField ,
#if defined(ENABLE_OVERLOADING)
ResolveLogFieldMethod ,
#endif
clearLogFieldKey ,
getLogFieldKey ,
#if defined(ENABLE_OVERLOADING)
logField_key ,
#endif
setLogFieldKey ,
getLogFieldLength ,
#if defined(ENABLE_OVERLOADING)
logField_length ,
#endif
setLogFieldLength ,
clearLogFieldValue ,
getLogFieldValue ,
#if defined(ENABLE_OVERLOADING)
logField_value ,
#endif
setLogFieldValue ,
) 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
newtype LogField = LogField (SP.ManagedPtr LogField)
deriving (LogField -> LogField -> Bool
(LogField -> LogField -> Bool)
-> (LogField -> LogField -> Bool) -> Eq LogField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogField -> LogField -> Bool
$c/= :: LogField -> LogField -> Bool
== :: LogField -> LogField -> Bool
$c== :: LogField -> LogField -> Bool
Eq)
instance SP.ManagedPtrNewtype LogField where
toManagedPtr :: LogField -> ManagedPtr LogField
toManagedPtr (LogField ManagedPtr LogField
p) = ManagedPtr LogField
p
instance BoxedPtr LogField where
boxedPtrCopy :: LogField -> IO LogField
boxedPtrCopy = \LogField
p -> LogField -> (Ptr LogField -> IO LogField) -> IO LogField
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr LogField
p (Int -> Ptr LogField -> IO (Ptr LogField)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
24 (Ptr LogField -> IO (Ptr LogField))
-> (Ptr LogField -> IO LogField) -> Ptr LogField -> IO LogField
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr LogField -> LogField) -> Ptr LogField -> IO LogField
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr LogField -> LogField
LogField)
boxedPtrFree :: LogField -> IO ()
boxedPtrFree = \LogField
x -> LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr LogField
x Ptr LogField -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr LogField where
boxedPtrCalloc :: IO (Ptr LogField)
boxedPtrCalloc = Int -> IO (Ptr LogField)
forall a. Int -> IO (Ptr a)
callocBytes Int
24
newZeroLogField :: MonadIO m => m LogField
newZeroLogField :: forall (m :: * -> *). MonadIO m => m LogField
newZeroLogField = IO LogField -> m LogField
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LogField -> m LogField) -> IO LogField -> m LogField
forall a b. (a -> b) -> a -> b
$ IO (Ptr LogField)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr LogField) -> (Ptr LogField -> IO LogField) -> IO LogField
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr LogField -> LogField) -> Ptr LogField -> IO LogField
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr LogField -> LogField
LogField
instance tag ~ 'AttrSet => Constructible LogField tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr LogField -> LogField)
-> [AttrOp LogField tag] -> m LogField
new ManagedPtr LogField -> LogField
_ [AttrOp LogField tag]
attrs = do
LogField
o <- m LogField
forall (m :: * -> *). MonadIO m => m LogField
newZeroLogField
LogField -> [AttrOp LogField 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set LogField
o [AttrOp LogField tag]
[AttrOp LogField 'AttrSet]
attrs
LogField -> m LogField
forall (m :: * -> *) a. Monad m => a -> m a
return LogField
o
getLogFieldKey :: MonadIO m => LogField -> m (Maybe T.Text)
getLogFieldKey :: forall (m :: * -> *). MonadIO m => LogField -> m (Maybe Text)
getLogFieldKey LogField
s = IO (Maybe Text) -> m (Maybe Text)
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
$ LogField -> (Ptr LogField -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr LogField -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr LogField
ptr Ptr LogField -> 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 (m :: * -> *) a. Monad m => a -> m a
return Text
val''
Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result
setLogFieldKey :: MonadIO m => LogField -> CString -> m ()
setLogFieldKey :: forall (m :: * -> *). MonadIO m => LogField -> CString -> m ()
setLogFieldKey LogField
s CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO ()) -> IO ())
-> (Ptr LogField -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LogField
ptr Ptr LogField -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CString
val :: CString)
clearLogFieldKey :: MonadIO m => LogField -> m ()
clearLogFieldKey :: forall (m :: * -> *). MonadIO m => LogField -> m ()
clearLogFieldKey LogField
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO ()) -> IO ())
-> (Ptr LogField -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LogField
ptr Ptr LogField -> 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 LogFieldKeyFieldInfo
instance AttrInfo LogFieldKeyFieldInfo where
type AttrBaseTypeConstraint LogFieldKeyFieldInfo = (~) LogField
type AttrAllowedOps LogFieldKeyFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint LogFieldKeyFieldInfo = (~) CString
type AttrTransferTypeConstraint LogFieldKeyFieldInfo = (~)CString
type AttrTransferType LogFieldKeyFieldInfo = CString
type AttrGetType LogFieldKeyFieldInfo = Maybe T.Text
type AttrLabel LogFieldKeyFieldInfo = "key"
type AttrOrigin LogFieldKeyFieldInfo = LogField
attrGet = getLogFieldKey
attrSet = setLogFieldKey
attrConstruct = undefined
attrClear = clearLogFieldKey
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GLib.Structs.LogField.key"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-LogField.html#g:attr:key"
})
logField_key :: AttrLabelProxy "key"
logField_key = AttrLabelProxy
#endif
getLogFieldValue :: MonadIO m => LogField -> m (Ptr ())
getLogFieldValue :: forall (m :: * -> *). MonadIO m => LogField -> m (Ptr ())
getLogFieldValue LogField
s = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr LogField -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr LogField
ptr Ptr LogField -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr ())
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
val
setLogFieldValue :: MonadIO m => LogField -> Ptr () -> m ()
setLogFieldValue :: forall (m :: * -> *). MonadIO m => LogField -> Ptr () -> m ()
setLogFieldValue LogField
s Ptr ()
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO ()) -> IO ())
-> (Ptr LogField -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LogField
ptr Ptr LogField -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr ()
val :: Ptr ())
clearLogFieldValue :: MonadIO m => LogField -> m ()
clearLogFieldValue :: forall (m :: * -> *). MonadIO m => LogField -> m ()
clearLogFieldValue LogField
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO ()) -> IO ())
-> (Ptr LogField -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LogField
ptr Ptr LogField -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())
#if defined(ENABLE_OVERLOADING)
data LogFieldValueFieldInfo
instance AttrInfo LogFieldValueFieldInfo where
type AttrBaseTypeConstraint LogFieldValueFieldInfo = (~) LogField
type AttrAllowedOps LogFieldValueFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint LogFieldValueFieldInfo = (~) (Ptr ())
type AttrTransferTypeConstraint LogFieldValueFieldInfo = (~)(Ptr ())
type AttrTransferType LogFieldValueFieldInfo = (Ptr ())
type AttrGetType LogFieldValueFieldInfo = Ptr ()
type AttrLabel LogFieldValueFieldInfo = "value"
type AttrOrigin LogFieldValueFieldInfo = LogField
attrGet = getLogFieldValue
attrSet = setLogFieldValue
attrConstruct = undefined
attrClear = clearLogFieldValue
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GLib.Structs.LogField.value"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-LogField.html#g:attr:value"
})
logField_value :: AttrLabelProxy "value"
logField_value = AttrLabelProxy
#endif
getLogFieldLength :: MonadIO m => LogField -> m Int64
getLogFieldLength :: forall (m :: * -> *). MonadIO m => LogField -> m Int64
getLogFieldLength LogField
s = IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO Int64) -> IO Int64
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO Int64) -> IO Int64)
-> (Ptr LogField -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Int64
val <- Ptr Int64 -> IO Int64
forall a. Storable a => Ptr a -> IO a
peek (Ptr LogField
ptr Ptr LogField -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int64
Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
val
setLogFieldLength :: MonadIO m => LogField -> Int64 -> m ()
setLogFieldLength :: forall (m :: * -> *). MonadIO m => LogField -> Int64 -> m ()
setLogFieldLength LogField
s Int64
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LogField -> (Ptr LogField -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LogField
s ((Ptr LogField -> IO ()) -> IO ())
-> (Ptr LogField -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr LogField
ptr -> do
Ptr Int64 -> Int64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LogField
ptr Ptr LogField -> Int -> Ptr Int64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int64
val :: Int64)
#if defined(ENABLE_OVERLOADING)
data LogFieldLengthFieldInfo
instance AttrInfo LogFieldLengthFieldInfo where
type AttrBaseTypeConstraint LogFieldLengthFieldInfo = (~) LogField
type AttrAllowedOps LogFieldLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint LogFieldLengthFieldInfo = (~) Int64
type AttrTransferTypeConstraint LogFieldLengthFieldInfo = (~)Int64
type AttrTransferType LogFieldLengthFieldInfo = Int64
type AttrGetType LogFieldLengthFieldInfo = Int64
type AttrLabel LogFieldLengthFieldInfo = "length"
type AttrOrigin LogFieldLengthFieldInfo = LogField
attrGet = getLogFieldLength
attrSet = setLogFieldLength
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GLib.Structs.LogField.length"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.26/docs/GI-GLib-Structs-LogField.html#g:attr:length"
})
logField_length :: AttrLabelProxy "length"
logField_length = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LogField
type instance O.AttributeList LogField = LogFieldAttributeList
type LogFieldAttributeList = ('[ '("key", LogFieldKeyFieldInfo), '("value", LogFieldValueFieldInfo), '("length", LogFieldLengthFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveLogFieldMethod (t :: Symbol) (o :: *) :: * where
ResolveLogFieldMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveLogFieldMethod t LogField, O.OverloadedMethod info LogField p) => OL.IsLabel t (LogField -> 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 ~ ResolveLogFieldMethod t LogField, O.OverloadedMethod info LogField p, R.HasField t LogField p) => R.HasField t LogField p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveLogFieldMethod t LogField, O.OverloadedMethodInfo info LogField) => OL.IsLabel t (O.MethodProxy info LogField) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif