| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Termonad.Types
Synopsis
- data TMTerm = TMTerm {}
- data TMNotebookTab = TMNotebookTab {}
- data TMNotebook = TMNotebook {}
- data TMState' = TMState {}
- type TMState = MVar TMState'
- createTMTerm :: Terminal -> Int -> Unique -> TMTerm
- newTMTerm :: Terminal -> Int -> IO TMTerm
- getFocusedTermFromState :: TMState -> IO (Maybe Terminal)
- createTMNotebookTab :: Label -> ScrolledWindow -> TMTerm -> TMNotebookTab
- createTMNotebook :: Notebook -> FocusList TMNotebookTab -> TMNotebook
- createEmptyTMNotebook :: Notebook -> TMNotebook
- notebookToList :: Notebook -> IO [Widget]
- newTMState :: TMConfig -> Application -> ApplicationWindow -> TMNotebook -> FontDescription -> IO TMState
- newEmptyTMState :: TMConfig -> Application -> ApplicationWindow -> Notebook -> FontDescription -> IO TMState
- newTMStateSingleTerm :: TMConfig -> Application -> ApplicationWindow -> Notebook -> Label -> ScrolledWindow -> Terminal -> Int -> FontDescription -> IO TMState
- traceShowMTMState :: TMState -> IO ()
- data FontSize
- defaultFontSize :: FontSize
- data FontConfig = FontConfig {
- fontFamily :: !Text
- fontSize :: !FontSize
- defaultFontConfig :: FontConfig
- data Option a
- whenSet :: Monoid m => Option a -> (a -> m) -> m
- data ShowScrollbar
- data ShowTabBar
- data ConfigOptions = ConfigOptions {}
- defaultConfigOptions :: ConfigOptions
- data TMConfig = TMConfig {
- options :: !ConfigOptions
- hooks :: !ConfigHooks
- defaultTMConfig :: TMConfig
- data ConfigHooks = ConfigHooks {
- createTermHook :: TMState -> Terminal -> IO ()
- defaultConfigHooks :: ConfigHooks
- defaultCreateTermHook :: TMState -> Terminal -> IO ()
- data FocusNotSameErr
- data TabsDoNotMatch
- data TMStateInvariantErr
- invariantTMState' :: TMState' -> IO [TMStateInvariantErr]
- assertInvariantTMState :: TMState -> IO ()
- pPrintTMState :: TMState -> IO ()
Documentation
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 | |
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
| Eq TMNotebookTab Source # | |
Defined in Termonad.Types Methods (==) :: TMNotebookTab -> TMNotebookTab -> Bool # (/=) :: TMNotebookTab -> TMNotebookTab -> Bool # | |
| Show TMNotebookTab Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> TMNotebookTab -> ShowS # show :: TMNotebookTab -> String # showList :: [TMNotebookTab] -> ShowS # | |
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
| Show TMNotebook Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> TMNotebook -> ShowS # show :: TMNotebook -> String # showList :: [TMNotebook] -> ShowS # | |
Constructors
| TMState | |
Fields | |
createTMNotebookTab :: Label -> ScrolledWindow -> TMTerm -> TMNotebookTab Source #
newTMState :: TMConfig -> Application -> ApplicationWindow -> TMNotebook -> FontDescription -> IO TMState Source #
newEmptyTMState :: TMConfig -> Application -> ApplicationWindow -> Notebook -> FontDescription -> IO TMState Source #
newTMStateSingleTerm :: TMConfig -> Application -> ApplicationWindow -> Notebook -> Label -> ScrolledWindow -> Terminal -> Int -> FontDescription -> IO TMState Source #
traceShowMTMState :: TMState -> IO () 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 |
| FontSizeUnits Double | This sets the font size based on "device units". In general, this
can be thought of as one pixel. The function
|
defaultFontSize :: FontSize Source #
The default FontSize used if not specified.
>>>defaultFontSizeFontSizePoints 12
data FontConfig Source #
Settings for the font to be used in Termonad.
Constructors
| FontConfig | |
Fields
| |
Instances
| Eq FontConfig Source # | |
Defined in Termonad.Types | |
| Show FontConfig Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> FontConfig -> ShowS # show :: FontConfig -> String # showList :: [FontConfig] -> ShowS # | |
defaultFontConfig :: FontConfig Source #
The default FontConfig to use if not specified.
>>>defaultFontConfig == FontConfig {fontFamily = "Monospace", fontSize = defaultFontSize}True
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.
Instances
| Functor Option Source # | |
| Foldable Option Source # | |
Defined in Termonad.Types Methods fold :: Monoid m => Option m -> 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 # elem :: Eq a => a -> Option a -> Bool # maximum :: Ord a => Option a -> a # minimum :: Ord a => Option a -> a # | |
| Eq a => Eq (Option a) Source # | |
| Ord a => Ord (Option a) Source # | |
Defined in Termonad.Types | |
| Read a => Read (Option a) Source # | |
| Show a => Show (Option a) Source # | |
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
| Eq ShowScrollbar Source # | |
Defined in Termonad.Types Methods (==) :: ShowScrollbar -> ShowScrollbar -> Bool # (/=) :: ShowScrollbar -> ShowScrollbar -> Bool # | |
| Show ShowScrollbar Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> ShowScrollbar -> ShowS # show :: ShowScrollbar -> String # showList :: [ShowScrollbar] -> ShowS # | |
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
| Eq ShowTabBar Source # | |
Defined in Termonad.Types | |
| Show ShowTabBar Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> ShowTabBar -> ShowS # show :: ShowTabBar -> String # showList :: [ShowTabBar] -> ShowS # | |
data ConfigOptions Source #
Configuration options for Termonad.
See defaultConfigOptions for the default values.
Constructors
| ConfigOptions | |
Fields
| |
Instances
| Eq ConfigOptions Source # | |
Defined in Termonad.Types Methods (==) :: ConfigOptions -> ConfigOptions -> Bool # (/=) :: ConfigOptions -> ConfigOptions -> Bool # | |
| Show ConfigOptions Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> ConfigOptions -> ShowS # show :: ConfigOptions -> String # showList :: [ConfigOptions] -> ShowS # | |
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 } in defaultConfigOptions == defConfOpt :} True
The Termonad ConfigOptions along with the ConfigHooks.
Constructors
| TMConfig | |
Fields
| |
defaultTMConfig :: TMConfig Source #
The default TMConfig.
options is defaultConfigOptions and hooks is defaultConfigHooks.
data 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
| Show ConfigHooks Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> ConfigHooks -> ShowS # show :: ConfigHooks -> String # showList :: [ConfigHooks] -> ShowS # | |
defaultConfigHooks :: ConfigHooks Source #
Default values for the ConfigHooks.
- The default function for
createTermHookisdefaultCreateTermHook.
defaultCreateTermHook :: TMState -> Terminal -> IO () Source #
Default value for createTermHook. Does nothing.
data FocusNotSameErr Source #
Constructors
| FocusListFocusExistsButNoNotebookTabWidget | |
| NotebookTabWidgetDiffersFromFocusListFocus | |
| NotebookTabWidgetExistsButNoFocusListFocus |
Instances
| Show FocusNotSameErr Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> FocusNotSameErr -> ShowS # show :: FocusNotSameErr -> String # showList :: [FocusNotSameErr] -> ShowS # | |
data TabsDoNotMatch Source #
Constructors
| TabLengthsDifferent Int Int | The first |
| TabAtIndexDifferent Int | The tab at index |
Instances
| Show TabsDoNotMatch Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> TabsDoNotMatch -> ShowS # show :: TabsDoNotMatch -> String # showList :: [TabsDoNotMatch] -> ShowS # | |
data TMStateInvariantErr Source #
Constructors
| FocusNotSame FocusNotSameErr Int | |
| TabsDoNotMatch TabsDoNotMatch |
Instances
| Show TMStateInvariantErr Source # | |
Defined in Termonad.Types Methods showsPrec :: Int -> TMStateInvariantErr -> ShowS # show :: TMStateInvariantErr -> String # showList :: [TMStateInvariantErr] -> ShowS # | |
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 #
pPrintTMState :: TMState -> IO () Source #