{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Pango.Objects.Font.Font' structure is used to represent
-- a font in a rendering-system-independent matter.
-- To create an implementation of a t'GI.Pango.Objects.Font.Font',
-- the rendering-system specific code should allocate
-- a larger structure that contains a nested
-- t'GI.Pango.Objects.Font.Font', fill in the \<structfield>klass\<\/structfield> member of
-- the nested t'GI.Pango.Objects.Font.Font' with a pointer to
-- a appropriate t'GI.Pango.Structs.FontClass.FontClass', then call
-- @/pango_font_init()/@ on the structure.
-- 
-- The t'GI.Pango.Objects.Font.Font' structure contains one member
-- which the implementation fills in.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Pango.Objects.Font
    ( 

-- * Exported types
    Font(..)                                ,
    IsFont                                  ,
    toFont                                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveFontMethod                       ,
#endif


-- ** describe #method:describe#

#if defined(ENABLE_OVERLOADING)
    FontDescribeMethodInfo                  ,
#endif
    fontDescribe                            ,


-- ** describeWithAbsoluteSize #method:describeWithAbsoluteSize#

#if defined(ENABLE_OVERLOADING)
    FontDescribeWithAbsoluteSizeMethodInfo  ,
#endif
    fontDescribeWithAbsoluteSize            ,


-- ** descriptionsFree #method:descriptionsFree#

    fontDescriptionsFree                    ,


-- ** findShaper #method:findShaper#

#if defined(ENABLE_OVERLOADING)
    FontFindShaperMethodInfo                ,
#endif
    fontFindShaper                          ,


-- ** getCoverage #method:getCoverage#

#if defined(ENABLE_OVERLOADING)
    FontGetCoverageMethodInfo               ,
#endif
    fontGetCoverage                         ,


-- ** getFontMap #method:getFontMap#

#if defined(ENABLE_OVERLOADING)
    FontGetFontMapMethodInfo                ,
#endif
    fontGetFontMap                          ,


-- ** getGlyphExtents #method:getGlyphExtents#

#if defined(ENABLE_OVERLOADING)
    FontGetGlyphExtentsMethodInfo           ,
#endif
    fontGetGlyphExtents                     ,


-- ** getMetrics #method:getMetrics#

#if defined(ENABLE_OVERLOADING)
    FontGetMetricsMethodInfo                ,
#endif
    fontGetMetrics                          ,


-- ** hasChar #method:hasChar#

#if defined(ENABLE_OVERLOADING)
    FontHasCharMethodInfo                   ,
#endif
    fontHasChar                             ,




    ) 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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Objects.Coverage as Pango.Coverage
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

-- | Memory-managed wrapper type.
newtype Font = Font (SP.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)

instance SP.ManagedPtrNewtype Font where
    toManagedPtr :: Font -> ManagedPtr Font
toManagedPtr (Font ManagedPtr Font
p) = ManagedPtr Font
p

foreign import ccall "pango_font_get_type"
    c_pango_font_get_type :: IO B.Types.GType

instance B.Types.TypedObject Font where
    glibType :: IO GType
glibType = IO GType
c_pango_font_get_type

instance B.Types.GObject Font

-- | Convert 'Font' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Font where
    toGValue :: Font -> IO GValue
toGValue 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 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
        
    

-- | Type class for types which can be safely cast to `Font`, for instance with `toFont`.
class (SP.GObject o, O.IsDescendantOf Font o) => IsFont o
instance (SP.GObject o, O.IsDescendantOf Font o) => IsFont o

instance O.HasParentTypes Font
type instance O.ParentTypes Font = '[GObject.Object.Object]

-- | Cast to `Font`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Font -> Font
Font

#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 "hasChar" o = FontHasCharMethodInfo
    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 "getCoverage" o = FontGetCoverageMethodInfo
    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

-- method Font::describe
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Pango" , name = "FontDescription" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_describe" pango_font_describe :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    IO (Ptr Pango.FontDescription.FontDescription)

-- | Returns a description of the font, with font size set in points.
-- Use 'GI.Pango.Objects.Font.fontDescribeWithAbsoluteSize' if you want the font
-- size in device units.
fontDescribe ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> m Pango.FontDescription.FontDescription
    -- ^ __Returns:__ a newly-allocated t'GI.Pango.Structs.FontDescription.FontDescription' object.
fontDescribe :: a -> m FontDescription
fontDescribe 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 Text
"fontDescribe" Ptr FontDescription
result
    FontDescription
result' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, GBoxed 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

-- method Font::describe_with_absolute_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Pango" , name = "FontDescription" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_describe_with_absolute_size" pango_font_describe_with_absolute_size :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    IO (Ptr Pango.FontDescription.FontDescription)

-- | Returns a description of the font, with absolute font size set
-- (in device units). Use 'GI.Pango.Objects.Font.fontDescribe' if you want the font
-- size in points.
-- 
-- /Since: 1.14/
fontDescribeWithAbsoluteSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> m Pango.FontDescription.FontDescription
    -- ^ __Returns:__ a newly-allocated t'GI.Pango.Structs.FontDescription.FontDescription' object.
fontDescribeWithAbsoluteSize :: a -> m FontDescription
fontDescribeWithAbsoluteSize 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 Text
"fontDescribeWithAbsoluteSize" Ptr FontDescription
result
    FontDescription
result' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, GBoxed 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

-- method Font::find_shaper
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "language"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Language" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the language tag" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ch"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a Unicode character."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "EngineShape" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_find_shaper" pango_font_find_shaper :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    Word32 ->                               -- ch : TBasicType TUInt32
    IO (Ptr Pango.EngineShape.EngineShape)

{-# DEPRECATED fontFindShaper ["Shape engines are no longer used"] #-}
-- | Finds the best matching shaper for a font for a particular
-- language tag and character point.
fontFindShaper ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> Pango.Language.Language
    -- ^ /@language@/: the language tag
    -> Word32
    -- ^ /@ch@/: a Unicode character.
    -> m Pango.EngineShape.EngineShape
    -- ^ __Returns:__ the best matching shaper.
fontFindShaper :: a -> Language -> Word32 -> m EngineShape
fontFindShaper a
font Language
language 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 Text
"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

-- method Font::get_coverage
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "language"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Language" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the language tag" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Coverage" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_get_coverage" pango_font_get_coverage :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    IO (Ptr Pango.Coverage.Coverage)

-- | Computes the coverage map for a given font and language tag.
fontGetCoverage ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> Pango.Language.Language
    -- ^ /@language@/: the language tag
    -> m Pango.Coverage.Coverage
    -- ^ __Returns:__ a newly-allocated t'GI.Pango.Objects.Coverage.Coverage'
    --   object.
fontGetCoverage :: a -> Language -> m Coverage
fontGetCoverage a
font Language
language = IO Coverage -> m Coverage
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Coverage -> m Coverage) -> IO Coverage -> m Coverage
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 Coverage
result <- Ptr Font -> Ptr Language -> IO (Ptr Coverage)
pango_font_get_coverage Ptr Font
font' Ptr Language
language'
    Text -> Ptr Coverage -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fontGetCoverage" Ptr Coverage
result
    Coverage
result' <- ((ManagedPtr Coverage -> Coverage) -> Ptr Coverage -> IO Coverage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Coverage -> Coverage
Pango.Coverage.Coverage) Ptr Coverage
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
font
    Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Language
language
    Coverage -> IO Coverage
forall (m :: * -> *) a. Monad m => a -> m a
return Coverage
result'

#if defined(ENABLE_OVERLOADING)
data FontGetCoverageMethodInfo
instance (signature ~ (Pango.Language.Language -> m Pango.Coverage.Coverage), MonadIO m, IsFont a) => O.MethodInfo FontGetCoverageMethodInfo a signature where
    overloadedMethod = fontGetCoverage

#endif

-- method Font::get_font_map
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "FontMap" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_get_font_map" pango_font_get_font_map :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    IO (Ptr Pango.FontMap.FontMap)

-- | Gets the font map for which the font was created.
-- 
-- Note that the font maintains a \<firstterm>weak\<\/firstterm> reference
-- to the font map, so if all references to font map are dropped, the font
-- map will be finalized even if there are fonts created with the font
-- map that are still alive.  In that case this function will return 'P.Nothing'.
-- It is the responsibility of the user to ensure that the font map is kept
-- alive.  In most uses this is not an issue as a t'GI.Pango.Objects.Context.Context' holds
-- a reference to the font map.
-- 
-- /Since: 1.10/
fontGetFontMap ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font', or 'P.Nothing'
    -> m (Maybe Pango.FontMap.FontMap)
    -- ^ __Returns:__ the t'GI.Pango.Objects.FontMap.FontMap' for the
    --               font, or 'P.Nothing' if /@font@/ is 'P.Nothing'.
fontGetFontMap :: a -> m (Maybe FontMap)
fontGetFontMap 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
$ \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

-- method Font::get_glyph_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyph"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the glyph index" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ink_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the extents of the glyph\n           as drawn or %NULL to indicate that the result is not needed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "logical_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the logical extents of\n           the glyph or %NULL to indicate that the result is not needed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_get_glyph_extents" pango_font_get_glyph_extents :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Word32 ->                               -- glyph : TBasicType TUInt32
    Ptr Pango.Rectangle.Rectangle ->        -- ink_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    Ptr Pango.Rectangle.Rectangle ->        -- logical_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Gets the logical and ink extents of a glyph within a font. The
-- coordinate system for each rectangle has its origin at the
-- base line and horizontal origin of the character with increasing
-- coordinates extending to the right and down. The macros @/PANGO_ASCENT()/@,
-- @/PANGO_DESCENT()/@, @/PANGO_LBEARING()/@, and @/PANGO_RBEARING()/@ can be used to convert
-- from the extents rectangle to more traditional font metrics. The units
-- of the rectangles are in 1\/PANGO_SCALE of a device unit.
-- 
-- If /@font@/ is 'P.Nothing', this function gracefully sets some sane values in the
-- output variables and returns.
fontGetGlyphExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> Word32
    -- ^ /@glyph@/: the glyph index
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
fontGetGlyphExtents :: a -> Word32 -> m (Rectangle, Rectangle)
fontGetGlyphExtents a
font 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)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
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, BoxedPtr 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, BoxedPtr 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

-- method Font::get_metrics
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "language"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Language" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "language tag used to determine which script to get the metrics\n           for, or %NULL to indicate to get the metrics for the entire font."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "FontMetrics" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_get_metrics" pango_font_get_metrics :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    IO (Ptr Pango.FontMetrics.FontMetrics)

-- | Gets overall metric information for a font. Since the metrics may be
-- substantially different for different scripts, a language tag can
-- be provided to indicate that the metrics should be retrieved that
-- correspond to the script(s) used by that language.
-- 
-- If /@font@/ is 'P.Nothing', this function gracefully sets some sane values in the
-- output variables and returns.
fontGetMetrics ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> Maybe (Pango.Language.Language)
    -- ^ /@language@/: language tag used to determine which script to get the metrics
    --            for, or 'P.Nothing' to indicate to get the metrics for the entire font.
    -> m Pango.FontMetrics.FontMetrics
    -- ^ __Returns:__ a t'GI.Pango.Structs.FontMetrics.FontMetrics' object. The caller must call 'GI.Pango.Structs.FontMetrics.fontMetricsUnref'
    --   when finished using the object.
fontGetMetrics :: a -> Maybe Language -> m FontMetrics
fontGetMetrics a
font 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
        Maybe Language
Nothing -> Ptr Language -> IO (Ptr Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Language
forall a. Ptr a
nullPtr
        Just 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 Text
"fontGetMetrics" Ptr FontMetrics
result
    FontMetrics
result' <- ((ManagedPtr FontMetrics -> FontMetrics)
-> Ptr FontMetrics -> IO FontMetrics
forall a.
(HasCallStack, GBoxed 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

-- method Font::has_char
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFont" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wc"
--           , argType = TBasicType TUniChar
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a Unicode character"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_has_char" pango_font_has_char :: 
    Ptr Font ->                             -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    CInt ->                                 -- wc : TBasicType TUniChar
    IO CInt

-- | Returns whether the font provides a glyph for this character.
-- 
-- Returns 'P.True' if /@font@/ can render /@wc@/
-- 
-- /Since: 1.44/
fontHasChar ::
    (B.CallStack.HasCallStack, MonadIO m, IsFont a) =>
    a
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'
    -> Char
    -- ^ /@wc@/: a Unicode character
    -> m Bool
fontHasChar :: a -> Char -> m Bool
fontHasChar a
font Char
wc = 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 Font
font' <- a -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
font
    let wc' :: CInt
wc' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Char -> Int) -> Char -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
ord) Char
wc
    CInt
result <- Ptr Font -> CInt -> IO CInt
pango_font_has_char Ptr Font
font' CInt
wc'
    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
font
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data FontHasCharMethodInfo
instance (signature ~ (Char -> m Bool), MonadIO m, IsFont a) => O.MethodInfo FontHasCharMethodInfo a signature where
    overloadedMethod = fontHasChar

#endif

-- method Font::descriptions_free
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "descs"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 1
--                 (TInterface
--                    Name { namespace = "Pango" , name = "FontDescription" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a pointer\nto an array of #PangoFontDescription, may be %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_descs"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of font descriptions in @descs"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_descs"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of font descriptions in @descs"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_descriptions_free" pango_font_descriptions_free :: 
    Ptr (Ptr Pango.FontDescription.FontDescription) -> -- descs : TCArray False (-1) 1 (TInterface (Name {namespace = "Pango", name = "FontDescription"}))
    Int32 ->                                -- n_descs : TBasicType TInt
    IO ()

-- | Frees an array of font descriptions.
fontDescriptionsFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Maybe ([Pango.FontDescription.FontDescription])
    -- ^ /@descs@/: a pointer
    -- to an array of t'GI.Pango.Structs.FontDescription.FontDescription', may be 'P.Nothing'
    -> m ()
fontDescriptionsFree :: Maybe [FontDescription] -> m ()
fontDescriptionsFree 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
            Maybe [FontDescription]
Nothing -> Int32
0
            Just [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
P.length [FontDescription]
jDescs
    Ptr (Ptr FontDescription)
maybeDescs <- case Maybe [FontDescription]
descs of
        Maybe [FontDescription]
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 [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, GBoxed 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