File: Theme.hs

package info (click to toggle)
haskell-hledger-ui 1.32.3-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, trixie
  • size: 420 kB
  • sloc: haskell: 2,443; makefile: 5
file content (113 lines) | stat: -rw-r--r-- 5,506 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
-- | The all-important theming engine!
--
-- Cf
-- https://hackage.haskell.org/package/vty/docs/Graphics-Vty-Attributes.html
-- http://hackage.haskell.org/package/brick/docs/Brick-AttrMap.html
-- http://hackage.haskell.org/package/brick-0.1/docs/Brick-Util.html
-- http://hackage.haskell.org/package/brick-0.1/docs/Brick-Widgets-Core.html#g:5
-- http://hackage.haskell.org/package/brick-0.1/docs/Brick-Widgets-Border.html

{-# LANGUAGE OverloadedStrings #-}

module Hledger.UI.Theme (
   defaultTheme
  ,getTheme
  ,themes
  ,themeNames
)
where

import qualified Data.Map as M
import Data.Maybe
import Graphics.Vty
import Brick

defaultTheme :: AttrMap
defaultTheme = fromMaybe (snd $ head themesList) $ getTheme "white"
  -- the theme named here should exist;
  -- otherwise it will take the first one from the list,
  -- which must be non-empty.

-- | Look up the named theme, if it exists.
getTheme :: String -> Maybe AttrMap
getTheme name = M.lookup name themes

-- | A selection of named themes specifying terminal colours and styles.
-- One of these is active at a time.
--
-- A hledger-ui theme is a vty/brick AttrMap.  Each theme specifies a
-- default style (Attr), plus extra styles which are applied when
-- their (hierarchical) name matches the widget rendering context.
-- "More specific styles, if present, are used and only fall back to
-- more general ones when the more specific ones are absent, but also
-- these styles get merged, so that if a more specific style only
-- provides the foreground color, its more general parent style can
-- set the background color, too."
-- For example: rendering a widget named "b" inside a widget named "a",
-- - if a style named "a" <> "b" exists, it will be used. Anything it
--   does not specify will be taken from a style named "a" if that
--   exists, otherwise from the default style.
-- - otherwise if a style named "a" exists, it will be used, and
--   anything it does not specify will be taken from the default style.
-- - otherwise (you guessed it) the default style is used.
--
themes :: M.Map String AttrMap
themes = M.fromList themesList

themeNames :: [String]
themeNames = map fst themesList

(&) = withStyle
active = fg brightWhite & bold
selectbg = yellow
select = black `on` selectbg

themesList :: [(String, AttrMap)]
themesList = [
   ("default", attrMap (black `on` white) [
     (attrName "border"                                        , white `on` black & dim)
    ,(attrName "border" <> attrName "bold"                              , currentAttr & bold)
    ,(attrName "border" <> attrName "depth"                             , active)
    ,(attrName "border" <> attrName "filename"                          , currentAttr)
    ,(attrName "border" <> attrName "key"                               , active)
    ,(attrName "border" <> attrName "minibuffer"                        , white `on` black & bold)
    ,(attrName "border" <> attrName "query"                             , active)
    ,(attrName "border" <> attrName "selected"                          , active)
    ,(attrName "error"                                         , fg red)
    ,(attrName "help"                                          , white `on` black & dim)
    ,(attrName "help" <> attrName "heading"                             , fg yellow)
    ,(attrName "help" <> attrName "key"                                 , active)
    -- ,(attrName "list"                                          , black `on` white)
    -- ,(attrName "list" <> attrName "amount"                              , currentAttr)
    ,(attrName "list" <> attrName "amount" <> attrName "decrease"                , fg red)
    -- ,(attrName "list" <> attrName "amount" <> attrName "increase"                , fg green)
    ,(attrName "list" <> attrName "amount" <> attrName "decrease" <> attrName "selected"  , red `on` selectbg & bold)
    -- ,(attrName "list" <> attrName "amount" <> attrName "increase" <> attrName "selected"  , green `on` selectbg & bold)
    ,(attrName "list" <> attrName "balance"                             , currentAttr & bold)
    ,(attrName "list" <> attrName "balance" <> attrName "negative"               , fg red)
    ,(attrName "list" <> attrName "balance" <> attrName "positive"               , fg black)
    ,(attrName "list" <> attrName "balance" <> attrName "negative" <> attrName "selected" , red `on` selectbg & bold)
    ,(attrName "list" <> attrName "balance" <> attrName "positive" <> attrName "selected" , select & bold)
    ,(attrName "list" <> attrName "selected"                            , select)
    -- ,(attrName "list" <> attrName "accounts"                         , white `on` brightGreen)
    -- ,(attrName "list" <> attrName "selected"                         , black `on` brightYellow)
  ])

  ,("greenterm", attrMap (green `on` black) [
    (attrName "list" <> attrName "selected"                             , black `on` green)
  ])

  ,("terminal", attrMap defAttr [
    (attrName "border"                                         , white `on` black),
    (attrName "list"                                           , defAttr),
    (attrName "list" <> attrName "selected"                             , defAttr & reverseVideo)
  ])

  ]

-- halfbrightattr = defAttr & dim
-- reverseattr = defAttr & reverseVideo
-- redattr = defAttr `withForeColor` red
-- greenattr = defAttr `withForeColor` green
-- reverseredattr = defAttr & reverseVideo `withForeColor` red
-- reversegreenattr= defAttr & reverseVideo `withForeColor` green