{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.GlyphItem
(
GlyphItem(..) ,
newZeroGlyphItem ,
#if defined(ENABLE_OVERLOADING)
ResolveGlyphItemMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
GlyphItemApplyAttrsMethodInfo ,
#endif
glyphItemApplyAttrs ,
#if defined(ENABLE_OVERLOADING)
GlyphItemCopyMethodInfo ,
#endif
glyphItemCopy ,
#if defined(ENABLE_OVERLOADING)
GlyphItemFreeMethodInfo ,
#endif
glyphItemFree ,
#if defined(ENABLE_OVERLOADING)
GlyphItemGetLogicalWidthsMethodInfo ,
#endif
glyphItemGetLogicalWidths ,
#if defined(ENABLE_OVERLOADING)
GlyphItemLetterSpaceMethodInfo ,
#endif
glyphItemLetterSpace ,
#if defined(ENABLE_OVERLOADING)
GlyphItemSplitMethodInfo ,
#endif
glyphItemSplit ,
clearGlyphItemGlyphs ,
getGlyphItemGlyphs ,
#if defined(ENABLE_OVERLOADING)
glyphItem_glyphs ,
#endif
setGlyphItemGlyphs ,
clearGlyphItemItem ,
getGlyphItemItem ,
#if defined(ENABLE_OVERLOADING)
glyphItem_item ,
#endif
setGlyphItemItem ,
) 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.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.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 {-# SOURCE #-} qualified GI.Pango.Structs.AttrList as Pango.AttrList
import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphString as Pango.GlyphString
import {-# SOURCE #-} qualified GI.Pango.Structs.Item as Pango.Item
import {-# SOURCE #-} qualified GI.Pango.Structs.LogAttr as Pango.LogAttr
newtype GlyphItem = GlyphItem (SP.ManagedPtr GlyphItem)
deriving (GlyphItem -> GlyphItem -> Bool
(GlyphItem -> GlyphItem -> Bool)
-> (GlyphItem -> GlyphItem -> Bool) -> Eq GlyphItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlyphItem -> GlyphItem -> Bool
$c/= :: GlyphItem -> GlyphItem -> Bool
== :: GlyphItem -> GlyphItem -> Bool
$c== :: GlyphItem -> GlyphItem -> Bool
Eq)
instance SP.ManagedPtrNewtype GlyphItem where
toManagedPtr :: GlyphItem -> ManagedPtr GlyphItem
toManagedPtr (GlyphItem ManagedPtr GlyphItem
p) = ManagedPtr GlyphItem
p
foreign import ccall "pango_glyph_item_get_type" c_pango_glyph_item_get_type ::
IO GType
type instance O.ParentTypes GlyphItem = '[]
instance O.HasParentTypes GlyphItem
instance B.Types.TypedObject GlyphItem where
glibType :: IO GType
glibType = IO GType
c_pango_glyph_item_get_type
instance B.Types.GBoxed GlyphItem
instance B.GValue.IsGValue GlyphItem where
toGValue :: GlyphItem -> IO GValue
toGValue GlyphItem
o = do
GType
gtype <- IO GType
c_pango_glyph_item_get_type
GlyphItem -> (Ptr GlyphItem -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GlyphItem
o (GType
-> (GValue -> Ptr GlyphItem -> IO ()) -> Ptr GlyphItem -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GlyphItem -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO GlyphItem
fromGValue GValue
gv = do
Ptr GlyphItem
ptr <- GValue -> IO (Ptr GlyphItem)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr GlyphItem)
(ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr GlyphItem -> GlyphItem
GlyphItem Ptr GlyphItem
ptr
newZeroGlyphItem :: MonadIO m => m GlyphItem
newZeroGlyphItem :: m GlyphItem
newZeroGlyphItem = IO GlyphItem -> m GlyphItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphItem -> m GlyphItem) -> IO GlyphItem -> m GlyphItem
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr GlyphItem)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
16 IO (Ptr GlyphItem)
-> (Ptr GlyphItem -> IO GlyphItem) -> IO GlyphItem
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItem -> GlyphItem
GlyphItem
instance tag ~ 'AttrSet => Constructible GlyphItem tag where
new :: (ManagedPtr GlyphItem -> GlyphItem)
-> [AttrOp GlyphItem tag] -> m GlyphItem
new ManagedPtr GlyphItem -> GlyphItem
_ [AttrOp GlyphItem tag]
attrs = do
GlyphItem
o <- m GlyphItem
forall (m :: * -> *). MonadIO m => m GlyphItem
newZeroGlyphItem
GlyphItem -> [AttrOp GlyphItem 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set GlyphItem
o [AttrOp GlyphItem tag]
[AttrOp GlyphItem 'AttrSet]
attrs
GlyphItem -> m GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
o
getGlyphItemItem :: MonadIO m => GlyphItem -> m (Maybe Pango.Item.Item)
getGlyphItemItem :: GlyphItem -> m (Maybe Item)
getGlyphItemItem GlyphItem
s = IO (Maybe Item) -> m (Maybe Item)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Item) -> m (Maybe Item))
-> IO (Maybe Item) -> m (Maybe Item)
forall a b. (a -> b) -> a -> b
$ GlyphItem -> (Ptr GlyphItem -> IO (Maybe Item)) -> IO (Maybe Item)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO (Maybe Item)) -> IO (Maybe Item))
-> (Ptr GlyphItem -> IO (Maybe Item)) -> IO (Maybe Item)
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr Item
val <- Ptr (Ptr Item) -> IO (Ptr Item)
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr Item)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO (Ptr Pango.Item.Item)
Maybe Item
result <- Ptr Item -> (Ptr Item -> IO Item) -> IO (Maybe Item)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Item
val ((Ptr Item -> IO Item) -> IO (Maybe Item))
-> (Ptr Item -> IO Item) -> IO (Maybe Item)
forall a b. (a -> b) -> a -> b
$ \Ptr Item
val' -> do
Item
val'' <- ((ManagedPtr Item -> Item) -> Ptr Item -> IO Item
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Item -> Item
Pango.Item.Item) Ptr Item
val'
Item -> IO Item
forall (m :: * -> *) a. Monad m => a -> m a
return Item
val''
Maybe Item -> IO (Maybe Item)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Item
result
setGlyphItemItem :: MonadIO m => GlyphItem -> Ptr Pango.Item.Item -> m ()
setGlyphItemItem :: GlyphItem -> Ptr Item -> m ()
setGlyphItemItem GlyphItem
s Ptr Item
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItem -> (Ptr GlyphItem -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO ()) -> IO ())
-> (Ptr GlyphItem -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr (Ptr Item) -> Ptr Item -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr Item)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Item
val :: Ptr Pango.Item.Item)
clearGlyphItemItem :: MonadIO m => GlyphItem -> m ()
clearGlyphItemItem :: GlyphItem -> m ()
clearGlyphItemItem GlyphItem
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItem -> (Ptr GlyphItem -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO ()) -> IO ())
-> (Ptr GlyphItem -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr (Ptr Item) -> Ptr Item -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr Item)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Ptr Item
forall a. Ptr a
FP.nullPtr :: Ptr Pango.Item.Item)
#if defined(ENABLE_OVERLOADING)
data GlyphItemItemFieldInfo
instance AttrInfo GlyphItemItemFieldInfo where
type AttrBaseTypeConstraint GlyphItemItemFieldInfo = (~) GlyphItem
type AttrAllowedOps GlyphItemItemFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint GlyphItemItemFieldInfo = (~) (Ptr Pango.Item.Item)
type AttrTransferTypeConstraint GlyphItemItemFieldInfo = (~)(Ptr Pango.Item.Item)
type AttrTransferType GlyphItemItemFieldInfo = (Ptr Pango.Item.Item)
type AttrGetType GlyphItemItemFieldInfo = Maybe Pango.Item.Item
type AttrLabel GlyphItemItemFieldInfo = "item"
type AttrOrigin GlyphItemItemFieldInfo = GlyphItem
attrGet = getGlyphItemItem
attrSet = setGlyphItemItem
attrConstruct = undefined
attrClear = clearGlyphItemItem
attrTransfer _ v = do
return v
glyphItem_item :: AttrLabelProxy "item"
glyphItem_item = AttrLabelProxy
#endif
getGlyphItemGlyphs :: MonadIO m => GlyphItem -> m (Maybe Pango.GlyphString.GlyphString)
getGlyphItemGlyphs :: GlyphItem -> m (Maybe GlyphString)
getGlyphItemGlyphs GlyphItem
s = IO (Maybe GlyphString) -> m (Maybe GlyphString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GlyphString) -> m (Maybe GlyphString))
-> IO (Maybe GlyphString) -> m (Maybe GlyphString)
forall a b. (a -> b) -> a -> b
$ GlyphItem
-> (Ptr GlyphItem -> IO (Maybe GlyphString))
-> IO (Maybe GlyphString)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO (Maybe GlyphString))
-> IO (Maybe GlyphString))
-> (Ptr GlyphItem -> IO (Maybe GlyphString))
-> IO (Maybe GlyphString)
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr GlyphString
val <- Ptr (Ptr GlyphString) -> IO (Ptr GlyphString)
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr GlyphString)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr Pango.GlyphString.GlyphString)
Maybe GlyphString
result <- Ptr GlyphString
-> (Ptr GlyphString -> IO GlyphString) -> IO (Maybe GlyphString)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GlyphString
val ((Ptr GlyphString -> IO GlyphString) -> IO (Maybe GlyphString))
-> (Ptr GlyphString -> IO GlyphString) -> IO (Maybe GlyphString)
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphString
val' -> do
GlyphString
val'' <- ((ManagedPtr GlyphString -> GlyphString)
-> Ptr GlyphString -> IO GlyphString
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GlyphString -> GlyphString
Pango.GlyphString.GlyphString) Ptr GlyphString
val'
GlyphString -> IO GlyphString
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphString
val''
Maybe GlyphString -> IO (Maybe GlyphString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphString
result
setGlyphItemGlyphs :: MonadIO m => GlyphItem -> Ptr Pango.GlyphString.GlyphString -> m ()
setGlyphItemGlyphs :: GlyphItem -> Ptr GlyphString -> m ()
setGlyphItemGlyphs GlyphItem
s Ptr GlyphString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItem -> (Ptr GlyphItem -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO ()) -> IO ())
-> (Ptr GlyphItem -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr (Ptr GlyphString) -> Ptr GlyphString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr GlyphString)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GlyphString
val :: Ptr Pango.GlyphString.GlyphString)
clearGlyphItemGlyphs :: MonadIO m => GlyphItem -> m ()
clearGlyphItemGlyphs :: GlyphItem -> m ()
clearGlyphItemGlyphs GlyphItem
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItem -> (Ptr GlyphItem -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItem
s ((Ptr GlyphItem -> IO ()) -> IO ())
-> (Ptr GlyphItem -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
ptr -> do
Ptr (Ptr GlyphString) -> Ptr GlyphString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItem
ptr Ptr GlyphItem -> Int -> Ptr (Ptr GlyphString)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr GlyphString
forall a. Ptr a
FP.nullPtr :: Ptr Pango.GlyphString.GlyphString)
#if defined(ENABLE_OVERLOADING)
data GlyphItemGlyphsFieldInfo
instance AttrInfo GlyphItemGlyphsFieldInfo where
type AttrBaseTypeConstraint GlyphItemGlyphsFieldInfo = (~) GlyphItem
type AttrAllowedOps GlyphItemGlyphsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint GlyphItemGlyphsFieldInfo = (~) (Ptr Pango.GlyphString.GlyphString)
type AttrTransferTypeConstraint GlyphItemGlyphsFieldInfo = (~)(Ptr Pango.GlyphString.GlyphString)
type AttrTransferType GlyphItemGlyphsFieldInfo = (Ptr Pango.GlyphString.GlyphString)
type AttrGetType GlyphItemGlyphsFieldInfo = Maybe Pango.GlyphString.GlyphString
type AttrLabel GlyphItemGlyphsFieldInfo = "glyphs"
type AttrOrigin GlyphItemGlyphsFieldInfo = GlyphItem
attrGet = getGlyphItemGlyphs
attrSet = setGlyphItemGlyphs
attrConstruct = undefined
attrClear = clearGlyphItemGlyphs
attrTransfer _ v = do
return v
glyphItem_glyphs :: AttrLabelProxy "glyphs"
glyphItem_glyphs = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphItem
type instance O.AttributeList GlyphItem = GlyphItemAttributeList
type GlyphItemAttributeList = ('[ '("item", GlyphItemItemFieldInfo), '("glyphs", GlyphItemGlyphsFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_glyph_item_apply_attrs" pango_glyph_item_apply_attrs ::
Ptr GlyphItem ->
CString ->
Ptr Pango.AttrList.AttrList ->
IO (Ptr (GSList (Ptr GlyphItem)))
glyphItemApplyAttrs ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> T.Text
-> Pango.AttrList.AttrList
-> m [GlyphItem]
glyphItemApplyAttrs :: GlyphItem -> Text -> AttrList -> m [GlyphItem]
glyphItemApplyAttrs GlyphItem
glyphItem Text
text AttrList
list = IO [GlyphItem] -> m [GlyphItem]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GlyphItem] -> m [GlyphItem])
-> IO [GlyphItem] -> m [GlyphItem]
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
CString
text' <- Text -> IO CString
textToCString Text
text
Ptr AttrList
list' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
list
Ptr (GSList (Ptr GlyphItem))
result <- Ptr GlyphItem
-> CString -> Ptr AttrList -> IO (Ptr (GSList (Ptr GlyphItem)))
pango_glyph_item_apply_attrs Ptr GlyphItem
glyphItem' CString
text' Ptr AttrList
list'
[Ptr GlyphItem]
result' <- Ptr (GSList (Ptr GlyphItem)) -> IO [Ptr GlyphItem]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr GlyphItem))
result
[GlyphItem]
result'' <- (Ptr GlyphItem -> IO GlyphItem)
-> [Ptr GlyphItem] -> IO [GlyphItem]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItem -> GlyphItem
GlyphItem) [Ptr GlyphItem]
result'
Ptr (GSList (Ptr GlyphItem)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr GlyphItem))
result
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrList
list
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
[GlyphItem] -> IO [GlyphItem]
forall (m :: * -> *) a. Monad m => a -> m a
return [GlyphItem]
result''
#if defined(ENABLE_OVERLOADING)
data GlyphItemApplyAttrsMethodInfo
instance (signature ~ (T.Text -> Pango.AttrList.AttrList -> m [GlyphItem]), MonadIO m) => O.MethodInfo GlyphItemApplyAttrsMethodInfo GlyphItem signature where
overloadedMethod = glyphItemApplyAttrs
#endif
foreign import ccall "pango_glyph_item_copy" pango_glyph_item_copy ::
Ptr GlyphItem ->
IO (Ptr GlyphItem)
glyphItemCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> m (Maybe GlyphItem)
glyphItemCopy :: GlyphItem -> m (Maybe GlyphItem)
glyphItemCopy GlyphItem
orig = IO (Maybe GlyphItem) -> m (Maybe GlyphItem)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GlyphItem) -> m (Maybe GlyphItem))
-> IO (Maybe GlyphItem) -> m (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
orig' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
orig
Ptr GlyphItem
result <- Ptr GlyphItem -> IO (Ptr GlyphItem)
pango_glyph_item_copy Ptr GlyphItem
orig'
Maybe GlyphItem
maybeResult <- Ptr GlyphItem
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GlyphItem
result ((Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem))
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ \Ptr GlyphItem
result' -> do
GlyphItem
result'' <- ((ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItem -> GlyphItem
GlyphItem) Ptr GlyphItem
result'
GlyphItem -> IO GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
result''
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
orig
Maybe GlyphItem -> IO (Maybe GlyphItem)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphItem
maybeResult
#if defined(ENABLE_OVERLOADING)
data GlyphItemCopyMethodInfo
instance (signature ~ (m (Maybe GlyphItem)), MonadIO m) => O.MethodInfo GlyphItemCopyMethodInfo GlyphItem signature where
overloadedMethod = glyphItemCopy
#endif
foreign import ccall "pango_glyph_item_free" pango_glyph_item_free ::
Ptr GlyphItem ->
IO ()
glyphItemFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> m ()
glyphItemFree :: GlyphItem -> m ()
glyphItemFree GlyphItem
glyphItem = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
Ptr GlyphItem -> IO ()
pango_glyph_item_free Ptr GlyphItem
glyphItem'
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GlyphItemFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo GlyphItemFreeMethodInfo GlyphItem signature where
overloadedMethod = glyphItemFree
#endif
foreign import ccall "pango_glyph_item_get_logical_widths" pango_glyph_item_get_logical_widths ::
Ptr GlyphItem ->
CString ->
Ptr Int32 ->
IO ()
glyphItemGetLogicalWidths ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> T.Text
-> [Int32]
-> m ()
glyphItemGetLogicalWidths :: GlyphItem -> Text -> [Int32] -> m ()
glyphItemGetLogicalWidths GlyphItem
glyphItem Text
text [Int32]
logicalWidths = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
CString
text' <- Text -> IO CString
textToCString Text
text
Ptr Int32
logicalWidths' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
logicalWidths
Ptr GlyphItem -> CString -> Ptr Int32 -> IO ()
pango_glyph_item_get_logical_widths Ptr GlyphItem
glyphItem' CString
text' Ptr Int32
logicalWidths'
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
logicalWidths'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GlyphItemGetLogicalWidthsMethodInfo
instance (signature ~ (T.Text -> [Int32] -> m ()), MonadIO m) => O.MethodInfo GlyphItemGetLogicalWidthsMethodInfo GlyphItem signature where
overloadedMethod = glyphItemGetLogicalWidths
#endif
foreign import ccall "pango_glyph_item_letter_space" pango_glyph_item_letter_space ::
Ptr GlyphItem ->
CString ->
Ptr Pango.LogAttr.LogAttr ->
Int32 ->
IO ()
glyphItemLetterSpace ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> T.Text
-> [Pango.LogAttr.LogAttr]
-> Int32
-> m ()
glyphItemLetterSpace :: GlyphItem -> Text -> [LogAttr] -> Int32 -> m ()
glyphItemLetterSpace GlyphItem
glyphItem Text
text [LogAttr]
logAttrs Int32
letterSpacing = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
CString
text' <- Text -> IO CString
textToCString Text
text
[Ptr LogAttr]
logAttrs' <- (LogAttr -> IO (Ptr LogAttr)) -> [LogAttr] -> IO [Ptr LogAttr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM LogAttr -> IO (Ptr LogAttr)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [LogAttr]
logAttrs
Ptr LogAttr
logAttrs'' <- Int -> [Ptr LogAttr] -> IO (Ptr LogAttr)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
52 [Ptr LogAttr]
logAttrs'
Ptr GlyphItem -> CString -> Ptr LogAttr -> Int32 -> IO ()
pango_glyph_item_letter_space Ptr GlyphItem
glyphItem' CString
text' Ptr LogAttr
logAttrs'' Int32
letterSpacing
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
(LogAttr -> IO ()) -> [LogAttr] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ LogAttr -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [LogAttr]
logAttrs
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
Ptr LogAttr -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr LogAttr
logAttrs''
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GlyphItemLetterSpaceMethodInfo
instance (signature ~ (T.Text -> [Pango.LogAttr.LogAttr] -> Int32 -> m ()), MonadIO m) => O.MethodInfo GlyphItemLetterSpaceMethodInfo GlyphItem signature where
overloadedMethod = glyphItemLetterSpace
#endif
foreign import ccall "pango_glyph_item_split" pango_glyph_item_split ::
Ptr GlyphItem ->
CString ->
Int32 ->
IO (Ptr GlyphItem)
glyphItemSplit ::
(B.CallStack.HasCallStack, MonadIO m) =>
GlyphItem
-> T.Text
-> Int32
-> m GlyphItem
glyphItemSplit :: GlyphItem -> Text -> Int32 -> m GlyphItem
glyphItemSplit GlyphItem
orig Text
text Int32
splitIndex = IO GlyphItem -> m GlyphItem
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphItem -> m GlyphItem) -> IO GlyphItem -> m GlyphItem
forall a b. (a -> b) -> a -> b
$ do
Ptr GlyphItem
orig' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
orig
CString
text' <- Text -> IO CString
textToCString Text
text
Ptr GlyphItem
result <- Ptr GlyphItem -> CString -> Int32 -> IO (Ptr GlyphItem)
pango_glyph_item_split Ptr GlyphItem
orig' CString
text' Int32
splitIndex
Text -> Ptr GlyphItem -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"glyphItemSplit" Ptr GlyphItem
result
GlyphItem
result' <- ((ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItem -> GlyphItem
GlyphItem) Ptr GlyphItem
result
GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
orig
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
GlyphItem -> IO GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
result'
#if defined(ENABLE_OVERLOADING)
data GlyphItemSplitMethodInfo
instance (signature ~ (T.Text -> Int32 -> m GlyphItem), MonadIO m) => O.MethodInfo GlyphItemSplitMethodInfo GlyphItem signature where
overloadedMethod = glyphItemSplit
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveGlyphItemMethod (t :: Symbol) (o :: *) :: * where
ResolveGlyphItemMethod "applyAttrs" o = GlyphItemApplyAttrsMethodInfo
ResolveGlyphItemMethod "copy" o = GlyphItemCopyMethodInfo
ResolveGlyphItemMethod "free" o = GlyphItemFreeMethodInfo
ResolveGlyphItemMethod "letterSpace" o = GlyphItemLetterSpaceMethodInfo
ResolveGlyphItemMethod "split" o = GlyphItemSplitMethodInfo
ResolveGlyphItemMethod "getLogicalWidths" o = GlyphItemGetLogicalWidthsMethodInfo
ResolveGlyphItemMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveGlyphItemMethod t GlyphItem, O.MethodInfo info GlyphItem p) => OL.IsLabel t (GlyphItem -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif