{-# LANGUAGE 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          ,
 
    C_FontChooserFontActivatedCallback      ,
    FontChooserFontActivatedCallback        ,
#if defined(ENABLE_OVERLOADING)
    FontChooserFontActivatedSignalInfo      ,
#endif
    afterFontChooserFontActivated           ,
    genClosure_FontChooserFontActivated     ,
    mk_FontChooserFontActivatedCallback     ,
    noFontChooserFontActivatedCallback      ,
    onFontChooserFontActivated              ,
    wrap_FontChooserFontActivatedCallback   ,
    ) 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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.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
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
/= :: FontChooser -> FontChooser -> Bool
$c/= :: FontChooser -> FontChooser -> Bool
== :: FontChooser -> FontChooser -> Bool
$c== :: 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
instance B.GValue.IsGValue FontChooser where
    toGValue :: FontChooser -> IO GValue
toGValue FontChooser
o = do
        GType
gtype <- IO GType
c_gtk_font_chooser_get_type
        FontChooser -> (Ptr FontChooser -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr FontChooser
o (GType
-> (GValue -> Ptr FontChooser -> IO ())
-> Ptr FontChooser
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr FontChooser -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO FontChooser
fromGValue GValue
gv = do
        Ptr FontChooser
ptr <- GValue -> IO (Ptr FontChooser)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr FontChooser)
        (ManagedPtr FontChooser -> FontChooser)
-> Ptr FontChooser -> IO FontChooser
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr FontChooser -> FontChooser
FontChooser Ptr FontChooser
ptr
        
    
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 :: (MonadIO m, IsFontChooser o) => o -> m FontChooser
toFontChooser :: o -> m FontChooser
toFontChooser = IO FontChooser -> m FontChooser
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr FontChooser -> FontChooser
FontChooser
   
   
   
getFontChooserFont :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserFont :: o -> m (Maybe Text)
getFontChooserFont o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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 :: o -> Text -> m ()
setFontChooserFont o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Text -> m (GValueConstruct o)
constructFontChooserFont Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
   
   
   
getFontChooserFontDesc :: (MonadIO m, IsFontChooser o) => o -> m (Maybe Pango.FontDescription.FontDescription)
getFontChooserFontDesc :: o -> m (Maybe FontDescription)
getFontChooserFontDesc o
obj = IO (Maybe FontDescription) -> m (Maybe FontDescription)
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
$ 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 :: o -> FontDescription -> m ()
setFontChooserFontDesc o
obj FontDescription
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: FontDescription -> m (GValueConstruct o)
constructFontChooserFontDesc FontDescription
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
   
   
   
getFontChooserFontFeatures :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserFontFeatures :: o -> m (Maybe Text)
getFontChooserFontFeatures o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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
#endif
   
   
   
getFontChooserLanguage :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserLanguage :: o -> m (Maybe Text)
getFontChooserLanguage o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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 :: o -> Text -> m ()
setFontChooserLanguage o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Text -> m (GValueConstruct o)
constructFontChooserLanguage Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
   
   
   
getFontChooserLevel :: (MonadIO m, IsFontChooser o) => o -> m [Gtk.Flags.FontChooserLevel]
getFontChooserLevel :: o -> m [FontChooserLevel]
getFontChooserLevel o
obj = IO [FontChooserLevel] -> m [FontChooserLevel]
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
$ 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 :: o -> [FontChooserLevel] -> m ()
setFontChooserLevel o
obj [FontChooserLevel]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: [FontChooserLevel] -> m (GValueConstruct o)
constructFontChooserLevel [FontChooserLevel]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
   
   
   
getFontChooserPreviewText :: (MonadIO m, IsFontChooser o) => o -> m (Maybe T.Text)
getFontChooserPreviewText :: o -> m (Maybe Text)
getFontChooserPreviewText o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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 :: o -> Text -> m ()
setFontChooserPreviewText o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Text -> m (GValueConstruct o)
constructFontChooserPreviewText Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#endif
   
   
   
getFontChooserShowPreviewEntry :: (MonadIO m, IsFontChooser o) => o -> m Bool
getFontChooserShowPreviewEntry :: o -> m Bool
getFontChooserShowPreviewEntry o
obj = IO Bool -> m Bool
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
$ 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 :: o -> Bool -> m ()
setFontChooserShowPreviewEntry o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ 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 :: Bool -> m (GValueConstruct o)
constructFontChooserShowPreviewEntry Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
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
$ 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
#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, *)])
#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 :: *) :: * 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.MethodInfo 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
#endif
foreign import ccall "gtk_font_chooser_get_font" gtk_font_chooser_get_font :: 
    Ptr FontChooser ->                      
    IO CString
fontChooserGetFont ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m (Maybe T.Text)
    
    
    
fontChooserGetFont :: a -> m (Maybe Text)
fontChooserGetFont a
fontchooser = IO (Maybe Text) -> m (Maybe Text)
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
result <- Ptr FontChooser -> IO CString
gtk_font_chooser_get_font Ptr FontChooser
fontchooser'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontMethodInfo a signature where
    overloadedMethod = fontChooserGetFont
#endif
foreign import ccall "gtk_font_chooser_get_font_desc" gtk_font_chooser_get_font_desc :: 
    Ptr FontChooser ->                      
    IO (Ptr Pango.FontDescription.FontDescription)
fontChooserGetFontDesc ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m (Maybe Pango.FontDescription.FontDescription)
    
    
fontChooserGetFontDesc :: a -> m (Maybe FontDescription)
fontChooserGetFontDesc a
fontchooser = IO (Maybe FontDescription) -> m (Maybe FontDescription)
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontDescription
result <- Ptr FontChooser -> IO (Ptr FontDescription)
gtk_font_chooser_get_font_desc Ptr FontChooser
fontchooser'
    Maybe FontDescription
maybeResult <- Ptr FontDescription
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontDescription
result ((Ptr FontDescription -> IO FontDescription)
 -> IO (Maybe FontDescription))
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ \Ptr FontDescription
result' -> do
        FontDescription
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'
        FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe FontDescription -> IO (Maybe FontDescription)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontDescription
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontDescMethodInfo
instance (signature ~ (m (Maybe Pango.FontDescription.FontDescription)), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontDescMethodInfo a signature where
    overloadedMethod = fontChooserGetFontDesc
#endif
foreign import ccall "gtk_font_chooser_get_font_face" gtk_font_chooser_get_font_face :: 
    Ptr FontChooser ->                      
    IO (Ptr Pango.FontFace.FontFace)
fontChooserGetFontFace ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m (Maybe Pango.FontFace.FontFace)
    
    
    
fontChooserGetFontFace :: a -> m (Maybe FontFace)
fontChooserGetFontFace a
fontchooser = IO (Maybe FontFace) -> m (Maybe FontFace)
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontFace
result <- Ptr FontChooser -> IO (Ptr FontFace)
gtk_font_chooser_get_font_face Ptr FontChooser
fontchooser'
    Maybe FontFace
maybeResult <- Ptr FontFace
-> (Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontFace
result ((Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace))
-> (Ptr FontFace -> IO FontFace) -> IO (Maybe FontFace)
forall a b. (a -> b) -> a -> b
$ \Ptr FontFace
result' -> do
        FontFace
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'
        FontFace -> IO FontFace
forall (m :: * -> *) a. Monad m => a -> m a
return FontFace
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe FontFace -> IO (Maybe FontFace)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFace
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFaceMethodInfo
instance (signature ~ (m (Maybe Pango.FontFace.FontFace)), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontFaceMethodInfo a signature where
    overloadedMethod = fontChooserGetFontFace
#endif
foreign import ccall "gtk_font_chooser_get_font_family" gtk_font_chooser_get_font_family :: 
    Ptr FontChooser ->                      
    IO (Ptr Pango.FontFamily.FontFamily)
fontChooserGetFontFamily ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m (Maybe Pango.FontFamily.FontFamily)
    
    
    
fontChooserGetFontFamily :: a -> m (Maybe FontFamily)
fontChooserGetFontFamily a
fontchooser = IO (Maybe FontFamily) -> m (Maybe FontFamily)
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontFamily
result <- Ptr FontChooser -> IO (Ptr FontFamily)
gtk_font_chooser_get_font_family Ptr FontChooser
fontchooser'
    Maybe FontFamily
maybeResult <- Ptr FontFamily
-> (Ptr FontFamily -> IO FontFamily) -> IO (Maybe FontFamily)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontFamily
result ((Ptr FontFamily -> IO FontFamily) -> IO (Maybe FontFamily))
-> (Ptr FontFamily -> IO FontFamily) -> IO (Maybe FontFamily)
forall a b. (a -> b) -> a -> b
$ \Ptr FontFamily
result' -> do
        FontFamily
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'
        FontFamily -> IO FontFamily
forall (m :: * -> *) a. Monad m => a -> m a
return FontFamily
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe FontFamily -> IO (Maybe FontFamily)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontFamily
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFamilyMethodInfo
instance (signature ~ (m (Maybe Pango.FontFamily.FontFamily)), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontFamilyMethodInfo a signature where
    overloadedMethod = fontChooserGetFontFamily
#endif
foreign import ccall "gtk_font_chooser_get_font_features" gtk_font_chooser_get_font_features :: 
    Ptr FontChooser ->                      
    IO CString
fontChooserGetFontFeatures ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m T.Text
    
fontChooserGetFontFeatures :: a -> m Text
fontChooserGetFontFeatures a
fontchooser = IO Text -> m Text
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
result <- Ptr FontChooser -> IO CString
gtk_font_chooser_get_font_features Ptr FontChooser
fontchooser'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fontChooserGetFontFeatures" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontFeaturesMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontFeaturesMethodInfo a signature where
    overloadedMethod = fontChooserGetFontFeatures
#endif
foreign import ccall "gtk_font_chooser_get_font_map" gtk_font_chooser_get_font_map :: 
    Ptr FontChooser ->                      
    IO (Ptr Pango.FontMap.FontMap)
fontChooserGetFontMap ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m (Maybe Pango.FontMap.FontMap)
    
fontChooserGetFontMap :: a -> m (Maybe FontMap)
fontChooserGetFontMap a
fontchooser = IO (Maybe FontMap) -> m (Maybe FontMap)
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontMap
result <- Ptr FontChooser -> IO (Ptr FontMap)
gtk_font_chooser_get_font_map Ptr FontChooser
fontchooser'
    Maybe FontMap
maybeResult <- Ptr FontMap -> (Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontMap
result ((Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap))
-> (Ptr FontMap -> IO FontMap) -> IO (Maybe FontMap)
forall a b. (a -> b) -> a -> b
$ \Ptr FontMap
result' -> do
        FontMap
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'
        FontMap -> IO FontMap
forall (m :: * -> *) a. Monad m => a -> m a
return FontMap
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe FontMap -> IO (Maybe FontMap)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontMap
maybeResult
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontMapMethodInfo
instance (signature ~ (m (Maybe Pango.FontMap.FontMap)), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontMapMethodInfo a signature where
    overloadedMethod = fontChooserGetFontMap
#endif
foreign import ccall "gtk_font_chooser_get_font_size" gtk_font_chooser_get_font_size :: 
    Ptr FontChooser ->                      
    IO Int32
fontChooserGetFontSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m Int32
    
    
fontChooserGetFontSize :: a -> m Int32
fontChooserGetFontSize a
fontchooser = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Int32
result <- Ptr FontChooser -> IO Int32
gtk_font_chooser_get_font_size Ptr FontChooser
fontchooser'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data FontChooserGetFontSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetFontSizeMethodInfo a signature where
    overloadedMethod = fontChooserGetFontSize
#endif
foreign import ccall "gtk_font_chooser_get_language" gtk_font_chooser_get_language :: 
    Ptr FontChooser ->                      
    IO CString
fontChooserGetLanguage ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m T.Text
    
fontChooserGetLanguage :: a -> m Text
fontChooserGetLanguage a
fontchooser = IO Text -> m Text
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
result <- Ptr FontChooser -> IO CString
gtk_font_chooser_get_language Ptr FontChooser
fontchooser'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fontChooserGetLanguage" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetLanguageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetLanguageMethodInfo a signature where
    overloadedMethod = fontChooserGetLanguage
#endif
foreign import ccall "gtk_font_chooser_get_level" gtk_font_chooser_get_level :: 
    Ptr FontChooser ->                      
    IO CUInt
fontChooserGetLevel ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m [Gtk.Flags.FontChooserLevel]
    
fontChooserGetLevel :: a -> m [FontChooserLevel]
fontChooserGetLevel a
fontchooser = IO [FontChooserLevel] -> m [FontChooserLevel]
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CUInt
result <- Ptr FontChooser -> IO CUInt
gtk_font_chooser_get_level Ptr FontChooser
fontchooser'
    let result' :: [FontChooserLevel]
result' = CUInt -> [FontChooserLevel]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    [FontChooserLevel] -> IO [FontChooserLevel]
forall (m :: * -> *) a. Monad m => a -> m a
return [FontChooserLevel]
result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetLevelMethodInfo
instance (signature ~ (m [Gtk.Flags.FontChooserLevel]), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetLevelMethodInfo a signature where
    overloadedMethod = fontChooserGetLevel
#endif
foreign import ccall "gtk_font_chooser_get_preview_text" gtk_font_chooser_get_preview_text :: 
    Ptr FontChooser ->                      
    IO CString
fontChooserGetPreviewText ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m T.Text
    
    
fontChooserGetPreviewText :: a -> m Text
fontChooserGetPreviewText a
fontchooser = IO Text -> m Text
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
result <- Ptr FontChooser -> IO CString
gtk_font_chooser_get_preview_text Ptr FontChooser
fontchooser'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"fontChooserGetPreviewText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetPreviewTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetPreviewTextMethodInfo a signature where
    overloadedMethod = fontChooserGetPreviewText
#endif
foreign import ccall "gtk_font_chooser_get_show_preview_entry" gtk_font_chooser_get_show_preview_entry :: 
    Ptr FontChooser ->                      
    IO CInt
fontChooserGetShowPreviewEntry ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> m Bool
    
    
fontChooserGetShowPreviewEntry :: a -> m Bool
fontChooserGetShowPreviewEntry a
fontchooser = IO Bool -> m Bool
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
    Ptr FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CInt
result <- Ptr FontChooser -> IO CInt
gtk_font_chooser_get_show_preview_entry Ptr FontChooser
fontchooser'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data FontChooserGetShowPreviewEntryMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserGetShowPreviewEntryMethodInfo a signature where
    overloadedMethod = 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 ()
fontChooserSetFilterFunc ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> Maybe (Gtk.Callbacks.FontFilterFunc)
    
    -> m ()
fontChooserSetFilterFunc :: a -> Maybe FontFilterFunc -> m ()
fontChooserSetFilterFunc a
fontchooser Maybe FontFilterFunc
filter = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    FunPtr C_FontFilterFunc
maybeFilter <- case Maybe FontFilterFunc
filter of
        Maybe FontFilterFunc
Nothing -> FunPtr C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_FontFilterFunc
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just FontFilterFunc
jFilter -> do
            FunPtr C_FontFilterFunc
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))
            FunPtr C_FontFilterFunc -> IO (FunPtr C_FontFilterFunc)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_FontFilterFunc
jFilter'
    let userData :: Ptr ()
userData = FunPtr C_FontFilterFunc -> Ptr ()
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_FontFilterFunc
maybeFilter
    let destroy :: FunPtr (Ptr a -> IO ())
destroy = FunPtr (Ptr a -> IO ())
forall a. FunPtr (Ptr a -> IO ())
safeFreeFunPtrPtr
    Ptr FontChooser
-> FunPtr C_FontFilterFunc
-> Ptr ()
-> FunPtr C_DestroyNotify
-> IO ()
gtk_font_chooser_set_filter_func Ptr FontChooser
fontchooser' FunPtr C_FontFilterFunc
maybeFilter Ptr ()
userData FunPtr C_DestroyNotify
forall a. FunPtr (Ptr a -> IO ())
destroy
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFilterFuncMethodInfo
instance (signature ~ (Maybe (Gtk.Callbacks.FontFilterFunc) -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetFilterFuncMethodInfo a signature where
    overloadedMethod = fontChooserSetFilterFunc
#endif
foreign import ccall "gtk_font_chooser_set_font" gtk_font_chooser_set_font :: 
    Ptr FontChooser ->                      
    CString ->                              
    IO ()
fontChooserSetFont ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> T.Text
    
    -> m ()
fontChooserSetFont :: a -> Text -> m ()
fontChooserSetFont a
fontchooser Text
fontname = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
fontname' <- Text -> IO CString
textToCString Text
fontname
    Ptr FontChooser -> CString -> IO ()
gtk_font_chooser_set_font Ptr FontChooser
fontchooser' CString
fontname'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fontname'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetFontMethodInfo a signature where
    overloadedMethod = fontChooserSetFont
#endif
foreign import ccall "gtk_font_chooser_set_font_desc" gtk_font_chooser_set_font_desc :: 
    Ptr FontChooser ->                      
    Ptr Pango.FontDescription.FontDescription -> 
    IO ()
fontChooserSetFontDesc ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> Pango.FontDescription.FontDescription
    
    -> m ()
fontChooserSetFontDesc :: a -> FontDescription -> m ()
fontChooserSetFontDesc a
fontchooser FontDescription
fontDesc = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontDescription
fontDesc' <- FontDescription -> IO (Ptr FontDescription)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontDescription
fontDesc
    Ptr FontChooser -> Ptr FontDescription -> IO ()
gtk_font_chooser_set_font_desc Ptr FontChooser
fontchooser' Ptr FontDescription
fontDesc'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    FontDescription -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontDescription
fontDesc
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontDescMethodInfo
instance (signature ~ (Pango.FontDescription.FontDescription -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetFontDescMethodInfo a signature where
    overloadedMethod = fontChooserSetFontDesc
#endif
foreign import ccall "gtk_font_chooser_set_font_map" gtk_font_chooser_set_font_map :: 
    Ptr FontChooser ->                      
    Ptr Pango.FontMap.FontMap ->            
    IO ()
fontChooserSetFontMap ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a, Pango.FontMap.IsFontMap b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
fontChooserSetFontMap :: a -> Maybe b -> m ()
fontChooserSetFontMap a
fontchooser Maybe b
fontmap = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    Ptr FontMap
maybeFontmap <- case Maybe b
fontmap of
        Maybe b
Nothing -> Ptr FontMap -> IO (Ptr FontMap)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FontMap
forall a. Ptr a
nullPtr
        Just b
jFontmap -> do
            Ptr FontMap
jFontmap' <- b -> IO (Ptr FontMap)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jFontmap
            Ptr FontMap -> IO (Ptr FontMap)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FontMap
jFontmap'
    Ptr FontChooser -> Ptr FontMap -> IO ()
gtk_font_chooser_set_font_map Ptr FontChooser
fontchooser' Ptr FontMap
maybeFontmap
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
fontmap b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetFontMapMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsFontChooser a, Pango.FontMap.IsFontMap b) => O.MethodInfo FontChooserSetFontMapMethodInfo a signature where
    overloadedMethod = fontChooserSetFontMap
#endif
foreign import ccall "gtk_font_chooser_set_language" gtk_font_chooser_set_language :: 
    Ptr FontChooser ->                      
    CString ->                              
    IO ()
fontChooserSetLanguage ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> T.Text
    
    -> m ()
fontChooserSetLanguage :: a -> Text -> m ()
fontChooserSetLanguage a
fontchooser Text
language = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
language' <- Text -> IO CString
textToCString Text
language
    Ptr FontChooser -> CString -> IO ()
gtk_font_chooser_set_language Ptr FontChooser
fontchooser' CString
language'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
language'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetLanguageMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetLanguageMethodInfo a signature where
    overloadedMethod = fontChooserSetLanguage
#endif
foreign import ccall "gtk_font_chooser_set_level" gtk_font_chooser_set_level :: 
    Ptr FontChooser ->                      
    CUInt ->                                
    IO ()
fontChooserSetLevel ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> [Gtk.Flags.FontChooserLevel]
    
    -> m ()
fontChooserSetLevel :: a -> [FontChooserLevel] -> m ()
fontChooserSetLevel a
fontchooser [FontChooserLevel]
level = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    let level' :: CUInt
level' = [FontChooserLevel] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [FontChooserLevel]
level
    Ptr FontChooser -> CUInt -> IO ()
gtk_font_chooser_set_level Ptr FontChooser
fontchooser' CUInt
level'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetLevelMethodInfo
instance (signature ~ ([Gtk.Flags.FontChooserLevel] -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetLevelMethodInfo a signature where
    overloadedMethod = fontChooserSetLevel
#endif
foreign import ccall "gtk_font_chooser_set_preview_text" gtk_font_chooser_set_preview_text :: 
    Ptr FontChooser ->                      
    CString ->                              
    IO ()
fontChooserSetPreviewText ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> T.Text
    
    -> m ()
fontChooserSetPreviewText :: a -> Text -> m ()
fontChooserSetPreviewText a
fontchooser Text
text = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr FontChooser -> CString -> IO ()
gtk_font_chooser_set_preview_text Ptr FontChooser
fontchooser' CString
text'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetPreviewTextMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetPreviewTextMethodInfo a signature where
    overloadedMethod = fontChooserSetPreviewText
#endif
foreign import ccall "gtk_font_chooser_set_show_preview_entry" gtk_font_chooser_set_show_preview_entry :: 
    Ptr FontChooser ->                      
    CInt ->                                 
    IO ()
fontChooserSetShowPreviewEntry ::
    (B.CallStack.HasCallStack, MonadIO m, IsFontChooser a) =>
    a
    
    -> Bool
    
    -> m ()
fontChooserSetShowPreviewEntry :: a -> Bool -> m ()
fontChooserSetShowPreviewEntry a
fontchooser Bool
showPreviewEntry = 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 FontChooser
fontchooser' <- a -> IO (Ptr FontChooser)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
fontchooser
    let showPreviewEntry' :: CInt
showPreviewEntry' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
showPreviewEntry
    Ptr FontChooser -> CInt -> IO ()
gtk_font_chooser_set_show_preview_entry Ptr FontChooser
fontchooser' CInt
showPreviewEntry'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
fontchooser
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data FontChooserSetShowPreviewEntryMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsFontChooser a) => O.MethodInfo FontChooserSetShowPreviewEntryMethodInfo a signature where
    overloadedMethod = fontChooserSetShowPreviewEntry
#endif
type FontChooserFontActivatedCallback =
    T.Text
    
    -> IO ()
noFontChooserFontActivatedCallback :: Maybe FontChooserFontActivatedCallback
noFontChooserFontActivatedCallback :: Maybe FontChooserFontActivatedCallback
noFontChooserFontActivatedCallback = Maybe FontChooserFontActivatedCallback
forall a. Maybe a
Nothing
type C_FontChooserFontActivatedCallback =
    Ptr () ->                               
    CString ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_FontChooserFontActivatedCallback :: C_FontChooserFontActivatedCallback -> IO (FunPtr C_FontChooserFontActivatedCallback)
genClosure_FontChooserFontActivated :: MonadIO m => FontChooserFontActivatedCallback -> m (GClosure C_FontChooserFontActivatedCallback)
genClosure_FontChooserFontActivated :: FontChooserFontActivatedCallback
-> m (GClosure C_FontChooserFontActivatedCallback)
genClosure_FontChooserFontActivated FontChooserFontActivatedCallback
cb = IO (GClosure C_FontChooserFontActivatedCallback)
-> m (GClosure C_FontChooserFontActivatedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FontChooserFontActivatedCallback)
 -> m (GClosure C_FontChooserFontActivatedCallback))
-> IO (GClosure C_FontChooserFontActivatedCallback)
-> m (GClosure C_FontChooserFontActivatedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_FontChooserFontActivatedCallback
cb' = FontChooserFontActivatedCallback
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback FontChooserFontActivatedCallback
cb
    C_FontChooserFontActivatedCallback
-> IO (FunPtr C_FontChooserFontActivatedCallback)
mk_FontChooserFontActivatedCallback C_FontChooserFontActivatedCallback
cb' IO (FunPtr C_FontChooserFontActivatedCallback)
-> (FunPtr C_FontChooserFontActivatedCallback
    -> IO (GClosure C_FontChooserFontActivatedCallback))
-> IO (GClosure C_FontChooserFontActivatedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FontChooserFontActivatedCallback
-> IO (GClosure C_FontChooserFontActivatedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_FontChooserFontActivatedCallback ::
    FontChooserFontActivatedCallback ->
    C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback :: FontChooserFontActivatedCallback
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback FontChooserFontActivatedCallback
_cb Ptr ()
_ CString
fontname Ptr ()
_ = do
    Text
fontname' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
fontname
    FontChooserFontActivatedCallback
_cb  Text
fontname'
onFontChooserFontActivated :: (IsFontChooser a, MonadIO m) => a -> FontChooserFontActivatedCallback -> m SignalHandlerId
onFontChooserFontActivated :: a -> FontChooserFontActivatedCallback -> m SignalHandlerId
onFontChooserFontActivated a
obj FontChooserFontActivatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_FontChooserFontActivatedCallback
cb' = FontChooserFontActivatedCallback
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback FontChooserFontActivatedCallback
cb
    FunPtr C_FontChooserFontActivatedCallback
cb'' <- C_FontChooserFontActivatedCallback
-> IO (FunPtr C_FontChooserFontActivatedCallback)
mk_FontChooserFontActivatedCallback C_FontChooserFontActivatedCallback
cb'
    a
-> Text
-> FunPtr C_FontChooserFontActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"font-activated" FunPtr C_FontChooserFontActivatedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterFontChooserFontActivated :: (IsFontChooser a, MonadIO m) => a -> FontChooserFontActivatedCallback -> m SignalHandlerId
afterFontChooserFontActivated :: a -> FontChooserFontActivatedCallback -> m SignalHandlerId
afterFontChooserFontActivated a
obj FontChooserFontActivatedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_FontChooserFontActivatedCallback
cb' = FontChooserFontActivatedCallback
-> C_FontChooserFontActivatedCallback
wrap_FontChooserFontActivatedCallback FontChooserFontActivatedCallback
cb
    FunPtr C_FontChooserFontActivatedCallback
cb'' <- C_FontChooserFontActivatedCallback
-> IO (FunPtr C_FontChooserFontActivatedCallback)
mk_FontChooserFontActivatedCallback C_FontChooserFontActivatedCallback
cb'
    a
-> Text
-> FunPtr C_FontChooserFontActivatedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"font-activated" FunPtr C_FontChooserFontActivatedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
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
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList FontChooser = FontChooserSignalList
type FontChooserSignalList = ('[ '("fontActivated", FontChooserFontActivatedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif