{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.GlyphVisAttr
(
GlyphVisAttr(..) ,
newZeroGlyphVisAttr ,
#if defined(ENABLE_OVERLOADING)
ResolveGlyphVisAttrMethod ,
#endif
getGlyphVisAttrIsClusterStart ,
#if defined(ENABLE_OVERLOADING)
glyphVisAttr_isClusterStart ,
#endif
setGlyphVisAttrIsClusterStart ,
getGlyphVisAttrIsColor ,
#if defined(ENABLE_OVERLOADING)
glyphVisAttr_isColor ,
#endif
setGlyphVisAttrIsColor ,
) 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 GlyphVisAttr = GlyphVisAttr (SP.ManagedPtr GlyphVisAttr)
deriving (GlyphVisAttr -> GlyphVisAttr -> Bool
(GlyphVisAttr -> GlyphVisAttr -> Bool)
-> (GlyphVisAttr -> GlyphVisAttr -> Bool) -> Eq GlyphVisAttr
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlyphVisAttr -> GlyphVisAttr -> Bool
$c/= :: GlyphVisAttr -> GlyphVisAttr -> Bool
== :: GlyphVisAttr -> GlyphVisAttr -> Bool
$c== :: GlyphVisAttr -> GlyphVisAttr -> Bool
Eq)
instance SP.ManagedPtrNewtype GlyphVisAttr where
toManagedPtr :: GlyphVisAttr -> ManagedPtr GlyphVisAttr
toManagedPtr (GlyphVisAttr ManagedPtr GlyphVisAttr
p) = ManagedPtr GlyphVisAttr
p
instance BoxedPtr GlyphVisAttr where
boxedPtrCopy :: GlyphVisAttr -> IO GlyphVisAttr
boxedPtrCopy = \GlyphVisAttr
p -> GlyphVisAttr
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr) -> IO GlyphVisAttr
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GlyphVisAttr
p (Int -> Ptr GlyphVisAttr -> IO (Ptr GlyphVisAttr)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
8 (Ptr GlyphVisAttr -> IO (Ptr GlyphVisAttr))
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr)
-> Ptr GlyphVisAttr
-> IO GlyphVisAttr
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr GlyphVisAttr -> GlyphVisAttr)
-> Ptr GlyphVisAttr -> IO GlyphVisAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr GlyphVisAttr -> GlyphVisAttr
GlyphVisAttr)
boxedPtrFree :: GlyphVisAttr -> IO ()
boxedPtrFree = \GlyphVisAttr
x -> GlyphVisAttr -> (Ptr GlyphVisAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr GlyphVisAttr
x Ptr GlyphVisAttr -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr GlyphVisAttr where
boxedPtrCalloc :: IO (Ptr GlyphVisAttr)
boxedPtrCalloc = Int -> IO (Ptr GlyphVisAttr)
forall a. Int -> IO (Ptr a)
callocBytes Int
8
newZeroGlyphVisAttr :: MonadIO m => m GlyphVisAttr
newZeroGlyphVisAttr :: forall (m :: * -> *). MonadIO m => m GlyphVisAttr
newZeroGlyphVisAttr = IO GlyphVisAttr -> m GlyphVisAttr
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphVisAttr -> m GlyphVisAttr)
-> IO GlyphVisAttr -> m GlyphVisAttr
forall a b. (a -> b) -> a -> b
$ IO (Ptr GlyphVisAttr)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr GlyphVisAttr)
-> (Ptr GlyphVisAttr -> IO GlyphVisAttr) -> IO GlyphVisAttr
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphVisAttr -> GlyphVisAttr)
-> Ptr GlyphVisAttr -> IO GlyphVisAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr GlyphVisAttr -> GlyphVisAttr
GlyphVisAttr
instance tag ~ 'AttrSet => Constructible GlyphVisAttr tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr GlyphVisAttr -> GlyphVisAttr)
-> [AttrOp GlyphVisAttr tag] -> m GlyphVisAttr
new ManagedPtr GlyphVisAttr -> GlyphVisAttr
_ [AttrOp GlyphVisAttr tag]
attrs = do
GlyphVisAttr
o <- m GlyphVisAttr
forall (m :: * -> *). MonadIO m => m GlyphVisAttr
newZeroGlyphVisAttr
GlyphVisAttr -> [AttrOp GlyphVisAttr 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set GlyphVisAttr
o [AttrOp GlyphVisAttr tag]
[AttrOp GlyphVisAttr 'AttrSet]
attrs
GlyphVisAttr -> m GlyphVisAttr
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphVisAttr
o
getGlyphVisAttrIsClusterStart :: MonadIO m => GlyphVisAttr -> m Word32
getGlyphVisAttrIsClusterStart :: forall (m :: * -> *). MonadIO m => GlyphVisAttr -> m Word32
getGlyphVisAttrIsClusterStart GlyphVisAttr
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ GlyphVisAttr -> (Ptr GlyphVisAttr -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphVisAttr
s ((Ptr GlyphVisAttr -> IO Word32) -> IO Word32)
-> (Ptr GlyphVisAttr -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphVisAttr
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphVisAttr
ptr Ptr GlyphVisAttr -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setGlyphVisAttrIsClusterStart :: MonadIO m => GlyphVisAttr -> Word32 -> m ()
setGlyphVisAttrIsClusterStart :: forall (m :: * -> *). MonadIO m => GlyphVisAttr -> Word32 -> m ()
setGlyphVisAttrIsClusterStart GlyphVisAttr
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphVisAttr -> (Ptr GlyphVisAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphVisAttr
s ((Ptr GlyphVisAttr -> IO ()) -> IO ())
-> (Ptr GlyphVisAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphVisAttr
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphVisAttr
ptr Ptr GlyphVisAttr -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data GlyphVisAttrIsClusterStartFieldInfo
instance AttrInfo GlyphVisAttrIsClusterStartFieldInfo where
type AttrBaseTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~) GlyphVisAttr
type AttrAllowedOps GlyphVisAttrIsClusterStartFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~) Word32
type AttrTransferTypeConstraint GlyphVisAttrIsClusterStartFieldInfo = (~)Word32
type AttrTransferType GlyphVisAttrIsClusterStartFieldInfo = Word32
type AttrGetType GlyphVisAttrIsClusterStartFieldInfo = Word32
type AttrLabel GlyphVisAttrIsClusterStartFieldInfo = "is_cluster_start"
type AttrOrigin GlyphVisAttrIsClusterStartFieldInfo = GlyphVisAttr
attrGet = getGlyphVisAttrIsClusterStart
attrSet = setGlyphVisAttrIsClusterStart
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.GlyphVisAttr.isClusterStart"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-GlyphVisAttr.html#g:attr:isClusterStart"
})
glyphVisAttr_isClusterStart :: AttrLabelProxy "isClusterStart"
glyphVisAttr_isClusterStart = AttrLabelProxy
#endif
getGlyphVisAttrIsColor :: MonadIO m => GlyphVisAttr -> m Word32
getGlyphVisAttrIsColor :: forall (m :: * -> *). MonadIO m => GlyphVisAttr -> m Word32
getGlyphVisAttrIsColor GlyphVisAttr
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ GlyphVisAttr -> (Ptr GlyphVisAttr -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphVisAttr
s ((Ptr GlyphVisAttr -> IO Word32) -> IO Word32)
-> (Ptr GlyphVisAttr -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphVisAttr
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphVisAttr
ptr Ptr GlyphVisAttr -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setGlyphVisAttrIsColor :: MonadIO m => GlyphVisAttr -> Word32 -> m ()
setGlyphVisAttrIsColor :: forall (m :: * -> *). MonadIO m => GlyphVisAttr -> Word32 -> m ()
setGlyphVisAttrIsColor GlyphVisAttr
s Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphVisAttr -> (Ptr GlyphVisAttr -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphVisAttr
s ((Ptr GlyphVisAttr -> IO ()) -> IO ())
-> (Ptr GlyphVisAttr -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphVisAttr
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphVisAttr
ptr Ptr GlyphVisAttr -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data GlyphVisAttrIsColorFieldInfo
instance AttrInfo GlyphVisAttrIsColorFieldInfo where
type AttrBaseTypeConstraint GlyphVisAttrIsColorFieldInfo = (~) GlyphVisAttr
type AttrAllowedOps GlyphVisAttrIsColorFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint GlyphVisAttrIsColorFieldInfo = (~) Word32
type AttrTransferTypeConstraint GlyphVisAttrIsColorFieldInfo = (~)Word32
type AttrTransferType GlyphVisAttrIsColorFieldInfo = Word32
type AttrGetType GlyphVisAttrIsColorFieldInfo = Word32
type AttrLabel GlyphVisAttrIsColorFieldInfo = "is_color"
type AttrOrigin GlyphVisAttrIsColorFieldInfo = GlyphVisAttr
attrGet = getGlyphVisAttrIsColor
attrSet = setGlyphVisAttrIsColor
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.GlyphVisAttr.isColor"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-GlyphVisAttr.html#g:attr:isColor"
})
glyphVisAttr_isColor :: AttrLabelProxy "isColor"
glyphVisAttr_isColor = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphVisAttr
type instance O.AttributeList GlyphVisAttr = GlyphVisAttrAttributeList
type GlyphVisAttrAttributeList = ('[ '("isClusterStart", GlyphVisAttrIsClusterStartFieldInfo), '("isColor", GlyphVisAttrIsColorFieldInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveGlyphVisAttrMethod (t :: Symbol) (o :: *) :: * where
ResolveGlyphVisAttrMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveGlyphVisAttrMethod t GlyphVisAttr, O.OverloadedMethod info GlyphVisAttr p) => OL.IsLabel t (GlyphVisAttr -> 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 ~ ResolveGlyphVisAttrMethod t GlyphVisAttr, O.OverloadedMethod info GlyphVisAttr p, R.HasField t GlyphVisAttr p) => R.HasField t GlyphVisAttr p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveGlyphVisAttrMethod t GlyphVisAttr, O.OverloadedMethodInfo info GlyphVisAttr) => OL.IsLabel t (O.MethodProxy info GlyphVisAttr) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif