{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Pango.Objects.Fontset.Fontset' represents a set of t'GI.Pango.Objects.Font.Font' to use
-- when rendering text. It is the result of resolving a
-- t'GI.Pango.Structs.FontDescription.FontDescription' against a particular t'GI.Pango.Objects.Context.Context'.
-- It has operations for finding the component font for
-- a particular Unicode character, and for finding a composite
-- set of metrics for the entire fontset.

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

module GI.Pango.Objects.Fontset
    ( 

-- * Exported types
    Fontset(..)                             ,
    IsFontset                               ,
    toFontset                               ,
    noFontset                               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveFontsetMethod                    ,
#endif


-- ** foreach #method:foreach#

#if defined(ENABLE_OVERLOADING)
    FontsetForeachMethodInfo                ,
#endif
    fontsetForeach                          ,


-- ** getFont #method:getFont#

#if defined(ENABLE_OVERLOADING)
    FontsetGetFontMethodInfo                ,
#endif
    fontsetGetFont                          ,


-- ** getMetrics #method:getMetrics#

#if defined(ENABLE_OVERLOADING)
    FontsetGetMetricsMethodInfo             ,
#endif
    fontsetGetMetrics                       ,




    ) 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 qualified GI.Pango.Callbacks as Pango.Callbacks
import {-# SOURCE #-} qualified GI.Pango.Objects.Font as Pango.Font
import {-# SOURCE #-} qualified GI.Pango.Structs.FontMetrics as Pango.FontMetrics

-- | Memory-managed wrapper type.
newtype Fontset = Fontset (ManagedPtr Fontset)
    deriving (Fontset -> Fontset -> Bool
(Fontset -> Fontset -> Bool)
-> (Fontset -> Fontset -> Bool) -> Eq Fontset
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fontset -> Fontset -> Bool
$c/= :: Fontset -> Fontset -> Bool
== :: Fontset -> Fontset -> Bool
$c== :: Fontset -> Fontset -> Bool
Eq)
foreign import ccall "pango_fontset_get_type"
    c_pango_fontset_get_type :: IO GType

instance GObject Fontset where
    gobjectType :: IO GType
gobjectType = IO GType
c_pango_fontset_get_type
    

-- | Convert 'Fontset' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Fontset where
    toGValue :: Fontset -> IO GValue
toGValue o :: Fontset
o = do
        GType
gtype <- IO GType
c_pango_fontset_get_type
        Fontset -> (Ptr Fontset -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Fontset
o (GType
-> (GValue -> Ptr Fontset -> IO ()) -> Ptr Fontset -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Fontset -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Fontset
fromGValue gv :: GValue
gv = do
        Ptr Fontset
ptr <- GValue -> IO (Ptr Fontset)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Fontset)
        (ManagedPtr Fontset -> Fontset) -> Ptr Fontset -> IO Fontset
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Fontset -> Fontset
Fontset Ptr Fontset
ptr
        
    

-- | Type class for types which can be safely cast to `Fontset`, for instance with `toFontset`.
class (GObject o, O.IsDescendantOf Fontset o) => IsFontset o
instance (GObject o, O.IsDescendantOf Fontset o) => IsFontset o

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

-- | Cast to `Fontset`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toFontset :: (MonadIO m, IsFontset o) => o -> m Fontset
toFontset :: o -> m Fontset
toFontset = IO Fontset -> m Fontset
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fontset -> m Fontset) -> (o -> IO Fontset) -> o -> m Fontset
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Fontset -> Fontset) -> o -> IO Fontset
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Fontset -> Fontset
Fontset

-- | A convenience alias for `Nothing` :: `Maybe` `Fontset`.
noFontset :: Maybe Fontset
noFontset :: Maybe Fontset
noFontset = Maybe Fontset
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveFontsetMethod (t :: Symbol) (o :: *) :: * where
    ResolveFontsetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveFontsetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveFontsetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveFontsetMethod "foreach" o = FontsetForeachMethodInfo
    ResolveFontsetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveFontsetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveFontsetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveFontsetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveFontsetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveFontsetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveFontsetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveFontsetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveFontsetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveFontsetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveFontsetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveFontsetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveFontsetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveFontsetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveFontsetMethod "getFont" o = FontsetGetFontMethodInfo
    ResolveFontsetMethod "getMetrics" o = FontsetGetMetricsMethodInfo
    ResolveFontsetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveFontsetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveFontsetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveFontsetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveFontsetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveFontsetMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveFontsetMethod t Fontset, O.MethodInfo info Fontset p) => OL.IsLabel t (Fontset -> 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 Fontset
type instance O.AttributeList Fontset = FontsetAttributeList
type FontsetAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Fontset = FontsetSignalList
type FontsetSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Fontset::foreach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fontset"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Fontset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFontset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType =
--               TInterface
--                 Name { namespace = "Pango" , name = "FontsetForeachFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Callback function" , sinceVersion = Nothing }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to the callback function"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_fontset_foreach" pango_fontset_foreach :: 
    Ptr Fontset ->                          -- fontset : TInterface (Name {namespace = "Pango", name = "Fontset"})
    FunPtr Pango.Callbacks.C_FontsetForeachFunc -> -- func : TInterface (Name {namespace = "Pango", name = "FontsetForeachFunc"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | Iterates through all the fonts in a fontset, calling /@func@/ for
-- each one. If /@func@/ returns 'P.True', that stops the iteration.
-- 
-- /Since: 1.4/
fontsetForeach ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontset a) =>
    a
    -- ^ /@fontset@/: a t'GI.Pango.Objects.Fontset.Fontset'
    -> Pango.Callbacks.FontsetForeachFunc
    -- ^ /@func@/: Callback function
    -> m ()
fontsetForeach :: a -> FontsetForeachFunc -> m ()
fontsetForeach fontset :: a
fontset func :: FontsetForeachFunc
func = 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 Fontset
fontset' <- a -> IO (Ptr Fontset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontset
    FunPtr C_FontsetForeachFunc
func' <- C_FontsetForeachFunc -> IO (FunPtr C_FontsetForeachFunc)
Pango.Callbacks.mk_FontsetForeachFunc (Maybe (Ptr (FunPtr C_FontsetForeachFunc))
-> FontsetForeachFunc_WithClosures -> C_FontsetForeachFunc
Pango.Callbacks.wrap_FontsetForeachFunc Maybe (Ptr (FunPtr C_FontsetForeachFunc))
forall a. Maybe a
Nothing (FontsetForeachFunc -> FontsetForeachFunc_WithClosures
Pango.Callbacks.drop_closures_FontsetForeachFunc FontsetForeachFunc
func))
    let data_ :: Ptr a
data_ = Ptr a
forall a. Ptr a
nullPtr
    Ptr Fontset -> FunPtr C_FontsetForeachFunc -> Ptr () -> IO ()
pango_fontset_foreach Ptr Fontset
fontset' FunPtr C_FontsetForeachFunc
func' Ptr ()
forall a. Ptr a
data_
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_FontsetForeachFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_FontsetForeachFunc
func'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontset
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FontsetForeachMethodInfo
instance (signature ~ (Pango.Callbacks.FontsetForeachFunc -> m ()), MonadIO m, IsFontset a) => O.MethodInfo FontsetForeachMethodInfo a signature where
    overloadedMethod = fontsetForeach

#endif

-- method Fontset::get_font
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fontset"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Fontset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFontset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wc"
--           , argType = TBasicType TUInt
--           , 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 = "Font" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_fontset_get_font" pango_fontset_get_font :: 
    Ptr Fontset ->                          -- fontset : TInterface (Name {namespace = "Pango", name = "Fontset"})
    Word32 ->                               -- wc : TBasicType TUInt
    IO (Ptr Pango.Font.Font)

-- | Returns the font in the fontset that contains the best glyph for the
-- Unicode character /@wc@/.
fontsetGetFont ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontset a) =>
    a
    -- ^ /@fontset@/: a t'GI.Pango.Objects.Fontset.Fontset'
    -> Word32
    -- ^ /@wc@/: a Unicode character
    -> m Pango.Font.Font
    -- ^ __Returns:__ a t'GI.Pango.Objects.Font.Font'. The caller must call
    --          g_object_unref when finished with the font.
fontsetGetFont :: a -> Word32 -> m Font
fontsetGetFont fontset :: a
fontset wc :: Word32
wc = IO Font -> m Font
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Font -> m Font) -> IO Font -> m Font
forall a b. (a -> b) -> a -> b
$ do
    Ptr Fontset
fontset' <- a -> IO (Ptr Fontset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontset
    Ptr Font
result <- Ptr Fontset -> Word32 -> IO (Ptr Font)
pango_fontset_get_font Ptr Fontset
fontset' Word32
wc
    Text -> Ptr Font -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontsetGetFont" Ptr Font
result
    Font
result' <- ((ManagedPtr Font -> Font) -> Ptr Font -> IO Font
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Font -> Font
Pango.Font.Font) Ptr Font
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontset
    Font -> IO Font
forall (m :: * -> *) a. Monad m => a -> m a
return Font
result'

#if defined(ENABLE_OVERLOADING)
data FontsetGetFontMethodInfo
instance (signature ~ (Word32 -> m Pango.Font.Font), MonadIO m, IsFontset a) => O.MethodInfo FontsetGetFontMethodInfo a signature where
    overloadedMethod = fontsetGetFont

#endif

-- method Fontset::get_metrics
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "fontset"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Fontset" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoFontset" , 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_fontset_get_metrics" pango_fontset_get_metrics :: 
    Ptr Fontset ->                          -- fontset : TInterface (Name {namespace = "Pango", name = "Fontset"})
    IO (Ptr Pango.FontMetrics.FontMetrics)

-- | Get overall metric information for the fonts in the fontset.
fontsetGetMetrics ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontset a) =>
    a
    -- ^ /@fontset@/: a t'GI.Pango.Objects.Fontset.Fontset'
    -> 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.
fontsetGetMetrics :: a -> m FontMetrics
fontsetGetMetrics fontset :: a
fontset = 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 Fontset
fontset' <- a -> IO (Ptr Fontset)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontset
    Ptr FontMetrics
result <- Ptr Fontset -> IO (Ptr FontMetrics)
pango_fontset_get_metrics Ptr Fontset
fontset'
    Text -> Ptr FontMetrics -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontsetGetMetrics" 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
fontset
    FontMetrics -> IO FontMetrics
forall (m :: * -> *) a. Monad m => a -> m a
return FontMetrics
result'

#if defined(ENABLE_OVERLOADING)
data FontsetGetMetricsMethodInfo
instance (signature ~ (m Pango.FontMetrics.FontMetrics), MonadIO m, IsFontset a) => O.MethodInfo FontsetGetMetricsMethodInfo a signature where
    overloadedMethod = fontsetGetMetrics

#endif