#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gtk.Structs.TextAppearance
(
TextAppearance(..) ,
newZeroTextAppearance ,
noTextAppearance ,
getTextAppearanceBgColor ,
#if ENABLE_OVERLOADING
textAppearance_bgColor ,
#endif
getTextAppearanceDrawBg ,
setTextAppearanceDrawBg ,
#if ENABLE_OVERLOADING
textAppearance_drawBg ,
#endif
getTextAppearanceFgColor ,
#if ENABLE_OVERLOADING
textAppearance_fgColor ,
#endif
getTextAppearanceInsideSelection ,
setTextAppearanceInsideSelection ,
#if ENABLE_OVERLOADING
textAppearance_insideSelection ,
#endif
getTextAppearanceIsText ,
setTextAppearanceIsText ,
#if ENABLE_OVERLOADING
textAppearance_isText ,
#endif
getTextAppearanceRise ,
setTextAppearanceRise ,
#if ENABLE_OVERLOADING
textAppearance_rise ,
#endif
getTextAppearanceStrikethrough ,
setTextAppearanceStrikethrough ,
#if ENABLE_OVERLOADING
textAppearance_strikethrough ,
#endif
getTextAppearanceUnderline ,
setTextAppearanceUnderline ,
#if ENABLE_OVERLOADING
textAppearance_underline ,
#endif
) 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.ManagedPtr as B.ManagedPtr
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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GI.Gdk.Structs.Color as Gdk.Color
newtype TextAppearance = TextAppearance (ManagedPtr TextAppearance)
instance WrappedPtr TextAppearance where
wrappedPtrCalloc = callocBytes 48
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 48 >=> wrapPtr TextAppearance)
wrappedPtrFree = Just ptr_to_g_free
newZeroTextAppearance :: MonadIO m => m TextAppearance
newZeroTextAppearance = liftIO $ wrappedPtrCalloc >>= wrapPtr TextAppearance
instance tag ~ 'AttrSet => Constructible TextAppearance tag where
new _ attrs = do
o <- newZeroTextAppearance
GI.Attributes.set o attrs
return o
noTextAppearance :: Maybe TextAppearance
noTextAppearance = Nothing
getTextAppearanceBgColor :: MonadIO m => TextAppearance -> m Gdk.Color.Color
getTextAppearanceBgColor s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 0 :: (Ptr Gdk.Color.Color)
val' <- (newBoxed Gdk.Color.Color) val
return val'
#if ENABLE_OVERLOADING
data TextAppearanceBgColorFieldInfo
instance AttrInfo TextAppearanceBgColorFieldInfo where
type AttrAllowedOps TextAppearanceBgColorFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint TextAppearanceBgColorFieldInfo = (~) (Ptr Gdk.Color.Color)
type AttrBaseTypeConstraint TextAppearanceBgColorFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceBgColorFieldInfo = Gdk.Color.Color
type AttrLabel TextAppearanceBgColorFieldInfo = "bg_color"
type AttrOrigin TextAppearanceBgColorFieldInfo = TextAppearance
attrGet _ = getTextAppearanceBgColor
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
textAppearance_bgColor :: AttrLabelProxy "bgColor"
textAppearance_bgColor = AttrLabelProxy
#endif
getTextAppearanceFgColor :: MonadIO m => TextAppearance -> m Gdk.Color.Color
getTextAppearanceFgColor s = liftIO $ withManagedPtr s $ \ptr -> do
let val = ptr `plusPtr` 12 :: (Ptr Gdk.Color.Color)
val' <- (newBoxed Gdk.Color.Color) val
return val'
#if ENABLE_OVERLOADING
data TextAppearanceFgColorFieldInfo
instance AttrInfo TextAppearanceFgColorFieldInfo where
type AttrAllowedOps TextAppearanceFgColorFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint TextAppearanceFgColorFieldInfo = (~) (Ptr Gdk.Color.Color)
type AttrBaseTypeConstraint TextAppearanceFgColorFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceFgColorFieldInfo = Gdk.Color.Color
type AttrLabel TextAppearanceFgColorFieldInfo = "fg_color"
type AttrOrigin TextAppearanceFgColorFieldInfo = TextAppearance
attrGet _ = getTextAppearanceFgColor
attrSet _ = undefined
attrConstruct = undefined
attrClear _ = undefined
textAppearance_fgColor :: AttrLabelProxy "fgColor"
textAppearance_fgColor = AttrLabelProxy
#endif
getTextAppearanceRise :: MonadIO m => TextAppearance -> m Int32
getTextAppearanceRise s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO Int32
return val
setTextAppearanceRise :: MonadIO m => TextAppearance -> Int32 -> m ()
setTextAppearanceRise s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Int32)
#if ENABLE_OVERLOADING
data TextAppearanceRiseFieldInfo
instance AttrInfo TextAppearanceRiseFieldInfo where
type AttrAllowedOps TextAppearanceRiseFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceRiseFieldInfo = (~) Int32
type AttrBaseTypeConstraint TextAppearanceRiseFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceRiseFieldInfo = Int32
type AttrLabel TextAppearanceRiseFieldInfo = "rise"
type AttrOrigin TextAppearanceRiseFieldInfo = TextAppearance
attrGet _ = getTextAppearanceRise
attrSet _ = setTextAppearanceRise
attrConstruct = undefined
attrClear _ = undefined
textAppearance_rise :: AttrLabelProxy "rise"
textAppearance_rise = AttrLabelProxy
#endif
getTextAppearanceUnderline :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceUnderline s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 28) :: IO Word32
return val
setTextAppearanceUnderline :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceUnderline s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 28) (val :: Word32)
#if ENABLE_OVERLOADING
data TextAppearanceUnderlineFieldInfo
instance AttrInfo TextAppearanceUnderlineFieldInfo where
type AttrAllowedOps TextAppearanceUnderlineFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceUnderlineFieldInfo = (~) Word32
type AttrBaseTypeConstraint TextAppearanceUnderlineFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceUnderlineFieldInfo = Word32
type AttrLabel TextAppearanceUnderlineFieldInfo = "underline"
type AttrOrigin TextAppearanceUnderlineFieldInfo = TextAppearance
attrGet _ = getTextAppearanceUnderline
attrSet _ = setTextAppearanceUnderline
attrConstruct = undefined
attrClear _ = undefined
textAppearance_underline :: AttrLabelProxy "underline"
textAppearance_underline = AttrLabelProxy
#endif
getTextAppearanceStrikethrough :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceStrikethrough s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO Word32
return val
setTextAppearanceStrikethrough :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceStrikethrough s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: Word32)
#if ENABLE_OVERLOADING
data TextAppearanceStrikethroughFieldInfo
instance AttrInfo TextAppearanceStrikethroughFieldInfo where
type AttrAllowedOps TextAppearanceStrikethroughFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceStrikethroughFieldInfo = (~) Word32
type AttrBaseTypeConstraint TextAppearanceStrikethroughFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceStrikethroughFieldInfo = Word32
type AttrLabel TextAppearanceStrikethroughFieldInfo = "strikethrough"
type AttrOrigin TextAppearanceStrikethroughFieldInfo = TextAppearance
attrGet _ = getTextAppearanceStrikethrough
attrSet _ = setTextAppearanceStrikethrough
attrConstruct = undefined
attrClear _ = undefined
textAppearance_strikethrough :: AttrLabelProxy "strikethrough"
textAppearance_strikethrough = AttrLabelProxy
#endif
getTextAppearanceDrawBg :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceDrawBg s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 36) :: IO Word32
return val
setTextAppearanceDrawBg :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceDrawBg s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 36) (val :: Word32)
#if ENABLE_OVERLOADING
data TextAppearanceDrawBgFieldInfo
instance AttrInfo TextAppearanceDrawBgFieldInfo where
type AttrAllowedOps TextAppearanceDrawBgFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceDrawBgFieldInfo = (~) Word32
type AttrBaseTypeConstraint TextAppearanceDrawBgFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceDrawBgFieldInfo = Word32
type AttrLabel TextAppearanceDrawBgFieldInfo = "draw_bg"
type AttrOrigin TextAppearanceDrawBgFieldInfo = TextAppearance
attrGet _ = getTextAppearanceDrawBg
attrSet _ = setTextAppearanceDrawBg
attrConstruct = undefined
attrClear _ = undefined
textAppearance_drawBg :: AttrLabelProxy "drawBg"
textAppearance_drawBg = AttrLabelProxy
#endif
getTextAppearanceInsideSelection :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceInsideSelection s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO Word32
return val
setTextAppearanceInsideSelection :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceInsideSelection s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 40) (val :: Word32)
#if ENABLE_OVERLOADING
data TextAppearanceInsideSelectionFieldInfo
instance AttrInfo TextAppearanceInsideSelectionFieldInfo where
type AttrAllowedOps TextAppearanceInsideSelectionFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceInsideSelectionFieldInfo = (~) Word32
type AttrBaseTypeConstraint TextAppearanceInsideSelectionFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceInsideSelectionFieldInfo = Word32
type AttrLabel TextAppearanceInsideSelectionFieldInfo = "inside_selection"
type AttrOrigin TextAppearanceInsideSelectionFieldInfo = TextAppearance
attrGet _ = getTextAppearanceInsideSelection
attrSet _ = setTextAppearanceInsideSelection
attrConstruct = undefined
attrClear _ = undefined
textAppearance_insideSelection :: AttrLabelProxy "insideSelection"
textAppearance_insideSelection = AttrLabelProxy
#endif
getTextAppearanceIsText :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceIsText s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 44) :: IO Word32
return val
setTextAppearanceIsText :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceIsText s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 44) (val :: Word32)
#if ENABLE_OVERLOADING
data TextAppearanceIsTextFieldInfo
instance AttrInfo TextAppearanceIsTextFieldInfo where
type AttrAllowedOps TextAppearanceIsTextFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceIsTextFieldInfo = (~) Word32
type AttrBaseTypeConstraint TextAppearanceIsTextFieldInfo = (~) TextAppearance
type AttrGetType TextAppearanceIsTextFieldInfo = Word32
type AttrLabel TextAppearanceIsTextFieldInfo = "is_text"
type AttrOrigin TextAppearanceIsTextFieldInfo = TextAppearance
attrGet _ = getTextAppearanceIsText
attrSet _ = setTextAppearanceIsText
attrConstruct = undefined
attrClear _ = undefined
textAppearance_isText :: AttrLabelProxy "isText"
textAppearance_isText = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList TextAppearance
type instance O.AttributeList TextAppearance = TextAppearanceAttributeList
type TextAppearanceAttributeList = ('[ '("bgColor", TextAppearanceBgColorFieldInfo), '("fgColor", TextAppearanceFgColorFieldInfo), '("rise", TextAppearanceRiseFieldInfo), '("underline", TextAppearanceUnderlineFieldInfo), '("strikethrough", TextAppearanceStrikethroughFieldInfo), '("drawBg", TextAppearanceDrawBgFieldInfo), '("insideSelection", TextAppearanceInsideSelectionFieldInfo), '("isText", TextAppearanceIsTextFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveTextAppearanceMethod (t :: Symbol) (o :: *) :: * where
ResolveTextAppearanceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTextAppearanceMethod t TextAppearance, O.MethodInfo info TextAppearance p) => O.IsLabelProxy t (TextAppearance -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveTextAppearanceMethod t TextAppearance, O.MethodInfo info TextAppearance p) => O.IsLabel t (TextAppearance -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif
#endif