{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Objects.Font
(
Font(..) ,
IsFont ,
toFont ,
noFont ,
#if defined(ENABLE_OVERLOADING)
ResolveFontMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FontDescribeMethodInfo ,
#endif
fontDescribe ,
#if defined(ENABLE_OVERLOADING)
FontDescribeWithAbsoluteSizeMethodInfo ,
#endif
fontDescribeWithAbsoluteSize ,
fontDescriptionsFree ,
#if defined(ENABLE_OVERLOADING)
FontFindShaperMethodInfo ,
#endif
fontFindShaper ,
#if defined(ENABLE_OVERLOADING)
FontGetFontMapMethodInfo ,
#endif
fontGetFontMap ,
#if defined(ENABLE_OVERLOADING)
FontGetGlyphExtentsMethodInfo ,
#endif
fontGetGlyphExtents ,
#if defined(ENABLE_OVERLOADING)
FontGetMetricsMethodInfo ,
#endif
fontGetMetrics ,
) 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.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 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Objects.EngineShape as Pango.EngineShape
import {-# SOURCE #-} qualified GI.Pango.Objects.FontMap as Pango.FontMap
import {-# SOURCE #-} qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import {-# SOURCE #-} qualified GI.Pango.Structs.FontMetrics as Pango.FontMetrics
import {-# SOURCE #-} qualified GI.Pango.Structs.Language as Pango.Language
import {-# SOURCE #-} qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
newtype Font = Font (ManagedPtr Font)
deriving (Font -> Font -> Bool
(Font -> Font -> Bool) -> (Font -> Font -> Bool) -> Eq Font
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Font -> Font -> Bool
$c/= :: Font -> Font -> Bool
== :: Font -> Font -> Bool
$c== :: Font -> Font -> Bool
Eq)
foreign import ccall "pango_font_get_type"
c_pango_font_get_type :: IO GType
instance GObject Font where
gobjectType :: IO GType
gobjectType = IO GType
c_pango_font_get_type
instance B.GValue.IsGValue Font where
toGValue :: Font -> IO GValue
toGValue o :: Font
o = do
GType
gtype <- IO GType
c_pango_font_get_type
Font -> (Ptr Font -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Font
o (GType -> (GValue -> Ptr Font -> IO ()) -> Ptr Font -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Font -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Font
fromGValue gv :: GValue
gv = do
Ptr Font
ptr <- GValue -> IO (Ptr Font)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Font)
(ManagedPtr Font -> Font) -> Ptr Font -> IO Font
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Font -> Font
Font Ptr Font
ptr
class (GObject o, O.IsDescendantOf Font o) => IsFont o
instance (GObject o, O.IsDescendantOf Font o) => IsFont o
instance O.HasParentTypes Font
type instance O.ParentTypes Font = '[GObject.Object.Object]
toFont :: (MonadIO m, IsFont o) => o -> m Font
toFont :: o -> m Font
toFont = IO Font -> m Font
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Font -> m Font) -> (o -> IO Font) -> o -> m Font
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Font -> Font) -> o -> IO Font
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Font -> Font
Font
noFont :: Maybe Font
noFont :: Maybe Font
noFont = Maybe Font
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveFontMethod (t :: Symbol) (o :: *) :: * where
ResolveFontMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFontMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFontMethod "describe" o = FontDescribeMethodInfo
ResolveFontMethod "describeWithAbsoluteSize" o = FontDescribeWithAbsoluteSizeMethodInfo
ResolveFontMethod "findShaper" o = FontFindShaperMethodInfo
ResolveFontMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFontMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFontMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFontMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFontMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFontMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFontMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFontMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFontMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFontMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFontMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFontMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFontMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFontMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFontMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFontMethod "getFontMap" o = FontGetFontMapMethodInfo
ResolveFontMethod "getGlyphExtents" o = FontGetGlyphExtentsMethodInfo
ResolveFontMethod "getMetrics" o = FontGetMetricsMethodInfo
ResolveFontMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFontMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFontMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFontMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFontMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFontMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFontMethod t Font, O.MethodInfo info Font p) => OL.IsLabel t (Font -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Font
type instance O.AttributeList Font = FontAttributeList
type FontAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Font = FontSignalList
type FontSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_font_describe" pango_font_describe ::
Ptr Font ->
IO (Ptr Pango.FontDescription.FontDescription)
fontDescribe ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> m Pango.FontDescription.FontDescription
fontDescribe :: a -> m FontDescription
fontDescribe font :: a
font = IO FontDescription -> m FontDescription
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontDescription -> m FontDescription)
-> IO FontDescription -> m FontDescription
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr FontDescription
result <- Ptr Font -> IO (Ptr FontDescription)
pango_font_describe Ptr Font
font'
Text -> Ptr FontDescription -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontDescribe" Ptr FontDescription
result
FontDescription
result' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
result'
#if defined(ENABLE_OVERLOADING)
data FontDescribeMethodInfo
instance (signature ~ (m Pango.FontDescription.FontDescription), MonadIO m, IsFont a) => O.MethodInfo FontDescribeMethodInfo a signature where
overloadedMethod = fontDescribe
#endif
foreign import ccall "pango_font_describe_with_absolute_size" pango_font_describe_with_absolute_size ::
Ptr Font ->
IO (Ptr Pango.FontDescription.FontDescription)
fontDescribeWithAbsoluteSize ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> m Pango.FontDescription.FontDescription
fontDescribeWithAbsoluteSize :: a -> m FontDescription
fontDescribeWithAbsoluteSize font :: a
font = IO FontDescription -> m FontDescription
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontDescription -> m FontDescription)
-> IO FontDescription -> m FontDescription
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr FontDescription
result <- Ptr Font -> IO (Ptr FontDescription)
pango_font_describe_with_absolute_size Ptr Font
font'
Text -> Ptr FontDescription -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontDescribeWithAbsoluteSize" Ptr FontDescription
result
FontDescription
result' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
result'
#if defined(ENABLE_OVERLOADING)
data FontDescribeWithAbsoluteSizeMethodInfo
instance (signature ~ (m Pango.FontDescription.FontDescription), MonadIO m, IsFont a) => O.MethodInfo FontDescribeWithAbsoluteSizeMethodInfo a signature where
overloadedMethod = fontDescribeWithAbsoluteSize
#endif
foreign import ccall "pango_font_find_shaper" pango_font_find_shaper ::
Ptr Font ->
Ptr Pango.Language.Language ->
Word32 ->
IO (Ptr Pango.EngineShape.EngineShape)
fontFindShaper ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> Pango.Language.Language
-> Word32
-> m Pango.EngineShape.EngineShape
fontFindShaper :: a -> Language -> Word32 -> m EngineShape
fontFindShaper font :: a
font language :: Language
language ch :: Word32
ch = IO EngineShape -> m EngineShape
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EngineShape -> m EngineShape)
-> IO EngineShape -> m EngineShape
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr Language
language' <- Language -> IO (Ptr Language)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Language
language
Ptr EngineShape
result <- Ptr Font -> Ptr Language -> Word32 -> IO (Ptr EngineShape)
pango_font_find_shaper Ptr Font
font' Ptr Language
language' Word32
ch
Text -> Ptr EngineShape -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontFindShaper" Ptr EngineShape
result
EngineShape
result' <- ((ManagedPtr EngineShape -> EngineShape)
-> Ptr EngineShape -> IO EngineShape
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr EngineShape -> EngineShape
Pango.EngineShape.EngineShape) Ptr EngineShape
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Language
language
EngineShape -> IO EngineShape
forall (m :: * -> *) a. Monad m => a -> m a
return EngineShape
result'
#if defined(ENABLE_OVERLOADING)
data FontFindShaperMethodInfo
instance (signature ~ (Pango.Language.Language -> Word32 -> m Pango.EngineShape.EngineShape), MonadIO m, IsFont a) => O.MethodInfo FontFindShaperMethodInfo a signature where
overloadedMethod = fontFindShaper
#endif
foreign import ccall "pango_font_get_font_map" pango_font_get_font_map ::
Ptr Font ->
IO (Ptr Pango.FontMap.FontMap)
fontGetFontMap ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> m (Maybe Pango.FontMap.FontMap)
fontGetFontMap :: a -> m (Maybe FontMap)
fontGetFontMap font :: a
font = IO (Maybe FontMap) -> m (Maybe FontMap)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontMap) -> m (Maybe FontMap))
-> IO (Maybe FontMap) -> m (Maybe FontMap)
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr FontMap
result <- Ptr Font -> IO (Ptr FontMap)
pango_font_get_font_map Ptr Font
font'
Maybe FontMap
maybeResult <- Ptr FontMap -> (Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontMap
result ((Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap))
-> (Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr FontMap
result' -> do
FontMap
result'' <- ((ManagedPtr FontMap -> FontMap) -> Ptr FontMap -> IO FontMap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontMap -> FontMap
Pango.FontMap.FontMap) Ptr FontMap
result'
FontMap -> IO FontMap
forall (m :: * -> *) a. Monad m => a -> m a
return FontMap
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
Maybe FontMap -> IO (Maybe FontMap)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontMap
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontGetFontMapMethodInfo
instance (signature ~ (m (Maybe Pango.FontMap.FontMap)), MonadIO m, IsFont a) => O.MethodInfo FontGetFontMapMethodInfo a signature where
overloadedMethod = fontGetFontMap
#endif
foreign import ccall "pango_font_get_glyph_extents" pango_font_get_glyph_extents ::
Ptr Font ->
Word32 ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
fontGetGlyphExtents ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> Word32
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
fontGetGlyphExtents :: a -> Word32 -> m (Rectangle, Rectangle)
fontGetGlyphExtents font :: a
font glyph :: Word32
glyph = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr Rectangle
inkRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Font -> Word32 -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_font_get_glyph_extents Ptr Font
font' Word32
glyph Ptr Rectangle
inkRect Ptr Rectangle
logicalRect
Rectangle
inkRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
inkRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data FontGetGlyphExtentsMethodInfo
instance (signature ~ (Word32 -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m, IsFont a) => O.MethodInfo FontGetGlyphExtentsMethodInfo a signature where
overloadedMethod = fontGetGlyphExtents
#endif
foreign import ccall "pango_font_get_metrics" pango_font_get_metrics ::
Ptr Font ->
Ptr Pango.Language.Language ->
IO (Ptr Pango.FontMetrics.FontMetrics)
fontGetMetrics ::
(B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
a
-> Maybe (Pango.Language.Language)
-> m Pango.FontMetrics.FontMetrics
fontGetMetrics :: a -> Maybe Language -> m FontMetrics
fontGetMetrics font :: a
font language :: Maybe Language
language = IO FontMetrics -> m FontMetrics
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontMetrics -> m FontMetrics)
-> IO FontMetrics -> m FontMetrics
forall a b. (a -> b) -> a -> b
$ do
Ptr Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
Ptr Language
maybeLanguage <- case Maybe Language
language of
Nothing -> Ptr Language -> IO (Ptr Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Language
forall a. Ptr a
nullPtr
Just jLanguage :: Language
jLanguage -> do
Ptr Language
jLanguage' <- Language -> IO (Ptr Language)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Language
jLanguage
Ptr Language -> IO (Ptr Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Language
jLanguage'
Ptr FontMetrics
result <- Ptr Font -> Ptr Language -> IO (Ptr FontMetrics)
pango_font_get_metrics Ptr Font
font' Ptr Language
maybeLanguage
Text -> Ptr FontMetrics -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontGetMetrics" Ptr FontMetrics
result
FontMetrics
result' <- ((ManagedPtr FontMetrics -> FontMetrics)
-> Ptr FontMetrics -> IO FontMetrics
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontMetrics -> FontMetrics
Pango.FontMetrics.FontMetrics) Ptr FontMetrics
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
Maybe Language -> (Language -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Language
language Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
FontMetrics -> IO FontMetrics
forall (m :: * -> *) a. Monad m => a -> m a
return FontMetrics
result'
#if defined(ENABLE_OVERLOADING)
data FontGetMetricsMethodInfo
instance (signature ~ (Maybe (Pango.Language.Language) -> m Pango.FontMetrics.FontMetrics), MonadIO m, IsFont a) => O.MethodInfo FontGetMetricsMethodInfo a signature where
overloadedMethod = fontGetMetrics
#endif
foreign import ccall "pango_font_descriptions_free" pango_font_descriptions_free ::
Ptr (Ptr Pango.FontDescription.FontDescription) ->
Int32 ->
IO ()
fontDescriptionsFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe ([Pango.FontDescription.FontDescription])
-> m ()
fontDescriptionsFree :: Maybe [FontDescription] -> m ()
fontDescriptionsFree descs :: Maybe [FontDescription]
descs = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nDescs :: Int32
nDescs = case Maybe [FontDescription]
descs of
Nothing -> 0
Just jDescs :: [FontDescription]
jDescs -> Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [FontDescription] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [FontDescription]
jDescs
Ptr (Ptr FontDescription)
maybeDescs <- case Maybe [FontDescription]
descs of
Nothing -> Ptr (Ptr FontDescription) -> IO (Ptr (Ptr FontDescription))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr FontDescription)
forall a. Ptr a
nullPtr
Just jDescs :: [FontDescription]
jDescs -> do
[Ptr FontDescription]
jDescs' <- (FontDescription -> IO (Ptr FontDescription))
-> [FontDescription] -> IO [Ptr FontDescription]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM FontDescription -> IO (Ptr FontDescription)
forall a. (HasCallStack, BoxedObject a) => a -> IO (Ptr a)
B.ManagedPtr.disownBoxed [FontDescription]
jDescs
Ptr (Ptr FontDescription)
jDescs'' <- [Ptr FontDescription] -> IO (Ptr (Ptr FontDescription))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr FontDescription]
jDescs'
Ptr (Ptr FontDescription) -> IO (Ptr (Ptr FontDescription))
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr FontDescription)
jDescs''
Ptr (Ptr FontDescription) -> Int32 -> IO ()
pango_font_descriptions_free Ptr (Ptr FontDescription)
maybeDescs Int32
nDescs
Maybe [FontDescription] -> ([FontDescription] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [FontDescription]
descs ((FontDescription -> IO ()) -> [FontDescription] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ FontDescription -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif