module Graphics.UI.Gtk.ModelView.CellRendererText (
CellRendererText,
CellRendererTextClass,
castToCellRendererText, gTypeCellRendererText,
toCellRendererText,
cellRendererTextNew,
cellRendererTextSetFixedHeightFromFont,
cellText,
cellTextMarkup,
--cellTextAttributes,
cellTextSingleParagraphMode,
cellTextBackground,
cellTextBackgroundColor,
cellTextBackgroundSet,
cellTextForeground,
cellTextForegroundColor,
cellTextForegroundSet,
cellTextEditable,
cellTextEditableSet,
cellTextFont,
cellTextFontDesc,
cellTextFamily,
cellTextFamilySet,
cellTextStyle,
cellTextStyleSet,
cellTextVariant,
cellTextVariantSet,
cellTextWeight,
cellTextWeightSet,
cellTextStretch,
cellTextStretchSet,
cellTextSize,
cellTextSizePoints,
cellTextSizeSet,
cellTextScale,
cellTextScaleSet,
cellTextRise,
cellTextRiseSet,
cellTextStrikethrough,
cellTextStrikethroughSet,
cellTextUnderline,
cellTextUnderlineSet,
cellTextLanguage,
cellTextLanguageSet,
cellTextEllipsize,
cellTextEllipsizeSet,
cellTextWidthChars,
cellTextWrapMode,
cellTextWrapWidth,
cellTextAlignment,
edited,
onEdited,
afterEdited
) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.Properties
import System.Glib.Attributes (Attr, WriteAttr)
import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.UI.Gtk.ModelView.Types
import Graphics.UI.Gtk.General.Structs (Color(..))
import Graphics.Rendering.Pango.Enums
import Graphics.Rendering.Pango.BasicTypes ( FontDescription(..),
makeNewFontDescription )
import Graphics.Rendering.Pango.Layout ( LayoutAlignment, LayoutWrapMode )
cellRendererTextNew :: IO CellRendererText
cellRendererTextNew =
makeNewObject mkCellRendererText $
liftM (castPtr :: Ptr CellRenderer -> Ptr CellRendererText) $
gtk_cell_renderer_text_new
cellRendererTextSetFixedHeightFromFont :: CellRendererTextClass self => self
-> Int
-> IO ()
cellRendererTextSetFixedHeightFromFont self numberOfRows =
(\(CellRendererText arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_cell_renderer_text_set_fixed_height_from_font argPtr1 arg2)
(toCellRendererText self)
(fromIntegral numberOfRows)
cellTextBackground :: CellRendererClass self => WriteAttr self String
cellTextBackground = writeAttrFromStringProperty "background"
cellTextBackgroundColor :: CellRendererClass self => Attr self Color
cellTextBackgroundColor = newAttrFromBoxedStorableProperty "background-gdk"
gdk_color_get_type
cellTextBackgroundSet :: CellRendererClass self => Attr self Bool
cellTextBackgroundSet = newAttrFromBoolProperty "background-set"
cellTextEditable :: CellRendererTextClass self => Attr self Bool
cellTextEditable = newAttrFromBoolProperty "editable"
cellTextEditableSet :: CellRendererTextClass self => Attr self Bool
cellTextEditableSet = newAttrFromBoolProperty "editable-set"
cellTextEllipsize :: CellRendererTextClass self => Attr self EllipsizeMode
cellTextEllipsize = newAttrFromEnumProperty "ellipsize"
pango_ellipsize_mode_get_type
cellTextEllipsizeSet :: CellRendererTextClass self => Attr self Bool
cellTextEllipsizeSet = newAttrFromBoolProperty "ellipsize-set"
cellTextFamily :: CellRendererTextClass self => Attr self String
cellTextFamily = newAttrFromStringProperty "family"
cellTextFamilySet :: CellRendererTextClass self => Attr self Bool
cellTextFamilySet = newAttrFromBoolProperty "family-set"
cellTextFont :: CellRendererTextClass self => Attr self String
cellTextFont = newAttrFromStringProperty "font"
cellTextFontDesc :: CellRendererTextClass self => Attr self FontDescription
cellTextFontDesc = newAttrFromBoxedOpaqueProperty makeNewFontDescription
(\(FontDescription fd) act -> withForeignPtr fd act) "font-desc"
pango_font_description_get_type
cellTextForeground :: CellRendererClass self => WriteAttr self String
cellTextForeground = writeAttrFromStringProperty "foreground"
cellTextForegroundColor :: CellRendererClass self => Attr self Color
cellTextForegroundColor = newAttrFromBoxedStorableProperty "foreground-gdk"
gdk_color_get_type
cellTextForegroundSet :: CellRendererClass self => Attr self Bool
cellTextForegroundSet = newAttrFromBoolProperty "foreground-set"
cellTextLanguage :: CellRendererTextClass self => Attr self (Maybe String)
cellTextLanguage = newAttrFromMaybeStringProperty "language"
cellTextLanguageSet :: CellRendererTextClass self => Attr self Bool
cellTextLanguageSet = newAttrFromBoolProperty "language-set"
cellTextMarkup :: CellRendererTextClass cr => WriteAttr cr (Maybe String)
cellTextMarkup = writeAttrFromMaybeStringProperty "markup"
cellTextRise :: CellRendererTextClass self => Attr self Int
cellTextRise = newAttrFromIntProperty "rise"
cellTextRiseSet :: CellRendererTextClass self => Attr self Bool
cellTextRiseSet = newAttrFromBoolProperty "rise-set"
cellTextScale :: CellRendererTextClass self => Attr self Double
cellTextScale = newAttrFromDoubleProperty "scale"
cellTextScaleSet :: CellRendererTextClass self => Attr self Bool
cellTextScaleSet = newAttrFromBoolProperty "scale-set"
cellTextSingleParagraphMode :: CellRendererTextClass self => Attr self Bool
cellTextSingleParagraphMode = newAttrFromBoolProperty "single-paragraph-mode"
cellTextSize :: CellRendererTextClass self => Attr self Double
cellTextSize = newAttrFromDoubleProperty "size-points"
cellTextSizePoints :: CellRendererTextClass self => Attr self Double
cellTextSizePoints = newAttrFromDoubleProperty "size-points"
cellTextSizeSet :: CellRendererTextClass self => Attr self Bool
cellTextSizeSet = newAttrFromBoolProperty "size-set"
cellTextStretch :: CellRendererTextClass self => Attr self Stretch
cellTextStretch = newAttrFromEnumProperty "stretch"
pango_stretch_get_type
cellTextStretchSet :: CellRendererTextClass self => Attr self Bool
cellTextStretchSet = newAttrFromBoolProperty "stretch-set"
cellTextStrikethrough :: CellRendererTextClass self => Attr self Bool
cellTextStrikethrough = newAttrFromBoolProperty "strikethrough"
cellTextStrikethroughSet :: CellRendererTextClass self => Attr self Bool
cellTextStrikethroughSet = newAttrFromBoolProperty "strikethrough-set"
cellTextStyle :: CellRendererTextClass self => Attr self FontStyle
cellTextStyle = newAttrFromEnumProperty "style"
pango_style_get_type
cellTextStyleSet :: CellRendererTextClass self => Attr self Bool
cellTextStyleSet = newAttrFromBoolProperty "style-set"
cellText :: CellRendererTextClass cr => Attr cr String
cellText = newAttrFromStringProperty "text"
cellTextUnderline :: CellRendererTextClass self => Attr self Underline
cellTextUnderline = newAttrFromEnumProperty "underline"
pango_underline_get_type
cellTextUnderlineSet :: CellRendererTextClass self => Attr self Bool
cellTextUnderlineSet = newAttrFromBoolProperty "underline-set"
cellTextVariant :: CellRendererTextClass self => Attr self Variant
cellTextVariant = newAttrFromEnumProperty "variant"
pango_variant_get_type
cellTextVariantSet :: CellRendererTextClass self => Attr self Bool
cellTextVariantSet = newAttrFromBoolProperty "variant-set"
cellTextWeight :: CellRendererTextClass self => Attr self Int
cellTextWeight = newAttrFromIntProperty "weight"
cellTextWeightSet :: CellRendererTextClass self => Attr self Bool
cellTextWeightSet = newAttrFromBoolProperty "weight-set"
cellTextWidthChars :: CellRendererTextClass self => Attr self Int
cellTextWidthChars = newAttrFromIntProperty "width-chars"
cellTextWrapMode :: CellRendererTextClass self => Attr self LayoutWrapMode
cellTextWrapMode = newAttrFromEnumProperty "wrap-mode"
pango_wrap_mode_get_type
cellTextWrapWidth :: CellRendererTextClass self => Attr self Int
cellTextWrapWidth = newAttrFromIntProperty "wrap-width"
cellTextAlignment :: CellRendererTextClass self => Attr self LayoutAlignment
cellTextAlignment = newAttrFromEnumProperty "alignment"
pango_alignment_get_type
edited :: CellRendererTextClass self =>
Signal self (TreePath -> String -> IO ())
edited = Signal internalEdited
onEdited :: CellRendererTextClass self => self
-> (TreePath -> String -> IO ())
-> IO (ConnectId self)
onEdited = internalEdited False
afterEdited :: CellRendererTextClass self => self
-> (TreePath -> String -> IO ())
-> IO (ConnectId self)
afterEdited = internalEdited True
internalEdited :: CellRendererTextClass cr =>
Bool -> cr ->
(TreePath -> String -> IO ()) ->
IO (ConnectId cr)
internalEdited after cr user =
connect_STRING_STRING__NONE "edited" after cr $ \path string -> do
user (stringToTreePath path) string
foreign import ccall unsafe "gtk_cell_renderer_text_new"
gtk_cell_renderer_text_new :: (IO (Ptr CellRenderer))
foreign import ccall safe "gtk_cell_renderer_text_set_fixed_height_from_font"
gtk_cell_renderer_text_set_fixed_height_from_font :: ((Ptr CellRendererText) -> (CInt -> (IO ())))
foreign import ccall unsafe "gdk_color_get_type"
gdk_color_get_type :: CUInt
foreign import ccall safe "pango_ellipsize_mode_get_type"
pango_ellipsize_mode_get_type :: CUInt
foreign import ccall unsafe "pango_font_description_get_type"
pango_font_description_get_type :: CUInt
foreign import ccall safe "pango_stretch_get_type"
pango_stretch_get_type :: CUInt
foreign import ccall safe "pango_style_get_type"
pango_style_get_type :: CUInt
foreign import ccall safe "pango_underline_get_type"
pango_underline_get_type :: CUInt
foreign import ccall safe "pango_variant_get_type"
pango_variant_get_type :: CUInt
foreign import ccall safe "pango_wrap_mode_get_type"
pango_wrap_mode_get_type :: CUInt
foreign import ccall unsafe "pango_alignment_get_type"
pango_alignment_get_type :: CUInt