termonad-4.4.0.0: Terminal emulator configurable in Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Termonad.Types

Synopsis

Documentation

data TMTerm Source #

A wrapper around a VTE Terminal. This also stores the process ID of the process running on this terminal, as well as a Unique that can be used for comparing terminals.

Constructors

TMTerm 

Fields

Instances

Instances details
Show TMTerm Source # 
Instance details

Defined in Termonad.Types

Eq TMTerm Source # 
Instance details

Defined in Termonad.Types

Methods

(==) :: TMTerm -> TMTerm -> Bool #

(/=) :: TMTerm -> TMTerm -> Bool #

data TMNotebookTab Source #

A container that holds everything in a given terminal window. The term in the TMTerm is inside the tmNotebookTabTermContainer ScrolledWindow. The notebook tab Label is also available.

Constructors

TMNotebookTab 

Fields

Instances

Instances details
Show TMNotebookTab Source # 
Instance details

Defined in Termonad.Types

Eq TMNotebookTab Source # 
Instance details

Defined in Termonad.Types

data TMNotebook Source #

This holds the GTK Notebook containing multiple tabs of Terminals. We keep a separate list of terminals in tmNotebookTabs.

Constructors

TMNotebook 

Fields

Instances

Instances details
Show TMNotebook Source # 
Instance details

Defined in Termonad.Types

data FontSize Source #

The font size for the Termonad terminal. There are two ways to set the fontsize, corresponding to the two different ways to set the font size in the Pango font rendering library.

If you're not sure which to use, try FontSizePoints first and see how it looks. It should generally correspond to font sizes you are used to from other applications.

Constructors

FontSizePoints Int

This sets the font size based on "points". The conversion between a point and an actual size depends on the system configuration and the output device. The function fontDescriptionSetSize is used to set the font size. See the documentation for that function for more info.

FontSizeUnits Double

This sets the font size based on "device units". In general, this can be thought of as one pixel. The function fontDescriptionSetAbsoluteSize is used to set the font size. See the documentation for that function for more info.

Instances

Instances details
FromJSON FontSize Source # 
Instance details

Defined in Termonad.Types

ToJSON FontSize Source # 
Instance details

Defined in Termonad.Types

Generic FontSize Source # 
Instance details

Defined in Termonad.Types

Associated Types

type Rep FontSize :: Type -> Type #

Methods

from :: FontSize -> Rep FontSize x #

to :: Rep FontSize x -> FontSize #

Show FontSize Source # 
Instance details

Defined in Termonad.Types

Eq FontSize Source # 
Instance details

Defined in Termonad.Types

type Rep FontSize Source # 
Instance details

Defined in Termonad.Types

type Rep FontSize = D1 ('MetaData "FontSize" "Termonad.Types" "termonad-4.4.0.0-inplace" 'False) (C1 ('MetaCons "FontSizePoints" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "FontSizeUnits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double)))

defaultFontSize :: FontSize Source #

The default FontSize used if not specified.

>>> defaultFontSize
FontSizePoints 12

modFontSize :: Int -> FontSize -> FontSize Source #

Modify a FontSize by adding some value.

>>> modFontSize 1 (FontSizePoints 13)
FontSizePoints 14
>>> modFontSize 1 (FontSizeUnits 9.0)
FontSizeUnits 10.0

You can reduce the font size by passing a negative value.

>>> modFontSize (-2) (FontSizePoints 13)
FontSizePoints 11

If you try to create a font size less than 1, then the old font size will be used.

>>> modFontSize (-10) (FontSizePoints 5)
FontSizePoints 5
>>> modFontSize (-1) (FontSizeUnits 1.0)
FontSizeUnits 1.0

data FontConfig Source #

Settings for the font to be used in Termonad.

Constructors

FontConfig 

Fields

Instances

Instances details
FromJSON FontConfig Source # 
Instance details

Defined in Termonad.Types

ToJSON FontConfig Source # 
Instance details

Defined in Termonad.Types

Generic FontConfig Source # 
Instance details

Defined in Termonad.Types

Associated Types

type Rep FontConfig :: Type -> Type #

Show FontConfig Source # 
Instance details

Defined in Termonad.Types

Eq FontConfig Source # 
Instance details

Defined in Termonad.Types

type Rep FontConfig Source # 
Instance details

Defined in Termonad.Types

type Rep FontConfig = D1 ('MetaData "FontConfig" "Termonad.Types" "termonad-4.4.0.0-inplace" 'False) (C1 ('MetaCons "FontConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "fontFamily") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "fontSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FontSize)))

defaultFontConfig :: FontConfig Source #

The default FontConfig to use if not specified.

>>> defaultFontConfig == FontConfig {fontFamily = "Monospace", fontSize = defaultFontSize}
True

data Option a Source #

This data type represents an option that can either be Set or Unset.

This data type is used in situations where leaving an option unset results in a special state that is not representable by setting any specific value.

Examples of this include the cursorFgColour and cursorBgColour options supplied by the ColourConfig ConfigExtension. By default, cursorFgColour and cursorBgColour are both Unset. However, when cursorBgColour is Set, cursorFgColour defaults to the color of the text underneath. There is no way to represent this by setting cursorFgColour.

Constructors

Unset 
Set !a 

Instances

Instances details
Foldable Option Source # 
Instance details

Defined in Termonad.Types

Methods

fold :: Monoid m => Option m -> m #

foldMap :: Monoid m => (a -> m) -> Option a -> m #

foldMap' :: Monoid m => (a -> m) -> Option a -> m #

foldr :: (a -> b -> b) -> b -> Option a -> b #

foldr' :: (a -> b -> b) -> b -> Option a -> b #

foldl :: (b -> a -> b) -> b -> Option a -> b #

foldl' :: (b -> a -> b) -> b -> Option a -> b #

foldr1 :: (a -> a -> a) -> Option a -> a #

foldl1 :: (a -> a -> a) -> Option a -> a #

toList :: Option a -> [a] #

null :: Option a -> Bool #

length :: Option a -> Int #

elem :: Eq a => a -> Option a -> Bool #

maximum :: Ord a => Option a -> a #

minimum :: Ord a => Option a -> a #

sum :: Num a => Option a -> a #

product :: Num a => Option a -> a #

Functor Option Source # 
Instance details

Defined in Termonad.Types

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Read a => Read (Option a) Source # 
Instance details

Defined in Termonad.Types

Show a => Show (Option a) Source # 
Instance details

Defined in Termonad.Types

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Eq a => Eq (Option a) Source # 
Instance details

Defined in Termonad.Types

Methods

(==) :: Option a -> Option a -> Bool #

(/=) :: Option a -> Option a -> Bool #

Ord a => Ord (Option a) Source # 
Instance details

Defined in Termonad.Types

Methods

compare :: Option a -> Option a -> Ordering #

(<) :: Option a -> Option a -> Bool #

(<=) :: Option a -> Option a -> Bool #

(>) :: Option a -> Option a -> Bool #

(>=) :: Option a -> Option a -> Bool #

max :: Option a -> Option a -> Option a #

min :: Option a -> Option a -> Option a #

whenSet :: Monoid m => Option a -> (a -> m) -> m Source #

Run a function over the value contained in an Option. Return mempty when Option is Unset.

>>> whenSet (Set [1,2,3]) (++ [4,5,6]) :: [Int]
[1,2,3,4,5,6]
>>> whenSet Unset (++ [4,5,6]) :: [Int]
[]

data ShowScrollbar Source #

Whether or not to show the scroll bar in a terminal.

Constructors

ShowScrollbarNever

Never show the scroll bar, even if there are too many lines on the terminal to show all at once. You should still be able to scroll with the mouse wheel.

ShowScrollbarAlways

Always show the scrollbar, even if it is not needed.

ShowScrollbarIfNeeded

Only show the scrollbar if there are too many lines on the terminal to show all at once.

Instances

Instances details
FromJSON ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

ToJSON ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

Enum ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

Generic ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

Associated Types

type Rep ShowScrollbar :: Type -> Type #

Show ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

Eq ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

type Rep ShowScrollbar Source # 
Instance details

Defined in Termonad.Types

type Rep ShowScrollbar = D1 ('MetaData "ShowScrollbar" "Termonad.Types" "termonad-4.4.0.0-inplace" 'False) (C1 ('MetaCons "ShowScrollbarNever" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ShowScrollbarAlways" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShowScrollbarIfNeeded" 'PrefixI 'False) (U1 :: Type -> Type)))

data ShowTabBar Source #

Whether or not to show the tab bar for switching tabs.

Constructors

ShowTabBarNever

Never show the tab bar, even if there are multiple tabs open. This may be confusing if you plan on using multiple tabs.

ShowTabBarAlways

Always show the tab bar, even if you only have one tab open.

ShowTabBarIfNeeded

Only show the tab bar if you have multiple tabs open.

Instances

Instances details
FromJSON ShowTabBar Source # 
Instance details

Defined in Termonad.Types

ToJSON ShowTabBar Source # 
Instance details

Defined in Termonad.Types

Enum ShowTabBar Source # 
Instance details

Defined in Termonad.Types

Generic ShowTabBar Source # 
Instance details

Defined in Termonad.Types

Associated Types

type Rep ShowTabBar :: Type -> Type #

Show ShowTabBar Source # 
Instance details

Defined in Termonad.Types

Eq ShowTabBar Source # 
Instance details

Defined in Termonad.Types

type Rep ShowTabBar Source # 
Instance details

Defined in Termonad.Types

type Rep ShowTabBar = D1 ('MetaData "ShowTabBar" "Termonad.Types" "termonad-4.4.0.0-inplace" 'False) (C1 ('MetaCons "ShowTabBarNever" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ShowTabBarAlways" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ShowTabBarIfNeeded" 'PrefixI 'False) (U1 :: Type -> Type)))

data ConfigOptions Source #

Configuration options for Termonad.

See defaultConfigOptions for the default values.

Constructors

ConfigOptions 

Fields

Instances

Instances details
FromJSON ConfigOptions Source # 
Instance details

Defined in Termonad.Types

ToJSON ConfigOptions Source # 
Instance details

Defined in Termonad.Types

Generic ConfigOptions Source # 
Instance details

Defined in Termonad.Types

Associated Types

type Rep ConfigOptions :: Type -> Type #

Show ConfigOptions Source # 
Instance details

Defined in Termonad.Types

Eq ConfigOptions Source # 
Instance details

Defined in Termonad.Types

type Rep ConfigOptions Source # 
Instance details

Defined in Termonad.Types

defaultConfigOptions :: ConfigOptions Source #

The default ConfigOptions.

>>> :{
  let defConfOpt =
        ConfigOptions
          { fontConfig = defaultFontConfig
          , showScrollbar = ShowScrollbarIfNeeded
          , scrollbackLen = 10000
          , confirmExit = True
          , wordCharExceptions = "-#%&+,./=?@\\_~\183:"
          , showMenu = True
          , showTabBar = ShowTabBarIfNeeded
          , cursorBlinkMode = CursorBlinkModeOn
          , boldIsBright = False
          , enableSixel = False
          }
  in defaultConfigOptions == defConfOpt
:}
True

data TMConfig Source #

The Termonad ConfigOptions along with the ConfigHooks.

Constructors

TMConfig 

Instances

Instances details
Show TMConfig Source # 
Instance details

Defined in Termonad.Types

newtype ConfigHooks Source #

Hooks into certain termonad operations and VTE events. Used to modify termonad's behaviour in order to implement new functionality. Fields should have sane Semigroup and Monoid instances so that config extensions can be combined uniformly and new hooks can be added without incident.

Constructors

ConfigHooks 

Fields

Instances

Instances details
Show ConfigHooks Source # 
Instance details

Defined in Termonad.Types

defaultConfigHooks :: ConfigHooks Source #

Default values for the ConfigHooks.

defaultCreateTermHook :: TMState -> Terminal -> IO () Source #

Default value for createTermHook. Does nothing.

data TabsDoNotMatch Source #

Constructors

TabLengthsDifferent Int Int

The first Int is the number of tabs in the actual GTK Notebook. The second Int is the number of tabs in the FocusList.

TabAtIndexDifferent Int

The tab at index Int is different between the actual GTK Notebook and the FocusList.

Instances

Instances details
Show TabsDoNotMatch Source # 
Instance details

Defined in Termonad.Types

invariantTMState' :: TMState' -> IO [TMStateInvariantErr] Source #

Gather up the invariants for TMState and return them as a list.

If no invariants have been violated, then this function should return an empty list.

assertInvariantTMState :: TMState -> IO () Source #

Check the invariants for TMState, and call fail if we find that they have been violated.

Orphan instances