{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.AttrShape
(
AttrShape(..) ,
newZeroAttrShape ,
#if defined(ENABLE_OVERLOADING)
ResolveAttrShapeMethod ,
#endif
attrShapeNew ,
attrShapeNewWithData ,
#if defined(ENABLE_OVERLOADING)
attrShape_attr ,
#endif
getAttrShapeAttr ,
#if defined(ENABLE_OVERLOADING)
attrShape_copyFunc ,
#endif
clearAttrShapeCopyFunc ,
getAttrShapeCopyFunc ,
setAttrShapeCopyFunc ,
#if defined(ENABLE_OVERLOADING)
attrShape_data ,
#endif
clearAttrShapeData ,
getAttrShapeData ,
setAttrShapeData ,
#if defined(ENABLE_OVERLOADING)
attrShape_destroyFunc ,
#endif
clearAttrShapeDestroyFunc ,
getAttrShapeDestroyFunc ,
setAttrShapeDestroyFunc ,
#if defined(ENABLE_OVERLOADING)
attrShape_inkRect ,
#endif
getAttrShapeInkRect ,
#if defined(ENABLE_OVERLOADING)
attrShape_logicalRect ,
#endif
getAttrShapeLogicalRect ,
) 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.GLib.Callbacks as GLib.Callbacks
import qualified GI.Pango.Callbacks as Pango.Callbacks
import {-# SOURCE #-} qualified GI.Pango.Structs.Attribute as Pango.Attribute
import {-# SOURCE #-} qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
newtype AttrShape = AttrShape (SP.ManagedPtr AttrShape)
deriving (AttrShape -> AttrShape -> Bool
(AttrShape -> AttrShape -> Bool)
-> (AttrShape -> AttrShape -> Bool) -> Eq AttrShape
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttrShape -> AttrShape -> Bool
$c/= :: AttrShape -> AttrShape -> Bool
== :: AttrShape -> AttrShape -> Bool
$c== :: AttrShape -> AttrShape -> Bool
Eq)
instance SP.ManagedPtrNewtype AttrShape where
toManagedPtr :: AttrShape -> ManagedPtr AttrShape
toManagedPtr (AttrShape ManagedPtr AttrShape
p) = ManagedPtr AttrShape
p
instance BoxedPtr AttrShape where
boxedPtrCopy :: AttrShape -> IO AttrShape
boxedPtrCopy = \AttrShape
p -> AttrShape -> (Ptr AttrShape -> IO AttrShape) -> IO AttrShape
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrShape
p (Int -> Ptr AttrShape -> IO (Ptr AttrShape)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
72 (Ptr AttrShape -> IO (Ptr AttrShape))
-> (Ptr AttrShape -> IO AttrShape) -> Ptr AttrShape -> IO AttrShape
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr AttrShape -> AttrShape)
-> Ptr AttrShape -> IO AttrShape
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr AttrShape -> AttrShape
AttrShape)
boxedPtrFree :: AttrShape -> IO ()
boxedPtrFree = \AttrShape
x -> AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr AttrShape
x Ptr AttrShape -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr AttrShape where
boxedPtrCalloc :: IO (Ptr AttrShape)
boxedPtrCalloc = Int -> IO (Ptr AttrShape)
forall a. Int -> IO (Ptr a)
callocBytes Int
72
newZeroAttrShape :: MonadIO m => m AttrShape
newZeroAttrShape :: forall (m :: * -> *). MonadIO m => m AttrShape
newZeroAttrShape = IO AttrShape -> m AttrShape
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrShape -> m AttrShape) -> IO AttrShape -> m AttrShape
forall a b. (a -> b) -> a -> b
$ IO (Ptr AttrShape)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr AttrShape)
-> (Ptr AttrShape -> IO AttrShape) -> IO AttrShape
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr AttrShape -> AttrShape)
-> Ptr AttrShape -> IO AttrShape
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr AttrShape -> AttrShape
AttrShape
instance tag ~ 'AttrSet => Constructible AttrShape tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr AttrShape -> AttrShape)
-> [AttrOp AttrShape tag] -> m AttrShape
new ManagedPtr AttrShape -> AttrShape
_ [AttrOp AttrShape tag]
attrs = do
AttrShape
o <- m AttrShape
forall (m :: * -> *). MonadIO m => m AttrShape
newZeroAttrShape
AttrShape -> [AttrOp AttrShape 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set AttrShape
o [AttrOp AttrShape tag]
[AttrOp AttrShape 'AttrSet]
attrs
AttrShape -> m AttrShape
forall (m :: * -> *) a. Monad m => a -> m a
return AttrShape
o
getAttrShapeAttr :: MonadIO m => AttrShape -> m Pango.Attribute.Attribute
getAttrShapeAttr :: forall (m :: * -> *). MonadIO m => AttrShape -> m Attribute
getAttrShapeAttr AttrShape
s = IO Attribute -> m Attribute
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attribute -> m Attribute) -> IO Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO Attribute) -> IO Attribute
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO Attribute) -> IO Attribute)
-> (Ptr AttrShape -> IO Attribute) -> IO Attribute
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
let val :: Ptr Attribute
val = Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr Attribute
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: (Ptr Pango.Attribute.Attribute)
Attribute
val' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
val
Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
val'
#if defined(ENABLE_OVERLOADING)
data AttrShapeAttrFieldInfo
instance AttrInfo AttrShapeAttrFieldInfo where
type AttrBaseTypeConstraint AttrShapeAttrFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeAttrFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeAttrFieldInfo = (~) (Ptr Pango.Attribute.Attribute)
type AttrTransferTypeConstraint AttrShapeAttrFieldInfo = (~)(Ptr Pango.Attribute.Attribute)
type AttrTransferType AttrShapeAttrFieldInfo = (Ptr Pango.Attribute.Attribute)
type AttrGetType AttrShapeAttrFieldInfo = Pango.Attribute.Attribute
type AttrLabel AttrShapeAttrFieldInfo = "attr"
type AttrOrigin AttrShapeAttrFieldInfo = AttrShape
attrGet = getAttrShapeAttr
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.attr"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:attr"
})
attrShape_attr :: AttrLabelProxy "attr"
attrShape_attr = AttrLabelProxy
#endif
getAttrShapeInkRect :: MonadIO m => AttrShape -> m Pango.Rectangle.Rectangle
getAttrShapeInkRect :: forall (m :: * -> *). MonadIO m => AttrShape -> m Rectangle
getAttrShapeInkRect AttrShape
s = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO Rectangle) -> IO Rectangle
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO Rectangle) -> IO Rectangle)
-> (Ptr AttrShape -> IO Rectangle) -> IO Rectangle
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
let val :: Ptr Rectangle
val = Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr Rectangle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: (Ptr Pango.Rectangle.Rectangle)
Rectangle
val' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
val
Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
val'
#if defined(ENABLE_OVERLOADING)
data AttrShapeInkRectFieldInfo
instance AttrInfo AttrShapeInkRectFieldInfo where
type AttrBaseTypeConstraint AttrShapeInkRectFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeInkRectFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeInkRectFieldInfo = (~) (Ptr Pango.Rectangle.Rectangle)
type AttrTransferTypeConstraint AttrShapeInkRectFieldInfo = (~)(Ptr Pango.Rectangle.Rectangle)
type AttrTransferType AttrShapeInkRectFieldInfo = (Ptr Pango.Rectangle.Rectangle)
type AttrGetType AttrShapeInkRectFieldInfo = Pango.Rectangle.Rectangle
type AttrLabel AttrShapeInkRectFieldInfo = "ink_rect"
type AttrOrigin AttrShapeInkRectFieldInfo = AttrShape
attrGet = getAttrShapeInkRect
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.inkRect"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:inkRect"
})
attrShape_inkRect :: AttrLabelProxy "inkRect"
attrShape_inkRect = AttrLabelProxy
#endif
getAttrShapeLogicalRect :: MonadIO m => AttrShape -> m Pango.Rectangle.Rectangle
getAttrShapeLogicalRect :: forall (m :: * -> *). MonadIO m => AttrShape -> m Rectangle
getAttrShapeLogicalRect AttrShape
s = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO Rectangle) -> IO Rectangle
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO Rectangle) -> IO Rectangle)
-> (Ptr AttrShape -> IO Rectangle) -> IO Rectangle
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
let val :: Ptr Rectangle
val = Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr Rectangle
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: (Ptr Pango.Rectangle.Rectangle)
Rectangle
val' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
val
Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
val'
#if defined(ENABLE_OVERLOADING)
data AttrShapeLogicalRectFieldInfo
instance AttrInfo AttrShapeLogicalRectFieldInfo where
type AttrBaseTypeConstraint AttrShapeLogicalRectFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeLogicalRectFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeLogicalRectFieldInfo = (~) (Ptr Pango.Rectangle.Rectangle)
type AttrTransferTypeConstraint AttrShapeLogicalRectFieldInfo = (~)(Ptr Pango.Rectangle.Rectangle)
type AttrTransferType AttrShapeLogicalRectFieldInfo = (Ptr Pango.Rectangle.Rectangle)
type AttrGetType AttrShapeLogicalRectFieldInfo = Pango.Rectangle.Rectangle
type AttrLabel AttrShapeLogicalRectFieldInfo = "logical_rect"
type AttrOrigin AttrShapeLogicalRectFieldInfo = AttrShape
attrGet = getAttrShapeLogicalRect
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.logicalRect"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:logicalRect"
})
attrShape_logicalRect :: AttrLabelProxy "logicalRect"
attrShape_logicalRect = AttrLabelProxy
#endif
getAttrShapeData :: MonadIO m => AttrShape -> m (Ptr ())
getAttrShapeData :: forall (m :: * -> *). MonadIO m => AttrShape -> m (Ptr ())
getAttrShapeData AttrShape
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
$ AttrShape -> (Ptr AttrShape -> IO (Ptr ())) -> IO (Ptr ())
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO (Ptr ())) -> IO (Ptr ()))
-> (Ptr AttrShape -> IO (Ptr ())) -> IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr ()
val <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO (Ptr ())
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
val
setAttrShapeData :: MonadIO m => AttrShape -> Ptr () -> m ()
setAttrShapeData :: forall (m :: * -> *). MonadIO m => AttrShape -> Ptr () -> m ()
setAttrShapeData AttrShape
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
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (Ptr ()
val :: Ptr ())
clearAttrShapeData :: MonadIO m => AttrShape -> m ()
clearAttrShapeData :: forall (m :: * -> *). MonadIO m => AttrShape -> m ()
clearAttrShapeData AttrShape
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (Ptr ()
forall a. Ptr a
FP.nullPtr :: Ptr ())
#if defined(ENABLE_OVERLOADING)
data AttrShapeDataFieldInfo
instance AttrInfo AttrShapeDataFieldInfo where
type AttrBaseTypeConstraint AttrShapeDataFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeDataFieldInfo = (~) (Ptr ())
type AttrTransferTypeConstraint AttrShapeDataFieldInfo = (~)(Ptr ())
type AttrTransferType AttrShapeDataFieldInfo = (Ptr ())
type AttrGetType AttrShapeDataFieldInfo = Ptr ()
type AttrLabel AttrShapeDataFieldInfo = "data"
type AttrOrigin AttrShapeDataFieldInfo = AttrShape
attrGet = getAttrShapeData
attrSet = setAttrShapeData
attrConstruct = undefined
attrClear = clearAttrShapeData
attrTransfer _ v = do
return v
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.data"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:data"
})
attrShape_data :: AttrLabelProxy "data"
attrShape_data = AttrLabelProxy
#endif
getAttrShapeCopyFunc :: MonadIO m => AttrShape -> m (Maybe Pango.Callbacks.AttrDataCopyFunc_WithClosures)
getAttrShapeCopyFunc :: forall (m :: * -> *).
MonadIO m =>
AttrShape -> m (Maybe (Ptr () -> IO (Ptr ())))
getAttrShapeCopyFunc AttrShape
s = IO (Maybe (Ptr () -> IO (Ptr ())))
-> m (Maybe (Ptr () -> IO (Ptr ())))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Ptr () -> IO (Ptr ())))
-> m (Maybe (Ptr () -> IO (Ptr ()))))
-> IO (Maybe (Ptr () -> IO (Ptr ())))
-> m (Maybe (Ptr () -> IO (Ptr ())))
forall a b. (a -> b) -> a -> b
$ AttrShape
-> (Ptr AttrShape -> IO (Maybe (Ptr () -> IO (Ptr ()))))
-> IO (Maybe (Ptr () -> IO (Ptr ())))
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO (Maybe (Ptr () -> IO (Ptr ()))))
-> IO (Maybe (Ptr () -> IO (Ptr ()))))
-> (Ptr AttrShape -> IO (Maybe (Ptr () -> IO (Ptr ()))))
-> IO (Maybe (Ptr () -> IO (Ptr ())))
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
FunPtr (Ptr () -> IO (Ptr ()))
val <- Ptr (FunPtr (Ptr () -> IO (Ptr ())))
-> IO (FunPtr (Ptr () -> IO (Ptr ())))
forall a. Storable a => Ptr a -> IO a
peek (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
Maybe (Ptr () -> IO (Ptr ()))
result <- FunPtr (Ptr () -> IO (Ptr ()))
-> (FunPtr (Ptr () -> IO (Ptr ())) -> IO (Ptr () -> IO (Ptr ())))
-> IO (Maybe (Ptr () -> IO (Ptr ())))
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr (Ptr () -> IO (Ptr ()))
val ((FunPtr (Ptr () -> IO (Ptr ())) -> IO (Ptr () -> IO (Ptr ())))
-> IO (Maybe (Ptr () -> IO (Ptr ()))))
-> (FunPtr (Ptr () -> IO (Ptr ())) -> IO (Ptr () -> IO (Ptr ())))
-> IO (Maybe (Ptr () -> IO (Ptr ())))
forall a b. (a -> b) -> a -> b
$ \FunPtr (Ptr () -> IO (Ptr ()))
val' -> do
let val'' :: Ptr () -> IO (Ptr ())
val'' = FunPtr (Ptr () -> IO (Ptr ())) -> Ptr () -> IO (Ptr ())
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr (Ptr () -> IO (Ptr ())) -> Ptr () -> m (Ptr ())
Pango.Callbacks.dynamic_AttrDataCopyFunc FunPtr (Ptr () -> IO (Ptr ()))
val'
(Ptr () -> IO (Ptr ())) -> IO (Ptr () -> IO (Ptr ()))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr () -> IO (Ptr ())
val''
Maybe (Ptr () -> IO (Ptr ())) -> IO (Maybe (Ptr () -> IO (Ptr ())))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Ptr () -> IO (Ptr ()))
result
setAttrShapeCopyFunc :: MonadIO m => AttrShape -> FunPtr Pango.Callbacks.C_AttrDataCopyFunc -> m ()
setAttrShapeCopyFunc :: forall (m :: * -> *).
MonadIO m =>
AttrShape -> FunPtr (Ptr () -> IO (Ptr ())) -> m ()
setAttrShapeCopyFunc AttrShape
s FunPtr (Ptr () -> IO (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
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (FunPtr (Ptr () -> IO (Ptr ())))
-> FunPtr (Ptr () -> IO (Ptr ())) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr (Ptr () -> IO (Ptr ()))
val :: FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
clearAttrShapeCopyFunc :: MonadIO m => AttrShape -> m ()
clearAttrShapeCopyFunc :: forall (m :: * -> *). MonadIO m => AttrShape -> m ()
clearAttrShapeCopyFunc AttrShape
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (FunPtr (Ptr () -> IO (Ptr ())))
-> FunPtr (Ptr () -> IO (Ptr ())) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO (Ptr ())))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (FunPtr (Ptr () -> IO (Ptr ()))
forall a. FunPtr a
FP.nullFunPtr :: FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
#if defined(ENABLE_OVERLOADING)
data AttrShapeCopyFuncFieldInfo
instance AttrInfo AttrShapeCopyFuncFieldInfo where
type AttrBaseTypeConstraint AttrShapeCopyFuncFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeCopyFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeCopyFuncFieldInfo = (~) (FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
type AttrTransferTypeConstraint AttrShapeCopyFuncFieldInfo = (~)Pango.Callbacks.AttrDataCopyFunc_WithClosures
type AttrTransferType AttrShapeCopyFuncFieldInfo = (FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
type AttrGetType AttrShapeCopyFuncFieldInfo = Maybe Pango.Callbacks.AttrDataCopyFunc_WithClosures
type AttrLabel AttrShapeCopyFuncFieldInfo = "copy_func"
type AttrOrigin AttrShapeCopyFuncFieldInfo = AttrShape
attrGet = getAttrShapeCopyFunc
attrSet = setAttrShapeCopyFunc
attrConstruct = undefined
attrClear = clearAttrShapeCopyFunc
attrTransfer _ v = do
Pango.Callbacks.mk_AttrDataCopyFunc (Pango.Callbacks.wrap_AttrDataCopyFunc Nothing v)
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.copyFunc"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:copyFunc"
})
attrShape_copyFunc :: AttrLabelProxy "copyFunc"
attrShape_copyFunc = AttrLabelProxy
#endif
getAttrShapeDestroyFunc :: MonadIO m => AttrShape -> m (Maybe GLib.Callbacks.DestroyNotify)
getAttrShapeDestroyFunc :: forall (m :: * -> *).
MonadIO m =>
AttrShape -> m (Maybe (Ptr () -> IO ()))
getAttrShapeDestroyFunc AttrShape
s = IO (Maybe (Ptr () -> IO ())) -> m (Maybe (Ptr () -> IO ()))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Ptr () -> IO ())) -> m (Maybe (Ptr () -> IO ())))
-> IO (Maybe (Ptr () -> IO ())) -> m (Maybe (Ptr () -> IO ()))
forall a b. (a -> b) -> a -> b
$ AttrShape
-> (Ptr AttrShape -> IO (Maybe (Ptr () -> IO ())))
-> IO (Maybe (Ptr () -> IO ()))
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO (Maybe (Ptr () -> IO ())))
-> IO (Maybe (Ptr () -> IO ())))
-> (Ptr AttrShape -> IO (Maybe (Ptr () -> IO ())))
-> IO (Maybe (Ptr () -> IO ()))
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
FunPtr (Ptr () -> IO ())
val <- Ptr (FunPtr (Ptr () -> IO ())) -> IO (FunPtr (Ptr () -> IO ()))
forall a. Storable a => Ptr a -> IO a
peek (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO ()))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO (FunPtr GLib.Callbacks.C_DestroyNotify)
Maybe (Ptr () -> IO ())
result <- FunPtr (Ptr () -> IO ())
-> (FunPtr (Ptr () -> IO ()) -> IO (Ptr () -> IO ()))
-> IO (Maybe (Ptr () -> IO ()))
forall a b. FunPtr a -> (FunPtr a -> IO b) -> IO (Maybe b)
SP.convertFunPtrIfNonNull FunPtr (Ptr () -> IO ())
val ((FunPtr (Ptr () -> IO ()) -> IO (Ptr () -> IO ()))
-> IO (Maybe (Ptr () -> IO ())))
-> (FunPtr (Ptr () -> IO ()) -> IO (Ptr () -> IO ()))
-> IO (Maybe (Ptr () -> IO ()))
forall a b. (a -> b) -> a -> b
$ \FunPtr (Ptr () -> IO ())
val' -> do
let val'' :: Ptr () -> IO ()
val'' = FunPtr (Ptr () -> IO ()) -> Ptr () -> IO ()
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FunPtr (Ptr () -> IO ()) -> Ptr () -> m ()
GLib.Callbacks.dynamic_DestroyNotify FunPtr (Ptr () -> IO ())
val'
(Ptr () -> IO ()) -> IO (Ptr () -> IO ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr () -> IO ()
val''
Maybe (Ptr () -> IO ()) -> IO (Maybe (Ptr () -> IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe (Ptr () -> IO ())
result
setAttrShapeDestroyFunc :: MonadIO m => AttrShape -> FunPtr GLib.Callbacks.C_DestroyNotify -> m ()
setAttrShapeDestroyFunc :: forall (m :: * -> *).
MonadIO m =>
AttrShape -> FunPtr (Ptr () -> IO ()) -> m ()
setAttrShapeDestroyFunc AttrShape
s FunPtr (Ptr () -> IO ())
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (FunPtr (Ptr () -> IO ())) -> FunPtr (Ptr () -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO ()))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (FunPtr (Ptr () -> IO ())
val :: FunPtr GLib.Callbacks.C_DestroyNotify)
clearAttrShapeDestroyFunc :: MonadIO m => AttrShape -> m ()
clearAttrShapeDestroyFunc :: forall (m :: * -> *). MonadIO m => AttrShape -> m ()
clearAttrShapeDestroyFunc AttrShape
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ AttrShape -> (Ptr AttrShape -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr AttrShape
s ((Ptr AttrShape -> IO ()) -> IO ())
-> (Ptr AttrShape -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr AttrShape
ptr -> do
Ptr (FunPtr (Ptr () -> IO ())) -> FunPtr (Ptr () -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AttrShape
ptr Ptr AttrShape -> Int -> Ptr (FunPtr (Ptr () -> IO ()))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (FunPtr (Ptr () -> IO ())
forall a. FunPtr a
FP.nullFunPtr :: FunPtr GLib.Callbacks.C_DestroyNotify)
#if defined(ENABLE_OVERLOADING)
data AttrShapeDestroyFuncFieldInfo
instance AttrInfo AttrShapeDestroyFuncFieldInfo where
type AttrBaseTypeConstraint AttrShapeDestroyFuncFieldInfo = (~) AttrShape
type AttrAllowedOps AttrShapeDestroyFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeDestroyFuncFieldInfo = (~) (FunPtr GLib.Callbacks.C_DestroyNotify)
type AttrTransferTypeConstraint AttrShapeDestroyFuncFieldInfo = (~)GLib.Callbacks.DestroyNotify
type AttrTransferType AttrShapeDestroyFuncFieldInfo = (FunPtr GLib.Callbacks.C_DestroyNotify)
type AttrGetType AttrShapeDestroyFuncFieldInfo = Maybe GLib.Callbacks.DestroyNotify
type AttrLabel AttrShapeDestroyFuncFieldInfo = "destroy_func"
type AttrOrigin AttrShapeDestroyFuncFieldInfo = AttrShape
attrGet = getAttrShapeDestroyFunc
attrSet = setAttrShapeDestroyFunc
attrConstruct = undefined
attrClear = clearAttrShapeDestroyFunc
attrTransfer _ v = do
GLib.Callbacks.mk_DestroyNotify (GLib.Callbacks.wrap_DestroyNotify Nothing v)
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrShape.destroyFunc"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrShape.html#g:attr:destroyFunc"
})
attrShape_destroyFunc :: AttrLabelProxy "destroyFunc"
attrShape_destroyFunc = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrShape
type instance O.AttributeList AttrShape = AttrShapeAttributeList
type AttrShapeAttributeList = ('[ '("attr", AttrShapeAttrFieldInfo), '("inkRect", AttrShapeInkRectFieldInfo), '("logicalRect", AttrShapeLogicalRectFieldInfo), '("data", AttrShapeDataFieldInfo), '("copyFunc", AttrShapeCopyFuncFieldInfo), '("destroyFunc", AttrShapeDestroyFuncFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_attr_shape_new" pango_attr_shape_new ::
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO (Ptr Pango.Attribute.Attribute)
attrShapeNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Pango.Rectangle.Rectangle
-> Pango.Rectangle.Rectangle
-> m Pango.Attribute.Attribute
attrShapeNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle -> Rectangle -> m Attribute
attrShapeNew Rectangle
inkRect Rectangle
logicalRect = IO Attribute -> m Attribute
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attribute -> m Attribute) -> IO Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ do
Ptr Rectangle
inkRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
inkRect
Ptr Rectangle
logicalRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
logicalRect
Ptr Attribute
result <- Ptr Rectangle -> Ptr Rectangle -> IO (Ptr Attribute)
pango_attr_shape_new Ptr Rectangle
inkRect' Ptr Rectangle
logicalRect'
Text -> Ptr Attribute -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrShapeNew" Ptr Attribute
result
Attribute
result' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
result
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
inkRect
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
logicalRect
Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "pango_attr_shape_new_with_data" pango_attr_shape_new_with_data ::
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
Ptr () ->
FunPtr Pango.Callbacks.C_AttrDataCopyFunc ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO (Ptr Pango.Attribute.Attribute)
attrShapeNewWithData ::
(B.CallStack.HasCallStack, MonadIO m) =>
Pango.Rectangle.Rectangle
-> Pango.Rectangle.Rectangle
-> Ptr ()
-> Maybe (Pango.Callbacks.AttrDataCopyFunc)
-> Maybe (GLib.Callbacks.DestroyNotify)
-> m Pango.Attribute.Attribute
attrShapeNewWithData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle
-> Rectangle
-> Ptr ()
-> Maybe (IO (Ptr ()))
-> Maybe (Ptr () -> IO ())
-> m Attribute
attrShapeNewWithData Rectangle
inkRect Rectangle
logicalRect Ptr ()
data_ Maybe (IO (Ptr ()))
copyFunc Maybe (Ptr () -> IO ())
destroyFunc = IO Attribute -> m Attribute
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Attribute -> m Attribute) -> IO Attribute -> m Attribute
forall a b. (a -> b) -> a -> b
$ do
Ptr Rectangle
inkRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
inkRect
Ptr Rectangle
logicalRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
logicalRect
FunPtr (Ptr () -> IO (Ptr ()))
maybeCopyFunc <- case Maybe (IO (Ptr ()))
copyFunc of
Maybe (IO (Ptr ()))
Nothing -> FunPtr (Ptr () -> IO (Ptr ()))
-> IO (FunPtr (Ptr () -> IO (Ptr ())))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr (Ptr () -> IO (Ptr ()))
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just IO (Ptr ())
jCopyFunc -> do
FunPtr (Ptr () -> IO (Ptr ()))
jCopyFunc' <- (Ptr () -> IO (Ptr ())) -> IO (FunPtr (Ptr () -> IO (Ptr ())))
Pango.Callbacks.mk_AttrDataCopyFunc (Maybe (Ptr (FunPtr (Ptr () -> IO (Ptr ()))))
-> (Ptr () -> IO (Ptr ())) -> Ptr () -> IO (Ptr ())
Pango.Callbacks.wrap_AttrDataCopyFunc Maybe (Ptr (FunPtr (Ptr () -> IO (Ptr ()))))
forall a. Maybe a
Nothing (IO (Ptr ()) -> Ptr () -> IO (Ptr ())
Pango.Callbacks.drop_closures_AttrDataCopyFunc IO (Ptr ())
jCopyFunc))
FunPtr (Ptr () -> IO (Ptr ()))
-> IO (FunPtr (Ptr () -> IO (Ptr ())))
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr (Ptr () -> IO (Ptr ()))
jCopyFunc'
FunPtr (Ptr () -> IO ())
maybeDestroyFunc <- case Maybe (Ptr () -> IO ())
destroyFunc of
Maybe (Ptr () -> IO ())
Nothing -> FunPtr (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr (Ptr () -> IO ())
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just Ptr () -> IO ()
jDestroyFunc -> do
Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroyFunc <- IO (Ptr (FunPtr (Ptr () -> IO ())))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
FunPtr (Ptr () -> IO ())
jDestroyFunc' <- (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr (Ptr () -> IO ())))
-> (Ptr () -> IO ()) -> Ptr () -> IO ()
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr (Ptr () -> IO ()))
-> Maybe (Ptr (FunPtr (Ptr () -> IO ())))
forall a. a -> Maybe a
Just Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroyFunc) Ptr () -> IO ()
jDestroyFunc)
Ptr (FunPtr (Ptr () -> IO ())) -> FunPtr (Ptr () -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroyFunc FunPtr (Ptr () -> IO ())
jDestroyFunc'
FunPtr (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr (Ptr () -> IO ())
jDestroyFunc'
Ptr Attribute
result <- Ptr Rectangle
-> Ptr Rectangle
-> Ptr ()
-> FunPtr (Ptr () -> IO (Ptr ()))
-> FunPtr (Ptr () -> IO ())
-> IO (Ptr Attribute)
pango_attr_shape_new_with_data Ptr Rectangle
inkRect' Ptr Rectangle
logicalRect' Ptr ()
data_ FunPtr (Ptr () -> IO (Ptr ()))
maybeCopyFunc FunPtr (Ptr () -> IO ())
maybeDestroyFunc
Text -> Ptr Attribute -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrShapeNewWithData" Ptr Attribute
result
Attribute
result' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
result
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
inkRect
Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
logicalRect
Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAttrShapeMethod (t :: Symbol) (o :: *) :: * where
ResolveAttrShapeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAttrShapeMethod t AttrShape, O.OverloadedMethod info AttrShape p) => OL.IsLabel t (AttrShape -> 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 ~ ResolveAttrShapeMethod t AttrShape, O.OverloadedMethod info AttrShape p, R.HasField t AttrShape p) => R.HasField t AttrShape p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAttrShapeMethod t AttrShape, O.OverloadedMethodInfo info AttrShape) => OL.IsLabel t (O.MethodProxy info AttrShape) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif