{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.FontMetrics
(
FontMetrics(..) ,
newZeroFontMetrics ,
#if defined(ENABLE_OVERLOADING)
ResolveFontMetricsMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FontMetricsGetApproximateCharWidthMethodInfo,
#endif
fontMetricsGetApproximateCharWidth ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetApproximateDigitWidthMethodInfo,
#endif
fontMetricsGetApproximateDigitWidth ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetAscentMethodInfo ,
#endif
fontMetricsGetAscent ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetDescentMethodInfo ,
#endif
fontMetricsGetDescent ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetHeightMethodInfo ,
#endif
fontMetricsGetHeight ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetStrikethroughPositionMethodInfo,
#endif
fontMetricsGetStrikethroughPosition ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetStrikethroughThicknessMethodInfo,
#endif
fontMetricsGetStrikethroughThickness ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetUnderlinePositionMethodInfo,
#endif
fontMetricsGetUnderlinePosition ,
#if defined(ENABLE_OVERLOADING)
FontMetricsGetUnderlineThicknessMethodInfo,
#endif
fontMetricsGetUnderlineThickness ,
#if defined(ENABLE_OVERLOADING)
FontMetricsRefMethodInfo ,
#endif
fontMetricsRef ,
#if defined(ENABLE_OVERLOADING)
FontMetricsUnrefMethodInfo ,
#endif
fontMetricsUnref ,
) 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.GArray as B.GArray
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.Coerce as Coerce
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 GHC.Records as R
newtype FontMetrics = FontMetrics (SP.ManagedPtr FontMetrics)
deriving (FontMetrics -> FontMetrics -> Bool
(FontMetrics -> FontMetrics -> Bool)
-> (FontMetrics -> FontMetrics -> Bool) -> Eq FontMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontMetrics -> FontMetrics -> Bool
$c/= :: FontMetrics -> FontMetrics -> Bool
== :: FontMetrics -> FontMetrics -> Bool
$c== :: FontMetrics -> FontMetrics -> Bool
Eq)
instance SP.ManagedPtrNewtype FontMetrics where
toManagedPtr :: FontMetrics -> ManagedPtr FontMetrics
toManagedPtr (FontMetrics ManagedPtr FontMetrics
p) = ManagedPtr FontMetrics
p
foreign import ccall "pango_font_metrics_get_type" c_pango_font_metrics_get_type ::
IO GType
type instance O.ParentTypes FontMetrics = '[]
instance O.HasParentTypes FontMetrics
instance B.Types.TypedObject FontMetrics where
glibType :: IO GType
glibType = IO GType
c_pango_font_metrics_get_type
instance B.Types.GBoxed FontMetrics
instance B.GValue.IsGValue (Maybe FontMetrics) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_pango_font_metrics_get_type
gvalueSet_ :: Ptr GValue -> Maybe FontMetrics -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FontMetrics
P.Nothing = Ptr GValue -> Ptr FontMetrics -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr FontMetrics
forall a. Ptr a
FP.nullPtr :: FP.Ptr FontMetrics)
gvalueSet_ Ptr GValue
gv (P.Just FontMetrics
obj) = FontMetrics -> (Ptr FontMetrics -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FontMetrics
obj (Ptr GValue -> Ptr FontMetrics -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe FontMetrics)
gvalueGet_ Ptr GValue
gv = do
Ptr FontMetrics
ptr <- Ptr GValue -> IO (Ptr FontMetrics)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr FontMetrics)
if Ptr FontMetrics
ptr Ptr FontMetrics -> Ptr FontMetrics -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr FontMetrics
forall a. Ptr a
FP.nullPtr
then FontMetrics -> Maybe FontMetrics
forall a. a -> Maybe a
P.Just (FontMetrics -> Maybe FontMetrics)
-> IO FontMetrics -> IO (Maybe FontMetrics)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr FontMetrics -> FontMetrics)
-> Ptr FontMetrics -> IO FontMetrics
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr FontMetrics -> FontMetrics
FontMetrics Ptr FontMetrics
ptr
else Maybe FontMetrics -> IO (Maybe FontMetrics)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontMetrics
forall a. Maybe a
P.Nothing
newZeroFontMetrics :: MonadIO m => m FontMetrics
newZeroFontMetrics :: forall (m :: * -> *). MonadIO m => m FontMetrics
newZeroFontMetrics = 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
$ Int -> IO (Ptr FontMetrics)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
40 IO (Ptr FontMetrics)
-> (Ptr FontMetrics -> IO FontMetrics) -> IO FontMetrics
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr FontMetrics -> FontMetrics)
-> Ptr FontMetrics -> IO FontMetrics
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontMetrics -> FontMetrics
FontMetrics
instance tag ~ 'AttrSet => Constructible FontMetrics tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr FontMetrics -> FontMetrics)
-> [AttrOp FontMetrics tag] -> m FontMetrics
new ManagedPtr FontMetrics -> FontMetrics
_ [AttrOp FontMetrics tag]
attrs = do
FontMetrics
o <- m FontMetrics
forall (m :: * -> *). MonadIO m => m FontMetrics
newZeroFontMetrics
FontMetrics -> [AttrOp FontMetrics 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set FontMetrics
o [AttrOp FontMetrics tag]
[AttrOp FontMetrics 'AttrSet]
attrs
FontMetrics -> m FontMetrics
forall (m :: * -> *) a. Monad m => a -> m a
return FontMetrics
o
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FontMetrics
type instance O.AttributeList FontMetrics = FontMetricsAttributeList
type FontMetricsAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "pango_font_metrics_get_approximate_char_width" pango_font_metrics_get_approximate_char_width ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetApproximateCharWidth ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetApproximateCharWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetApproximateCharWidth FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_approximate_char_width Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetApproximateCharWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetApproximateCharWidthMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetApproximateCharWidth
instance O.OverloadedMethodInfo FontMetricsGetApproximateCharWidthMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetApproximateCharWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetApproximateCharWidth"
})
#endif
foreign import ccall "pango_font_metrics_get_approximate_digit_width" pango_font_metrics_get_approximate_digit_width ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetApproximateDigitWidth ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetApproximateDigitWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetApproximateDigitWidth FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_approximate_digit_width Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetApproximateDigitWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetApproximateDigitWidthMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetApproximateDigitWidth
instance O.OverloadedMethodInfo FontMetricsGetApproximateDigitWidthMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetApproximateDigitWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetApproximateDigitWidth"
})
#endif
foreign import ccall "pango_font_metrics_get_ascent" pango_font_metrics_get_ascent ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetAscent ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetAscent :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetAscent FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_ascent Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetAscentMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetAscentMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetAscent
instance O.OverloadedMethodInfo FontMetricsGetAscentMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetAscent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetAscent"
})
#endif
foreign import ccall "pango_font_metrics_get_descent" pango_font_metrics_get_descent ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetDescent ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetDescent :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetDescent FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_descent Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetDescentMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetDescentMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetDescent
instance O.OverloadedMethodInfo FontMetricsGetDescentMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetDescent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetDescent"
})
#endif
foreign import ccall "pango_font_metrics_get_height" pango_font_metrics_get_height ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetHeight ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetHeight :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetHeight FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_height Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetHeightMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetHeight
instance O.OverloadedMethodInfo FontMetricsGetHeightMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetHeight",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetHeight"
})
#endif
foreign import ccall "pango_font_metrics_get_strikethrough_position" pango_font_metrics_get_strikethrough_position ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetStrikethroughPosition ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetStrikethroughPosition :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetStrikethroughPosition FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_strikethrough_position Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetStrikethroughPositionMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetStrikethroughPositionMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetStrikethroughPosition
instance O.OverloadedMethodInfo FontMetricsGetStrikethroughPositionMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetStrikethroughPosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetStrikethroughPosition"
})
#endif
foreign import ccall "pango_font_metrics_get_strikethrough_thickness" pango_font_metrics_get_strikethrough_thickness ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetStrikethroughThickness ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetStrikethroughThickness :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetStrikethroughThickness FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_strikethrough_thickness Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetStrikethroughThicknessMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetStrikethroughThicknessMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetStrikethroughThickness
instance O.OverloadedMethodInfo FontMetricsGetStrikethroughThicknessMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetStrikethroughThickness",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetStrikethroughThickness"
})
#endif
foreign import ccall "pango_font_metrics_get_underline_position" pango_font_metrics_get_underline_position ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetUnderlinePosition ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetUnderlinePosition :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetUnderlinePosition FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_underline_position Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetUnderlinePositionMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetUnderlinePositionMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetUnderlinePosition
instance O.OverloadedMethodInfo FontMetricsGetUnderlinePositionMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetUnderlinePosition",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetUnderlinePosition"
})
#endif
foreign import ccall "pango_font_metrics_get_underline_thickness" pango_font_metrics_get_underline_thickness ::
Ptr FontMetrics ->
IO Int32
fontMetricsGetUnderlineThickness ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m Int32
fontMetricsGetUnderlineThickness :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m Int32
fontMetricsGetUnderlineThickness FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Int32
result <- Ptr FontMetrics -> IO Int32
pango_font_metrics_get_underline_thickness Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontMetricsGetUnderlineThicknessMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.OverloadedMethod FontMetricsGetUnderlineThicknessMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsGetUnderlineThickness
instance O.OverloadedMethodInfo FontMetricsGetUnderlineThicknessMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsGetUnderlineThickness",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsGetUnderlineThickness"
})
#endif
foreign import ccall "pango_font_metrics_ref" pango_font_metrics_ref ::
Ptr FontMetrics ->
IO (Ptr FontMetrics)
fontMetricsRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m (Maybe FontMetrics)
fontMetricsRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m (Maybe FontMetrics)
fontMetricsRef FontMetrics
metrics = IO (Maybe FontMetrics) -> m (Maybe FontMetrics)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontMetrics) -> m (Maybe FontMetrics))
-> IO (Maybe FontMetrics) -> m (Maybe FontMetrics)
forall a b. (a -> b) -> a -> b
$ do
Ptr FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Ptr FontMetrics
result <- Ptr FontMetrics -> IO (Ptr FontMetrics)
pango_font_metrics_ref Ptr FontMetrics
metrics'
Maybe FontMetrics
maybeResult <- Ptr FontMetrics
-> (Ptr FontMetrics -> IO FontMetrics) -> IO (Maybe FontMetrics)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontMetrics
result ((Ptr FontMetrics -> IO FontMetrics) -> IO (Maybe FontMetrics))
-> (Ptr FontMetrics -> IO FontMetrics) -> IO (Maybe FontMetrics)
forall a b. (a -> b) -> a -> b
$ \Ptr FontMetrics
result' -> do
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
FontMetrics) Ptr FontMetrics
result'
FontMetrics -> IO FontMetrics
forall (m :: * -> *) a. Monad m => a -> m a
return FontMetrics
result''
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
Maybe FontMetrics -> IO (Maybe FontMetrics)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontMetrics
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontMetricsRefMethodInfo
instance (signature ~ (m (Maybe FontMetrics)), MonadIO m) => O.OverloadedMethod FontMetricsRefMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsRef
instance O.OverloadedMethodInfo FontMetricsRefMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsRef"
})
#endif
foreign import ccall "pango_font_metrics_unref" pango_font_metrics_unref ::
Ptr FontMetrics ->
IO ()
fontMetricsUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
FontMetrics
-> m ()
fontMetricsUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
FontMetrics -> m ()
fontMetricsUnref FontMetrics
metrics = 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 FontMetrics
metrics' <- FontMetrics -> IO (Ptr FontMetrics)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontMetrics
metrics
Ptr FontMetrics -> IO ()
pango_font_metrics_unref Ptr FontMetrics
metrics'
FontMetrics -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontMetrics
metrics
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontMetricsUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod FontMetricsUnrefMethodInfo FontMetrics signature where
overloadedMethod = fontMetricsUnref
instance O.OverloadedMethodInfo FontMetricsUnrefMethodInfo FontMetrics where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.FontMetrics.fontMetricsUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-FontMetrics.html#v:fontMetricsUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveFontMetricsMethod (t :: Symbol) (o :: *) :: * where
ResolveFontMetricsMethod "ref" o = FontMetricsRefMethodInfo
ResolveFontMetricsMethod "unref" o = FontMetricsUnrefMethodInfo
ResolveFontMetricsMethod "getApproximateCharWidth" o = FontMetricsGetApproximateCharWidthMethodInfo
ResolveFontMetricsMethod "getApproximateDigitWidth" o = FontMetricsGetApproximateDigitWidthMethodInfo
ResolveFontMetricsMethod "getAscent" o = FontMetricsGetAscentMethodInfo
ResolveFontMetricsMethod "getDescent" o = FontMetricsGetDescentMethodInfo
ResolveFontMetricsMethod "getHeight" o = FontMetricsGetHeightMethodInfo
ResolveFontMetricsMethod "getStrikethroughPosition" o = FontMetricsGetStrikethroughPositionMethodInfo
ResolveFontMetricsMethod "getStrikethroughThickness" o = FontMetricsGetStrikethroughThicknessMethodInfo
ResolveFontMetricsMethod "getUnderlinePosition" o = FontMetricsGetUnderlinePositionMethodInfo
ResolveFontMetricsMethod "getUnderlineThickness" o = FontMetricsGetUnderlineThicknessMethodInfo
ResolveFontMetricsMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFontMetricsMethod t FontMetrics, O.OverloadedMethod info FontMetrics p) => OL.IsLabel t (FontMetrics -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveFontMetricsMethod t FontMetrics, O.OverloadedMethod info FontMetrics p, R.HasField t FontMetrics p) => R.HasField t FontMetrics p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveFontMetricsMethod t FontMetrics, O.OverloadedMethodInfo info FontMetrics) => OL.IsLabel t (O.MethodProxy info FontMetrics) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif