File: EditorLineNumbersDemo.hs

package info (click to toggle)
haskell-brick 2.1.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, trixie
  • size: 1,328 kB
  • sloc: haskell: 8,492; makefile: 5
file content (135 lines) | stat: -rw-r--r-- 4,737 bytes parent folder | download | duplicates (2)
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
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
module Main where

import Control.Monad (void)
import Lens.Micro
import Lens.Micro.TH
import Lens.Micro.Mtl
import qualified Graphics.Vty as V
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup ((<>))
#endif

import qualified Brick.Main as M
import qualified Brick.Types as T
import Brick.Widgets.Core
  ( (<+>)
  , vBox
  , hLimit
  , vLimit
  , str
  , visible
  , viewport
  , withDefAttr
  )
import qualified Brick.Widgets.Center as C
import qualified Brick.Widgets.Edit as E
import qualified Brick.AttrMap as A
import Brick.Util (on, fg)

data Name = Edit
          | EditLines
          deriving (Ord, Show, Eq)

data St =
    St { _edit :: E.Editor String Name
       }

makeLenses ''St

drawUI :: St -> [T.Widget Name]
drawUI st = [ui]
    where
        e = renderWithLineNumbers (st^.edit)
        ui = C.center $ hLimit 50 $ vLimit 10 e

-- | Given an editor, render the editor with line numbers to the left of
-- the editor.
--
-- This essentially exploits knowledge of how the editor is implemented:
-- we make a viewport containing line numbers that is just as high as
-- the editor, then request that the line number associated with the
-- editor's current line position be made visible, thus scrolling it
-- into view. This is slightly brittle, however, because it relies on
-- essentially keeping the line number viewport and the editor viewport
-- in the same vertical scrolling state; with direct scrolling requests
-- from EventM it is easily possible to put the two viewports into a
-- state where they do not have the same vertical scrolling offset. That
-- means that visibility requests made with 'visible' won't necessarily
-- have the same effect in each viewport in that case. So this is
-- only really usable in the case where you're sure that the editor's
-- viewport and the line number viewports will not be managed by direct
-- viewport operations in EventM. That's what I'd recommend anyway, but
-- still, this is an important caveat.
--
-- There's another important caveat here: this particular implementation
-- has @O(n)@ performance for editor height @n@ because we generate
-- the entire list of line numbers on each rendering depending on the
-- height of the editor. That means that for sufficiently large files,
-- it will get more expensive to render the line numbers. There is a way
-- around this problem, which is to take the approach that the @List@
-- implementation takes: only render a region of visible line numbers
-- around the currently-edited line that is just large enough to be
-- guaranteed to fill the viewport, then translate that so that it
-- appears at the right viewport offset, thus faking a viewport filled
-- with line numbers when in fact we'd only ever render at most @2 * K +
-- 1@ line numbers for a viewport height of @K@. That's more involved,
-- so I didn't do it here, but that would be the way to go for a Real
-- Application.
renderWithLineNumbers :: E.Editor String Name -> T.Widget Name
renderWithLineNumbers e =
    lineNumbersVp <+> editorVp
    where
        lineNumbersVp = hLimit (maxNumWidth + 1) $ viewport EditLines T.Vertical body
        editorVp = E.renderEditor (str . unlines) True e
        body = withDefAttr lineNumberAttr $ vBox numWidgets
        numWidgets = mkNumWidget <$> numbers
        mkNumWidget i = maybeVisible i $ str $ show i
        maybeVisible i
            | i == curLine + 1 =
                visible . withDefAttr currentLineNumberAttr
            | otherwise =
                id
        numbers = [1..h]
        contents = E.getEditContents e
        h = length contents
        curLine = fst $ E.getCursorPosition e
        maxNumWidth = length $ show h

appEvent :: T.BrickEvent Name e -> T.EventM Name St ()
appEvent (T.VtyEvent (V.EvKey V.KEsc [])) =
    M.halt
appEvent ev = do
    zoom edit $ E.handleEditorEvent ev

initialState :: St
initialState =
    St (E.editor Edit Nothing "")

lineNumberAttr :: A.AttrName
lineNumberAttr = A.attrName "lineNumber"

currentLineNumberAttr :: A.AttrName
currentLineNumberAttr = lineNumberAttr <> A.attrName "current"

theMap :: A.AttrMap
theMap = A.attrMap V.defAttr
    [ (E.editAttr,              V.white `on` V.blue)
    , (E.editFocusedAttr,       V.black `on` V.yellow)
    , (lineNumberAttr,          fg V.cyan)
    , (currentLineNumberAttr,   V.defAttr `V.withStyle` V.bold)
    ]

theApp :: M.App St e Name
theApp =
    M.App { M.appDraw = drawUI
          , M.appChooseCursor = const $ M.showCursorNamed Edit
          , M.appHandleEvent = appEvent
          , M.appStartEvent = return ()
          , M.appAttrMap = const theMap
          }

main :: IO ()
main = do
    void $ M.defaultMain theApp initialState