module GI.Poppler.Structs.TextSpan
(
TextSpan(..) ,
noTextSpan ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanCopyMethodInfo ,
#endif
textSpanCopy ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanFreeMethodInfo ,
#endif
textSpanFree ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanGetColorMethodInfo ,
#endif
textSpanGetColor ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanGetFontNameMethodInfo ,
#endif
textSpanGetFontName ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanGetTextMethodInfo ,
#endif
textSpanGetText ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanIsBoldFontMethodInfo ,
#endif
textSpanIsBoldFont ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanIsFixedWidthFontMethodInfo ,
#endif
textSpanIsFixedWidthFont ,
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
TextSpanIsSerifFontMethodInfo ,
#endif
textSpanIsSerifFont ,
) 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.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
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 GI.Poppler.Structs.Color as Poppler.Color
newtype TextSpan = TextSpan (ManagedPtr TextSpan)
foreign import ccall "poppler_text_span_get_type" c_poppler_text_span_get_type ::
IO GType
instance BoxedObject TextSpan where
boxedType _ = c_poppler_text_span_get_type
noTextSpan :: Maybe TextSpan
noTextSpan = Nothing
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
instance O.HasAttributeList TextSpan
type instance O.AttributeList TextSpan = TextSpanAttributeList
type TextSpanAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "poppler_text_span_copy" poppler_text_span_copy ::
Ptr TextSpan ->
IO (Ptr TextSpan)
textSpanCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m TextSpan
textSpanCopy popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_copy popplerTextSpan'
checkUnexpectedReturnNULL "textSpanCopy" result
result' <- (wrapBoxed TextSpan) result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanCopyMethodInfo
instance (signature ~ (m TextSpan), MonadIO m) => O.MethodInfo TextSpanCopyMethodInfo TextSpan signature where
overloadedMethod _ = textSpanCopy
#endif
foreign import ccall "poppler_text_span_free" poppler_text_span_free ::
Ptr TextSpan ->
IO ()
textSpanFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m ()
textSpanFree popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
poppler_text_span_free popplerTextSpan'
touchManagedPtr popplerTextSpan
return ()
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo TextSpanFreeMethodInfo TextSpan signature where
overloadedMethod _ = textSpanFree
#endif
foreign import ccall "poppler_text_span_get_color" poppler_text_span_get_color ::
Ptr TextSpan ->
Ptr Poppler.Color.Color ->
IO ()
textSpanGetColor ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m (Poppler.Color.Color)
textSpanGetColor popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
color <- callocBoxedBytes 6 :: IO (Ptr Poppler.Color.Color)
poppler_text_span_get_color popplerTextSpan' color
color' <- (wrapBoxed Poppler.Color.Color) color
touchManagedPtr popplerTextSpan
return color'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanGetColorMethodInfo
instance (signature ~ (m (Poppler.Color.Color)), MonadIO m) => O.MethodInfo TextSpanGetColorMethodInfo TextSpan signature where
overloadedMethod _ = textSpanGetColor
#endif
foreign import ccall "poppler_text_span_get_font_name" poppler_text_span_get_font_name ::
Ptr TextSpan ->
IO CString
textSpanGetFontName ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m T.Text
textSpanGetFontName popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_get_font_name popplerTextSpan'
checkUnexpectedReturnNULL "textSpanGetFontName" result
result' <- cstringToText result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanGetFontNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo TextSpanGetFontNameMethodInfo TextSpan signature where
overloadedMethod _ = textSpanGetFontName
#endif
foreign import ccall "poppler_text_span_get_text" poppler_text_span_get_text ::
Ptr TextSpan ->
IO CString
textSpanGetText ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m T.Text
textSpanGetText popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_get_text popplerTextSpan'
checkUnexpectedReturnNULL "textSpanGetText" result
result' <- cstringToText result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanGetTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo TextSpanGetTextMethodInfo TextSpan signature where
overloadedMethod _ = textSpanGetText
#endif
foreign import ccall "poppler_text_span_is_bold_font" poppler_text_span_is_bold_font ::
Ptr TextSpan ->
IO CInt
textSpanIsBoldFont ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m Bool
textSpanIsBoldFont popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_is_bold_font popplerTextSpan'
let result' = (/= 0) result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanIsBoldFontMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextSpanIsBoldFontMethodInfo TextSpan signature where
overloadedMethod _ = textSpanIsBoldFont
#endif
foreign import ccall "poppler_text_span_is_fixed_width_font" poppler_text_span_is_fixed_width_font ::
Ptr TextSpan ->
IO CInt
textSpanIsFixedWidthFont ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m Bool
textSpanIsFixedWidthFont popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_is_fixed_width_font popplerTextSpan'
let result' = (/= 0) result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanIsFixedWidthFontMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextSpanIsFixedWidthFontMethodInfo TextSpan signature where
overloadedMethod _ = textSpanIsFixedWidthFont
#endif
foreign import ccall "poppler_text_span_is_serif_font" poppler_text_span_is_serif_font ::
Ptr TextSpan ->
IO CInt
textSpanIsSerifFont ::
(B.CallStack.HasCallStack, MonadIO m) =>
TextSpan
-> m Bool
textSpanIsSerifFont popplerTextSpan = liftIO $ do
popplerTextSpan' <- unsafeManagedPtrGetPtr popplerTextSpan
result <- poppler_text_span_is_serif_font popplerTextSpan'
let result' = (/= 0) result
touchManagedPtr popplerTextSpan
return result'
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
data TextSpanIsSerifFontMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo TextSpanIsSerifFontMethodInfo TextSpan signature where
overloadedMethod _ = textSpanIsSerifFont
#endif
#if defined(ENABLE_OVERLOADING) && !defined(__HADDOCK_VERSION__)
type family ResolveTextSpanMethod (t :: Symbol) (o :: *) :: * where
ResolveTextSpanMethod "copy" o = TextSpanCopyMethodInfo
ResolveTextSpanMethod "free" o = TextSpanFreeMethodInfo
ResolveTextSpanMethod "isBoldFont" o = TextSpanIsBoldFontMethodInfo
ResolveTextSpanMethod "isFixedWidthFont" o = TextSpanIsFixedWidthFontMethodInfo
ResolveTextSpanMethod "isSerifFont" o = TextSpanIsSerifFontMethodInfo
ResolveTextSpanMethod "getColor" o = TextSpanGetColorMethodInfo
ResolveTextSpanMethod "getFontName" o = TextSpanGetFontNameMethodInfo
ResolveTextSpanMethod "getText" o = TextSpanGetTextMethodInfo
ResolveTextSpanMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextSpanMethod t TextSpan, O.MethodInfo info TextSpan p) => O.IsLabelProxy t (TextSpan -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTextSpanMethod t TextSpan, O.MethodInfo info TextSpan p) => O.IsLabel t (TextSpan -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif