{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Objects.FontFamily
(
FontFamily(..) ,
IsFontFamily ,
toFontFamily ,
#if defined(ENABLE_OVERLOADING)
ResolveFontFamilyMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FontFamilyGetFaceMethodInfo ,
#endif
fontFamilyGetFace ,
#if defined(ENABLE_OVERLOADING)
FontFamilyGetNameMethodInfo ,
#endif
fontFamilyGetName ,
#if defined(ENABLE_OVERLOADING)
FontFamilyIsMonospaceMethodInfo ,
#endif
fontFamilyIsMonospace ,
#if defined(ENABLE_OVERLOADING)
FontFamilyIsVariableMethodInfo ,
#endif
fontFamilyIsVariable ,
#if defined(ENABLE_OVERLOADING)
FontFamilyListFacesMethodInfo ,
#endif
fontFamilyListFaces ,
) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Objects.FontFace as Pango.FontFace
newtype FontFamily = FontFamily (SP.ManagedPtr FontFamily)
deriving (FontFamily -> FontFamily -> Bool
(FontFamily -> FontFamily -> Bool)
-> (FontFamily -> FontFamily -> Bool) -> Eq FontFamily
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontFamily -> FontFamily -> Bool
$c/= :: FontFamily -> FontFamily -> Bool
== :: FontFamily -> FontFamily -> Bool
$c== :: FontFamily -> FontFamily -> Bool
Eq)
instance SP.ManagedPtrNewtype FontFamily where
toManagedPtr :: FontFamily -> ManagedPtr FontFamily
toManagedPtr (FontFamily ManagedPtr FontFamily
p) = ManagedPtr FontFamily
p
foreign import ccall "pango_font_family_get_type"
c_pango_font_family_get_type :: IO B.Types.GType
instance B.Types.TypedObject FontFamily where
glibType :: IO GType
glibType = IO GType
c_pango_font_family_get_type
instance B.Types.GObject FontFamily
class (SP.GObject o, O.IsDescendantOf FontFamily o) => IsFontFamily o
instance (SP.GObject o, O.IsDescendantOf FontFamily o) => IsFontFamily o
instance O.HasParentTypes FontFamily
type instance O.ParentTypes FontFamily = '[GObject.Object.Object]
toFontFamily :: (MIO.MonadIO m, IsFontFamily o) => o -> m FontFamily
toFontFamily :: forall (m :: * -> *) o.
(MonadIO m, IsFontFamily o) =>
o -> m FontFamily
toFontFamily = IO FontFamily -> m FontFamily
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FontFamily -> m FontFamily)
-> (o -> IO FontFamily) -> o -> m FontFamily
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FontFamily -> FontFamily) -> o -> IO FontFamily
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FontFamily -> FontFamily
FontFamily
instance B.GValue.IsGValue (Maybe FontFamily) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_pango_font_family_get_type
gvalueSet_ :: Ptr GValue -> Maybe FontFamily -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FontFamily
P.Nothing = Ptr GValue -> Ptr FontFamily -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FontFamily
forall a. Ptr a
FP.nullPtr :: FP.Ptr FontFamily)
gvalueSet_ Ptr GValue
gv (P.Just FontFamily
obj) = FontFamily -> (Ptr FontFamily -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FontFamily
obj (Ptr GValue -> Ptr FontFamily -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe FontFamily)
gvalueGet_ Ptr GValue
gv = do
Ptr FontFamily
ptr <- Ptr GValue -> IO (Ptr FontFamily)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FontFamily)
if Ptr FontFamily
ptr Ptr FontFamily -> Ptr FontFamily -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FontFamily
forall a. Ptr a
FP.nullPtr
then FontFamily -> Maybe FontFamily
forall a. a -> Maybe a
P.Just (FontFamily -> Maybe FontFamily)
-> IO FontFamily -> IO (Maybe FontFamily)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FontFamily -> FontFamily)
-> Ptr FontFamily -> IO FontFamily
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FontFamily -> FontFamily
FontFamily Ptr FontFamily
ptr
else Maybe FontFamily -> IO (Maybe FontFamily)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFamily
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveFontFamilyMethod (t :: Symbol) (o :: *) :: * where
ResolveFontFamilyMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFontFamilyMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFontFamilyMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFontFamilyMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFontFamilyMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFontFamilyMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFontFamilyMethod "isMonospace" o = FontFamilyIsMonospaceMethodInfo
ResolveFontFamilyMethod "isVariable" o = FontFamilyIsVariableMethodInfo
ResolveFontFamilyMethod "listFaces" o = FontFamilyListFacesMethodInfo
ResolveFontFamilyMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFontFamilyMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFontFamilyMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFontFamilyMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFontFamilyMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFontFamilyMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFontFamilyMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFontFamilyMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFontFamilyMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFontFamilyMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFontFamilyMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFontFamilyMethod "getFace" o = FontFamilyGetFaceMethodInfo
ResolveFontFamilyMethod "getName" o = FontFamilyGetNameMethodInfo
ResolveFontFamilyMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFontFamilyMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFontFamilyMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFontFamilyMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFontFamilyMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFontFamilyMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFontFamilyMethod t FontFamily, O.OverloadedMethod info FontFamily p) => OL.IsLabel t (FontFamily -> 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 ~ ResolveFontFamilyMethod t FontFamily, O.OverloadedMethod info FontFamily p, R.HasField t FontFamily p) => R.HasField t FontFamily p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveFontFamilyMethod t FontFamily, O.OverloadedMethodInfo info FontFamily) => OL.IsLabel t (O.MethodProxy info FontFamily) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FontFamily
type instance O.AttributeList FontFamily = FontFamilyAttributeList
type FontFamilyAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FontFamily = FontFamilySignalList
type FontFamilySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_font_family_get_face" pango_font_family_get_face ::
Ptr FontFamily ->
CString ->
IO (Ptr Pango.FontFace.FontFace)
fontFamilyGetFace ::
(B.CallStack.HasCallStack, MonadIO m, IsFontFamily a) =>
a
-> Maybe (T.Text)
-> m (Maybe Pango.FontFace.FontFace)
fontFamilyGetFace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontFamily a) =>
a -> Maybe Text -> m (Maybe FontFace)
fontFamilyGetFace a
family Maybe Text
name = IO (Maybe FontFace) -> m (Maybe FontFace)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontFace) -> m (Maybe FontFace))
-> IO (Maybe FontFace) -> m (Maybe FontFace)
forall a b. (a -> b) -> a -> b
$ do
Ptr FontFamily
family' <- a -> IO (Ptr FontFamily)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
family
Ptr CChar
maybeName <- case Maybe Text
name of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
Just Text
jName -> do
Ptr CChar
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jName'
Ptr FontFace
result <- Ptr FontFamily -> Ptr CChar -> IO (Ptr FontFace)
pango_font_family_get_face Ptr FontFamily
family' Ptr CChar
maybeName
Maybe FontFace
maybeResult <- Ptr FontFace
-> (Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontFace
result ((Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace))
-> (Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace)
forall a b. (a -> b) -> a -> b
$ \Ptr FontFace
result' -> do
FontFace
result'' <- ((ManagedPtr FontFace -> FontFace) -> Ptr FontFace -> IO FontFace
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontFace -> FontFace
Pango.FontFace.FontFace) Ptr FontFace
result'
FontFace -> IO FontFace
forall (m :: * -> *) a. Monad m => a -> m a
return FontFace
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
family
Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeName
Maybe FontFace -> IO (Maybe FontFace)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFace
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontFamilyGetFaceMethodInfo
instance (signature ~ (Maybe (T.Text) -> m (Maybe Pango.FontFace.FontFace)), MonadIO m, IsFontFamily a) => O.OverloadedMethod FontFamilyGetFaceMethodInfo a signature where
overloadedMethod = fontFamilyGetFace
instance O.OverloadedMethodInfo FontFamilyGetFaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Objects.FontFamily.fontFamilyGetFace",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-FontFamily.html#v:fontFamilyGetFace"
})
#endif
foreign import ccall "pango_font_family_get_name" pango_font_family_get_name ::
Ptr FontFamily ->
IO CString
fontFamilyGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsFontFamily a) =>
a
-> m T.Text
fontFamilyGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontFamily a) =>
a -> m Text
fontFamilyGetName a
family = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr FontFamily
family' <- a -> IO (Ptr FontFamily)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
family
Ptr CChar
result <- Ptr FontFamily -> IO (Ptr CChar)
pango_font_family_get_name Ptr FontFamily
family'
Text -> Ptr CChar -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fontFamilyGetName" Ptr CChar
result
Text
result' <- HasCallStack => Ptr CChar -> IO Text
Ptr CChar -> IO Text
cstringToText Ptr CChar
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
family
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FontFamilyGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontFamily a) => O.OverloadedMethod FontFamilyGetNameMethodInfo a signature where
overloadedMethod = fontFamilyGetName
instance O.OverloadedMethodInfo FontFamilyGetNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Objects.FontFamily.fontFamilyGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-FontFamily.html#v:fontFamilyGetName"
})
#endif
foreign import ccall "pango_font_family_is_monospace" pango_font_family_is_monospace ::
Ptr FontFamily ->
IO CInt
fontFamilyIsMonospace ::
(B.CallStack.HasCallStack, MonadIO m, IsFontFamily a) =>
a
-> m Bool
fontFamilyIsMonospace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontFamily a) =>
a -> m Bool
fontFamilyIsMonospace a
family = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr FontFamily
family' <- a -> IO (Ptr FontFamily)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
family
CInt
result <- Ptr FontFamily -> IO CInt
pango_font_family_is_monospace Ptr FontFamily
family'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
family
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FontFamilyIsMonospaceMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFontFamily a) => O.OverloadedMethod FontFamilyIsMonospaceMethodInfo a signature where
overloadedMethod = fontFamilyIsMonospace
instance O.OverloadedMethodInfo FontFamilyIsMonospaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Objects.FontFamily.fontFamilyIsMonospace",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-FontFamily.html#v:fontFamilyIsMonospace"
})
#endif
foreign import ccall "pango_font_family_is_variable" pango_font_family_is_variable ::
Ptr FontFamily ->
IO CInt
fontFamilyIsVariable ::
(B.CallStack.HasCallStack, MonadIO m, IsFontFamily a) =>
a
-> m Bool
fontFamilyIsVariable :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontFamily a) =>
a -> m Bool
fontFamilyIsVariable a
family = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr FontFamily
family' <- a -> IO (Ptr FontFamily)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
family
CInt
result <- Ptr FontFamily -> IO CInt
pango_font_family_is_variable Ptr FontFamily
family'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
family
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FontFamilyIsVariableMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFontFamily a) => O.OverloadedMethod FontFamilyIsVariableMethodInfo a signature where
overloadedMethod = fontFamilyIsVariable
instance O.OverloadedMethodInfo FontFamilyIsVariableMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Objects.FontFamily.fontFamilyIsVariable",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-FontFamily.html#v:fontFamilyIsVariable"
})
#endif
foreign import ccall "pango_font_family_list_faces" pango_font_family_list_faces ::
Ptr FontFamily ->
Ptr (Ptr (Ptr Pango.FontFace.FontFace)) ->
Ptr Int32 ->
IO ()
fontFamilyListFaces ::
(B.CallStack.HasCallStack, MonadIO m, IsFontFamily a) =>
a
-> m ([Pango.FontFace.FontFace])
fontFamilyListFaces :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontFamily a) =>
a -> m [FontFace]
fontFamilyListFaces a
family = IO [FontFace] -> m [FontFace]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [FontFace] -> m [FontFace]) -> IO [FontFace] -> m [FontFace]
forall a b. (a -> b) -> a -> b
$ do
Ptr FontFamily
family' <- a -> IO (Ptr FontFamily)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
family
Ptr (Ptr (Ptr FontFace))
faces <- IO (Ptr (Ptr (Ptr FontFace)))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr (Ptr Pango.FontFace.FontFace)))
Ptr Int32
nFaces <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr FontFamily -> Ptr (Ptr (Ptr FontFace)) -> Ptr Int32 -> IO ()
pango_font_family_list_faces Ptr FontFamily
family' Ptr (Ptr (Ptr FontFace))
faces Ptr Int32
nFaces
Int32
nFaces' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nFaces
Ptr (Ptr FontFace)
faces' <- Ptr (Ptr (Ptr FontFace)) -> IO (Ptr (Ptr FontFace))
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr (Ptr FontFace))
faces
[Ptr FontFace]
faces'' <- (Int32 -> Ptr (Ptr FontFace) -> IO [Ptr FontFace]
forall a b. Integral a => a -> Ptr (Ptr b) -> IO [Ptr b]
unpackPtrArrayWithLength Int32
nFaces') Ptr (Ptr FontFace)
faces'
[FontFace]
faces''' <- (Ptr FontFace -> IO FontFace) -> [Ptr FontFace] -> IO [FontFace]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr FontFace -> FontFace) -> Ptr FontFace -> IO FontFace
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontFace -> FontFace
Pango.FontFace.FontFace) [Ptr FontFace]
faces''
Ptr (Ptr FontFace) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr FontFace)
faces'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
family
Ptr (Ptr (Ptr FontFace)) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr (Ptr FontFace))
faces
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nFaces
[FontFace] -> IO [FontFace]
forall (m :: * -> *) a. Monad m => a -> m a
return [FontFace]
faces'''
#if defined(ENABLE_OVERLOADING)
data FontFamilyListFacesMethodInfo
instance (signature ~ (m ([Pango.FontFace.FontFace])), MonadIO m, IsFontFamily a) => O.OverloadedMethod FontFamilyListFacesMethodInfo a signature where
overloadedMethod = fontFamilyListFaces
instance O.OverloadedMethodInfo FontFamilyListFacesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Objects.FontFamily.fontFamilyListFaces",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-FontFamily.html#v:fontFamilyListFaces"
})
#endif