{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-unused-imports #-} -- Generated code. {-# OPTIONS_GHC -fno-warn-unused-imports #-} {-# LANGUAGE ForeignFunctionInterface, ConstraintKinds, TypeFamilies, MultiParamTypeClasses, KindSignatures, FlexibleInstances, UndecidableInstances, DataKinds, OverloadedStrings, NegativeLiterals, FlexibleContexts #-} module GI.VteAttributes where import Prelude () import Data.GI.Base.ShortPrelude import Data.Char import Data.Int import Data.Word import qualified Data.ByteString.Char8 as B import Data.ByteString.Char8 (ByteString) import qualified Data.Map as Map import Foreign.C import Foreign.Ptr import Foreign.ForeignPtr import Foreign.ForeignPtr.Unsafe (unsafeForeignPtrToPtr) import Foreign.Storable (peek, poke, sizeOf) import Control.Applicative ((<$>)) import Control.Exception (onException) import Control.Monad.IO.Class import qualified Data.Text as T import Data.GI.Base.Attributes hiding (get, set) import Data.GI.Base.BasicTypes import Data.GI.Base.BasicConversions import Data.GI.Base.Closure import Data.GI.Base.GError import Data.GI.Base.GHashTable import Data.GI.Base.GParamSpec import Data.GI.Base.GVariant import Data.GI.Base.GValue import Data.GI.Base.ManagedPtr import Data.GI.Base.Overloading import Data.GI.Base.Properties hiding (new) import Data.GI.Base.Signals (SignalConnectMode(..), connectSignalFunPtr, SignalHandlerId) import Data.GI.Base.Utils import qualified GI.Gtk as Gtk import qualified GI.GtkAttributes as GtkA import qualified GI.Pango as Pango import qualified GI.PangoAttributes as PangoA import GI.Vte -- VVV Prop "fd" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPtyFd :: (MonadIO m, PtyK o) => o -> m Int32 getPtyFd obj = liftIO $ getObjectPropertyCInt obj "fd" constructPtyFd :: Int32 -> IO ([Char], GValue) constructPtyFd val = constructObjectPropertyCInt "fd" val data PtyFdPropertyInfo instance AttrInfo PtyFdPropertyInfo where type AttrAllowedOps PtyFdPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PtyFdPropertyInfo = (~) Int32 type AttrBaseTypeConstraint PtyFdPropertyInfo = PtyK type AttrGetType PtyFdPropertyInfo = Int32 type AttrLabel PtyFdPropertyInfo = "Pty::fd" attrGet _ = getPtyFd attrSet _ = undefined attrConstruct _ = constructPtyFd -- VVV Prop "flags" -- Type: TInterface "Vte" "PtyFlags" -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly] getPtyFlags :: (MonadIO m, PtyK o) => o -> m [PtyFlags] getPtyFlags obj = liftIO $ getObjectPropertyFlags obj "flags" constructPtyFlags :: [PtyFlags] -> IO ([Char], GValue) constructPtyFlags val = constructObjectPropertyFlags "flags" val data PtyFlagsPropertyInfo instance AttrInfo PtyFlagsPropertyInfo where type AttrAllowedOps PtyFlagsPropertyInfo = '[ 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint PtyFlagsPropertyInfo = (~) [PtyFlags] type AttrBaseTypeConstraint PtyFlagsPropertyInfo = PtyK type AttrGetType PtyFlagsPropertyInfo = [PtyFlags] type AttrLabel PtyFlagsPropertyInfo = "Pty::flags" attrGet _ = getPtyFlags attrSet _ = undefined attrConstruct _ = constructPtyFlags type instance AttributeList Pty = '[ '("fd", PtyFdPropertyInfo), '("flags", PtyFlagsPropertyInfo)] -- VVV Prop "allow-bold" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalAllowBold :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalAllowBold obj = liftIO $ getObjectPropertyBool obj "allow-bold" setTerminalAllowBold :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalAllowBold obj val = liftIO $ setObjectPropertyBool obj "allow-bold" val constructTerminalAllowBold :: Bool -> IO ([Char], GValue) constructTerminalAllowBold val = constructObjectPropertyBool "allow-bold" val data TerminalAllowBoldPropertyInfo instance AttrInfo TerminalAllowBoldPropertyInfo where type AttrAllowedOps TerminalAllowBoldPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalAllowBoldPropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalAllowBoldPropertyInfo = TerminalK type AttrGetType TerminalAllowBoldPropertyInfo = Bool type AttrLabel TerminalAllowBoldPropertyInfo = "Terminal::allow-bold" attrGet _ = getTerminalAllowBold attrSet _ = setTerminalAllowBold attrConstruct _ = constructTerminalAllowBold -- VVV Prop "audible-bell" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalAudibleBell :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalAudibleBell obj = liftIO $ getObjectPropertyBool obj "audible-bell" setTerminalAudibleBell :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalAudibleBell obj val = liftIO $ setObjectPropertyBool obj "audible-bell" val constructTerminalAudibleBell :: Bool -> IO ([Char], GValue) constructTerminalAudibleBell val = constructObjectPropertyBool "audible-bell" val data TerminalAudibleBellPropertyInfo instance AttrInfo TerminalAudibleBellPropertyInfo where type AttrAllowedOps TerminalAudibleBellPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalAudibleBellPropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalAudibleBellPropertyInfo = TerminalK type AttrGetType TerminalAudibleBellPropertyInfo = Bool type AttrLabel TerminalAudibleBellPropertyInfo = "Terminal::audible-bell" attrGet _ = getTerminalAudibleBell attrSet _ = setTerminalAudibleBell attrConstruct _ = constructTerminalAudibleBell -- VVV Prop "backspace-binding" -- Type: TInterface "Vte" "EraseBinding" -- Flags: [PropertyReadable,PropertyWritable] getTerminalBackspaceBinding :: (MonadIO m, TerminalK o) => o -> m EraseBinding getTerminalBackspaceBinding obj = liftIO $ getObjectPropertyEnum obj "backspace-binding" setTerminalBackspaceBinding :: (MonadIO m, TerminalK o) => o -> EraseBinding -> m () setTerminalBackspaceBinding obj val = liftIO $ setObjectPropertyEnum obj "backspace-binding" val constructTerminalBackspaceBinding :: EraseBinding -> IO ([Char], GValue) constructTerminalBackspaceBinding val = constructObjectPropertyEnum "backspace-binding" val data TerminalBackspaceBindingPropertyInfo instance AttrInfo TerminalBackspaceBindingPropertyInfo where type AttrAllowedOps TerminalBackspaceBindingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalBackspaceBindingPropertyInfo = (~) EraseBinding type AttrBaseTypeConstraint TerminalBackspaceBindingPropertyInfo = TerminalK type AttrGetType TerminalBackspaceBindingPropertyInfo = EraseBinding type AttrLabel TerminalBackspaceBindingPropertyInfo = "Terminal::backspace-binding" attrGet _ = getTerminalBackspaceBinding attrSet _ = setTerminalBackspaceBinding attrConstruct _ = constructTerminalBackspaceBinding -- VVV Prop "cjk-ambiguous-width" -- Type: TBasicType TInt32 -- Flags: [PropertyReadable,PropertyWritable] getTerminalCjkAmbiguousWidth :: (MonadIO m, TerminalK o) => o -> m Int32 getTerminalCjkAmbiguousWidth obj = liftIO $ getObjectPropertyCInt obj "cjk-ambiguous-width" setTerminalCjkAmbiguousWidth :: (MonadIO m, TerminalK o) => o -> Int32 -> m () setTerminalCjkAmbiguousWidth obj val = liftIO $ setObjectPropertyCInt obj "cjk-ambiguous-width" val constructTerminalCjkAmbiguousWidth :: Int32 -> IO ([Char], GValue) constructTerminalCjkAmbiguousWidth val = constructObjectPropertyCInt "cjk-ambiguous-width" val data TerminalCjkAmbiguousWidthPropertyInfo instance AttrInfo TerminalCjkAmbiguousWidthPropertyInfo where type AttrAllowedOps TerminalCjkAmbiguousWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalCjkAmbiguousWidthPropertyInfo = (~) Int32 type AttrBaseTypeConstraint TerminalCjkAmbiguousWidthPropertyInfo = TerminalK type AttrGetType TerminalCjkAmbiguousWidthPropertyInfo = Int32 type AttrLabel TerminalCjkAmbiguousWidthPropertyInfo = "Terminal::cjk-ambiguous-width" attrGet _ = getTerminalCjkAmbiguousWidth attrSet _ = setTerminalCjkAmbiguousWidth attrConstruct _ = constructTerminalCjkAmbiguousWidth -- VVV Prop "current-directory-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getTerminalCurrentDirectoryUri :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalCurrentDirectoryUri obj = liftIO $ getObjectPropertyString obj "current-directory-uri" data TerminalCurrentDirectoryUriPropertyInfo instance AttrInfo TerminalCurrentDirectoryUriPropertyInfo where type AttrAllowedOps TerminalCurrentDirectoryUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint TerminalCurrentDirectoryUriPropertyInfo = (~) () type AttrBaseTypeConstraint TerminalCurrentDirectoryUriPropertyInfo = TerminalK type AttrGetType TerminalCurrentDirectoryUriPropertyInfo = T.Text type AttrLabel TerminalCurrentDirectoryUriPropertyInfo = "Terminal::current-directory-uri" attrGet _ = getTerminalCurrentDirectoryUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "current-file-uri" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getTerminalCurrentFileUri :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalCurrentFileUri obj = liftIO $ getObjectPropertyString obj "current-file-uri" data TerminalCurrentFileUriPropertyInfo instance AttrInfo TerminalCurrentFileUriPropertyInfo where type AttrAllowedOps TerminalCurrentFileUriPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint TerminalCurrentFileUriPropertyInfo = (~) () type AttrBaseTypeConstraint TerminalCurrentFileUriPropertyInfo = TerminalK type AttrGetType TerminalCurrentFileUriPropertyInfo = T.Text type AttrLabel TerminalCurrentFileUriPropertyInfo = "Terminal::current-file-uri" attrGet _ = getTerminalCurrentFileUri attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "cursor-blink-mode" -- Type: TInterface "Vte" "CursorBlinkMode" -- Flags: [PropertyReadable,PropertyWritable] getTerminalCursorBlinkMode :: (MonadIO m, TerminalK o) => o -> m CursorBlinkMode getTerminalCursorBlinkMode obj = liftIO $ getObjectPropertyEnum obj "cursor-blink-mode" setTerminalCursorBlinkMode :: (MonadIO m, TerminalK o) => o -> CursorBlinkMode -> m () setTerminalCursorBlinkMode obj val = liftIO $ setObjectPropertyEnum obj "cursor-blink-mode" val constructTerminalCursorBlinkMode :: CursorBlinkMode -> IO ([Char], GValue) constructTerminalCursorBlinkMode val = constructObjectPropertyEnum "cursor-blink-mode" val data TerminalCursorBlinkModePropertyInfo instance AttrInfo TerminalCursorBlinkModePropertyInfo where type AttrAllowedOps TerminalCursorBlinkModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalCursorBlinkModePropertyInfo = (~) CursorBlinkMode type AttrBaseTypeConstraint TerminalCursorBlinkModePropertyInfo = TerminalK type AttrGetType TerminalCursorBlinkModePropertyInfo = CursorBlinkMode type AttrLabel TerminalCursorBlinkModePropertyInfo = "Terminal::cursor-blink-mode" attrGet _ = getTerminalCursorBlinkMode attrSet _ = setTerminalCursorBlinkMode attrConstruct _ = constructTerminalCursorBlinkMode -- VVV Prop "cursor-shape" -- Type: TInterface "Vte" "CursorShape" -- Flags: [PropertyReadable,PropertyWritable] getTerminalCursorShape :: (MonadIO m, TerminalK o) => o -> m CursorShape getTerminalCursorShape obj = liftIO $ getObjectPropertyEnum obj "cursor-shape" setTerminalCursorShape :: (MonadIO m, TerminalK o) => o -> CursorShape -> m () setTerminalCursorShape obj val = liftIO $ setObjectPropertyEnum obj "cursor-shape" val constructTerminalCursorShape :: CursorShape -> IO ([Char], GValue) constructTerminalCursorShape val = constructObjectPropertyEnum "cursor-shape" val data TerminalCursorShapePropertyInfo instance AttrInfo TerminalCursorShapePropertyInfo where type AttrAllowedOps TerminalCursorShapePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalCursorShapePropertyInfo = (~) CursorShape type AttrBaseTypeConstraint TerminalCursorShapePropertyInfo = TerminalK type AttrGetType TerminalCursorShapePropertyInfo = CursorShape type AttrLabel TerminalCursorShapePropertyInfo = "Terminal::cursor-shape" attrGet _ = getTerminalCursorShape attrSet _ = setTerminalCursorShape attrConstruct _ = constructTerminalCursorShape -- VVV Prop "delete-binding" -- Type: TInterface "Vte" "EraseBinding" -- Flags: [PropertyReadable,PropertyWritable] getTerminalDeleteBinding :: (MonadIO m, TerminalK o) => o -> m EraseBinding getTerminalDeleteBinding obj = liftIO $ getObjectPropertyEnum obj "delete-binding" setTerminalDeleteBinding :: (MonadIO m, TerminalK o) => o -> EraseBinding -> m () setTerminalDeleteBinding obj val = liftIO $ setObjectPropertyEnum obj "delete-binding" val constructTerminalDeleteBinding :: EraseBinding -> IO ([Char], GValue) constructTerminalDeleteBinding val = constructObjectPropertyEnum "delete-binding" val data TerminalDeleteBindingPropertyInfo instance AttrInfo TerminalDeleteBindingPropertyInfo where type AttrAllowedOps TerminalDeleteBindingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalDeleteBindingPropertyInfo = (~) EraseBinding type AttrBaseTypeConstraint TerminalDeleteBindingPropertyInfo = TerminalK type AttrGetType TerminalDeleteBindingPropertyInfo = EraseBinding type AttrLabel TerminalDeleteBindingPropertyInfo = "Terminal::delete-binding" attrGet _ = getTerminalDeleteBinding attrSet _ = setTerminalDeleteBinding attrConstruct _ = constructTerminalDeleteBinding -- VVV Prop "encoding" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable,PropertyWritable] getTerminalEncoding :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalEncoding obj = liftIO $ getObjectPropertyString obj "encoding" setTerminalEncoding :: (MonadIO m, TerminalK o) => o -> T.Text -> m () setTerminalEncoding obj val = liftIO $ setObjectPropertyString obj "encoding" val constructTerminalEncoding :: T.Text -> IO ([Char], GValue) constructTerminalEncoding val = constructObjectPropertyString "encoding" val data TerminalEncodingPropertyInfo instance AttrInfo TerminalEncodingPropertyInfo where type AttrAllowedOps TerminalEncodingPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalEncodingPropertyInfo = (~) T.Text type AttrBaseTypeConstraint TerminalEncodingPropertyInfo = TerminalK type AttrGetType TerminalEncodingPropertyInfo = T.Text type AttrLabel TerminalEncodingPropertyInfo = "Terminal::encoding" attrGet _ = getTerminalEncoding attrSet _ = setTerminalEncoding attrConstruct _ = constructTerminalEncoding -- VVV Prop "font-desc" -- Type: TInterface "Pango" "FontDescription" -- Flags: [PropertyReadable,PropertyWritable] getTerminalFontDesc :: (MonadIO m, TerminalK o) => o -> m Pango.FontDescription getTerminalFontDesc obj = liftIO $ getObjectPropertyBoxed obj "font-desc" Pango.FontDescription setTerminalFontDesc :: (MonadIO m, TerminalK o) => o -> Pango.FontDescription -> m () setTerminalFontDesc obj val = liftIO $ setObjectPropertyBoxed obj "font-desc" val constructTerminalFontDesc :: Pango.FontDescription -> IO ([Char], GValue) constructTerminalFontDesc val = constructObjectPropertyBoxed "font-desc" val data TerminalFontDescPropertyInfo instance AttrInfo TerminalFontDescPropertyInfo where type AttrAllowedOps TerminalFontDescPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalFontDescPropertyInfo = (~) Pango.FontDescription type AttrBaseTypeConstraint TerminalFontDescPropertyInfo = TerminalK type AttrGetType TerminalFontDescPropertyInfo = Pango.FontDescription type AttrLabel TerminalFontDescPropertyInfo = "Terminal::font-desc" attrGet _ = getTerminalFontDesc attrSet _ = setTerminalFontDesc attrConstruct _ = constructTerminalFontDesc -- VVV Prop "font-scale" -- Type: TBasicType TDouble -- Flags: [PropertyReadable,PropertyWritable] getTerminalFontScale :: (MonadIO m, TerminalK o) => o -> m Double getTerminalFontScale obj = liftIO $ getObjectPropertyDouble obj "font-scale" setTerminalFontScale :: (MonadIO m, TerminalK o) => o -> Double -> m () setTerminalFontScale obj val = liftIO $ setObjectPropertyDouble obj "font-scale" val constructTerminalFontScale :: Double -> IO ([Char], GValue) constructTerminalFontScale val = constructObjectPropertyDouble "font-scale" val data TerminalFontScalePropertyInfo instance AttrInfo TerminalFontScalePropertyInfo where type AttrAllowedOps TerminalFontScalePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalFontScalePropertyInfo = (~) Double type AttrBaseTypeConstraint TerminalFontScalePropertyInfo = TerminalK type AttrGetType TerminalFontScalePropertyInfo = Double type AttrLabel TerminalFontScalePropertyInfo = "Terminal::font-scale" attrGet _ = getTerminalFontScale attrSet _ = setTerminalFontScale attrConstruct _ = constructTerminalFontScale -- VVV Prop "icon-title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getTerminalIconTitle :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalIconTitle obj = liftIO $ getObjectPropertyString obj "icon-title" data TerminalIconTitlePropertyInfo instance AttrInfo TerminalIconTitlePropertyInfo where type AttrAllowedOps TerminalIconTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint TerminalIconTitlePropertyInfo = (~) () type AttrBaseTypeConstraint TerminalIconTitlePropertyInfo = TerminalK type AttrGetType TerminalIconTitlePropertyInfo = T.Text type AttrLabel TerminalIconTitlePropertyInfo = "Terminal::icon-title" attrGet _ = getTerminalIconTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "input-enabled" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalInputEnabled :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalInputEnabled obj = liftIO $ getObjectPropertyBool obj "input-enabled" setTerminalInputEnabled :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalInputEnabled obj val = liftIO $ setObjectPropertyBool obj "input-enabled" val constructTerminalInputEnabled :: Bool -> IO ([Char], GValue) constructTerminalInputEnabled val = constructObjectPropertyBool "input-enabled" val data TerminalInputEnabledPropertyInfo instance AttrInfo TerminalInputEnabledPropertyInfo where type AttrAllowedOps TerminalInputEnabledPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalInputEnabledPropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalInputEnabledPropertyInfo = TerminalK type AttrGetType TerminalInputEnabledPropertyInfo = Bool type AttrLabel TerminalInputEnabledPropertyInfo = "Terminal::input-enabled" attrGet _ = getTerminalInputEnabled attrSet _ = setTerminalInputEnabled attrConstruct _ = constructTerminalInputEnabled -- VVV Prop "pointer-autohide" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalPointerAutohide :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalPointerAutohide obj = liftIO $ getObjectPropertyBool obj "pointer-autohide" setTerminalPointerAutohide :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalPointerAutohide obj val = liftIO $ setObjectPropertyBool obj "pointer-autohide" val constructTerminalPointerAutohide :: Bool -> IO ([Char], GValue) constructTerminalPointerAutohide val = constructObjectPropertyBool "pointer-autohide" val data TerminalPointerAutohidePropertyInfo instance AttrInfo TerminalPointerAutohidePropertyInfo where type AttrAllowedOps TerminalPointerAutohidePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalPointerAutohidePropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalPointerAutohidePropertyInfo = TerminalK type AttrGetType TerminalPointerAutohidePropertyInfo = Bool type AttrLabel TerminalPointerAutohidePropertyInfo = "Terminal::pointer-autohide" attrGet _ = getTerminalPointerAutohide attrSet _ = setTerminalPointerAutohide attrConstruct _ = constructTerminalPointerAutohide -- VVV Prop "pty" -- Type: TInterface "Vte" "Pty" -- Flags: [PropertyReadable,PropertyWritable] getTerminalPty :: (MonadIO m, TerminalK o) => o -> m Pty getTerminalPty obj = liftIO $ getObjectPropertyObject obj "pty" Pty setTerminalPty :: (MonadIO m, TerminalK o, PtyK a) => o -> a -> m () setTerminalPty obj val = liftIO $ setObjectPropertyObject obj "pty" val constructTerminalPty :: (PtyK a) => a -> IO ([Char], GValue) constructTerminalPty val = constructObjectPropertyObject "pty" val data TerminalPtyPropertyInfo instance AttrInfo TerminalPtyPropertyInfo where type AttrAllowedOps TerminalPtyPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalPtyPropertyInfo = PtyK type AttrBaseTypeConstraint TerminalPtyPropertyInfo = TerminalK type AttrGetType TerminalPtyPropertyInfo = Pty type AttrLabel TerminalPtyPropertyInfo = "Terminal::pty" attrGet _ = getTerminalPty attrSet _ = setTerminalPty attrConstruct _ = constructTerminalPty -- VVV Prop "rewrap-on-resize" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalRewrapOnResize :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalRewrapOnResize obj = liftIO $ getObjectPropertyBool obj "rewrap-on-resize" setTerminalRewrapOnResize :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalRewrapOnResize obj val = liftIO $ setObjectPropertyBool obj "rewrap-on-resize" val constructTerminalRewrapOnResize :: Bool -> IO ([Char], GValue) constructTerminalRewrapOnResize val = constructObjectPropertyBool "rewrap-on-resize" val data TerminalRewrapOnResizePropertyInfo instance AttrInfo TerminalRewrapOnResizePropertyInfo where type AttrAllowedOps TerminalRewrapOnResizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalRewrapOnResizePropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalRewrapOnResizePropertyInfo = TerminalK type AttrGetType TerminalRewrapOnResizePropertyInfo = Bool type AttrLabel TerminalRewrapOnResizePropertyInfo = "Terminal::rewrap-on-resize" attrGet _ = getTerminalRewrapOnResize attrSet _ = setTerminalRewrapOnResize attrConstruct _ = constructTerminalRewrapOnResize -- VVV Prop "scroll-on-keystroke" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalScrollOnKeystroke :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalScrollOnKeystroke obj = liftIO $ getObjectPropertyBool obj "scroll-on-keystroke" setTerminalScrollOnKeystroke :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalScrollOnKeystroke obj val = liftIO $ setObjectPropertyBool obj "scroll-on-keystroke" val constructTerminalScrollOnKeystroke :: Bool -> IO ([Char], GValue) constructTerminalScrollOnKeystroke val = constructObjectPropertyBool "scroll-on-keystroke" val data TerminalScrollOnKeystrokePropertyInfo instance AttrInfo TerminalScrollOnKeystrokePropertyInfo where type AttrAllowedOps TerminalScrollOnKeystrokePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalScrollOnKeystrokePropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalScrollOnKeystrokePropertyInfo = TerminalK type AttrGetType TerminalScrollOnKeystrokePropertyInfo = Bool type AttrLabel TerminalScrollOnKeystrokePropertyInfo = "Terminal::scroll-on-keystroke" attrGet _ = getTerminalScrollOnKeystroke attrSet _ = setTerminalScrollOnKeystroke attrConstruct _ = constructTerminalScrollOnKeystroke -- VVV Prop "scroll-on-output" -- Type: TBasicType TBoolean -- Flags: [PropertyReadable,PropertyWritable] getTerminalScrollOnOutput :: (MonadIO m, TerminalK o) => o -> m Bool getTerminalScrollOnOutput obj = liftIO $ getObjectPropertyBool obj "scroll-on-output" setTerminalScrollOnOutput :: (MonadIO m, TerminalK o) => o -> Bool -> m () setTerminalScrollOnOutput obj val = liftIO $ setObjectPropertyBool obj "scroll-on-output" val constructTerminalScrollOnOutput :: Bool -> IO ([Char], GValue) constructTerminalScrollOnOutput val = constructObjectPropertyBool "scroll-on-output" val data TerminalScrollOnOutputPropertyInfo instance AttrInfo TerminalScrollOnOutputPropertyInfo where type AttrAllowedOps TerminalScrollOnOutputPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalScrollOnOutputPropertyInfo = (~) Bool type AttrBaseTypeConstraint TerminalScrollOnOutputPropertyInfo = TerminalK type AttrGetType TerminalScrollOnOutputPropertyInfo = Bool type AttrLabel TerminalScrollOnOutputPropertyInfo = "Terminal::scroll-on-output" attrGet _ = getTerminalScrollOnOutput attrSet _ = setTerminalScrollOnOutput attrConstruct _ = constructTerminalScrollOnOutput -- VVV Prop "scrollback-lines" -- Type: TBasicType TUInt32 -- Flags: [PropertyReadable,PropertyWritable] getTerminalScrollbackLines :: (MonadIO m, TerminalK o) => o -> m Word32 getTerminalScrollbackLines obj = liftIO $ getObjectPropertyCUInt obj "scrollback-lines" setTerminalScrollbackLines :: (MonadIO m, TerminalK o) => o -> Word32 -> m () setTerminalScrollbackLines obj val = liftIO $ setObjectPropertyCUInt obj "scrollback-lines" val constructTerminalScrollbackLines :: Word32 -> IO ([Char], GValue) constructTerminalScrollbackLines val = constructObjectPropertyCUInt "scrollback-lines" val data TerminalScrollbackLinesPropertyInfo instance AttrInfo TerminalScrollbackLinesPropertyInfo where type AttrAllowedOps TerminalScrollbackLinesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet] type AttrSetTypeConstraint TerminalScrollbackLinesPropertyInfo = (~) Word32 type AttrBaseTypeConstraint TerminalScrollbackLinesPropertyInfo = TerminalK type AttrGetType TerminalScrollbackLinesPropertyInfo = Word32 type AttrLabel TerminalScrollbackLinesPropertyInfo = "Terminal::scrollback-lines" attrGet _ = getTerminalScrollbackLines attrSet _ = setTerminalScrollbackLines attrConstruct _ = constructTerminalScrollbackLines -- VVV Prop "window-title" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getTerminalWindowTitle :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalWindowTitle obj = liftIO $ getObjectPropertyString obj "window-title" data TerminalWindowTitlePropertyInfo instance AttrInfo TerminalWindowTitlePropertyInfo where type AttrAllowedOps TerminalWindowTitlePropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint TerminalWindowTitlePropertyInfo = (~) () type AttrBaseTypeConstraint TerminalWindowTitlePropertyInfo = TerminalK type AttrGetType TerminalWindowTitlePropertyInfo = T.Text type AttrLabel TerminalWindowTitlePropertyInfo = "Terminal::window-title" attrGet _ = getTerminalWindowTitle attrSet _ = undefined attrConstruct _ = undefined -- VVV Prop "word-char-exceptions" -- Type: TBasicType TUTF8 -- Flags: [PropertyReadable] getTerminalWordCharExceptions :: (MonadIO m, TerminalK o) => o -> m T.Text getTerminalWordCharExceptions obj = liftIO $ getObjectPropertyString obj "word-char-exceptions" data TerminalWordCharExceptionsPropertyInfo instance AttrInfo TerminalWordCharExceptionsPropertyInfo where type AttrAllowedOps TerminalWordCharExceptionsPropertyInfo = '[ 'AttrGet] type AttrSetTypeConstraint TerminalWordCharExceptionsPropertyInfo = (~) () type AttrBaseTypeConstraint TerminalWordCharExceptionsPropertyInfo = TerminalK type AttrGetType TerminalWordCharExceptionsPropertyInfo = T.Text type AttrLabel TerminalWordCharExceptionsPropertyInfo = "Terminal::word-char-exceptions" attrGet _ = getTerminalWordCharExceptions attrSet _ = undefined attrConstruct _ = undefined type instance AttributeList Terminal = '[ '("allow-bold", TerminalAllowBoldPropertyInfo), '("app-paintable", GtkA.WidgetAppPaintablePropertyInfo), '("audible-bell", TerminalAudibleBellPropertyInfo), '("backspace-binding", TerminalBackspaceBindingPropertyInfo), '("can-default", GtkA.WidgetCanDefaultPropertyInfo), '("can-focus", GtkA.WidgetCanFocusPropertyInfo), '("cjk-ambiguous-width", TerminalCjkAmbiguousWidthPropertyInfo), '("composite-child", GtkA.WidgetCompositeChildPropertyInfo), '("current-directory-uri", TerminalCurrentDirectoryUriPropertyInfo), '("current-file-uri", TerminalCurrentFileUriPropertyInfo), '("cursor-blink-mode", TerminalCursorBlinkModePropertyInfo), '("cursor-shape", TerminalCursorShapePropertyInfo), '("delete-binding", TerminalDeleteBindingPropertyInfo), '("double-buffered", GtkA.WidgetDoubleBufferedPropertyInfo), '("encoding", TerminalEncodingPropertyInfo), '("events", GtkA.WidgetEventsPropertyInfo), '("expand", GtkA.WidgetExpandPropertyInfo), '("font-desc", TerminalFontDescPropertyInfo), '("font-scale", TerminalFontScalePropertyInfo), '("hadjustment", GtkA.ScrollableHadjustmentPropertyInfo), '("halign", GtkA.WidgetHalignPropertyInfo), '("has-default", GtkA.WidgetHasDefaultPropertyInfo), '("has-focus", GtkA.WidgetHasFocusPropertyInfo), '("has-tooltip", GtkA.WidgetHasTooltipPropertyInfo), '("height-request", GtkA.WidgetHeightRequestPropertyInfo), '("hexpand", GtkA.WidgetHexpandPropertyInfo), '("hexpand-set", GtkA.WidgetHexpandSetPropertyInfo), '("hscroll-policy", GtkA.ScrollableHscrollPolicyPropertyInfo), '("icon-title", TerminalIconTitlePropertyInfo), '("input-enabled", TerminalInputEnabledPropertyInfo), '("is-focus", GtkA.WidgetIsFocusPropertyInfo), '("margin", GtkA.WidgetMarginPropertyInfo), '("margin-bottom", GtkA.WidgetMarginBottomPropertyInfo), '("margin-end", GtkA.WidgetMarginEndPropertyInfo), '("margin-left", GtkA.WidgetMarginLeftPropertyInfo), '("margin-right", GtkA.WidgetMarginRightPropertyInfo), '("margin-start", GtkA.WidgetMarginStartPropertyInfo), '("margin-top", GtkA.WidgetMarginTopPropertyInfo), '("name", GtkA.WidgetNamePropertyInfo), '("no-show-all", GtkA.WidgetNoShowAllPropertyInfo), '("opacity", GtkA.WidgetOpacityPropertyInfo), '("parent", GtkA.WidgetParentPropertyInfo), '("pointer-autohide", TerminalPointerAutohidePropertyInfo), '("pty", TerminalPtyPropertyInfo), '("receives-default", GtkA.WidgetReceivesDefaultPropertyInfo), '("rewrap-on-resize", TerminalRewrapOnResizePropertyInfo), '("scale-factor", GtkA.WidgetScaleFactorPropertyInfo), '("scroll-on-keystroke", TerminalScrollOnKeystrokePropertyInfo), '("scroll-on-output", TerminalScrollOnOutputPropertyInfo), '("scrollback-lines", TerminalScrollbackLinesPropertyInfo), '("sensitive", GtkA.WidgetSensitivePropertyInfo), '("style", GtkA.WidgetStylePropertyInfo), '("tooltip-markup", GtkA.WidgetTooltipMarkupPropertyInfo), '("tooltip-text", GtkA.WidgetTooltipTextPropertyInfo), '("vadjustment", GtkA.ScrollableVadjustmentPropertyInfo), '("valign", GtkA.WidgetValignPropertyInfo), '("vexpand", GtkA.WidgetVexpandPropertyInfo), '("vexpand-set", GtkA.WidgetVexpandSetPropertyInfo), '("visible", GtkA.WidgetVisiblePropertyInfo), '("vscroll-policy", GtkA.ScrollableVscrollPolicyPropertyInfo), '("width-request", GtkA.WidgetWidthRequestPropertyInfo), '("window", GtkA.WidgetWindowPropertyInfo), '("window-title", TerminalWindowTitlePropertyInfo), '("word-char-exceptions", TerminalWordCharExceptionsPropertyInfo)]