module Graphics.UI.Gtk.Multiline.TextTag (
  TextTag,
  TextTagClass,
  castToTextTag, gTypeTextTag,
  toTextTag,
  TagName,
  textTagNew,
  textTagSetPriority,
  textTagGetPriority,
  TextAttributes(..),
  textAttributesNew,
  textAttributesCopy,
  textAttributesCopyValues,
  makeNewTextAttributes, 
  textTagName,
  textTagBackground,
  textTagBackgroundSet,
  textTagBackgroundFullHeight,
  textTagBackgroundFullHeightSet,
  textTagBackgroundGdk,
  textTagBackgroundStipple,
  textTagBackgroundStippleSet,
  textTagForeground,
  textTagForegroundSet,
  textTagForegroundGdk,
  textTagForegroundStipple,
  textTagForegroundStippleSet,
  textTagDirection,
  textTagEditable,
  textTagEditableSet,
  textTagFont,
  textTagFontDesc,
  textTagFamily,
  textTagFamilySet,
  textTagStyle,
  textTagStyleSet,
  
  textTagTabsSet,
  textTagVariant,
  textTagVariantSet,
  textTagWeight,
  textTagWeightSet,
  textTagStretch,
  textTagStretchSet,
  textTagSize,
  textTagSizeSet,
  textTagScale,
  textTagScaleSet,
  textTagSizePoints,
  textTagJustification,
  textTagJustificationSet,
  textTagLanguage,
  textTagLanguageSet,
  textTagLeftMargin,
  textTagLeftMarginSet,
  textTagRightMargin,
  textTagRightMarginSet,
  textTagIndent,
  textTagIndentSet,
  textTagRise,
  textTagRiseSet,
  textTagPixelsAboveLines,
  textTagPixelsAboveLinesSet,
  textTagPixelsBelowLines,
  textTagPixelsBelowLinesSet,
  textTagPixelsInsideWrap,
  textTagPixelsInsideWrapSet,
  textTagStrikethrough,
  textTagStrikethroughSet,
  textTagUnderline,
  textTagUnderlineSet,
  textTagWrapMode,
  textTagWrapModeSet,
  textTagInvisible,
  textTagInvisibleSet,
  textTagParagraphBackground,
  textTagParagraphBackgroundSet,
  textTagParagraphBackgroundGdk,
  textTagPriority,
  textTagEvent,
  onTextTagEvent
  ) where
import Control.Monad (liftM)
import System.Glib.FFI
import System.Glib.UTFString
import System.Glib.Attributes
import System.Glib.Properties
import Graphics.UI.Gtk.Types
import Graphics.UI.Gtk.Signals
import Graphics.Rendering.Pango.Font
import Graphics.Rendering.Pango.BasicTypes (FontDescription (..), makeNewFontDescription)
import Graphics.Rendering.Pango.Enums (FontStyle(..), Variant(..),
                                         Stretch(..), Underline(..))
import Graphics.UI.Gtk.General.Enums (TextDirection(..),
                                         Justification(..), WrapMode(..))
import Graphics.UI.Gtk.General.Structs (Color(..))
import Graphics.UI.Gtk.Multiline.Types ( TextIter, mkTextIterCopy )
import Graphics.UI.Gtk.Gdk.Events (Event, marshalEvent)
import Graphics.UI.Gtk.Gdk.EventM (EventM, EAny)
import Control.Monad.Reader ( runReaderT )
type TagName = DefaultGlibString
textTagNew :: Maybe TagName -> IO TextTag
textTagNew (Just name) =
  wrapNewGObject mkTextTag $
  withUTFString name $ \namePtr ->
  gtk_text_tag_new
    namePtr
textTagNew Nothing =
  wrapNewGObject mkTextTag $ gtk_text_tag_new nullPtr
textTagGetPriority :: TextTagClass self => self -> IO Int
textTagGetPriority self =
  liftM fromIntegral $
  (\(TextTag arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_tag_get_priority argPtr1)
    (toTextTag self)
textTagSetPriority :: TextTagClass self => self -> Int -> IO ()
textTagSetPriority self priority =
  (\(TextTag arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_tag_set_priority argPtr1 arg2)
    (toTextTag self)
    (fromIntegral priority)
newtype TextAttributes = TextAttributes (ForeignPtr (TextAttributes))
textAttributesNew :: IO TextAttributes
textAttributesNew =
  gtk_text_attributes_new >>= makeNewTextAttributes
textAttributesCopy ::
  TextAttributes 
 -> IO TextAttributes
textAttributesCopy src =
  (\(TextAttributes arg1) -> withForeignPtr arg1 $ \argPtr1 ->gtk_text_attributes_copy argPtr1) src >>= makeNewTextAttributes
textAttributesCopyValues :: TextAttributes -> TextAttributes -> IO ()
textAttributesCopyValues src dest =
  (\(TextAttributes arg1) (TextAttributes arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gtk_text_attributes_copy_values argPtr1 argPtr2) src dest
makeNewTextAttributes :: Ptr TextAttributes -> IO TextAttributes
makeNewTextAttributes ptr =
  liftM TextAttributes $ newForeignPtr ptr text_attributes_unref
foreign import ccall unsafe ">k_text_attributes_unref"
  text_attributes_unref :: FinalizerPtr TextAttributes
textTagName :: (TextTagClass self, GlibString string) => Attr self (Maybe string)
textTagName = newAttrFromMaybeStringProperty "name"
textTagBackground :: (TextTagClass self, GlibString string) => WriteAttr self string
textTagBackground = writeAttrFromStringProperty "background"
textTagBackgroundSet :: TextTagClass self => Attr self Bool
textTagBackgroundSet = newAttrFromBoolProperty "background-set"
textTagBackgroundFullHeight :: TextTagClass self => Attr self Bool
textTagBackgroundFullHeight = newAttrFromBoolProperty "background-full-height"
textTagBackgroundFullHeightSet :: TextTagClass self => Attr self Bool
textTagBackgroundFullHeightSet = newAttrFromBoolProperty "background-full-height-set"
textTagBackgroundGdk :: TextTagClass self => Attr self Color
textTagBackgroundGdk =
  newAttrFromBoxedStorableProperty "background-gdk"
  gdk_color_get_type
textTagBackgroundStipple :: (TextTagClass self, PixmapClass pixmap) => ReadWriteAttr self Pixmap pixmap
textTagBackgroundStipple = newAttrFromObjectProperty "background-stipple"
  gdk_pixmap_get_type
textTagBackgroundStippleSet :: TextTagClass self => Attr self Bool
textTagBackgroundStippleSet = newAttrFromBoolProperty "background-stipple-set"
textTagForeground :: (TextTagClass self, GlibString string) => WriteAttr self string
textTagForeground = writeAttrFromStringProperty "foreground"
textTagForegroundSet :: TextTagClass self => Attr self Bool
textTagForegroundSet = newAttrFromBoolProperty "foreground-set"
textTagForegroundGdk :: TextTagClass self => Attr self Color
textTagForegroundGdk =
  newAttrFromBoxedStorableProperty "foreground-gdk"
  gdk_color_get_type
textTagForegroundStipple :: (TextTagClass self, PixmapClass pixmap) => ReadWriteAttr self Pixmap pixmap
textTagForegroundStipple = newAttrFromObjectProperty "foreground-stipple"
  gdk_pixmap_get_type
textTagForegroundStippleSet :: TextTagClass self => Attr self Bool
textTagForegroundStippleSet = newAttrFromBoolProperty "foreground-stipple-set"
textTagDirection :: TextTagClass self => Attr self TextDirection
textTagDirection = newAttrFromEnumProperty "direction"
  gtk_text_direction_get_type
textTagEditable :: TextTagClass self => Attr self Bool
textTagEditable = newAttrFromBoolProperty "editable"
textTagEditableSet :: TextTagClass self => Attr self Bool
textTagEditableSet = newAttrFromBoolProperty "editable-set"
textTagFont :: (TextTagClass self, GlibString string) => Attr self string
textTagFont = newAttrFromStringProperty "font"
textTagFontDesc :: TextTagClass self => Attr self FontDescription
textTagFontDesc = newAttrFromBoxedOpaqueProperty makeNewFontDescription
  (\(FontDescription fd) act -> withForeignPtr fd act) "font-desc"
  pango_font_description_get_type
textTagFamily :: (TextTagClass self, GlibString string) => Attr self string
textTagFamily = newAttrFromStringProperty "family"
textTagFamilySet :: TextTagClass self => Attr self Bool
textTagFamilySet = newAttrFromBoolProperty "family-set"
textTagStyle :: TextTagClass self => Attr self FontStyle
textTagStyle = newAttrFromEnumProperty "style"
  pango_style_get_type
textTagStyleSet :: TextTagClass self => Attr self Bool
textTagStyleSet = newAttrFromBoolProperty "style-set"
textTagTabsSet :: TextTagClass self => Attr self Bool
textTagTabsSet = newAttrFromBoolProperty "tabs-set"
textTagVariant :: TextTagClass self => Attr self Variant
textTagVariant = newAttrFromEnumProperty "variant"
  pango_variant_get_type
textTagVariantSet :: TextTagClass self => Attr self Bool
textTagVariantSet = newAttrFromBoolProperty "variant-set"
textTagWeight :: TextTagClass self => Attr self Int
textTagWeight = newAttrFromIntProperty "weight"
textTagWeightSet :: TextTagClass self => Attr self Bool
textTagWeightSet = newAttrFromBoolProperty "weight-set"
textTagStretch :: TextTagClass self => Attr self Stretch
textTagStretch = newAttrFromEnumProperty "stretch"
  pango_stretch_get_type
textTagStretchSet :: TextTagClass self => Attr self Bool
textTagStretchSet = newAttrFromBoolProperty "stretch-set"
textTagSize :: TextTagClass self => Attr self Int
textTagSize = newAttrFromIntProperty "size"
textTagSizeSet :: TextTagClass self => Attr self Bool
textTagSizeSet = newAttrFromBoolProperty "size-set"
textTagScale :: TextTagClass self => Attr self Double
textTagScale = newAttrFromDoubleProperty "scale"
textTagScaleSet :: TextTagClass self => Attr self Bool
textTagScaleSet = newAttrFromBoolProperty "scale-set"
textTagSizePoints :: TextTagClass self => Attr self Double
textTagSizePoints = newAttrFromDoubleProperty "size-points"
textTagJustification :: TextTagClass self => Attr self Justification
textTagJustification = newAttrFromEnumProperty "justification"
  gtk_justification_get_type
textTagJustificationSet :: TextTagClass self => Attr self Bool
textTagJustificationSet = newAttrFromBoolProperty "justification-set"
textTagLanguage :: (TextTagClass self, GlibString string) => Attr self string
textTagLanguage = newAttrFromStringProperty "language"
textTagLanguageSet :: TextTagClass self => Attr self Bool
textTagLanguageSet = newAttrFromBoolProperty "language-set"
textTagLeftMargin :: TextTagClass self => Attr self Int
textTagLeftMargin = newAttrFromIntProperty "left-margin"
textTagLeftMarginSet :: TextTagClass self => Attr self Bool
textTagLeftMarginSet = newAttrFromBoolProperty "left-margin-set"
textTagRightMargin :: TextTagClass self => Attr self Int
textTagRightMargin = newAttrFromIntProperty "right-margin"
textTagRightMarginSet :: TextTagClass self => Attr self Bool
textTagRightMarginSet = newAttrFromBoolProperty "right-margin-set"
textTagIndent :: TextTagClass self => Attr self Int
textTagIndent = newAttrFromIntProperty "indent"
textTagIndentSet :: TextTagClass self => Attr self Bool
textTagIndentSet = newAttrFromBoolProperty "indent-set"
textTagRise :: TextTagClass self => Attr self Int
textTagRise = newAttrFromIntProperty "rise"
textTagRiseSet :: TextTagClass self => Attr self Bool
textTagRiseSet = newAttrFromBoolProperty "rise-set"
textTagPixelsAboveLines :: TextTagClass self => Attr self Int
textTagPixelsAboveLines = newAttrFromIntProperty "pixels-above-lines"
textTagPixelsAboveLinesSet :: TextTagClass self => Attr self Bool
textTagPixelsAboveLinesSet = newAttrFromBoolProperty "pixels-above-lines-set"
textTagPixelsBelowLines :: TextTagClass self => Attr self Int
textTagPixelsBelowLines = newAttrFromIntProperty "pixels-below-lines"
textTagPixelsBelowLinesSet :: TextTagClass self => Attr self Bool
textTagPixelsBelowLinesSet = newAttrFromBoolProperty "pixels-below-lines-set"
textTagPixelsInsideWrap :: TextTagClass self => Attr self Int
textTagPixelsInsideWrap = newAttrFromIntProperty "pixels-inside-wrap"
textTagPixelsInsideWrapSet :: TextTagClass self => Attr self Bool
textTagPixelsInsideWrapSet = newAttrFromBoolProperty "pixels-inside-wrap-set"
textTagStrikethrough :: TextTagClass self => Attr self Bool
textTagStrikethrough = newAttrFromBoolProperty "strikethrough"
textTagStrikethroughSet :: TextTagClass self => Attr self Bool
textTagStrikethroughSet = newAttrFromBoolProperty "strikethrough-set"
textTagUnderline :: TextTagClass self => Attr self Underline
textTagUnderline = newAttrFromEnumProperty "underline"
  pango_underline_get_type
textTagUnderlineSet :: TextTagClass self => Attr self Bool
textTagUnderlineSet = newAttrFromBoolProperty "underline-set"
textTagWrapMode :: TextTagClass self => Attr self WrapMode
textTagWrapMode = newAttrFromEnumProperty "wrap-mode"
  gtk_wrap_mode_get_type
textTagWrapModeSet :: TextTagClass self => Attr self Bool
textTagWrapModeSet = newAttrFromBoolProperty "wrap-mode-set"
textTagInvisible :: TextTagClass self => Attr self Bool
textTagInvisible = newAttrFromBoolProperty "invisible"
textTagInvisibleSet :: TextTagClass self => Attr self Bool
textTagInvisibleSet = newAttrFromBoolProperty "invisible-set"
textTagParagraphBackground :: (TextTagClass self, GlibString string) => WriteAttr self string
textTagParagraphBackground = writeAttrFromStringProperty "paragraph-background"
textTagParagraphBackgroundSet :: TextTagClass self => Attr self Bool
textTagParagraphBackgroundSet = newAttrFromBoolProperty "paragraph-background-set"
textTagParagraphBackgroundGdk :: TextTagClass self => Attr self Color
textTagParagraphBackgroundGdk =
  newAttrFromBoxedStorableProperty "paragraph-background-gdk"
  gdk_color_get_type
textTagPriority :: TextTagClass self => Attr self Int
textTagPriority = newAttr
  textTagGetPriority
  textTagSetPriority
textTagEvent :: TextTagClass self => Signal self (GObject -> TextIter -> EventM EAny Bool)
textTagEvent = Signal (\after obj fun ->
                       connect_OBJECT_PTR_BOXED__BOOL "event" mkTextIterCopy after obj
                         (\tv eventPtr iter -> runReaderT (fun tv iter) eventPtr)
                      )
onTextTagEvent :: TextTagClass t => t -> (Event -> TextIter -> IO ()) ->
                  IO (ConnectId t)
onTextTagEvent tt act =
  connect_PTR_BOXED_BOXED__BOOL "event" marshalEvent mkTextIterCopy False tt
    (\_ event iter -> act event iter >> return False)
foreign import ccall unsafe "gtk_text_tag_new"
  gtk_text_tag_new :: ((Ptr CChar) -> (IO (Ptr TextTag)))
foreign import ccall unsafe "gtk_text_tag_get_priority"
  gtk_text_tag_get_priority :: ((Ptr TextTag) -> (IO CInt))
foreign import ccall safe "gtk_text_tag_set_priority"
  gtk_text_tag_set_priority :: ((Ptr TextTag) -> (CInt -> (IO ())))
foreign import ccall unsafe "gtk_text_attributes_new"
  gtk_text_attributes_new :: (IO (Ptr TextAttributes))
foreign import ccall safe "gtk_text_attributes_copy"
  gtk_text_attributes_copy :: ((Ptr TextAttributes) -> (IO (Ptr TextAttributes)))
foreign import ccall safe "gtk_text_attributes_copy_values"
  gtk_text_attributes_copy_values :: ((Ptr TextAttributes) -> ((Ptr TextAttributes) -> (IO ())))
foreign import ccall unsafe "gdk_color_get_type"
  gdk_color_get_type :: CULong
foreign import ccall unsafe "gdk_pixmap_get_type"
  gdk_pixmap_get_type :: CULong
foreign import ccall unsafe "gtk_text_direction_get_type"
  gtk_text_direction_get_type :: CULong
foreign import ccall unsafe "pango_font_description_get_type"
  pango_font_description_get_type :: CULong
foreign import ccall unsafe "pango_style_get_type"
  pango_style_get_type :: CULong
foreign import ccall unsafe "pango_variant_get_type"
  pango_variant_get_type :: CULong
foreign import ccall unsafe "pango_stretch_get_type"
  pango_stretch_get_type :: CULong
foreign import ccall unsafe "gtk_justification_get_type"
  gtk_justification_get_type :: CULong
foreign import ccall unsafe "pango_underline_get_type"
  pango_underline_get_type :: CULong
foreign import ccall unsafe "gtk_wrap_mode_get_type"
  gtk_wrap_mode_get_type :: CULong