Skip to content

Commit fa72f73

Browse files
clojjChrisPenner
authored andcommitted
Introduce BufTextChanged event (hiding text lenses and range lens)
1 parent eb2f7ff commit fa72f73

File tree

13 files changed

+46
-19
lines changed

13 files changed

+46
-19
lines changed

.gitignore

+1
Original file line numberDiff line numberDiff line change
@@ -19,3 +19,4 @@ cabal.sandbox.config
1919
cabal.project.local
2020
.HTF/
2121
*.log
22+
.imdone/

rasa-example-config/app/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -29,4 +29,4 @@ main = rasa $ do
2929
logger
3030
slate
3131
style
32-
onInit . void $ newBuffer "This is a buffer to get you started!\nYou can also pass command line args to rasa"
32+
onInit . void $ newBuffer "This is a buffer to get you started!\nYou can also pass command line args to rasa"

rasa-ext-cursors/src/Rasa/Ext/Cursors/Internal/Actions.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ findNext pat = do
5151
-- | Get the 'Coord' of the next occurence of the given text after the given 'Coord'
5252
findNextFrom :: Y.YiString -> Coord -> BufAction Coord
5353
findNextFrom pat c = do
54-
distance <- use (text . afterC c . asText . tillNext (Y.toText pat) . from asText . to sizeOf)
54+
distance <- use (getText . afterC c . asText . tillNext (Y.toText pat) . from asText . to sizeOf)
5555
return (distance + c)
5656

5757
-- | Move all ranges to the location of the previous occurence of the given text.
@@ -66,9 +66,9 @@ findPrev pat = do
6666
-- | Get the 'Coord' of the previous occurence of the given text before the given 'Coord'
6767
findPrevFrom :: Y.YiString -> Coord -> BufAction Coord
6868
findPrevFrom pat c = do
69-
txt <- use text
69+
txt <- use getText
7070
let Offset o = c^.from (asCoord txt)
71-
distance <- use (text . asText . before o . tillPrev (Y.toText pat) . to T.length .to negate)
71+
distance <- use (getText . asText . before o . tillPrev (Y.toText pat) . to T.length .to negate)
7272
return ((Offset $ distance + o)^.asCoord txt)
7373

7474
-- | Move all ranges by the given number of columns

rasa-ext-cursors/src/Rasa/Ext/Cursors/Internal/Base.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ cleanRanges txt = fmap (ensureSize . clampRange txt) . reverse . nub . sort
4747
ranges :: HasBuffer s => Lens' s [CrdRange]
4848
ranges = lens getter setter
4949
where getter buf = buf^.bufExt.cursors
50-
setter buf new = let txt = buf^.text
50+
setter buf new = let txt = buf^.getText
5151
in buf & bufExt.cursors .~ cleanRanges txt new
5252

5353
-- | A Traversal over each Range for the given buffer.

rasa-ext-files/src/Rasa/Ext/Files.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -47,7 +47,7 @@ showFilename = focusDo_ $ do
4747
where disp name = "<" <> name <> ">"
4848

4949
saveAs :: Y.YiString -> BufAction ()
50-
saveAs fName = use text >>= liftIO . TIO.writeFile (Y.toString fName) . Y.toText
50+
saveAs fName = use getText >>= liftIO . TIO.writeFile (Y.toString fName) . Y.toText
5151

5252
save :: BufAction ()
5353
save = do

rasa-ext-slate/src/Rasa/Ext/Slate/Internal/Render.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -84,7 +84,7 @@ renderView (width, height) (vw, buf) = appendActiveBar . resize . addEndBar $ te
8484
textImage :: V.Image
8585
textImage = applyAttrs adjustedStyles txt
8686
txt :: Y.YiString
87-
txt = buf^.text & trimText
87+
txt = buf^.getText & trimText
8888
adjustedStyles :: [Span CrdRange V.Attr]
8989
adjustedStyles = bimap adjustStylePositions convertStyle <$> buf^.styles
9090
adjustStylePositions :: CrdRange -> CrdRange

rasa-ext-vim/src/Rasa/Ext/Vim.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -120,7 +120,7 @@ normal [KDown] = liftAction focusViewBelow
120120

121121

122122
normal [Keypress 'G' []] = do
123-
txt <- use text
123+
txt <- use getText
124124
ranges.= [Range ((Offset $ Y.length txt - 1)^.asCoord txt) ((Offset $ Y.length txt)^.asCoord txt)]
125125

126126
normal [Keypress 'o' []] = endOfLine >> insertText "\n" >> moveRangesByN 1 >> mode .= Insert

rasa/src/Rasa/Ext.hs

+3-5
Original file line numberDiff line numberDiff line change
@@ -107,10 +107,8 @@ module Rasa.Ext
107107
, HasBuffer
108108
, BufRef
109109
, HasEditor
110-
, text
111-
-- | A lens over the buffer's Text as a 'Yi.Rope.YiString'. Use within a 'BufAction':
112-
--
113-
-- > txt <- use text
110+
, getText
111+
, getRange
114112

115113
-- * Events
116114
, Keypress(..)
@@ -143,6 +141,7 @@ module Rasa.Ext
143141
, afterNextRender
144142
, onExit
145143
, onBufAdded
144+
, onBufTextChanged
146145

147146
-- * Ranges
148147
, Range(..)
@@ -160,7 +159,6 @@ module Rasa.Ext
160159
, asCoord
161160
, clampCoord
162161
, clampRange
163-
, range
164162
, rStart
165163
, rEnd
166164
, sizeOfR

rasa/src/Rasa/Internal/Buffer.hs

+5
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Rasa.Internal.Buffer
1313
( Buffer
1414
, HasBuffer(..)
1515
, text
16+
, getText
1617
, bufExt
1718
, Ext(..)
1819
, mkBuffer
@@ -50,6 +51,10 @@ instance HasBuffer Buffer where
5051
text :: HasBuffer b => Lens' b Y.YiString
5152
text = buffer.text'
5253

54+
-- | This getter-lens focuses the text of the in-scope buffer.
55+
getText :: HasBuffer b => Getting r b Y.YiString
56+
getText = buffer.text'
57+
5358
-- | This lens focuses the Extensions States map of the in-scope buffer.
5459
bufExts :: HasBuffer b => Lens' b ExtMap
5560
bufExts = buffer.bufExts'

rasa/src/Rasa/Internal/Directive.hs

+7-6
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,6 @@ module Rasa.Internal.Directive
2424
, sizeOf
2525
) where
2626

27-
import Rasa.Internal.Text
2827
import Rasa.Internal.Editor
2928
import Rasa.Internal.Action
3029
import Rasa.Internal.Range
@@ -119,17 +118,19 @@ exit = exiting .= True
119118

120119
-- | Deletes the text in the given range from the buffer.
121120
deleteRange :: CrdRange -> BufAction ()
122-
deleteRange r = range r.asText .= ""
121+
deleteRange r = replaceRange r ""
123122

124123
-- | Replaces the text in the given range from the buffer.
125124
replaceRange :: CrdRange -> Y.YiString -> BufAction ()
126-
replaceRange r txt = range r .= txt
125+
replaceRange r txt = overRange r (const txt)
127126

128127
-- | Inserts text into the buffer at the given Coord.
129128
insertAt :: Coord -> Y.YiString -> BufAction ()
130-
insertAt c txt = range (Range c c) .= txt
129+
insertAt c = replaceRange r
130+
where r = Range c c
131131

132132
-- | Runs the given function over the text in the range, replacing it with the results.
133133
overRange :: CrdRange -> (Y.YiString -> Y.YiString) -> BufAction ()
134-
overRange r f = range r %= f
135-
134+
overRange r f = do
135+
newText <- range r <%= f
136+
liftAction $ dispatchEvent (BufTextChanged r newText)

rasa/src/Rasa/Internal/Events.hs

+8
Original file line numberDiff line numberDiff line change
@@ -9,10 +9,13 @@ module Rasa.Internal.Events
99
, BufAdded(..)
1010
, Keypress(..)
1111
, Mod(..)
12+
, BufTextChanged(..)
1213
) where
1314

1415
import Data.Dynamic
1516
import Rasa.Internal.Editor
17+
import Rasa.Internal.Range
18+
import qualified Yi.Rope as Y
1619

1720
-- | The Event type represents a common denominator for all actions that could
1821
-- occur Event transmitters express events that have occured as a member of this
@@ -64,3 +67,8 @@ data Mod
6467
| Alt
6568
| Shift
6669
deriving (Show, Eq)
70+
71+
data BufTextChanged
72+
= BufTextChanged CrdRange Y.YiString
73+
deriving (Show, Eq, Typeable)
74+

rasa/src/Rasa/Internal/Range.hs

+6
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Rasa.Internal.Range
2222
, range
2323
, rStart
2424
, rEnd
25+
, getRange
2526
, sizeOf
2627
, sizeOfR
2728
, moveRange
@@ -249,3 +250,8 @@ range :: HasBuffer s => CrdRange -> Lens' s Y.YiString
249250
range (Range start end) = lens getter setter
250251
where getter = view (text . beforeC end . afterC start)
251252
setter old new = old & text . beforeC end . afterC start .~ new
253+
254+
-- | A getter-lens over text which is encompassed by a 'Range'
255+
getRange :: HasBuffer s => CrdRange -> Getting r s Y.YiString
256+
getRange (Range start end) = to getter
257+
where getter = view (text . beforeC end . afterC start)

rasa/src/Rasa/Internal/Scheduler.hs

+8
Original file line numberDiff line numberDiff line change
@@ -24,19 +24,22 @@ module Rasa.Internal.Scheduler
2424
, removeListener
2525
, matchingHooks
2626
, onBufAdded
27+
, onBufTextChanged
2728
) where
2829

2930

3031
import Rasa.Internal.Action
3132
import Rasa.Internal.Events
3233
import Rasa.Internal.Editor
34+
import Rasa.Internal.Range
3335

3436
import Control.Lens
3537
import Control.Monad
3638
import Data.Dynamic
3739
import Data.Foldable
3840
import Data.Map hiding (filter)
3941
import Unsafe.Coerce
42+
import qualified Yi.Rope as Y
4043

4144
-- | Use this to dispatch an event of any type, any hooks which are listening for this event will be triggered
4245
-- with the provided event. Use this within an Action.
@@ -167,3 +170,8 @@ onBufAdded :: (BufRef -> Action ()) -> Action HookId
167170
onBufAdded f = onEveryTrigger listener
168171
where
169172
listener (BufAdded bRef) = f bRef
173+
174+
onBufTextChanged :: (CrdRange -> Y.YiString -> Action ()) -> Action HookId
175+
onBufTextChanged f = onEveryTrigger listener
176+
where
177+
listener (BufTextChanged r newText) = f r newText

0 commit comments

Comments
 (0)