{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Pango.Objects.FontsetSimple.FontsetSimple' is a implementation of the abstract
-- t'GI.Pango.Objects.Fontset.Fontset' base class in terms of an array of fonts,
-- which the creator provides when constructing the
-- t'GI.Pango.Objects.FontsetSimple.FontsetSimple'.

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

module GI.Pango.Objects.FontsetSimple
    ( 

-- * Exported types
    FontsetSimple(..)                       ,
    IsFontsetSimple                         ,
    toFontsetSimple                         ,
    noFontsetSimple                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveFontsetSimpleMethod              ,
#endif


-- ** append #method:append#

#if defined(ENABLE_OVERLOADING)
    FontsetSimpleAppendMethodInfo           ,
#endif
    fontsetSimpleAppend                     ,


-- ** new #method:new#

    fontsetSimpleNew                        ,


-- ** size #method:size#

#if defined(ENABLE_OVERLOADING)
    FontsetSimpleSizeMethodInfo             ,
#endif
    fontsetSimpleSize                       ,




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

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

instance GObject FontsetSimple where
    gobjectType :: IO GType
gobjectType = IO GType
c_pango_fontset_simple_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `FontsetSimple`.
noFontsetSimple :: Maybe FontsetSimple
noFontsetSimple :: Maybe FontsetSimple
noFontsetSimple = Maybe FontsetSimple
forall a. Maybe a
Nothing

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

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "pango_fontset_simple_new" pango_fontset_simple_new :: 
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    IO (Ptr FontsetSimple)

-- | Creates a new t'GI.Pango.Objects.FontsetSimple.FontsetSimple' for the given language.
fontsetSimpleNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Pango.Language.Language
    -- ^ /@language@/: a t'GI.Pango.Structs.Language.Language' tag
    -> m FontsetSimple
    -- ^ __Returns:__ the newly allocated t'GI.Pango.Objects.FontsetSimple.FontsetSimple', which should
    --               be freed with 'GI.GObject.Objects.Object.objectUnref'.
fontsetSimpleNew :: Language -> m FontsetSimple
fontsetSimpleNew language :: Language
language = IO FontsetSimple -> m FontsetSimple
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontsetSimple -> m FontsetSimple)
-> IO FontsetSimple -> m FontsetSimple
forall a b. (a -> b) -> a -> b
$ do
    Ptr Language
language' <- Language -> IO (Ptr Language)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Language
language
    Ptr FontsetSimple
result <- Ptr Language -> IO (Ptr FontsetSimple)
pango_fontset_simple_new Ptr Language
language'
    Text -> Ptr FontsetSimple -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontsetSimpleNew" Ptr FontsetSimple
result
    FontsetSimple
result' <- ((ManagedPtr FontsetSimple -> FontsetSimple)
-> Ptr FontsetSimple -> IO FontsetSimple
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FontsetSimple -> FontsetSimple
FontsetSimple) Ptr FontsetSimple
result
    Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Language
language
    FontsetSimple -> IO FontsetSimple
forall (m :: * -> *) a. Monad m => a -> m a
return FontsetSimple
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Adds a font to the fontset.
fontsetSimpleAppend ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontsetSimple a, Pango.Font.IsFont b) =>
    a
    -- ^ /@fontset@/: a t'GI.Pango.Objects.FontsetSimple.FontsetSimple'.
    -> b
    -- ^ /@font@/: a t'GI.Pango.Objects.Font.Font'.
    -> m ()
fontsetSimpleAppend :: a -> b -> m ()
fontsetSimpleAppend fontset :: a
fontset font :: b
font = 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 FontsetSimple
fontset' <- a -> IO (Ptr FontsetSimple)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontset
    Ptr Font
font' <- b -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
font
    Ptr FontsetSimple -> Ptr Font -> IO ()
pango_fontset_simple_append Ptr FontsetSimple
fontset' Ptr Font
font'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontset
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
font
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FontsetSimpleAppendMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsFontsetSimple a, Pango.Font.IsFont b) => O.MethodInfo FontsetSimpleAppendMethodInfo a signature where
    overloadedMethod = fontsetSimpleAppend

#endif

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

foreign import ccall "pango_fontset_simple_size" pango_fontset_simple_size :: 
    Ptr FontsetSimple ->                    -- fontset : TInterface (Name {namespace = "Pango", name = "FontsetSimple"})
    IO Int32

-- | Returns the number of fonts in the fontset.
fontsetSimpleSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontsetSimple a) =>
    a
    -- ^ /@fontset@/: a t'GI.Pango.Objects.FontsetSimple.FontsetSimple'.
    -> m Int32
    -- ^ __Returns:__ the size of /@fontset@/.
fontsetSimpleSize :: a -> m Int32
fontsetSimpleSize fontset :: a
fontset = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr FontsetSimple
fontset' <- a -> IO (Ptr FontsetSimple)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontset
    Int32
result <- Ptr FontsetSimple -> IO Int32
pango_fontset_simple_size Ptr FontsetSimple
fontset'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontset
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data FontsetSimpleSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFontsetSimple a) => O.MethodInfo FontsetSimpleSizeMethodInfo a signature where
    overloadedMethod = fontsetSimpleSize

#endif