{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Poppler.Objects.FontInfo
    ( 

-- * Exported types
    FontInfo(..)                            ,
    IsFontInfo                              ,
    toFontInfo                              ,
    noFontInfo                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveFontInfoMethod                   ,
#endif


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    FontInfoFreeMethodInfo                  ,
#endif
    fontInfoFree                            ,


-- ** new #method:new#

    fontInfoNew                             ,


-- ** scan #method:scan#

#if defined(ENABLE_OVERLOADING)
    FontInfoScanMethodInfo                  ,
#endif
    fontInfoScan                            ,




    ) 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.Poppler.Objects.Document as Poppler.Document
import {-# SOURCE #-} qualified GI.Poppler.Structs.FontsIter as Poppler.FontsIter

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

instance GObject FontInfo where
    gobjectType :: IO GType
gobjectType = IO GType
c_poppler_font_info_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `FontInfo`.
noFontInfo :: Maybe FontInfo
noFontInfo :: Maybe FontInfo
noFontInfo = Maybe FontInfo
forall a. Maybe a
Nothing

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

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "poppler_font_info_new" poppler_font_info_new :: 
    Ptr Poppler.Document.Document ->        -- document : TInterface (Name {namespace = "Poppler", name = "Document"})
    IO (Ptr FontInfo)

-- | Creates a new t'GI.Poppler.Objects.FontInfo.FontInfo' object
fontInfoNew ::
    (B.CallStack.HasCallStack, MonadIO m, Poppler.Document.IsDocument a) =>
    a
    -- ^ /@document@/: a t'GI.Poppler.Objects.Document.Document'
    -> m FontInfo
    -- ^ __Returns:__ a new t'GI.Poppler.Objects.FontInfo.FontInfo' instance
fontInfoNew :: a -> m FontInfo
fontInfoNew document :: a
document = IO FontInfo -> m FontInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontInfo -> m FontInfo) -> IO FontInfo -> m FontInfo
forall a b. (a -> b) -> a -> b
$ do
    Ptr Document
document' <- a -> IO (Ptr Document)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
document
    Ptr FontInfo
result <- Ptr Document -> IO (Ptr FontInfo)
poppler_font_info_new Ptr Document
document'
    Text -> Ptr FontInfo -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "fontInfoNew" Ptr FontInfo
result
    FontInfo
result' <- ((ManagedPtr FontInfo -> FontInfo) -> Ptr FontInfo -> IO FontInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FontInfo -> FontInfo
FontInfo) Ptr FontInfo
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
document
    FontInfo -> IO FontInfo
forall (m :: * -> *) a. Monad m => a -> m a
return FontInfo
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method FontInfo::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font_info"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "FontInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "poppler_font_info_free" poppler_font_info_free :: 
    Ptr FontInfo ->                         -- font_info : TInterface (Name {namespace = "Poppler", name = "FontInfo"})
    IO ()

-- | /No description available in the introspection data./
fontInfoFree ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontInfo a) =>
    a
    -> m ()
fontInfoFree :: a -> m ()
fontInfoFree fontInfo :: a
fontInfo = 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 FontInfo
fontInfo' <- a -> IO (Ptr FontInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontInfo
    Ptr FontInfo -> IO ()
poppler_font_info_free Ptr FontInfo
fontInfo'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontInfo
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data FontInfoFreeMethodInfo
instance (signature ~ (m ()), MonadIO m, IsFontInfo a) => O.MethodInfo FontInfoFreeMethodInfo a signature where
    overloadedMethod = fontInfoFree

#endif

-- method FontInfo::scan
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "font_info"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "FontInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PopplerFontInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_pages"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of pages to scan"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Poppler" , name = "FontsIter" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #PopplerFontsIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "poppler_font_info_scan" poppler_font_info_scan :: 
    Ptr FontInfo ->                         -- font_info : TInterface (Name {namespace = "Poppler", name = "FontInfo"})
    Int32 ->                                -- n_pages : TBasicType TInt
    Ptr (Ptr Poppler.FontsIter.FontsIter) -> -- iter : TInterface (Name {namespace = "Poppler", name = "FontsIter"})
    IO CInt

-- | Scans the document associated with /@fontInfo@/ for fonts. At most
-- /@nPages@/ will be scanned starting from the current iterator. /@iter@/ will
-- point to the first font scanned.
-- 
-- Here is a simple example of code to scan fonts in a document
-- 
-- \<informalexample>\<programlisting>
-- font_info = poppler_font_info_new (document);
-- while (poppler_font_info_scan (font_info, 20, &fonts_iter)) {
--         if (!fonts_iter)
--                 continue; \/\<!-- -->* No fonts found in these 20 pages *\<!-- -->\/
--         do {
--                 \/\<!-- -->* Do something with font iter *\<!-- -->\/
--                 g_print (\"Font Name: @/s/@\\n\", poppler_fonts_iter_get_name (fonts_iter));
--         } while (poppler_fonts_iter_next (fonts_iter));
--         poppler_fonts_iter_free (fonts_iter);
-- }
-- \<\/programlisting>\<\/informalexample>
fontInfoScan ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontInfo a) =>
    a
    -- ^ /@fontInfo@/: a t'GI.Poppler.Objects.FontInfo.FontInfo'
    -> Int32
    -- ^ /@nPages@/: number of pages to scan
    -> m ((Bool, Poppler.FontsIter.FontsIter))
    -- ^ __Returns:__ 'P.True', if there are more fonts left to scan
fontInfoScan :: a -> Int32 -> m (Bool, FontsIter)
fontInfoScan fontInfo :: a
fontInfo nPages :: Int32
nPages = IO (Bool, FontsIter) -> m (Bool, FontsIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, FontsIter) -> m (Bool, FontsIter))
-> IO (Bool, FontsIter) -> m (Bool, FontsIter)
forall a b. (a -> b) -> a -> b
$ do
    Ptr FontInfo
fontInfo' <- a -> IO (Ptr FontInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontInfo
    Ptr (Ptr FontsIter)
iter <- IO (Ptr (Ptr FontsIter))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Poppler.FontsIter.FontsIter))
    CInt
result <- Ptr FontInfo -> Int32 -> Ptr (Ptr FontsIter) -> IO CInt
poppler_font_info_scan Ptr FontInfo
fontInfo' Int32
nPages Ptr (Ptr FontsIter)
iter
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Ptr FontsIter
iter' <- Ptr (Ptr FontsIter) -> IO (Ptr FontsIter)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr FontsIter)
iter
    FontsIter
iter'' <- ((ManagedPtr FontsIter -> FontsIter)
-> Ptr FontsIter -> IO FontsIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontsIter -> FontsIter
Poppler.FontsIter.FontsIter) Ptr FontsIter
iter'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontInfo
    Ptr (Ptr FontsIter) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr FontsIter)
iter
    (Bool, FontsIter) -> IO (Bool, FontsIter)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', FontsIter
iter'')

#if defined(ENABLE_OVERLOADING)
data FontInfoScanMethodInfo
instance (signature ~ (Int32 -> m ((Bool, Poppler.FontsIter.FontsIter))), MonadIO m, IsFontInfo a) => O.MethodInfo FontInfoScanMethodInfo a signature where
    overloadedMethod = fontInfoScan

#endif