module GI.Pango.Structs.AttrShape
(
AttrShape(..) ,
newZeroAttrShape ,
noAttrShape ,
attrShapeNew ,
attrShape_attr ,
getAttrShapeAttr ,
attrShape_copyFunc ,
clearAttrShapeCopyFunc ,
getAttrShapeCopyFunc ,
setAttrShapeCopyFunc ,
attrShape_data ,
clearAttrShapeData ,
getAttrShapeData ,
setAttrShapeData ,
attrShape_destroyFunc ,
clearAttrShapeDestroyFunc ,
getAttrShapeDestroyFunc ,
setAttrShapeDestroyFunc ,
attrShape_inkRect ,
getAttrShapeInkRect ,
attrShape_logicalRect ,
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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.Pango.Callbacks as Pango.Callbacks
import qualified GI.Pango.Structs.Attribute as Pango.Attribute
import qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
newtype AttrShape = AttrShape (ManagedPtr AttrShape)
instance WrappedPtr AttrShape where
wrappedPtrCalloc = callocBytes 72
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 72 >=> wrapPtr AttrShape)
wrappedPtrFree = Just ptr_to_g_free
newZeroAttrShape :: MonadIO m => m AttrShape
newZeroAttrShape = liftIO $ wrappedPtrCalloc >>= wrapPtr AttrShape
instance tag ~ 'AttrSet => Constructible AttrShape tag where
new _ attrs = do
o <- newZeroAttrShape
GI.Attributes.set o attrs
return o
noAttrShape :: Maybe AttrShape
noAttrShape = Nothing
getAttrShapeAttr :: MonadIO m => AttrShape -> m Pango.Attribute.Attribute
getAttrShapeAttr s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 0 :: (Ptr Pango.Attribute.Attribute)
val' <- (newPtr Pango.Attribute.Attribute) val
return val'
data AttrShapeAttrFieldInfo
instance AttrInfo AttrShapeAttrFieldInfo where
type AttrAllowedOps AttrShapeAttrFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeAttrFieldInfo = (~) (Ptr Pango.Attribute.Attribute)
type AttrBaseTypeConstraint AttrShapeAttrFieldInfo = (~) AttrShape
type AttrGetType AttrShapeAttrFieldInfo = Pango.Attribute.Attribute
type AttrLabel AttrShapeAttrFieldInfo = "attr"
type AttrOrigin AttrShapeAttrFieldInfo = AttrShape
attrGet _ = getAttrShapeAttr
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
attrShape_attr :: AttrLabelProxy "attr"
attrShape_attr = AttrLabelProxy
getAttrShapeInkRect :: MonadIO m => AttrShape -> m Pango.Rectangle.Rectangle
getAttrShapeInkRect s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 16 :: (Ptr Pango.Rectangle.Rectangle)
val' <- (newPtr Pango.Rectangle.Rectangle) val
return val'
data AttrShapeInkRectFieldInfo
instance AttrInfo AttrShapeInkRectFieldInfo where
type AttrAllowedOps AttrShapeInkRectFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeInkRectFieldInfo = (~) (Ptr Pango.Rectangle.Rectangle)
type AttrBaseTypeConstraint AttrShapeInkRectFieldInfo = (~) AttrShape
type AttrGetType AttrShapeInkRectFieldInfo = Pango.Rectangle.Rectangle
type AttrLabel AttrShapeInkRectFieldInfo = "ink_rect"
type AttrOrigin AttrShapeInkRectFieldInfo = AttrShape
attrGet _ = getAttrShapeInkRect
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
attrShape_inkRect :: AttrLabelProxy "inkRect"
attrShape_inkRect = AttrLabelProxy
getAttrShapeLogicalRect :: MonadIO m => AttrShape -> m Pango.Rectangle.Rectangle
getAttrShapeLogicalRect s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 32 :: (Ptr Pango.Rectangle.Rectangle)
val' <- (newPtr Pango.Rectangle.Rectangle) val
return val'
data AttrShapeLogicalRectFieldInfo
instance AttrInfo AttrShapeLogicalRectFieldInfo where
type AttrAllowedOps AttrShapeLogicalRectFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint AttrShapeLogicalRectFieldInfo = (~) (Ptr Pango.Rectangle.Rectangle)
type AttrBaseTypeConstraint AttrShapeLogicalRectFieldInfo = (~) AttrShape
type AttrGetType AttrShapeLogicalRectFieldInfo = Pango.Rectangle.Rectangle
type AttrLabel AttrShapeLogicalRectFieldInfo = "logical_rect"
type AttrOrigin AttrShapeLogicalRectFieldInfo = AttrShape
attrGet _ = getAttrShapeLogicalRect
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
attrShape_logicalRect :: AttrLabelProxy "logicalRect"
attrShape_logicalRect = AttrLabelProxy
getAttrShapeData :: MonadIO m => AttrShape -> m (Ptr ())
getAttrShapeData s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO (Ptr ())
return val
setAttrShapeData :: MonadIO m => AttrShape -> Ptr () -> m ()
setAttrShapeData s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (val :: Ptr ())
clearAttrShapeData :: MonadIO m => AttrShape -> m ()
clearAttrShapeData s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 48) (FP.nullPtr :: Ptr ())
data AttrShapeDataFieldInfo
instance AttrInfo AttrShapeDataFieldInfo where
type AttrAllowedOps AttrShapeDataFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeDataFieldInfo = (~) (Ptr ())
type AttrBaseTypeConstraint AttrShapeDataFieldInfo = (~) AttrShape
type AttrGetType AttrShapeDataFieldInfo = Ptr ()
type AttrLabel AttrShapeDataFieldInfo = "data"
type AttrOrigin AttrShapeDataFieldInfo = AttrShape
attrGet _ = getAttrShapeData
attrSet _ = setAttrShapeData
attrConstruct = undefined
attrClear _ = clearAttrShapeData
attrShape_data :: AttrLabelProxy "data"
attrShape_data = AttrLabelProxy
getAttrShapeCopyFunc :: MonadIO m => AttrShape -> m (Maybe Pango.Callbacks.AttrDataCopyFunc_WithClosures)
getAttrShapeCopyFunc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO (FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = Pango.Callbacks.dynamic_AttrDataCopyFunc val'
return val''
return result
setAttrShapeCopyFunc :: MonadIO m => AttrShape -> FunPtr Pango.Callbacks.C_AttrDataCopyFunc -> m ()
setAttrShapeCopyFunc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (val :: FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
clearAttrShapeCopyFunc :: MonadIO m => AttrShape -> m ()
clearAttrShapeCopyFunc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (FP.nullFunPtr :: FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
data AttrShapeCopyFuncFieldInfo
instance AttrInfo AttrShapeCopyFuncFieldInfo where
type AttrAllowedOps AttrShapeCopyFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeCopyFuncFieldInfo = (~) (FunPtr Pango.Callbacks.C_AttrDataCopyFunc)
type AttrBaseTypeConstraint AttrShapeCopyFuncFieldInfo = (~) AttrShape
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
attrShape_copyFunc :: AttrLabelProxy "copyFunc"
attrShape_copyFunc = AttrLabelProxy
getAttrShapeDestroyFunc :: MonadIO m => AttrShape -> m (Maybe GLib.Callbacks.DestroyNotify)
getAttrShapeDestroyFunc s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO (FunPtr GLib.Callbacks.C_DestroyNotify)
result <- SP.convertFunPtrIfNonNull val $ \val' -> do
let val'' = GLib.Callbacks.dynamic_DestroyNotify val'
return val''
return result
setAttrShapeDestroyFunc :: MonadIO m => AttrShape -> FunPtr GLib.Callbacks.C_DestroyNotify -> m ()
setAttrShapeDestroyFunc s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (val :: FunPtr GLib.Callbacks.C_DestroyNotify)
clearAttrShapeDestroyFunc :: MonadIO m => AttrShape -> m ()
clearAttrShapeDestroyFunc s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 64) (FP.nullFunPtr :: FunPtr GLib.Callbacks.C_DestroyNotify)
data AttrShapeDestroyFuncFieldInfo
instance AttrInfo AttrShapeDestroyFuncFieldInfo where
type AttrAllowedOps AttrShapeDestroyFuncFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint AttrShapeDestroyFuncFieldInfo = (~) (FunPtr GLib.Callbacks.C_DestroyNotify)
type AttrBaseTypeConstraint AttrShapeDestroyFuncFieldInfo = (~) AttrShape
type AttrGetType AttrShapeDestroyFuncFieldInfo = Maybe GLib.Callbacks.DestroyNotify
type AttrLabel AttrShapeDestroyFuncFieldInfo = "destroy_func"
type AttrOrigin AttrShapeDestroyFuncFieldInfo = AttrShape
attrGet _ = getAttrShapeDestroyFunc
attrSet _ = setAttrShapeDestroyFunc
attrConstruct = undefined
attrClear _ = clearAttrShapeDestroyFunc
attrShape_destroyFunc :: AttrLabelProxy "destroyFunc"
attrShape_destroyFunc = AttrLabelProxy
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, *)])
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 inkRect logicalRect = liftIO $ do
inkRect' <- unsafeManagedPtrGetPtr inkRect
logicalRect' <- unsafeManagedPtrGetPtr logicalRect
result <- pango_attr_shape_new inkRect' logicalRect'
checkUnexpectedReturnNULL "attrShapeNew" result
result' <- (wrapPtr Pango.Attribute.Attribute) result
touchManagedPtr inkRect
touchManagedPtr logicalRect
return result'
type family ResolveAttrShapeMethod (t :: Symbol) (o :: *) :: * where
ResolveAttrShapeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAttrShapeMethod t AttrShape, O.MethodInfo info AttrShape p) => O.IsLabelProxy t (AttrShape -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveAttrShapeMethod t AttrShape, O.MethodInfo info AttrShape p) => O.IsLabel t (AttrShape -> p) where
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif