{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Interfaces.FontChooser
(
FontChooser(..) ,
IsFontChooser ,
toFontChooser ,
#if defined(ENABLE_OVERLOADING)
ResolveFontChooserMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontMethodInfo ,
#endif
fontChooserGetFont ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontDescMethodInfo ,
#endif
fontChooserGetFontDesc ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontFaceMethodInfo ,
#endif
fontChooserGetFontFace ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontFamilyMethodInfo ,
#endif
fontChooserGetFontFamily ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontFeaturesMethodInfo ,
#endif
fontChooserGetFontFeatures ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontMapMethodInfo ,
#endif
fontChooserGetFontMap ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetFontSizeMethodInfo ,
#endif
fontChooserGetFontSize ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetLanguageMethodInfo ,
#endif
fontChooserGetLanguage ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetLevelMethodInfo ,
#endif
fontChooserGetLevel ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetPreviewTextMethodInfo ,
#endif
fontChooserGetPreviewText ,
#if defined(ENABLE_OVERLOADING)
FontChooserGetShowPreviewEntryMethodInfo,
#endif
fontChooserGetShowPreviewEntry ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetFilterFuncMethodInfo ,
#endif
fontChooserSetFilterFunc ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetFontMethodInfo ,
#endif
fontChooserSetFont ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetFontDescMethodInfo ,
#endif
fontChooserSetFontDesc ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetFontMapMethodInfo ,
#endif
fontChooserSetFontMap ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetLanguageMethodInfo ,
#endif
fontChooserSetLanguage ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetLevelMethodInfo ,
#endif
fontChooserSetLevel ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetPreviewTextMethodInfo ,
#endif
fontChooserSetPreviewText ,
#if defined(ENABLE_OVERLOADING)
FontChooserSetShowPreviewEntryMethodInfo,
#endif
fontChooserSetShowPreviewEntry ,
#if defined(ENABLE_OVERLOADING)
FontChooserFontPropertyInfo ,
#endif
constructFontChooserFont ,
#if defined(ENABLE_OVERLOADING)
fontChooserFont ,
#endif
getFontChooserFont ,
setFontChooserFont ,
#if defined(ENABLE_OVERLOADING)
FontChooserFontDescPropertyInfo ,
#endif
constructFontChooserFontDesc ,
#if defined(ENABLE_OVERLOADING)
fontChooserFontDesc ,
#endif
getFontChooserFontDesc ,
setFontChooserFontDesc ,
#if defined(ENABLE_OVERLOADING)
FontChooserFontFeaturesPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
fontChooserFontFeatures ,
#endif
getFontChooserFontFeatures ,
#if defined(ENABLE_OVERLOADING)
FontChooserLanguagePropertyInfo ,
#endif
constructFontChooserLanguage ,
#if defined(ENABLE_OVERLOADING)
fontChooserLanguage ,
#endif
getFontChooserLanguage ,
setFontChooserLanguage ,
#if defined(ENABLE_OVERLOADING)
FontChooserLevelPropertyInfo ,
#endif
constructFontChooserLevel ,
#if defined(ENABLE_OVERLOADING)
fontChooserLevel ,
#endif
getFontChooserLevel ,
setFontChooserLevel ,
#if defined(ENABLE_OVERLOADING)
FontChooserPreviewTextPropertyInfo ,
#endif
constructFontChooserPreviewText ,
#if defined(ENABLE_OVERLOADING)
fontChooserPreviewText ,
#endif
getFontChooserPreviewText ,
setFontChooserPreviewText ,
#if defined(ENABLE_OVERLOADING)
FontChooserShowPreviewEntryPropertyInfo ,
#endif
constructFontChooserShowPreviewEntry ,
#if defined(ENABLE_OVERLOADING)
fontChooserShowPreviewEntry ,
#endif
getFontChooserShowPreviewEntry ,
setFontChooserShowPreviewEntry ,
FontChooserFontActivatedCallback ,
#if defined(ENABLE_OVERLOADING)
FontChooserFontActivatedSignalInfo ,
#endif
afterFontChooserFontActivated ,
onFontChooserFontActivated ,
) 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.GHashTable as B.GHT
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.Kind as DK
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
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import qualified GI.Pango.Objects.FontFace as Pango.FontFace
import qualified GI.Pango.Objects.FontFamily as Pango.FontFamily
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
#else
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import qualified GI.Pango.Objects.FontFace as Pango.FontFace
import qualified GI.Pango.Objects.FontFamily as Pango.FontFamily
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
#endif
{-# DEPRECATED FontChooser ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
newtype FontChooser = FontChooser (SP.ManagedPtr FontChooser)
deriving (FontChooser -> FontChooser -> Bool
(FontChooser -> FontChooser -> Bool)
-> (FontChooser -> FontChooser -> Bool) -> Eq FontChooser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FontChooser -> FontChooser -> Bool
== :: FontChooser -> FontChooser -> Bool
$c/= :: FontChooser -> FontChooser -> Bool
/= :: FontChooser -> FontChooser -> Bool
Eq)
instance SP.ManagedPtrNewtype FontChooser where
toManagedPtr :: FontChooser -> ManagedPtr FontChooser
toManagedPtr (FontChooser ManagedPtr FontChooser
p) = ManagedPtr FontChooser
p
foreign import ccall "gtk_font_chooser_get_type"
c_gtk_font_chooser_get_type :: IO B.Types.GType
instance B.Types.TypedObject FontChooser where
glibType :: IO GType
glibType = IO GType
c_gtk_font_chooser_get_type
instance B.Types.GObject FontChooser
class (SP.GObject o, O.IsDescendantOf FontChooser o) => IsFontChooser o
instance (SP.GObject o, O.IsDescendantOf FontChooser o) => IsFontChooser o
instance O.HasParentTypes FontChooser
type instance O.ParentTypes FontChooser = '[GObject.Object.Object]
toFontChooser :: (MIO.MonadIO m, IsFontChooser o) => o -> m FontChooser
toFontChooser :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m FontChooser
toFontChooser = IO FontChooser -> m FontChooser
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO FontChooser -> m FontChooser)
-> (o -> IO FontChooser) -> o -> m FontChooser
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr FontChooser -> FontChooser) -> o -> IO FontChooser
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr FontChooser -> FontChooser
FontChooser
instance B.GValue.IsGValue (Maybe FontChooser) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_font_chooser_get_type
gvalueSet_ :: Ptr GValue -> Maybe FontChooser -> IO ()
gvalueSet_ Ptr GValue
gv Maybe FontChooser
P.Nothing = Ptr GValue -> Ptr FontChooser -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr FontChooser
forall a. Ptr a
FP.nullPtr :: FP.Ptr FontChooser)
gvalueSet_ Ptr GValue
gv (P.Just FontChooser
obj) = FontChooser -> (Ptr FontChooser -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FontChooser
obj (Ptr GValue -> Ptr FontChooser -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe FontChooser)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr FontChooser)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr FontChooser)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject FontChooser ptr
else return P.Nothing
getFontChooserFont :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserFont :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m (Maybe Text)
getFontChooserFont o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"font"
setFontChooserFont :: (MonadIO m, IsFontChooser o) => o -> T.Text -> m ()
setFontChooserFont :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> Text -> m ()
setFontChooserFont o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"font" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructFontChooserFont :: (IsFontChooser o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructFontChooserFont :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructFontChooserFont Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"font" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data FontChooserFontPropertyInfo
instance AttrInfo FontChooserFontPropertyInfo where
type AttrAllowedOps FontChooserFontPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserFontPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserFontPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint FontChooserFontPropertyInfo = (~) T.Text
type AttrTransferType FontChooserFontPropertyInfo = T.Text
type AttrGetType FontChooserFontPropertyInfo = (Maybe T.Text)
type AttrLabel FontChooserFontPropertyInfo = "font"
type AttrOrigin FontChooserFontPropertyInfo = FontChooser
attrGet = getFontChooserFont
attrSet = setFontChooserFont
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserFont
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.font"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:font"
})
#endif
getFontChooserFontDesc :: (MonadIO m, IsFontChooser o) => o -> m (Maybe Pango.FontDescription.FontDescription)
getFontChooserFontDesc :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m (Maybe FontDescription)
getFontChooserFontDesc o
obj = IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe FontDescription) -> m (Maybe FontDescription))
-> IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr FontDescription -> FontDescription)
-> IO (Maybe FontDescription)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"font-desc" ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription
setFontChooserFontDesc :: (MonadIO m, IsFontChooser o) => o -> Pango.FontDescription.FontDescription -> m ()
setFontChooserFontDesc :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> FontDescription -> m ()
setFontChooserFontDesc o
obj FontDescription
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe FontDescription -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"font-desc" (FontDescription -> Maybe FontDescription
forall a. a -> Maybe a
Just FontDescription
val)
constructFontChooserFontDesc :: (IsFontChooser o, MIO.MonadIO m) => Pango.FontDescription.FontDescription -> m (GValueConstruct o)
constructFontChooserFontDesc :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
FontDescription -> m (GValueConstruct o)
constructFontChooserFontDesc FontDescription
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe FontDescription -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"font-desc" (FontDescription -> Maybe FontDescription
forall a. a -> Maybe a
P.Just FontDescription
val)
#if defined(ENABLE_OVERLOADING)
data FontChooserFontDescPropertyInfo
instance AttrInfo FontChooserFontDescPropertyInfo where
type AttrAllowedOps FontChooserFontDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserFontDescPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserFontDescPropertyInfo = (~) Pango.FontDescription.FontDescription
type AttrTransferTypeConstraint FontChooserFontDescPropertyInfo = (~) Pango.FontDescription.FontDescription
type AttrTransferType FontChooserFontDescPropertyInfo = Pango.FontDescription.FontDescription
type AttrGetType FontChooserFontDescPropertyInfo = (Maybe Pango.FontDescription.FontDescription)
type AttrLabel FontChooserFontDescPropertyInfo = "font-desc"
type AttrOrigin FontChooserFontDescPropertyInfo = FontChooser
attrGet = getFontChooserFontDesc
attrSet = setFontChooserFontDesc
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserFontDesc
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontDesc"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:fontDesc"
})
#endif
getFontChooserFontFeatures :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserFontFeatures :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m (Maybe Text)
getFontChooserFontFeatures o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"font-features"
#if defined(ENABLE_OVERLOADING)
data FontChooserFontFeaturesPropertyInfo
instance AttrInfo FontChooserFontFeaturesPropertyInfo where
type AttrAllowedOps FontChooserFontFeaturesPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint FontChooserFontFeaturesPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserFontFeaturesPropertyInfo = (~) ()
type AttrTransferTypeConstraint FontChooserFontFeaturesPropertyInfo = (~) ()
type AttrTransferType FontChooserFontFeaturesPropertyInfo = ()
type AttrGetType FontChooserFontFeaturesPropertyInfo = (Maybe T.Text)
type AttrLabel FontChooserFontFeaturesPropertyInfo = "font-features"
type AttrOrigin FontChooserFontFeaturesPropertyInfo = FontChooser
attrGet = getFontChooserFontFeatures
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontFeatures"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:fontFeatures"
})
#endif
getFontChooserLanguage :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserLanguage :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m (Maybe Text)
getFontChooserLanguage o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"language"
setFontChooserLanguage :: (MonadIO m, IsFontChooser o) => o -> T.Text -> m ()
setFontChooserLanguage :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> Text -> m ()
setFontChooserLanguage o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"language" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructFontChooserLanguage :: (IsFontChooser o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructFontChooserLanguage :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructFontChooserLanguage Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"language" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data FontChooserLanguagePropertyInfo
instance AttrInfo FontChooserLanguagePropertyInfo where
type AttrAllowedOps FontChooserLanguagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserLanguagePropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserLanguagePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint FontChooserLanguagePropertyInfo = (~) T.Text
type AttrTransferType FontChooserLanguagePropertyInfo = T.Text
type AttrGetType FontChooserLanguagePropertyInfo = (Maybe T.Text)
type AttrLabel FontChooserLanguagePropertyInfo = "language"
type AttrOrigin FontChooserLanguagePropertyInfo = FontChooser
attrGet = getFontChooserLanguage
attrSet = setFontChooserLanguage
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserLanguage
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.language"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:language"
})
#endif
getFontChooserLevel :: (MonadIO m, IsFontChooser o) => o -> m [Gtk.Flags.FontChooserLevel]
getFontChooserLevel :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m [FontChooserLevel]
getFontChooserLevel o
obj = IO [FontChooserLevel] -> m [FontChooserLevel]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [FontChooserLevel] -> m [FontChooserLevel])
-> IO [FontChooserLevel] -> m [FontChooserLevel]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [FontChooserLevel]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"level"
setFontChooserLevel :: (MonadIO m, IsFontChooser o) => o -> [Gtk.Flags.FontChooserLevel] -> m ()
setFontChooserLevel :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> [FontChooserLevel] -> m ()
setFontChooserLevel o
obj [FontChooserLevel]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> [FontChooserLevel] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"level" [FontChooserLevel]
val
constructFontChooserLevel :: (IsFontChooser o, MIO.MonadIO m) => [Gtk.Flags.FontChooserLevel] -> m (GValueConstruct o)
constructFontChooserLevel :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
[FontChooserLevel] -> m (GValueConstruct o)
constructFontChooserLevel [FontChooserLevel]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [FontChooserLevel] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"level" [FontChooserLevel]
val
#if defined(ENABLE_OVERLOADING)
data FontChooserLevelPropertyInfo
instance AttrInfo FontChooserLevelPropertyInfo where
type AttrAllowedOps FontChooserLevelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserLevelPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserLevelPropertyInfo = (~) [Gtk.Flags.FontChooserLevel]
type AttrTransferTypeConstraint FontChooserLevelPropertyInfo = (~) [Gtk.Flags.FontChooserLevel]
type AttrTransferType FontChooserLevelPropertyInfo = [Gtk.Flags.FontChooserLevel]
type AttrGetType FontChooserLevelPropertyInfo = [Gtk.Flags.FontChooserLevel]
type AttrLabel FontChooserLevelPropertyInfo = "level"
type AttrOrigin FontChooserLevelPropertyInfo = FontChooser
attrGet = getFontChooserLevel
attrSet = setFontChooserLevel
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserLevel
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.level"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:level"
})
#endif
getFontChooserPreviewText :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserPreviewText :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> m (Maybe Text)
getFontChooserPreviewText o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"preview-text"
setFontChooserPreviewText :: (MonadIO m, IsFontChooser o) => o -> T.Text -> m ()
setFontChooserPreviewText :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> Text -> m ()
setFontChooserPreviewText o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"preview-text" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructFontChooserPreviewText :: (IsFontChooser o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructFontChooserPreviewText :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructFontChooserPreviewText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"preview-text" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data FontChooserPreviewTextPropertyInfo
instance AttrInfo FontChooserPreviewTextPropertyInfo where
type AttrAllowedOps FontChooserPreviewTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserPreviewTextPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserPreviewTextPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint FontChooserPreviewTextPropertyInfo = (~) T.Text
type AttrTransferType FontChooserPreviewTextPropertyInfo = T.Text
type AttrGetType FontChooserPreviewTextPropertyInfo = (Maybe T.Text)
type AttrLabel FontChooserPreviewTextPropertyInfo = "preview-text"
type AttrOrigin FontChooserPreviewTextPropertyInfo = FontChooser
attrGet = getFontChooserPreviewText
attrSet = setFontChooserPreviewText
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserPreviewText
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.previewText"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:previewText"
})
#endif
getFontChooserShowPreviewEntry :: (MonadIO m, IsFontChooser o) => o -> m Bool
getFontChooserShowPreviewEntry :: forall (m :: * -> *) o. (MonadIO m, IsFontChooser o) => o -> m Bool
getFontChooserShowPreviewEntry o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"show-preview-entry"
setFontChooserShowPreviewEntry :: (MonadIO m, IsFontChooser o) => o -> Bool -> m ()
setFontChooserShowPreviewEntry :: forall (m :: * -> *) o.
(MonadIO m, IsFontChooser o) =>
o -> Bool -> m ()
setFontChooserShowPreviewEntry o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"show-preview-entry" Bool
val
constructFontChooserShowPreviewEntry :: (IsFontChooser o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructFontChooserShowPreviewEntry :: forall o (m :: * -> *).
(IsFontChooser o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructFontChooserShowPreviewEntry Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"show-preview-entry" Bool
val
#if defined(ENABLE_OVERLOADING)
data FontChooserShowPreviewEntryPropertyInfo
instance AttrInfo FontChooserShowPreviewEntryPropertyInfo where
type AttrAllowedOps FontChooserShowPreviewEntryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint FontChooserShowPreviewEntryPropertyInfo = IsFontChooser
type AttrSetTypeConstraint FontChooserShowPreviewEntryPropertyInfo = (~) Bool
type AttrTransferTypeConstraint FontChooserShowPreviewEntryPropertyInfo = (~) Bool
type AttrTransferType FontChooserShowPreviewEntryPropertyInfo = Bool
type AttrGetType FontChooserShowPreviewEntryPropertyInfo = Bool
type AttrLabel FontChooserShowPreviewEntryPropertyInfo = "show-preview-entry"
type AttrOrigin FontChooserShowPreviewEntryPropertyInfo = FontChooser
attrGet = getFontChooserShowPreviewEntry
attrSet = setFontChooserShowPreviewEntry
attrTransfer _ v = do
return v
attrConstruct = constructFontChooserShowPreviewEntry
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.showPreviewEntry"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:attr:showPreviewEntry"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList FontChooser
type instance O.AttributeList FontChooser = FontChooserAttributeList
type FontChooserAttributeList = ('[ '("font", FontChooserFontPropertyInfo), '("fontDesc", FontChooserFontDescPropertyInfo), '("fontFeatures", FontChooserFontFeaturesPropertyInfo), '("language", FontChooserLanguagePropertyInfo), '("level", FontChooserLevelPropertyInfo), '("previewText", FontChooserPreviewTextPropertyInfo), '("showPreviewEntry", FontChooserShowPreviewEntryPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
fontChooserFont :: AttrLabelProxy "font"
fontChooserFont = AttrLabelProxy
fontChooserFontDesc :: AttrLabelProxy "fontDesc"
fontChooserFontDesc = AttrLabelProxy
fontChooserFontFeatures :: AttrLabelProxy "fontFeatures"
fontChooserFontFeatures = AttrLabelProxy
fontChooserLanguage :: AttrLabelProxy "language"
fontChooserLanguage = AttrLabelProxy
fontChooserLevel :: AttrLabelProxy "level"
fontChooserLevel = AttrLabelProxy
fontChooserPreviewText :: AttrLabelProxy "previewText"
fontChooserPreviewText = AttrLabelProxy
fontChooserShowPreviewEntry :: AttrLabelProxy "showPreviewEntry"
fontChooserShowPreviewEntry = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveFontChooserMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveFontChooserMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveFontChooserMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveFontChooserMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveFontChooserMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveFontChooserMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveFontChooserMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveFontChooserMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveFontChooserMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveFontChooserMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveFontChooserMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveFontChooserMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveFontChooserMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveFontChooserMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveFontChooserMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveFontChooserMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveFontChooserMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveFontChooserMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveFontChooserMethod "getFont" o = FontChooserGetFontMethodInfo
ResolveFontChooserMethod "getFontDesc" o = FontChooserGetFontDescMethodInfo
ResolveFontChooserMethod "getFontFace" o = FontChooserGetFontFaceMethodInfo
ResolveFontChooserMethod "getFontFamily" o = FontChooserGetFontFamilyMethodInfo
ResolveFontChooserMethod "getFontFeatures" o = FontChooserGetFontFeaturesMethodInfo
ResolveFontChooserMethod "getFontMap" o = FontChooserGetFontMapMethodInfo
ResolveFontChooserMethod "getFontSize" o = FontChooserGetFontSizeMethodInfo
ResolveFontChooserMethod "getLanguage" o = FontChooserGetLanguageMethodInfo
ResolveFontChooserMethod "getLevel" o = FontChooserGetLevelMethodInfo
ResolveFontChooserMethod "getPreviewText" o = FontChooserGetPreviewTextMethodInfo
ResolveFontChooserMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveFontChooserMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveFontChooserMethod "getShowPreviewEntry" o = FontChooserGetShowPreviewEntryMethodInfo
ResolveFontChooserMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveFontChooserMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveFontChooserMethod "setFilterFunc" o = FontChooserSetFilterFuncMethodInfo
ResolveFontChooserMethod "setFont" o = FontChooserSetFontMethodInfo
ResolveFontChooserMethod "setFontDesc" o = FontChooserSetFontDescMethodInfo
ResolveFontChooserMethod "setFontMap" o = FontChooserSetFontMapMethodInfo
ResolveFontChooserMethod "setLanguage" o = FontChooserSetLanguageMethodInfo
ResolveFontChooserMethod "setLevel" o = FontChooserSetLevelMethodInfo
ResolveFontChooserMethod "setPreviewText" o = FontChooserSetPreviewTextMethodInfo
ResolveFontChooserMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveFontChooserMethod "setShowPreviewEntry" o = FontChooserSetShowPreviewEntryMethodInfo
ResolveFontChooserMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveFontChooserMethod t FontChooser, O.OverloadedMethod info FontChooser p) => OL.IsLabel t (FontChooser -> 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 ~ ResolveFontChooserMethod t FontChooser, O.OverloadedMethod info FontChooser p, R.HasField t FontChooser p) => R.HasField t FontChooser p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveFontChooserMethod t FontChooser, O.OverloadedMethodInfo info FontChooser) => OL.IsLabel t (O.MethodProxy info FontChooser) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "gtk_font_chooser_get_font" gtk_font_chooser_get_font ::
Ptr FontChooser ->
IO CString
{-# DEPRECATED fontChooserGetFont ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFont ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m (Maybe T.Text)
fontChooserGetFont :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m (Maybe Text)
fontChooserGetFont a
fontchooser = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font fontchooser'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
freeMem result'
return result''
touchManagedPtr fontchooser
return maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontMethodInfo a signature where
overloadedMethod = fontChooserGetFont
instance O.OverloadedMethodInfo FontChooserGetFontMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFont",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFont"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_desc" gtk_font_chooser_get_font_desc ::
Ptr FontChooser ->
IO (Ptr Pango.FontDescription.FontDescription)
{-# DEPRECATED fontChooserGetFontDesc ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontDesc ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m (Maybe Pango.FontDescription.FontDescription)
fontChooserGetFontDesc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m (Maybe FontDescription)
fontChooserGetFontDesc a
fontchooser = IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontDescription) -> m (Maybe FontDescription))
-> IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_desc fontchooser'
maybeResult <- convertIfNonNull result $ \Ptr FontDescription
result' -> do
result'' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
result'
return result''
touchManagedPtr fontchooser
return maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontDescMethodInfo
instance (signature ~ (m (Maybe Pango.FontDescription.FontDescription)), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontDescMethodInfo a signature where
overloadedMethod = fontChooserGetFontDesc
instance O.OverloadedMethodInfo FontChooserGetFontDescMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontDesc",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontDesc"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_face" gtk_font_chooser_get_font_face ::
Ptr FontChooser ->
IO (Ptr Pango.FontFace.FontFace)
{-# DEPRECATED fontChooserGetFontFace ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontFace ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m (Maybe Pango.FontFace.FontFace)
fontChooserGetFontFace :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m (Maybe FontFace)
fontChooserGetFontFace a
fontchooser = IO (Maybe FontFace) -> m (Maybe FontFace)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontFace) -> m (Maybe FontFace))
-> IO (Maybe FontFace) -> m (Maybe FontFace)
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_face fontchooser'
maybeResult <- convertIfNonNull result $ \Ptr FontFace
result' -> do
result'' <- ((ManagedPtr FontFace -> FontFace) -> Ptr FontFace -> IO FontFace
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontFace -> FontFace
Pango.FontFace.FontFace) Ptr FontFace
result'
return result''
touchManagedPtr fontchooser
return maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFaceMethodInfo
instance (signature ~ (m (Maybe Pango.FontFace.FontFace)), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontFaceMethodInfo a signature where
overloadedMethod = fontChooserGetFontFace
instance O.OverloadedMethodInfo FontChooserGetFontFaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontFace",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontFace"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_family" gtk_font_chooser_get_font_family ::
Ptr FontChooser ->
IO (Ptr Pango.FontFamily.FontFamily)
{-# DEPRECATED fontChooserGetFontFamily ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontFamily ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m (Maybe Pango.FontFamily.FontFamily)
fontChooserGetFontFamily :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m (Maybe FontFamily)
fontChooserGetFontFamily a
fontchooser = IO (Maybe FontFamily) -> m (Maybe FontFamily)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontFamily) -> m (Maybe FontFamily))
-> IO (Maybe FontFamily) -> m (Maybe FontFamily)
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_family fontchooser'
maybeResult <- convertIfNonNull result $ \Ptr FontFamily
result' -> do
result'' <- ((ManagedPtr FontFamily -> FontFamily)
-> Ptr FontFamily -> IO FontFamily
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontFamily -> FontFamily
Pango.FontFamily.FontFamily) Ptr FontFamily
result'
return result''
touchManagedPtr fontchooser
return maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFamilyMethodInfo
instance (signature ~ (m (Maybe Pango.FontFamily.FontFamily)), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontFamilyMethodInfo a signature where
overloadedMethod = fontChooserGetFontFamily
instance O.OverloadedMethodInfo FontChooserGetFontFamilyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontFamily",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontFamily"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_features" gtk_font_chooser_get_font_features ::
Ptr FontChooser ->
IO CString
{-# DEPRECATED fontChooserGetFontFeatures ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontFeatures ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m T.Text
fontChooserGetFontFeatures :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m Text
fontChooserGetFontFeatures a
fontchooser = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_features fontchooser'
checkUnexpectedReturnNULL "fontChooserGetFontFeatures" result
result' <- cstringToText result
freeMem result
touchManagedPtr fontchooser
return result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFeaturesMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontFeaturesMethodInfo a signature where
overloadedMethod = fontChooserGetFontFeatures
instance O.OverloadedMethodInfo FontChooserGetFontFeaturesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontFeatures",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontFeatures"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_map" gtk_font_chooser_get_font_map ::
Ptr FontChooser ->
IO (Ptr Pango.FontMap.FontMap)
{-# DEPRECATED fontChooserGetFontMap ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontMap ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m (Maybe Pango.FontMap.FontMap)
fontChooserGetFontMap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m (Maybe FontMap)
fontChooserGetFontMap a
fontchooser = IO (Maybe FontMap) -> m (Maybe FontMap)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontMap) -> m (Maybe FontMap))
-> IO (Maybe FontMap) -> m (Maybe FontMap)
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_map fontchooser'
maybeResult <- convertIfNonNull result $ \Ptr FontMap
result' -> do
result'' <- ((ManagedPtr FontMap -> FontMap) -> Ptr FontMap -> IO FontMap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr FontMap -> FontMap
Pango.FontMap.FontMap) Ptr FontMap
result'
return result''
touchManagedPtr fontchooser
return maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontMapMethodInfo
instance (signature ~ (m (Maybe Pango.FontMap.FontMap)), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontMapMethodInfo a signature where
overloadedMethod = fontChooserGetFontMap
instance O.OverloadedMethodInfo FontChooserGetFontMapMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontMap",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontMap"
})
#endif
foreign import ccall "gtk_font_chooser_get_font_size" gtk_font_chooser_get_font_size ::
Ptr FontChooser ->
IO Int32
{-# DEPRECATED fontChooserGetFontSize ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetFontSize ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m Int32
fontChooserGetFontSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m Int32
fontChooserGetFontSize a
fontchooser = IO Int32 -> m Int32
forall a. IO a -> m a
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
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_font_size fontchooser'
touchManagedPtr fontchooser
return result
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetFontSizeMethodInfo a signature where
overloadedMethod = fontChooserGetFontSize
instance O.OverloadedMethodInfo FontChooserGetFontSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetFontSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetFontSize"
})
#endif
foreign import ccall "gtk_font_chooser_get_language" gtk_font_chooser_get_language ::
Ptr FontChooser ->
IO CString
{-# DEPRECATED fontChooserGetLanguage ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetLanguage ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m T.Text
fontChooserGetLanguage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m Text
fontChooserGetLanguage a
fontchooser = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_language fontchooser'
checkUnexpectedReturnNULL "fontChooserGetLanguage" result
result' <- cstringToText result
freeMem result
touchManagedPtr fontchooser
return result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetLanguageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetLanguageMethodInfo a signature where
overloadedMethod = fontChooserGetLanguage
instance O.OverloadedMethodInfo FontChooserGetLanguageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetLanguage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetLanguage"
})
#endif
foreign import ccall "gtk_font_chooser_get_level" gtk_font_chooser_get_level ::
Ptr FontChooser ->
IO CUInt
{-# DEPRECATED fontChooserGetLevel ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetLevel ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m [Gtk.Flags.FontChooserLevel]
fontChooserGetLevel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m [FontChooserLevel]
fontChooserGetLevel a
fontchooser = IO [FontChooserLevel] -> m [FontChooserLevel]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [FontChooserLevel] -> m [FontChooserLevel])
-> IO [FontChooserLevel] -> m [FontChooserLevel]
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_level fontchooser'
let result' = CUInt -> [FontChooserLevel]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
touchManagedPtr fontchooser
return result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetLevelMethodInfo
instance (signature ~ (m [Gtk.Flags.FontChooserLevel]), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetLevelMethodInfo a signature where
overloadedMethod = fontChooserGetLevel
instance O.OverloadedMethodInfo FontChooserGetLevelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetLevel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetLevel"
})
#endif
foreign import ccall "gtk_font_chooser_get_preview_text" gtk_font_chooser_get_preview_text ::
Ptr FontChooser ->
IO CString
{-# DEPRECATED fontChooserGetPreviewText ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetPreviewText ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m T.Text
fontChooserGetPreviewText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m Text
fontChooserGetPreviewText a
fontchooser = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_preview_text fontchooser'
checkUnexpectedReturnNULL "fontChooserGetPreviewText" result
result' <- cstringToText result
freeMem result
touchManagedPtr fontchooser
return result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetPreviewTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetPreviewTextMethodInfo a signature where
overloadedMethod = fontChooserGetPreviewText
instance O.OverloadedMethodInfo FontChooserGetPreviewTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetPreviewText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetPreviewText"
})
#endif
foreign import ccall "gtk_font_chooser_get_show_preview_entry" gtk_font_chooser_get_show_preview_entry ::
Ptr FontChooser ->
IO CInt
{-# DEPRECATED fontChooserGetShowPreviewEntry ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserGetShowPreviewEntry ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> m Bool
fontChooserGetShowPreviewEntry :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> m Bool
fontChooserGetShowPreviewEntry a
fontchooser = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
result <- gtk_font_chooser_get_show_preview_entry fontchooser'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr fontchooser
return result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetShowPreviewEntryMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserGetShowPreviewEntryMethodInfo a signature where
overloadedMethod = fontChooserGetShowPreviewEntry
instance O.OverloadedMethodInfo FontChooserGetShowPreviewEntryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserGetShowPreviewEntry",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserGetShowPreviewEntry"
})
#endif
foreign import ccall "gtk_font_chooser_set_filter_func" gtk_font_chooser_set_filter_func ::
Ptr FontChooser ->
FunPtr Gtk.Callbacks.C_FontFilterFunc ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
{-# DEPRECATED fontChooserSetFilterFunc ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetFilterFunc ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> Maybe (Gtk.Callbacks.FontFilterFunc)
-> m ()
fontChooserSetFilterFunc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> Maybe FontFilterFunc -> m ()
fontChooserSetFilterFunc a
fontchooser Maybe FontFilterFunc
filter = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
maybeFilter <- case filter of
Maybe FontFilterFunc
Nothing -> FunPtr C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_FontFilterFunc
forall a. FunPtr a
FP.nullFunPtr
Just FontFilterFunc
jFilter -> do
jFilter' <- C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc)
Gtk.Callbacks.mk_FontFilterFunc (Maybe (Ptr (FunPtr C_FontFilterFunc))
-> FontFilterFunc_WithClosures -> C_FontFilterFunc
Gtk.Callbacks.wrap_FontFilterFunc Maybe (Ptr (FunPtr C_FontFilterFunc))
forall a. Maybe a
Nothing (FontFilterFunc -> FontFilterFunc_WithClosures
Gtk.Callbacks.drop_closures_FontFilterFunc FontFilterFunc
jFilter))
return jFilter'
let userData = FunPtr C_FontFilterFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_FontFilterFunc
maybeFilter
let destroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
SP.safeFreeFunPtrPtr
gtk_font_chooser_set_filter_func fontchooser' maybeFilter userData destroy
touchManagedPtr fontchooser
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFilterFuncMethodInfo
instance (signature ~ (Maybe (Gtk.Callbacks.FontFilterFunc) -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetFilterFuncMethodInfo a signature where
overloadedMethod = fontChooserSetFilterFunc
instance O.OverloadedMethodInfo FontChooserSetFilterFuncMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetFilterFunc",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetFilterFunc"
})
#endif
foreign import ccall "gtk_font_chooser_set_font" gtk_font_chooser_set_font ::
Ptr FontChooser ->
CString ->
IO ()
{-# DEPRECATED fontChooserSetFont ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetFont ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> T.Text
-> m ()
fontChooserSetFont :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> Text -> m ()
fontChooserSetFont a
fontchooser Text
fontname = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
fontname' <- textToCString fontname
gtk_font_chooser_set_font fontchooser' fontname'
touchManagedPtr fontchooser
freeMem fontname'
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetFontMethodInfo a signature where
overloadedMethod = fontChooserSetFont
instance O.OverloadedMethodInfo FontChooserSetFontMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetFont",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetFont"
})
#endif
foreign import ccall "gtk_font_chooser_set_font_desc" gtk_font_chooser_set_font_desc ::
Ptr FontChooser ->
Ptr Pango.FontDescription.FontDescription ->
IO ()
{-# DEPRECATED fontChooserSetFontDesc ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetFontDesc ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> Pango.FontDescription.FontDescription
-> m ()
fontChooserSetFontDesc :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> FontDescription -> m ()
fontChooserSetFontDesc a
fontchooser FontDescription
fontDesc = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
fontDesc' <- unsafeManagedPtrGetPtr fontDesc
gtk_font_chooser_set_font_desc fontchooser' fontDesc'
touchManagedPtr fontchooser
touchManagedPtr fontDesc
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontDescMethodInfo
instance (signature ~ (Pango.FontDescription.FontDescription -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetFontDescMethodInfo a signature where
overloadedMethod = fontChooserSetFontDesc
instance O.OverloadedMethodInfo FontChooserSetFontDescMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetFontDesc",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetFontDesc"
})
#endif
foreign import ccall "gtk_font_chooser_set_font_map" gtk_font_chooser_set_font_map ::
Ptr FontChooser ->
Ptr Pango.FontMap.FontMap ->
IO ()
{-# DEPRECATED fontChooserSetFontMap ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetFontMap ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a, Pango.FontMap.IsFontMap b) =>
a
-> Maybe (b)
-> m ()
fontChooserSetFontMap :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsFontChooser a, IsFontMap b) =>
a -> Maybe b -> m ()
fontChooserSetFontMap a
fontchooser Maybe b
fontmap = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
maybeFontmap <- case fontmap of
Maybe b
Nothing -> Ptr FontMap -> IO (Ptr FontMap)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FontMap
forall a. Ptr a
FP.nullPtr
Just b
jFontmap -> do
jFontmap' <- b -> IO (Ptr FontMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFontmap
return jFontmap'
gtk_font_chooser_set_font_map fontchooser' maybeFontmap
touchManagedPtr fontchooser
whenJust fontmap touchManagedPtr
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontMapMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsFontChooser a, Pango.FontMap.IsFontMap b) => O.OverloadedMethod FontChooserSetFontMapMethodInfo a signature where
overloadedMethod = fontChooserSetFontMap
instance O.OverloadedMethodInfo FontChooserSetFontMapMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetFontMap",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetFontMap"
})
#endif
foreign import ccall "gtk_font_chooser_set_language" gtk_font_chooser_set_language ::
Ptr FontChooser ->
CString ->
IO ()
{-# DEPRECATED fontChooserSetLanguage ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetLanguage ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> T.Text
-> m ()
fontChooserSetLanguage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> Text -> m ()
fontChooserSetLanguage a
fontchooser Text
language = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
language' <- textToCString language
gtk_font_chooser_set_language fontchooser' language'
touchManagedPtr fontchooser
freeMem language'
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetLanguageMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetLanguageMethodInfo a signature where
overloadedMethod = fontChooserSetLanguage
instance O.OverloadedMethodInfo FontChooserSetLanguageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetLanguage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetLanguage"
})
#endif
foreign import ccall "gtk_font_chooser_set_level" gtk_font_chooser_set_level ::
Ptr FontChooser ->
CUInt ->
IO ()
{-# DEPRECATED fontChooserSetLevel ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetLevel ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> [Gtk.Flags.FontChooserLevel]
-> m ()
fontChooserSetLevel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> [FontChooserLevel] -> m ()
fontChooserSetLevel a
fontchooser [FontChooserLevel]
level = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
let level' = [FontChooserLevel] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [FontChooserLevel]
level
gtk_font_chooser_set_level fontchooser' level'
touchManagedPtr fontchooser
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetLevelMethodInfo
instance (signature ~ ([Gtk.Flags.FontChooserLevel] -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetLevelMethodInfo a signature where
overloadedMethod = fontChooserSetLevel
instance O.OverloadedMethodInfo FontChooserSetLevelMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetLevel",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetLevel"
})
#endif
foreign import ccall "gtk_font_chooser_set_preview_text" gtk_font_chooser_set_preview_text ::
Ptr FontChooser ->
CString ->
IO ()
{-# DEPRECATED fontChooserSetPreviewText ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetPreviewText ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> T.Text
-> m ()
fontChooserSetPreviewText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> Text -> m ()
fontChooserSetPreviewText a
fontchooser Text
text = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
text' <- textToCString text
gtk_font_chooser_set_preview_text fontchooser' text'
touchManagedPtr fontchooser
freeMem text'
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetPreviewTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetPreviewTextMethodInfo a signature where
overloadedMethod = fontChooserSetPreviewText
instance O.OverloadedMethodInfo FontChooserSetPreviewTextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetPreviewText",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetPreviewText"
})
#endif
foreign import ccall "gtk_font_chooser_set_show_preview_entry" gtk_font_chooser_set_show_preview_entry ::
Ptr FontChooser ->
CInt ->
IO ()
{-# DEPRECATED fontChooserSetShowPreviewEntry ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton'","instead"] #-}
fontChooserSetShowPreviewEntry ::
(B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
a
-> Bool
-> m ()
fontChooserSetShowPreviewEntry :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsFontChooser a) =>
a -> Bool -> m ()
fontChooserSetShowPreviewEntry a
fontchooser Bool
showPreviewEntry = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
let showPreviewEntry' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
showPreviewEntry
gtk_font_chooser_set_show_preview_entry fontchooser' showPreviewEntry'
touchManagedPtr fontchooser
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetShowPreviewEntryMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFontChooser a) => O.OverloadedMethod FontChooserSetShowPreviewEntryMethodInfo a signature where
overloadedMethod = fontChooserSetShowPreviewEntry
instance O.OverloadedMethodInfo FontChooserSetShowPreviewEntryMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser.fontChooserSetShowPreviewEntry",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#v:fontChooserSetShowPreviewEntry"
})
#endif
{-# DEPRECATED FontChooserFontActivatedCallback ["(Since version 4.10)","Use t'GI.Gtk.Objects.FontDialog.FontDialog' and t'GI.Gtk.Objects.FontDialogButton.FontDialogButton' instead"] #-}
type FontChooserFontActivatedCallback =
T.Text
-> IO ()
type C_FontChooserFontActivatedCallback =
Ptr FontChooser ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_FontChooserFontActivatedCallback :: C_FontChooserFontActivatedCallback -> IO (FunPtr C_FontChooserFontActivatedCallback)
wrap_FontChooserFontActivatedCallback ::
GObject a => (a -> FontChooserFontActivatedCallback) ->
C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback :: forall a.
GObject a =>
(a -> FontChooserFontActivatedCallback)
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback a -> FontChooserFontActivatedCallback
gi'cb Ptr FontChooser
gi'selfPtr CString
fontname Ptr ()
_ = do
fontname' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
fontname
B.ManagedPtr.withNewObject gi'selfPtr $ \FontChooser
gi'self -> a -> FontChooserFontActivatedCallback
gi'cb (FontChooser -> a
forall a b. Coercible a b => a -> b
Coerce.coerce FontChooser
gi'self) Text
fontname'
onFontChooserFontActivated :: (IsFontChooser a, MonadIO m) => a -> ((?self :: a) => FontChooserFontActivatedCallback) -> m SignalHandlerId
onFontChooserFontActivated :: forall a (m :: * -> *).
(IsFontChooser a, MonadIO m) =>
a
-> ((?self::a) => FontChooserFontActivatedCallback)
-> m SignalHandlerId
onFontChooserFontActivated a
obj (?self::a) => FontChooserFontActivatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FontChooserFontActivatedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FontChooserFontActivatedCallback
FontChooserFontActivatedCallback
cb
let wrapped' :: C_FontChooserFontActivatedCallback
wrapped' = (a -> FontChooserFontActivatedCallback)
-> C_FontChooserFontActivatedCallback
forall a.
GObject a =>
(a -> FontChooserFontActivatedCallback)
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback a -> FontChooserFontActivatedCallback
wrapped
wrapped'' <- C_FontChooserFontActivatedCallback
-> IO (FunPtr C_FontChooserFontActivatedCallback)
mk_FontChooserFontActivatedCallback C_FontChooserFontActivatedCallback
wrapped'
connectSignalFunPtr obj "font-activated" wrapped'' SignalConnectBefore Nothing
afterFontChooserFontActivated :: (IsFontChooser a, MonadIO m) => a -> ((?self :: a) => FontChooserFontActivatedCallback) -> m SignalHandlerId
afterFontChooserFontActivated :: forall a (m :: * -> *).
(IsFontChooser a, MonadIO m) =>
a
-> ((?self::a) => FontChooserFontActivatedCallback)
-> m SignalHandlerId
afterFontChooserFontActivated a
obj (?self::a) => FontChooserFontActivatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> FontChooserFontActivatedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => FontChooserFontActivatedCallback
FontChooserFontActivatedCallback
cb
let wrapped' :: C_FontChooserFontActivatedCallback
wrapped' = (a -> FontChooserFontActivatedCallback)
-> C_FontChooserFontActivatedCallback
forall a.
GObject a =>
(a -> FontChooserFontActivatedCallback)
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback a -> FontChooserFontActivatedCallback
wrapped
wrapped'' <- C_FontChooserFontActivatedCallback
-> IO (FunPtr C_FontChooserFontActivatedCallback)
mk_FontChooserFontActivatedCallback C_FontChooserFontActivatedCallback
wrapped'
connectSignalFunPtr obj "font-activated" wrapped'' SignalConnectAfter Nothing
#if defined(ENABLE_OVERLOADING)
data FontChooserFontActivatedSignalInfo
instance SignalInfo FontChooserFontActivatedSignalInfo where
type HaskellCallbackType FontChooserFontActivatedSignalInfo = FontChooserFontActivatedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_FontChooserFontActivatedCallback cb
cb'' <- mk_FontChooserFontActivatedCallback cb'
connectSignalFunPtr obj "font-activated" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Interfaces.FontChooser::font-activated"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Interfaces-FontChooser.html#g:signal:fontActivated"})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FontChooser = FontChooserSignalList
type FontChooserSignalList = ('[ '("fontActivated", FontChooserFontActivatedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif