{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.TextAppearance
(
TextAppearance(..) ,
newZeroTextAppearance ,
noTextAppearance ,
#if defined(ENABLE_OVERLOADING)
ResolveTextAppearanceMethod ,
#endif
getTextAppearanceBgColor ,
#if defined(ENABLE_OVERLOADING)
textAppearance_bgColor ,
#endif
getTextAppearanceDrawBg ,
setTextAppearanceDrawBg ,
#if defined(ENABLE_OVERLOADING)
textAppearance_drawBg ,
#endif
getTextAppearanceFgColor ,
#if defined(ENABLE_OVERLOADING)
textAppearance_fgColor ,
#endif
getTextAppearanceInsideSelection ,
setTextAppearanceInsideSelection ,
#if defined(ENABLE_OVERLOADING)
textAppearance_insideSelection ,
#endif
getTextAppearanceIsText ,
setTextAppearanceIsText ,
#if defined(ENABLE_OVERLOADING)
textAppearance_isText ,
#endif
getTextAppearanceRise ,
setTextAppearanceRise ,
#if defined(ENABLE_OVERLOADING)
textAppearance_rise ,
#endif
getTextAppearanceStrikethrough ,
setTextAppearanceStrikethrough ,
#if defined(ENABLE_OVERLOADING)
textAppearance_strikethrough ,
#endif
getTextAppearanceUnderline ,
setTextAppearanceUnderline ,
#if defined(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.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 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.Gdk.Structs.Color as Gdk.Color
newtype TextAppearance = TextAppearance (ManagedPtr TextAppearance)
deriving (TextAppearance -> TextAppearance -> Bool
(TextAppearance -> TextAppearance -> Bool)
-> (TextAppearance -> TextAppearance -> Bool) -> Eq TextAppearance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextAppearance -> TextAppearance -> Bool
$c/= :: TextAppearance -> TextAppearance -> Bool
== :: TextAppearance -> TextAppearance -> Bool
$c== :: TextAppearance -> TextAppearance -> Bool
Eq)
instance WrappedPtr TextAppearance where
wrappedPtrCalloc :: IO (Ptr TextAppearance)
wrappedPtrCalloc = Int -> IO (Ptr TextAppearance)
forall a. Int -> IO (Ptr a)
callocBytes 48
wrappedPtrCopy :: TextAppearance -> IO TextAppearance
wrappedPtrCopy = \p :: TextAppearance
p -> TextAppearance
-> (Ptr TextAppearance -> IO TextAppearance) -> IO TextAppearance
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
p (Int -> Ptr TextAppearance -> IO (Ptr TextAppearance)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 48 (Ptr TextAppearance -> IO (Ptr TextAppearance))
-> (Ptr TextAppearance -> IO TextAppearance)
-> Ptr TextAppearance
-> IO TextAppearance
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TextAppearance -> TextAppearance)
-> Ptr TextAppearance -> IO TextAppearance
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TextAppearance -> TextAppearance
TextAppearance)
wrappedPtrFree :: Maybe (GDestroyNotify TextAppearance)
wrappedPtrFree = GDestroyNotify TextAppearance
-> Maybe (GDestroyNotify TextAppearance)
forall a. a -> Maybe a
Just GDestroyNotify TextAppearance
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free
newZeroTextAppearance :: MonadIO m => m TextAppearance
newZeroTextAppearance :: m TextAppearance
newZeroTextAppearance = IO TextAppearance -> m TextAppearance
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TextAppearance -> m TextAppearance)
-> IO TextAppearance -> m TextAppearance
forall a b. (a -> b) -> a -> b
$ IO (Ptr TextAppearance)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr TextAppearance)
-> (Ptr TextAppearance -> IO TextAppearance) -> IO TextAppearance
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TextAppearance -> TextAppearance)
-> Ptr TextAppearance -> IO TextAppearance
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TextAppearance -> TextAppearance
TextAppearance
instance tag ~ 'AttrSet => Constructible TextAppearance tag where
new :: (ManagedPtr TextAppearance -> TextAppearance)
-> [AttrOp TextAppearance tag] -> m TextAppearance
new _ attrs :: [AttrOp TextAppearance tag]
attrs = do
TextAppearance
o <- m TextAppearance
forall (m :: * -> *). MonadIO m => m TextAppearance
newZeroTextAppearance
TextAppearance -> [AttrOp TextAppearance 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TextAppearance
o [AttrOp TextAppearance tag]
[AttrOp TextAppearance 'AttrSet]
attrs
TextAppearance -> m TextAppearance
forall (m :: * -> *) a. Monad m => a -> m a
return TextAppearance
o
noTextAppearance :: Maybe TextAppearance
noTextAppearance :: Maybe TextAppearance
noTextAppearance = Maybe TextAppearance
forall a. Maybe a
Nothing
getTextAppearanceBgColor :: MonadIO m => TextAppearance -> m Gdk.Color.Color
getTextAppearanceBgColor :: TextAppearance -> m Color
getTextAppearanceBgColor s :: TextAppearance
s = IO Color -> m Color
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Color -> m Color) -> IO Color -> m Color
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Color) -> IO Color
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Color) -> IO Color)
-> (Ptr TextAppearance -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
let val :: Ptr Color
val = Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: (Ptr Gdk.Color.Color)
Color
val' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Gdk.Color.Color) Ptr Color
val
Color -> IO Color
forall (m :: * -> *) a. Monad m => a -> m a
return Color
val'
#if defined(ENABLE_OVERLOADING)
data TextAppearanceBgColorFieldInfo
instance AttrInfo TextAppearanceBgColorFieldInfo where
type AttrBaseTypeConstraint TextAppearanceBgColorFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceBgColorFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint TextAppearanceBgColorFieldInfo = (~) (Ptr Gdk.Color.Color)
type AttrTransferTypeConstraint TextAppearanceBgColorFieldInfo = (~)(Ptr Gdk.Color.Color)
type AttrTransferType TextAppearanceBgColorFieldInfo = (Ptr Gdk.Color.Color)
type AttrGetType TextAppearanceBgColorFieldInfo = Gdk.Color.Color
type AttrLabel TextAppearanceBgColorFieldInfo = "bg_color"
type AttrOrigin TextAppearanceBgColorFieldInfo = TextAppearance
attrGet = getTextAppearanceBgColor
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
textAppearance_bgColor :: AttrLabelProxy "bgColor"
textAppearance_bgColor = AttrLabelProxy
#endif
getTextAppearanceFgColor :: MonadIO m => TextAppearance -> m Gdk.Color.Color
getTextAppearanceFgColor :: TextAppearance -> m Color
getTextAppearanceFgColor s :: TextAppearance
s = IO Color -> m Color
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Color -> m Color) -> IO Color -> m Color
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Color) -> IO Color
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Color) -> IO Color)
-> (Ptr TextAppearance -> IO Color) -> IO Color
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
let val :: Ptr Color
val = Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Color
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: (Ptr Gdk.Color.Color)
Color
val' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Gdk.Color.Color) Ptr Color
val
Color -> IO Color
forall (m :: * -> *) a. Monad m => a -> m a
return Color
val'
#if defined(ENABLE_OVERLOADING)
data TextAppearanceFgColorFieldInfo
instance AttrInfo TextAppearanceFgColorFieldInfo where
type AttrBaseTypeConstraint TextAppearanceFgColorFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceFgColorFieldInfo = '[ 'AttrGet]
type AttrSetTypeConstraint TextAppearanceFgColorFieldInfo = (~) (Ptr Gdk.Color.Color)
type AttrTransferTypeConstraint TextAppearanceFgColorFieldInfo = (~)(Ptr Gdk.Color.Color)
type AttrTransferType TextAppearanceFgColorFieldInfo = (Ptr Gdk.Color.Color)
type AttrGetType TextAppearanceFgColorFieldInfo = Gdk.Color.Color
type AttrLabel TextAppearanceFgColorFieldInfo = "fg_color"
type AttrOrigin TextAppearanceFgColorFieldInfo = TextAppearance
attrGet = getTextAppearanceFgColor
attrSet = undefined
attrConstruct = undefined
attrClear = undefined
attrTransfer = undefined
textAppearance_fgColor :: AttrLabelProxy "fgColor"
textAppearance_fgColor = AttrLabelProxy
#endif
getTextAppearanceRise :: MonadIO m => TextAppearance -> m Int32
getTextAppearanceRise :: TextAppearance -> m Int32
getTextAppearanceRise s :: TextAppearance
s = 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
$ TextAppearance -> (Ptr TextAppearance -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Int32) -> IO Int32)
-> (Ptr TextAppearance -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setTextAppearanceRise :: MonadIO m => TextAppearance -> Int32 -> m ()
setTextAppearanceRise :: TextAppearance -> Int32 -> m ()
setTextAppearanceRise s :: TextAppearance
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceRiseFieldInfo
instance AttrInfo TextAppearanceRiseFieldInfo where
type AttrBaseTypeConstraint TextAppearanceRiseFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceRiseFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceRiseFieldInfo = (~) Int32
type AttrTransferTypeConstraint TextAppearanceRiseFieldInfo = (~)Int32
type AttrTransferType TextAppearanceRiseFieldInfo = Int32
type AttrGetType TextAppearanceRiseFieldInfo = Int32
type AttrLabel TextAppearanceRiseFieldInfo = "rise"
type AttrOrigin TextAppearanceRiseFieldInfo = TextAppearance
attrGet = getTextAppearanceRise
attrSet = setTextAppearanceRise
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_rise :: AttrLabelProxy "rise"
textAppearance_rise = AttrLabelProxy
#endif
getTextAppearanceUnderline :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceUnderline :: TextAppearance -> m Word32
getTextAppearanceUnderline s :: TextAppearance
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Word32) -> IO Word32)
-> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTextAppearanceUnderline :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceUnderline :: TextAppearance -> Word32 -> m ()
setTextAppearanceUnderline s :: TextAppearance
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceUnderlineFieldInfo
instance AttrInfo TextAppearanceUnderlineFieldInfo where
type AttrBaseTypeConstraint TextAppearanceUnderlineFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceUnderlineFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceUnderlineFieldInfo = (~) Word32
type AttrTransferTypeConstraint TextAppearanceUnderlineFieldInfo = (~)Word32
type AttrTransferType TextAppearanceUnderlineFieldInfo = Word32
type AttrGetType TextAppearanceUnderlineFieldInfo = Word32
type AttrLabel TextAppearanceUnderlineFieldInfo = "underline"
type AttrOrigin TextAppearanceUnderlineFieldInfo = TextAppearance
attrGet = getTextAppearanceUnderline
attrSet = setTextAppearanceUnderline
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_underline :: AttrLabelProxy "underline"
textAppearance_underline = AttrLabelProxy
#endif
getTextAppearanceStrikethrough :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceStrikethrough :: TextAppearance -> m Word32
getTextAppearanceStrikethrough s :: TextAppearance
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Word32) -> IO Word32)
-> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTextAppearanceStrikethrough :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceStrikethrough :: TextAppearance -> Word32 -> m ()
setTextAppearanceStrikethrough s :: TextAppearance
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceStrikethroughFieldInfo
instance AttrInfo TextAppearanceStrikethroughFieldInfo where
type AttrBaseTypeConstraint TextAppearanceStrikethroughFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceStrikethroughFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceStrikethroughFieldInfo = (~) Word32
type AttrTransferTypeConstraint TextAppearanceStrikethroughFieldInfo = (~)Word32
type AttrTransferType TextAppearanceStrikethroughFieldInfo = Word32
type AttrGetType TextAppearanceStrikethroughFieldInfo = Word32
type AttrLabel TextAppearanceStrikethroughFieldInfo = "strikethrough"
type AttrOrigin TextAppearanceStrikethroughFieldInfo = TextAppearance
attrGet = getTextAppearanceStrikethrough
attrSet = setTextAppearanceStrikethrough
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_strikethrough :: AttrLabelProxy "strikethrough"
textAppearance_strikethrough = AttrLabelProxy
#endif
getTextAppearanceDrawBg :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceDrawBg :: TextAppearance -> m Word32
getTextAppearanceDrawBg s :: TextAppearance
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Word32) -> IO Word32)
-> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTextAppearanceDrawBg :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceDrawBg :: TextAppearance -> Word32 -> m ()
setTextAppearanceDrawBg s :: TextAppearance
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceDrawBgFieldInfo
instance AttrInfo TextAppearanceDrawBgFieldInfo where
type AttrBaseTypeConstraint TextAppearanceDrawBgFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceDrawBgFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceDrawBgFieldInfo = (~) Word32
type AttrTransferTypeConstraint TextAppearanceDrawBgFieldInfo = (~)Word32
type AttrTransferType TextAppearanceDrawBgFieldInfo = Word32
type AttrGetType TextAppearanceDrawBgFieldInfo = Word32
type AttrLabel TextAppearanceDrawBgFieldInfo = "draw_bg"
type AttrOrigin TextAppearanceDrawBgFieldInfo = TextAppearance
attrGet = getTextAppearanceDrawBg
attrSet = setTextAppearanceDrawBg
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_drawBg :: AttrLabelProxy "drawBg"
textAppearance_drawBg = AttrLabelProxy
#endif
getTextAppearanceInsideSelection :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceInsideSelection :: TextAppearance -> m Word32
getTextAppearanceInsideSelection s :: TextAppearance
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Word32) -> IO Word32)
-> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTextAppearanceInsideSelection :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceInsideSelection :: TextAppearance -> Word32 -> m ()
setTextAppearanceInsideSelection s :: TextAppearance
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceInsideSelectionFieldInfo
instance AttrInfo TextAppearanceInsideSelectionFieldInfo where
type AttrBaseTypeConstraint TextAppearanceInsideSelectionFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceInsideSelectionFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceInsideSelectionFieldInfo = (~) Word32
type AttrTransferTypeConstraint TextAppearanceInsideSelectionFieldInfo = (~)Word32
type AttrTransferType TextAppearanceInsideSelectionFieldInfo = Word32
type AttrGetType TextAppearanceInsideSelectionFieldInfo = Word32
type AttrLabel TextAppearanceInsideSelectionFieldInfo = "inside_selection"
type AttrOrigin TextAppearanceInsideSelectionFieldInfo = TextAppearance
attrGet = getTextAppearanceInsideSelection
attrSet = setTextAppearanceInsideSelection
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_insideSelection :: AttrLabelProxy "insideSelection"
textAppearance_insideSelection = AttrLabelProxy
#endif
getTextAppearanceIsText :: MonadIO m => TextAppearance -> m Word32
getTextAppearanceIsText :: TextAppearance -> m Word32
getTextAppearanceIsText s :: TextAppearance
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO Word32) -> IO Word32)
-> (Ptr TextAppearance -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setTextAppearanceIsText :: MonadIO m => TextAppearance -> Word32 -> m ()
setTextAppearanceIsText :: TextAppearance -> Word32 -> m ()
setTextAppearanceIsText s :: TextAppearance
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ TextAppearance -> (Ptr TextAppearance -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr TextAppearance
s ((Ptr TextAppearance -> IO ()) -> IO ())
-> (Ptr TextAppearance -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr TextAppearance
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr TextAppearance
ptr Ptr TextAppearance -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data TextAppearanceIsTextFieldInfo
instance AttrInfo TextAppearanceIsTextFieldInfo where
type AttrBaseTypeConstraint TextAppearanceIsTextFieldInfo = (~) TextAppearance
type AttrAllowedOps TextAppearanceIsTextFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint TextAppearanceIsTextFieldInfo = (~) Word32
type AttrTransferTypeConstraint TextAppearanceIsTextFieldInfo = (~)Word32
type AttrTransferType TextAppearanceIsTextFieldInfo = Word32
type AttrGetType TextAppearanceIsTextFieldInfo = Word32
type AttrLabel TextAppearanceIsTextFieldInfo = "is_text"
type AttrOrigin TextAppearanceIsTextFieldInfo = TextAppearance
attrGet = getTextAppearanceIsText
attrSet = setTextAppearanceIsText
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
textAppearance_isText :: AttrLabelProxy "isText"
textAppearance_isText = AttrLabelProxy
#endif
#if defined(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 defined(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) => OL.IsLabel t (TextAppearance -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif