module GI.Gtk.Interfaces.FontChooser
(
FontChooser(..) ,
noFontChooser ,
FontChooserK ,
toFontChooser ,
fontChooserGetFont ,
fontChooserGetFontDesc ,
fontChooserGetFontFace ,
fontChooserGetFontFamily ,
fontChooserGetFontSize ,
fontChooserGetPreviewText ,
fontChooserGetShowPreviewEntry ,
fontChooserSetFilterFunc ,
fontChooserSetFont ,
fontChooserSetFontDesc ,
fontChooserSetPreviewText ,
fontChooserSetShowPreviewEntry ,
FontChooserFontPropertyInfo ,
constructFontChooserFont ,
getFontChooserFont ,
setFontChooserFont ,
FontChooserFontDescPropertyInfo ,
constructFontChooserFontDesc ,
getFontChooserFontDesc ,
setFontChooserFontDesc ,
FontChooserPreviewTextPropertyInfo ,
constructFontChooserPreviewText ,
getFontChooserPreviewText ,
setFontChooserPreviewText ,
FontChooserShowPreviewEntryPropertyInfo ,
constructFontChooserShowPreviewEntry ,
getFontChooserShowPreviewEntry ,
setFontChooserShowPreviewEntry ,
FontChooserFontActivatedCallback ,
FontChooserFontActivatedCallbackC ,
FontChooserFontActivatedSignalInfo ,
afterFontChooserFontActivated ,
fontChooserFontActivatedCallbackWrapper ,
fontChooserFontActivatedClosure ,
mkFontChooserFontActivatedCallback ,
noFontChooserFontActivatedCallback ,
onFontChooserFontActivated ,
) where
import Prelude ()
import Data.GI.Base.ShortPrelude
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import GI.Gtk.Types
import GI.Gtk.Callbacks
import qualified GI.GLib as GLib
import qualified GI.GObject as GObject
import qualified GI.Pango as Pango
newtype FontChooser = FontChooser (ForeignPtr FontChooser)
noFontChooser :: Maybe FontChooser
noFontChooser = Nothing
type FontChooserFontActivatedCallback =
T.Text ->
IO ()
noFontChooserFontActivatedCallback :: Maybe FontChooserFontActivatedCallback
noFontChooserFontActivatedCallback = Nothing
type FontChooserFontActivatedCallbackC =
Ptr () ->
CString ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mkFontChooserFontActivatedCallback :: FontChooserFontActivatedCallbackC -> IO (FunPtr FontChooserFontActivatedCallbackC)
fontChooserFontActivatedClosure :: FontChooserFontActivatedCallback -> IO Closure
fontChooserFontActivatedClosure cb = newCClosure =<< mkFontChooserFontActivatedCallback wrapped
where wrapped = fontChooserFontActivatedCallbackWrapper cb
fontChooserFontActivatedCallbackWrapper ::
FontChooserFontActivatedCallback ->
Ptr () ->
CString ->
Ptr () ->
IO ()
fontChooserFontActivatedCallbackWrapper _cb _ fontname _ = do
fontname' <- cstringToText fontname
_cb fontname'
onFontChooserFontActivated :: (GObject a, MonadIO m) => a -> FontChooserFontActivatedCallback -> m SignalHandlerId
onFontChooserFontActivated obj cb = liftIO $ connectFontChooserFontActivated obj cb SignalConnectBefore
afterFontChooserFontActivated :: (GObject a, MonadIO m) => a -> FontChooserFontActivatedCallback -> m SignalHandlerId
afterFontChooserFontActivated obj cb = connectFontChooserFontActivated obj cb SignalConnectAfter
connectFontChooserFontActivated :: (GObject a, MonadIO m) =>
a -> FontChooserFontActivatedCallback -> SignalConnectMode -> m SignalHandlerId
connectFontChooserFontActivated obj cb after = liftIO $ do
cb' <- mkFontChooserFontActivatedCallback (fontChooserFontActivatedCallbackWrapper cb)
connectSignalFunPtr obj "font-activated" cb' after
getFontChooserFont :: (MonadIO m, FontChooserK o) => o -> m T.Text
getFontChooserFont obj = liftIO $ getObjectPropertyString obj "font"
setFontChooserFont :: (MonadIO m, FontChooserK o) => o -> T.Text -> m ()
setFontChooserFont obj val = liftIO $ setObjectPropertyString obj "font" val
constructFontChooserFont :: T.Text -> IO ([Char], GValue)
constructFontChooserFont val = constructObjectPropertyString "font" val
data FontChooserFontPropertyInfo
instance AttrInfo FontChooserFontPropertyInfo where
type AttrAllowedOps FontChooserFontPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint FontChooserFontPropertyInfo = (~) T.Text
type AttrBaseTypeConstraint FontChooserFontPropertyInfo = FontChooserK
type AttrGetType FontChooserFontPropertyInfo = T.Text
type AttrLabel FontChooserFontPropertyInfo = "FontChooser::font"
attrGet _ = getFontChooserFont
attrSet _ = setFontChooserFont
attrConstruct _ = constructFontChooserFont
getFontChooserFontDesc :: (MonadIO m, FontChooserK o) => o -> m Pango.FontDescription
getFontChooserFontDesc obj = liftIO $ getObjectPropertyBoxed obj "font-desc" Pango.FontDescription
setFontChooserFontDesc :: (MonadIO m, FontChooserK o) => o -> Pango.FontDescription -> m ()
setFontChooserFontDesc obj val = liftIO $ setObjectPropertyBoxed obj "font-desc" val
constructFontChooserFontDesc :: Pango.FontDescription -> IO ([Char], GValue)
constructFontChooserFontDesc val = constructObjectPropertyBoxed "font-desc" val
data FontChooserFontDescPropertyInfo
instance AttrInfo FontChooserFontDescPropertyInfo where
type AttrAllowedOps FontChooserFontDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint FontChooserFontDescPropertyInfo = (~) Pango.FontDescription
type AttrBaseTypeConstraint FontChooserFontDescPropertyInfo = FontChooserK
type AttrGetType FontChooserFontDescPropertyInfo = Pango.FontDescription
type AttrLabel FontChooserFontDescPropertyInfo = "FontChooser::font-desc"
attrGet _ = getFontChooserFontDesc
attrSet _ = setFontChooserFontDesc
attrConstruct _ = constructFontChooserFontDesc
getFontChooserPreviewText :: (MonadIO m, FontChooserK o) => o -> m T.Text
getFontChooserPreviewText obj = liftIO $ getObjectPropertyString obj "preview-text"
setFontChooserPreviewText :: (MonadIO m, FontChooserK o) => o -> T.Text -> m ()
setFontChooserPreviewText obj val = liftIO $ setObjectPropertyString obj "preview-text" val
constructFontChooserPreviewText :: T.Text -> IO ([Char], GValue)
constructFontChooserPreviewText val = constructObjectPropertyString "preview-text" val
data FontChooserPreviewTextPropertyInfo
instance AttrInfo FontChooserPreviewTextPropertyInfo where
type AttrAllowedOps FontChooserPreviewTextPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint FontChooserPreviewTextPropertyInfo = (~) T.Text
type AttrBaseTypeConstraint FontChooserPreviewTextPropertyInfo = FontChooserK
type AttrGetType FontChooserPreviewTextPropertyInfo = T.Text
type AttrLabel FontChooserPreviewTextPropertyInfo = "FontChooser::preview-text"
attrGet _ = getFontChooserPreviewText
attrSet _ = setFontChooserPreviewText
attrConstruct _ = constructFontChooserPreviewText
getFontChooserShowPreviewEntry :: (MonadIO m, FontChooserK o) => o -> m Bool
getFontChooserShowPreviewEntry obj = liftIO $ getObjectPropertyBool obj "show-preview-entry"
setFontChooserShowPreviewEntry :: (MonadIO m, FontChooserK o) => o -> Bool -> m ()
setFontChooserShowPreviewEntry obj val = liftIO $ setObjectPropertyBool obj "show-preview-entry" val
constructFontChooserShowPreviewEntry :: Bool -> IO ([Char], GValue)
constructFontChooserShowPreviewEntry val = constructObjectPropertyBool "show-preview-entry" val
data FontChooserShowPreviewEntryPropertyInfo
instance AttrInfo FontChooserShowPreviewEntryPropertyInfo where
type AttrAllowedOps FontChooserShowPreviewEntryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrSetTypeConstraint FontChooserShowPreviewEntryPropertyInfo = (~) Bool
type AttrBaseTypeConstraint FontChooserShowPreviewEntryPropertyInfo = FontChooserK
type AttrGetType FontChooserShowPreviewEntryPropertyInfo = Bool
type AttrLabel FontChooserShowPreviewEntryPropertyInfo = "FontChooser::show-preview-entry"
attrGet _ = getFontChooserShowPreviewEntry
attrSet _ = setFontChooserShowPreviewEntry
attrConstruct _ = constructFontChooserShowPreviewEntry
type instance AttributeList FontChooser = FontChooserAttributeList
type FontChooserAttributeList = ('[ '("font", FontChooserFontPropertyInfo), '("font-desc", FontChooserFontDescPropertyInfo), '("preview-text", FontChooserPreviewTextPropertyInfo), '("show-preview-entry", FontChooserShowPreviewEntryPropertyInfo)] :: [(Symbol, *)])
data FontChooserFontActivatedSignalInfo
instance SignalInfo FontChooserFontActivatedSignalInfo where
type HaskellCallbackType FontChooserFontActivatedSignalInfo = FontChooserFontActivatedCallback
connectSignal _ = connectFontChooserFontActivated
type instance SignalList FontChooser = FontChooserSignalList
type FontChooserSignalList = ('[ '("font-activated", FontChooserFontActivatedSignalInfo), '("notify", GObject.ObjectNotifySignalInfo), '("notify::[property]", GObjectNotifySignalInfo)] :: [(Symbol, *)])
foreign import ccall "gtk_font_chooser_get_type"
c_gtk_font_chooser_get_type :: IO GType
type instance ParentTypes FontChooser = FontChooserParentTypes
type FontChooserParentTypes = '[GObject.Object]
instance GObject FontChooser where
gobjectIsInitiallyUnowned _ = False
gobjectType _ = c_gtk_font_chooser_get_type
class GObject o => FontChooserK o
instance (GObject o, IsDescendantOf FontChooser o) => FontChooserK o
toFontChooser :: FontChooserK o => o -> IO FontChooser
toFontChooser = unsafeCastTo FontChooser
foreign import ccall "gtk_font_chooser_get_font" gtk_font_chooser_get_font ::
Ptr FontChooser ->
IO CString
fontChooserGetFont ::
(MonadIO m, FontChooserK a) =>
a ->
m T.Text
fontChooserGetFont _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_font _obj'
checkUnexpectedReturnNULL "gtk_font_chooser_get_font" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_get_font_desc" gtk_font_chooser_get_font_desc ::
Ptr FontChooser ->
IO (Ptr Pango.FontDescription)
fontChooserGetFontDesc ::
(MonadIO m, FontChooserK a) =>
a ->
m Pango.FontDescription
fontChooserGetFontDesc _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_font_desc _obj'
checkUnexpectedReturnNULL "gtk_font_chooser_get_font_desc" result
result' <- (wrapBoxed Pango.FontDescription) result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_get_font_face" gtk_font_chooser_get_font_face ::
Ptr FontChooser ->
IO (Ptr Pango.FontFace)
fontChooserGetFontFace ::
(MonadIO m, FontChooserK a) =>
a ->
m Pango.FontFace
fontChooserGetFontFace _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_font_face _obj'
checkUnexpectedReturnNULL "gtk_font_chooser_get_font_face" result
result' <- (newObject Pango.FontFace) result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_get_font_family" gtk_font_chooser_get_font_family ::
Ptr FontChooser ->
IO (Ptr Pango.FontFamily)
fontChooserGetFontFamily ::
(MonadIO m, FontChooserK a) =>
a ->
m Pango.FontFamily
fontChooserGetFontFamily _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_font_family _obj'
checkUnexpectedReturnNULL "gtk_font_chooser_get_font_family" result
result' <- (newObject Pango.FontFamily) result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_get_font_size" gtk_font_chooser_get_font_size ::
Ptr FontChooser ->
IO Int32
fontChooserGetFontSize ::
(MonadIO m, FontChooserK a) =>
a ->
m Int32
fontChooserGetFontSize _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_font_size _obj'
touchManagedPtr _obj
return result
foreign import ccall "gtk_font_chooser_get_preview_text" gtk_font_chooser_get_preview_text ::
Ptr FontChooser ->
IO CString
fontChooserGetPreviewText ::
(MonadIO m, FontChooserK a) =>
a ->
m T.Text
fontChooserGetPreviewText _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_preview_text _obj'
checkUnexpectedReturnNULL "gtk_font_chooser_get_preview_text" result
result' <- cstringToText result
freeMem result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_get_show_preview_entry" gtk_font_chooser_get_show_preview_entry ::
Ptr FontChooser ->
IO CInt
fontChooserGetShowPreviewEntry ::
(MonadIO m, FontChooserK a) =>
a ->
m Bool
fontChooserGetShowPreviewEntry _obj = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
result <- gtk_font_chooser_get_show_preview_entry _obj'
let result' = (/= 0) result
touchManagedPtr _obj
return result'
foreign import ccall "gtk_font_chooser_set_filter_func" gtk_font_chooser_set_filter_func ::
Ptr FontChooser ->
FunPtr FontFilterFuncC ->
Ptr () ->
FunPtr GLib.DestroyNotifyC ->
IO ()
fontChooserSetFilterFunc ::
(MonadIO m, FontChooserK a) =>
a ->
Maybe (FontFilterFunc) ->
m ()
fontChooserSetFilterFunc _obj filter = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
maybeFilter <- case filter of
Nothing -> return (castPtrToFunPtr nullPtr)
Just jFilter -> do
jFilter' <- mkFontFilterFunc (fontFilterFuncWrapper Nothing jFilter)
return jFilter'
let user_data = castFunPtrToPtr maybeFilter
let destroy = safeFreeFunPtrPtr
gtk_font_chooser_set_filter_func _obj' maybeFilter user_data destroy
touchManagedPtr _obj
return ()
foreign import ccall "gtk_font_chooser_set_font" gtk_font_chooser_set_font ::
Ptr FontChooser ->
CString ->
IO ()
fontChooserSetFont ::
(MonadIO m, FontChooserK a) =>
a ->
T.Text ->
m ()
fontChooserSetFont _obj fontname = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
fontname' <- textToCString fontname
gtk_font_chooser_set_font _obj' fontname'
touchManagedPtr _obj
freeMem fontname'
return ()
foreign import ccall "gtk_font_chooser_set_font_desc" gtk_font_chooser_set_font_desc ::
Ptr FontChooser ->
Ptr Pango.FontDescription ->
IO ()
fontChooserSetFontDesc ::
(MonadIO m, FontChooserK a) =>
a ->
Pango.FontDescription ->
m ()
fontChooserSetFontDesc _obj font_desc = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let font_desc' = unsafeManagedPtrGetPtr font_desc
gtk_font_chooser_set_font_desc _obj' font_desc'
touchManagedPtr _obj
touchManagedPtr font_desc
return ()
foreign import ccall "gtk_font_chooser_set_preview_text" gtk_font_chooser_set_preview_text ::
Ptr FontChooser ->
CString ->
IO ()
fontChooserSetPreviewText ::
(MonadIO m, FontChooserK a) =>
a ->
T.Text ->
m ()
fontChooserSetPreviewText _obj text = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
text' <- textToCString text
gtk_font_chooser_set_preview_text _obj' text'
touchManagedPtr _obj
freeMem text'
return ()
foreign import ccall "gtk_font_chooser_set_show_preview_entry" gtk_font_chooser_set_show_preview_entry ::
Ptr FontChooser ->
CInt ->
IO ()
fontChooserSetShowPreviewEntry ::
(MonadIO m, FontChooserK a) =>
a ->
Bool ->
m ()
fontChooserSetShowPreviewEntry _obj show_preview_entry = liftIO $ do
let _obj' = unsafeManagedPtrCastPtr _obj
let show_preview_entry' = (fromIntegral . fromEnum) show_preview_entry
gtk_font_chooser_set_show_preview_entry _obj' show_preview_entry'
touchManagedPtr _obj
return ()