File: BufferExCommand.hs

package info (click to toggle)
haskell-yi-keymap-vim 0.19.0-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,512 kB
  • sloc: haskell: 6,068; makefile: 6
file content (174 lines) | stat: -rw-r--r-- 6,349 bytes parent folder | download | duplicates (4)
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
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
{-# LANGUAGE OverloadedStrings #-}
-- | Tests for the :buffer ex command in the Vim keymap
--
module Vim.EditorManipulations.BufferExCommand (tests) where

import qualified Data.List.NonEmpty as NE
import           Generic.TestUtils
import           Test.Tasty (TestTree, testGroup)
import           Test.Tasty.HUnit
import           Yi.Buffer
import           Yi.Config (Config)
import           Yi.Editor
import           Yi.Rope ()

type BufferName = String

-- | Create three bufs and return the 'BufferRef' and buffer name of
-- each.
createInitialBuffers :: EditorM [(BufferRef, BufferName)]
createInitialBuffers = do
  one   <- newBufferE (FileBuffer "one")   "Buffer one"
  two   <- newBufferE (FileBuffer "two")   "Buffer two"
  three <- newBufferE (FileBuffer "three") "Buffer three"
  return [(one, "one"), (two, "two"), (three, "three")]


nthBufferRef :: Int -> [(BufferRef, BufferName)] -> BufferRef
nthBufferRef n bufs = fst $ bufs !! n

nthBufferName :: Int -> [(BufferRef, BufferName)] -> BufferName
nthBufferName n bufs = snd $ bufs !! n


tests :: Config -> KeyEval -> TestTree
tests c ev =
    testGroup ":buffer" [
        testCase ":buffer {bufname} switches to the named buffer" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

                testActions bufs =
                    ev $ ":buffer " ++ nthBufferName 1 bufs ++ "<CR>"

                assertions editor bufs = do
                    assertContentOfCurrentBuffer c "Buffer two" editor
                    assertCurrentBuffer (nthBufferRef 1 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase ":buffer N switches to the numbered buffer" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

                testActions bufs =
                    let (BufferRef bref) = nthBufferRef 1 bufs
                    in ev $ ":buffer " ++ show bref ++ "<CR>"

                assertions editor bufs = do
                    assertContentOfCurrentBuffer c "Buffer two" editor
                    assertCurrentBuffer (nthBufferRef 1 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase ":buffer # switches to the previous buffer" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertEqual "Unexpected buffer stack"
                        [nthBufferRef 2 bufs, nthBufferRef 1 bufs]
                        (take 2 . NE.toList $ bufferStack editor)

                testActions _ =
                    ev $ ":buffer #<CR>"

                assertions editor bufs = do
                    assertEqual "Unexpected buffer stack"
                        [nthBufferRef 1 bufs, nthBufferRef 2 bufs]
                        (take 2 . NE.toList $ bufferStack editor)

            runTest setupActions preConditions testActions assertions c


      , testCase ":buffer % is a no-op" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertCurrentBuffer (nthBufferRef 2 bufs) editor

                testActions _ =
                    ev $ ":buffer %<CR>"

                assertions editor bufs = do
                    assertContentOfCurrentBuffer c "Buffer three" editor
                    assertCurrentBuffer (nthBufferRef 2 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase ":buffer is a no-op" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertCurrentBuffer (nthBufferRef 2 bufs) editor

                testActions _ =
                    ev $ ":buffer<CR>"

                assertions editor bufs = do
                    assertContentOfCurrentBuffer c "Buffer three" editor
                    assertCurrentBuffer (nthBufferRef 2 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase "A modified buffer is not abandoned" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

                testActions bufs = do
                    withCurrentBuffer $ insertN "The buffer is altered"
                    ev $ ":buffer " ++ nthBufferName 1 bufs ++ "<CR>"

                assertions editor bufs = do
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase "A modified buffer can be abandoned with a bang" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

                testActions bufs = do
                    withCurrentBuffer $ insertN "The buffer is altered"
                    ev $ ":buffer! " ++ nthBufferName 1 bufs ++ "<CR>"

                assertions editor bufs = do
                    assertCurrentBuffer (nthBufferRef 1 bufs) editor

            runTest setupActions preConditions testActions assertions c


      , testCase ":Nbuffer switches to the numbered buffer" $ do
            let setupActions = createInitialBuffers

                preConditions editor bufs =
                    assertNotCurrentBuffer (nthBufferRef 1 bufs) editor

                testActions bufs =
                    -- return ()
                    let (BufferRef bref) = nthBufferRef 1 bufs
                    in ev $ ":" ++ show bref ++ "buffer<CR>"
                    -- in ev $ ":buffer " ++ show bref ++ "<CR>"

                assertions editor bufs = do
                    -- assertContentOfCurrentBuffer c "Buffer two" editor
                    assertCurrentBuffer (nthBufferRef 1 bufs) editor

            runTest setupActions preConditions testActions assertions c


      -- , testCase "A named buffer can be shown in a split window" $ do
      -- , testCase "A numbered buffer can be shown in a split window" $ do
    ]