| Copyright | (c) Dennis Gosnell 2018 |
|---|---|
| License | BSD3 |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Termonad.Config.Colour
Contents
Description
To use this config extension in your ~/.config/termonad/termonad.hs, first
import this module. Create a new ColourExtension with the createColourExtension function.
Then add the ColourExtension to your TMConfig with the addColourExtension function.
See this code for a simple example.
Synopsis
- data ColourConfig c = ColourConfig {
- cursorFgColour :: !(Option c)
- cursorBgColour :: !(Option c)
- foregroundColour :: !c
- backgroundColour :: !c
- palette :: !(Palette c)
- defaultColourConfig :: ColourConfig (Colour Double)
- lensCursorFgColour :: forall c. Lens' (ColourConfig c) (Option c)
- lensCursorBgColour :: forall c. Lens' (ColourConfig c) (Option c)
- lensForegroundColour :: forall c. Lens' (ColourConfig c) c
- lensBackgroundColour :: forall c. Lens' (ColourConfig c) c
- lensPalette :: forall c. Lens' (ColourConfig c) (Palette c)
- data ColourExtension = ColourExtension {
- colourExtConf :: MVar (ColourConfig (Colour Double))
- colourExtCreateTermHook :: TMState -> Terminal -> IO ()
- createColourExtension :: ColourConfig (Colour Double) -> IO ColourExtension
- createDefColourExtension :: IO ColourExtension
- addColourExtension :: TMConfig -> ColourExtension -> TMConfig
- addColourConfig :: TMConfig -> ColourConfig (Colour Double) -> IO TMConfig
- colourHook :: MVar (ColourConfig (Colour Double)) -> TMState -> Terminal -> IO ()
- addColourHook :: (TMState -> Terminal -> IO ()) -> (TMState -> Terminal -> IO ()) -> TMState -> Terminal -> IO ()
- data Palette c
- defaultStandardColours :: (Ord b, Floating b) => Vec N8 (Colour b)
- defaultLightColours :: (Ord b, Floating b) => Vec N8 (Colour b)
- defaultColourCube :: (Ord b, Floating b) => Matrix '[N6, N6, N6] (Colour b)
- defaultGreyscale :: (Ord b, Floating b) => Vec N24 (Colour b)
- data Colour a
- sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b
- sRGB24show :: (RealFrac b, Floating b) => Colour b -> String
- showColourVec :: forall n. Vec n (Colour Double) -> [String]
- showColourCube :: Matrix '[N6, N6, N6] (Colour Double) -> String
- paletteToList :: Palette c -> [c]
- coloursFromBits :: forall b. (Ord b, Floating b) => Word8 -> Word8 -> Vec N8 (Colour b)
- cube :: forall b. Fractional b => Colour b -> Vec N3 (Colour b) -> Matrix '[N6, N6, N6] (Colour b)
Colour Config
data ColourConfig c Source #
The configuration for the colors used by Termonad.
foregroundColour and backgroundColour allow you to set the color of the
foreground text and background of the terminal (although see the WARNING
below). Most people use a black background and a light foreground for their
terminal, so this is the default.
palette allows you to set the full color palette used by the terminal.
See Palette for more information.
If you want to use a terminal with a white (or light) background and a black
foreground, it may be a good idea to change some of the colors in the
Palette as well.
(WARNING: Currently due to issues either with VTE or the bindings generated for
Haskell, background colour cannot be set independently of the palette.
The backgroundColour field will be ignored and the 0th colour in the
palette (by default black) will be used as the background colour. See
this issue.
VTE works as follows: if you don't explicitly set a background or foreground color,
it takes the 0th colour from the palette to be the background color, and the 7th
colour from the palette to be the foreground color. If you notice oddities with
colouring in certain applications, it may be helpful to make sure that these
palette colours match up with the backgroundColour and foregroundColour you
have set.)
cursorFgColour and cursorBgColour allow you to set the foreground color
of the text under the cursor, as well as the color of the cursor itself.
Termonad will behave differently depending on the combination
cursorFgColour and cursorBgColour being Set vs. Unset.
Here is the summary of the different possibilities:
cursorFgColourisSetandcursorBgColourisSetThe foreground and background colors of the cursor are as you have set.
cursorFgColourisSetandcursorBgColourisUnsetThe cursor background color turns completely black so that it is not visible. The foreground color of the cursor is the color that you have
Set. This ends up being mostly unusable, so you are recommended to alwaysSetcursorBgColourwhen you haveSetcursorFgColour.cursorFgColourisUnsetandcursorBgColourisSetThe cursor background color becomes the color you
Set, while the cursor foreground color doesn't change from the letter it is over. For instance, imagine there is a letter on the screen with a black background and a green foreground. If you bring the cursor overtop of it, the cursor background will be the color you haveSet, while the cursor foreground will be green.This is completely usable, but is slightly annoying if you place the cursor over a letter with the same foreground color as the cursor's background color, because the letter will not be readable. For instance, imagine you have set your cursor background color to red, and somewhere on the screen there is a letter with a black background and a red foreground. If you move your cursor over the letter, the background of the cursor will be red (as you have set), and the cursor foreground will be red (to match the original foreground color of the letter). This will make it so you can't actually read the letter, because the foreground and background are both red.
cursorFgColourisUnsetandcursorBgColourisUnsetThis combination makes the cursor inverse of whatever text it is over. If your cursor is over red text with a black background, the cursor background will be red and the cursor foreground will be black.
This is the default.
See defaultColourConfig for the defaults for ColourConfig used in Termonad.
Constructors
| ColourConfig | |
Fields
| |
Instances
| Functor ColourConfig Source # | |
Defined in Termonad.Config.Colour Methods fmap :: (a -> b) -> ColourConfig a -> ColourConfig b # (<$) :: a -> ColourConfig b -> ColourConfig a # | |
| Eq c => Eq (ColourConfig c) Source # | |
Defined in Termonad.Config.Colour Methods (==) :: ColourConfig c -> ColourConfig c -> Bool # (/=) :: ColourConfig c -> ColourConfig c -> Bool # | |
| Show c => Show (ColourConfig c) Source # | |
Defined in Termonad.Config.Colour Methods showsPrec :: Int -> ColourConfig c -> ShowS # show :: ColourConfig c -> String # showList :: [ColourConfig c] -> ShowS # | |
defaultColourConfig :: ColourConfig (Colour Double) Source #
Default setting for a ColourConfig. The cursor colors are left at their
default for VTE. The foreground text for the terminal is grey and the
background of the terminal is black. The palette is left as the default for
VTE.
>>>let fgGrey = sRGB24 192 192 192>>>let bgBlack = sRGB24 0 0 0>>>let defCC = ColourConfig { cursorFgColour = Unset, cursorBgColour = Unset, foregroundColour = fgGrey, backgroundColour = bgBlack, palette = NoPalette }>>>defaultColourConfig == defCCTrue
Colour Config Lenses
lensCursorFgColour :: forall c. Lens' (ColourConfig c) (Option c) Source #
lensCursorBgColour :: forall c. Lens' (ColourConfig c) (Option c) Source #
lensForegroundColour :: forall c. Lens' (ColourConfig c) c Source #
lensBackgroundColour :: forall c. Lens' (ColourConfig c) c Source #
lensPalette :: forall c. Lens' (ColourConfig c) (Palette c) Source #
Colour Extension
data ColourExtension Source #
Extension that allows setting colors for terminals in Termonad.
Constructors
| ColourExtension | |
Fields
| |
createColourExtension :: ColourConfig (Colour Double) -> IO ColourExtension Source #
Create a ColourExtension based on a given ColourConfig.
Most users will want to use this.
createDefColourExtension :: IO ColourExtension Source #
Create a ColourExtension based on defaultColourConfig.
Note that this is not needed if you just want to use the default colors for
Termonad. However, if you want to pass around the MVar ColourConfig for
extensions to use, then you may need this function.
addColourExtension :: TMConfig -> ColourExtension -> TMConfig Source #
This is similar to addColourConfig, but can be used on a
ColourExtension created with createColourExtension.
addColourConfig :: TMConfig -> ColourConfig (Colour Double) -> IO TMConfig Source #
Add a given ColourConfig to a TMConfig. This adds colourHook to the
createTermHook in TMConfig.
colourHook :: MVar (ColourConfig (Colour Double)) -> TMState -> Terminal -> IO () Source #
The default createTermHook for colourExtCreateTermHook. Set the colors
for a terminal based on the given ColourConfig.
Arguments
| :: (TMState -> Terminal -> IO ()) | New hook |
| -> (TMState -> Terminal -> IO ()) | Old hook |
| -> TMState | |
| -> Terminal | |
| -> IO () |
This function shows how to combine createTermHooks.
This first runs the old hook, followed by the new hook.
This is used internally by addColourConfig and addColourExtension.
Palette
This is the color palette to use for the terminal. Each data constructor lets you set progressively more colors. These colors are used by the terminal to render ANSI escape color codes.
There are 256 total terminal colors. BasicPalette lets you set the first 8,
ExtendedPalette lets you set the first 16, ColourCubePalette lets you set
the first 232, and FullPalette lets you set all 256.
The first 8 colors codes are the standard colors. The next 8 are the extended (light) colors. The next 216 are a full color cube. The last 24 are a grey scale.
The following image gives an idea of what each individual color looks like:

This picture does not exactly match up with Termonad's default colors, but it gives an idea of what each block of colors represents.
You can use defaultStandardColours, defaultLightColours,
defaultColourCube, and defaultGreyscale as a starting point to
customize the colors. The only time you'd need to use a constructor other
than NoPalette is when you want to customize the default colors.
That is to say, using FullPalette with all the defaults should give you the
same result as using NoPalette.
Constructors
| NoPalette | Don't set any colors and just use the default from VTE. This is a black background with light grey text. |
| BasicPalette !(Vec N8 c) | Set the colors from the standard colors. |
| ExtendedPalette !(Vec N8 c) !(Vec N8 c) | Set the colors from the extended (light) colors (as well as standard colors). |
| ColourCubePalette !(Vec N8 c) !(Vec N8 c) !(Matrix '[N6, N6, N6] c) | Set the colors from the color cube (as well as the standard colors and extended colors). |
| FullPalette !(Vec N8 c) !(Vec N8 c) !(Matrix '[N6, N6, N6] c) !(Vec N24 c) | Set the colors from the grey scale (as well as the standard colors, extended colors, and color cube). |
Instances
| Functor Palette Source # | |
| Foldable Palette Source # | |
Defined in Termonad.Config.Colour Methods fold :: Monoid m => Palette m -> m # foldMap :: Monoid m => (a -> m) -> Palette a -> m # foldr :: (a -> b -> b) -> b -> Palette a -> b # foldr' :: (a -> b -> b) -> b -> Palette a -> b # foldl :: (b -> a -> b) -> b -> Palette a -> b # foldl' :: (b -> a -> b) -> b -> Palette a -> b # foldr1 :: (a -> a -> a) -> Palette a -> a # foldl1 :: (a -> a -> a) -> Palette a -> a # elem :: Eq a => a -> Palette a -> Bool # maximum :: Ord a => Palette a -> a # minimum :: Ord a => Palette a -> a # | |
| Eq c => Eq (Palette c) Source # | |
| Show c => Show (Palette c) Source # | |
defaultStandardColours :: (Ord b, Floating b) => Vec N8 (Colour b) Source #
A Vec of standard colors. Default value for BasicPalette.
>>>showColourVec defaultStandardColours["#000000","#c00000","#00c000","#c0c000","#0000c0","#c000c0","#00c0c0","#c0c0c0"]
defaultLightColours :: (Ord b, Floating b) => Vec N8 (Colour b) Source #
A Vec of extended (light) colors. Default value for ExtendedPalette.
>>>showColourVec defaultLightColours["#3f3f3f","#ff3f3f","#3fff3f","#ffff3f","#3f3fff","#ff3fff","#3fffff","#ffffff"]
defaultColourCube :: (Ord b, Floating b) => Matrix '[N6, N6, N6] (Colour b) Source #
A matrix of a 6 x 6 x 6 color cube. Default value for ColourCubePalette.
>>>putStrLn $ pack $ showColourCube defaultColourCube[ [ #000000, #00005f, #000087, #0000af, #0000d7, #0000ff , #005f00, #005f5f, #005f87, #005faf, #005fd7, #005fff , #008700, #00875f, #008787, #0087af, #0087d7, #0087ff , #00af00, #00af5f, #00af87, #00afaf, #00afd7, #00afff , #00d700, #00d75f, #00d787, #00d7af, #00d7d7, #00d7ff , #00ff00, #00ff5f, #00ff87, #00ffaf, #00ffd7, #00ffff ] , [ #5f0000, #5f005f, #5f0087, #5f00af, #5f00d7, #5f00ff , #5f5f00, #5f5f5f, #5f5f87, #5f5faf, #5f5fd7, #5f5fff , #5f8700, #5f875f, #5f8787, #5f87af, #5f87d7, #5f87ff , #5faf00, #5faf5f, #5faf87, #5fafaf, #5fafd7, #5fafff , #5fd700, #5fd75f, #5fd787, #5fd7af, #5fd7d7, #5fd7ff , #5fff00, #5fff5f, #5fff87, #5fffaf, #5fffd7, #5fffff ] , [ #870000, #87005f, #870087, #8700af, #8700d7, #8700ff , #875f00, #875f5f, #875f87, #875faf, #875fd7, #875fff , #878700, #87875f, #878787, #8787af, #8787d7, #8787ff , #87af00, #87af5f, #87af87, #87afaf, #87afd7, #87afff , #87d700, #87d75f, #87d787, #87d7af, #87d7d7, #87d7ff , #87ff00, #87ff5f, #87ff87, #87ffaf, #87ffd7, #87ffff ] , [ #af0000, #af005f, #af0087, #af00af, #af00d7, #af00ff , #af5f00, #af5f5f, #af5f87, #af5faf, #af5fd7, #af5fff , #af8700, #af875f, #af8787, #af87af, #af87d7, #af87ff , #afaf00, #afaf5f, #afaf87, #afafaf, #afafd7, #afafff , #afd700, #afd75f, #afd787, #afd7af, #afd7d7, #afd7ff , #afff00, #afff5f, #afff87, #afffaf, #afffd7, #afffff ] , [ #d70000, #d7005f, #d70087, #d700af, #d700d7, #d700ff , #d75f00, #d75f5f, #d75f87, #d75faf, #d75fd7, #d75fff , #d78700, #d7875f, #d78787, #d787af, #d787d7, #d787ff , #d7af00, #d7af5f, #d7af87, #d7afaf, #d7afd7, #d7afff , #d7d700, #d7d75f, #d7d787, #d7d7af, #d7d7d7, #d7d7ff , #d7ff00, #d7ff5f, #d7ff87, #d7ffaf, #d7ffd7, #d7ffff ] , [ #ff0000, #ff005f, #ff0087, #ff00af, #ff00d7, #ff00ff , #ff5f00, #ff5f5f, #ff5f87, #ff5faf, #ff5fd7, #ff5fff , #ff8700, #ff875f, #ff8787, #ff87af, #ff87d7, #ff87ff , #ffaf00, #ffaf5f, #ffaf87, #ffafaf, #ffafd7, #ffafff , #ffd700, #ffd75f, #ffd787, #ffd7af, #ffd7d7, #ffd7ff , #ffff00, #ffff5f, #ffff87, #ffffaf, #ffffd7, #ffffff ] ]
defaultGreyscale :: (Ord b, Floating b) => Vec N24 (Colour b) Source #
A Vec of a grey scale. Default value for FullPalette.
>>>showColourVec defaultGreyscale["#080808","#121212","#1c1c1c","#262626","#303030","#3a3a3a","#444444","#4e4e4e","#585858","#626262","#6c6c6c","#767676","#808080","#8a8a8a","#949494","#9e9e9e","#a8a8a8","#b2b2b2","#bcbcbc","#c6c6c6","#d0d0d0","#dadada","#e4e4e4","#eeeeee"]
Colour
Check out the Data.Colour module for more info about Colour.
This type represents the human preception of colour.
The a parameter is a numeric type used internally for the
representation.
The Monoid instance allows one to add colours, but beware that adding
colours can take you out of gamut. Consider using blend whenever
possible.
sRGB24 :: (Ord b, Floating b) => Word8 -> Word8 -> Word8 -> Colour b #
Construct a colour from a 24-bit (three 8-bit words) sRGB specification.
sRGB24show :: (RealFrac b, Floating b) => Colour b -> String #
Show a colour in hexadecimal form, e.g. "#00aaff"
Debugging and Internal Methods
showColourVec :: forall n. Vec n (Colour Double) -> [String] Source #
A helper function for showing all the colors in Vec of colors.
showColourCube :: Matrix '[N6, N6, N6] (Colour Double) -> String Source #
Helper function for showing all the colors in a color cube. This is used for debugging.
paletteToList :: Palette c -> [c] Source #
Convert a Palette to a list of colors. This is helpful for debugging.
coloursFromBits :: forall b. (Ord b, Floating b) => Word8 -> Word8 -> Vec N8 (Colour b) Source #
Create a vector of colors based on input bits.
This is used to derive defaultStandardColours and defaultLightColours.
>>>coloursFromBits 192 0 == defaultStandardColoursTrue
>>>coloursFromBits 192 63 == defaultLightColoursTrue
In general, as an end-user, you shouldn't need to use this.