diff options
Diffstat (limited to 'interactive-edit-lens/src/Interact.hs')
-rw-r--r-- | interactive-edit-lens/src/Interact.hs | 142 |
1 files changed, 95 insertions, 47 deletions
diff --git a/interactive-edit-lens/src/Interact.hs b/interactive-edit-lens/src/Interact.hs index 0074e86..662052b 100644 --- a/interactive-edit-lens/src/Interact.hs +++ b/interactive-edit-lens/src/Interact.hs | |||
@@ -14,6 +14,7 @@ import Interact.Types | |||
14 | 14 | ||
15 | import Data.Text (Text) | 15 | import Data.Text (Text) |
16 | import qualified Data.Text as Text | 16 | import qualified Data.Text as Text |
17 | import qualified Data.Text.IO as Text | ||
17 | 18 | ||
18 | import Data.Text.Zipper | 19 | import Data.Text.Zipper |
19 | 20 | ||
@@ -41,6 +42,7 @@ import Brick hiding (on) | |||
41 | import Brick.Focus | 42 | import Brick.Focus |
42 | import Brick.Widgets.Center | 43 | import Brick.Widgets.Center |
43 | import Brick.Widgets.Border | 44 | import Brick.Widgets.Border |
45 | import Brick.Widgets.FileBrowser | ||
44 | import Graphics.Vty hiding (showCursor) | 46 | import Graphics.Vty hiding (showCursor) |
45 | 47 | ||
46 | import Config.Dyre | 48 | import Config.Dyre |
@@ -48,14 +50,20 @@ import Config.Dyre | |||
48 | import System.IO.Unsafe | 50 | import System.IO.Unsafe |
49 | import Debug.Trace | 51 | import Debug.Trace |
50 | 52 | ||
51 | interactiveEditLens :: (Params (InteractConfig c) -> Params (InteractConfig c)) -> InteractConfig c -> IO () | 53 | import System.CPUTime |
54 | import Text.Printf | ||
55 | |||
56 | import Control.Exception (evaluate) | ||
57 | import Control.DeepSeq | ||
58 | |||
59 | interactiveEditLens :: forall c. NFData c => (Params (InteractConfig c) -> Params (InteractConfig c)) -> InteractConfig c -> IO () | ||
52 | interactiveEditLens f = wrapMain . f $ defaultParams | 60 | interactiveEditLens f = wrapMain . f $ defaultParams |
53 | { projectName = "interact-edit-lens" | 61 | { projectName = "interact-edit-lens" |
54 | , showError = \s err -> s & compileError .~ Just err | 62 | , showError = \s err -> s & compileError .~ Just err |
55 | , realMain = interactiveEditLens' | 63 | , realMain = interactiveEditLens' |
56 | } | 64 | } |
57 | 65 | ||
58 | interactiveEditLens' :: forall c. InteractConfig c -> IO () | 66 | interactiveEditLens' :: forall c. NFData c => InteractConfig c -> IO () |
59 | interactiveEditLens' cfg@InteractConfig{..} | 67 | interactiveEditLens' cfg@InteractConfig{..} |
60 | | Just err <- icfgCompileError | 68 | | Just err <- icfgCompileError |
61 | = hPutStrLn stderr err | 69 | = hPutStrLn stderr err |
@@ -89,9 +97,8 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
89 | where | 97 | where |
90 | infix 1 &?~ | 98 | infix 1 &?~ |
91 | 99 | ||
92 | (&?~) :: a -> RWS (InteractConfig c) () a b -> a | 100 | (&?~), actOn :: a -> RWS (InteractConfig c) () a b -> a |
93 | st &?~ act = (\(s, ()) -> s) $ execRWS act cfg st | 101 | st &?~ act = (\(s, ()) -> s) $ execRWS act cfg st |
94 | |||
95 | actOn = (&?~) | 102 | actOn = (&?~) |
96 | 103 | ||
97 | initialState :: InteractState c | 104 | initialState :: InteractState c |
@@ -101,6 +108,8 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
101 | , istRight = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty) | 108 | , istRight = (Last Valid, Last (init @(StringEdits Natural Char), 0), mempty) |
102 | , istFocus = focusRing [LeftEditor, RightEditor] & | 109 | , istFocus = focusRing [LeftEditor, RightEditor] & |
103 | focusSetCurrent (case icfgInitial of InitialRight _ -> RightEditor; _other -> LeftEditor) | 110 | focusSetCurrent (case icfgInitial of InitialRight _ -> RightEditor; _other -> LeftEditor) |
111 | , istActive = True | ||
112 | , istLoadBrowser = Nothing | ||
104 | } | 113 | } |
105 | 114 | ||
106 | app :: InteractApp c | 115 | app :: InteractApp c |
@@ -109,10 +118,15 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
109 | appDraw :: InteractState c -> [Widget InteractName] | 118 | appDraw :: InteractState c -> [Widget InteractName] |
110 | appDraw InteractState{..} = [ editors ] | 119 | appDraw InteractState{..} = [ editors ] |
111 | where | 120 | where |
112 | editors = hBox | 121 | editors = vBox |
113 | [ mbInvalid (withFocusRing istFocus renderEditor') (istLeft `WithName` LeftEditor) | 122 | [ case istLoadBrowser of |
114 | , vBorder | 123 | Nothing -> hBox |
115 | , mbInvalid (withFocusRing istFocus renderEditor') (istRight `WithName` RightEditor) | 124 | [ mbInvalid (withFocusRing istFocus renderEditor') (istLeft `WithName` LeftEditor) |
125 | , vBorder | ||
126 | , mbInvalid (withFocusRing istFocus renderEditor') (istRight `WithName` RightEditor) | ||
127 | ] | ||
128 | Just lBrowser -> renderFileBrowser True lBrowser | ||
129 | , hCenter . str $ bool "Inactive" "" istActive | ||
116 | ] | 130 | ] |
117 | renderEditor' :: Bool -> (Seq Char, Int) `WithName` InteractName -> Widget InteractName | 131 | renderEditor' :: Bool -> (Seq Char, Int) `WithName` InteractName -> Widget InteractName |
118 | renderEditor' foc ((content, cPos) `WithName` n) | 132 | renderEditor' foc ((content, cPos) `WithName` n) |
@@ -133,42 +147,75 @@ interactiveEditLens' cfg@InteractConfig{..} | |||
133 | mbInvalid f ((Last Valid , Last x, _) `WithName` n) = f $ x `WithName` n | 147 | mbInvalid f ((Last Valid , Last x, _) `WithName` n) = f $ x `WithName` n |
134 | 148 | ||
135 | appHandleEvent :: InteractState c -> BrickEvent InteractName InteractEvent -> EventM InteractName (Next (InteractState c)) | 149 | appHandleEvent :: InteractState c -> BrickEvent InteractName InteractEvent -> EventM InteractName (Next (InteractState c)) |
136 | appHandleEvent st@InteractState{..} (VtyEvent ev) = case ev of | 150 | appHandleEvent st@InteractState{..} (VtyEvent ev) |
137 | EvKey KEsc [] -> halt st | 151 | | Nothing <- istLoadBrowser = case ev of |
138 | EvKey (KChar 'c') [MCtrl] -> halt st | 152 | EvKey KEsc [] -> halt st |
139 | EvKey (KChar '\t') [] -> continue $ st & focus %~ focusNext | 153 | EvKey (KChar 'c') [MCtrl] -> halt st |
140 | EvKey KBackTab [] -> continue $ st & focus %~ focusPrev | 154 | EvKey (KChar '\t') [] -> continue . actOn st . runMaybeT $ do |
141 | EvKey (KChar 'a') [MCtrl] -> continue $ st &?~ doMove | 155 | guard =<< use active |
142 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, 0) else (l, 0)) | 156 | focus %= focusNext |
143 | EvKey (KChar 'e') [MCtrl] -> continue $ st &?~ doMove | 157 | EvKey KBackTab [] -> continue . actOn st . runMaybeT $ do |
144 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') $ c l then (pred l, Seq.length . c $ pred l) else (l, Seq.length $ c l)) | 158 | guard =<< use active |
145 | EvKey KLeft [MCtrl] -> continue $ st &?~ doMove | 159 | focus %= focusPrev |
146 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace (c l) || Seq.null (c l) then (pred l, 0) else (l - 2, 0)) | 160 | EvKey (KChar 'a') [MCtrl] -> continue $ st &?~ doMove |
147 | EvKey KRight [MCtrl] -> continue $ st &?~ doMove | 161 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, 0) else (l, 0)) |
148 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace $ c l then (succ l, 0) else (l + 2, 0)) | 162 | EvKey (KChar 'e') [MCtrl] -> continue $ st &?~ doMove |
149 | EvKey KUp [] -> continue $ st &?~ doMove | 163 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') $ c l then (pred l, Seq.length . c $ pred l) else (l, Seq.length $ c l)) |
150 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, p) else (l - 2, p)) | 164 | EvKey KLeft [MCtrl] -> continue $ st &?~ doMove |
151 | EvKey KDown [] -> continue $ st &?~ doMove | 165 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace (c l) || Seq.null (c l) then (pred l, 0) else (l - 2, 0)) |
152 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) then (succ l, p) else (l + 2, p)) | 166 | EvKey KRight [MCtrl] -> continue $ st &?~ doMove |
153 | EvKey KLeft [] -> continue $ st &?~ doMove moveLeft | 167 | (moveSplit isSpace $ \(c, (l, _)) -> if any isSpace $ c l then (succ l, 0) else (l + 2, 0)) |
154 | EvKey KRight [] -> continue $ st &?~ doMove moveRight | 168 | EvKey KUp [] -> continue $ st &?~ doMove |
155 | EvKey KDel [] -> continue $ st &?~ doEdit (delete 0) | 169 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) || Seq.null (c l) then (pred l, p) else (l - 2, p)) |
156 | EvKey KBS [] -> continue . actOn st $ do | 170 | EvKey KDown [] -> continue $ st &?~ doMove |
157 | focused' <- preuse $ focused . _2 . _Wrapped | 171 | (moveSplit (== '\n') $ \(c, (l, p)) -> if any (== '\n') (c l) then (succ l, p) else (l + 2, p)) |
158 | doEdit . delete $ -1 | 172 | EvKey KLeft [] -> continue $ st &?~ doMove moveLeft |
159 | unless (maybe False ((==) <$> view _2 <*> view (_1 . to Seq.length)) focused') $ | 173 | EvKey KRight [] -> continue $ st &?~ doMove moveRight |
160 | doMove moveLeft | 174 | EvKey KDel [] -> continue $ st &?~ doEdit (delete 0) |
161 | EvKey (KChar c) [] -> continue . actOn st $ do | 175 | EvKey KBS [] -> continue . actOn st $ do |
162 | doEdit $ insert 0 c | 176 | focused' <- preuse $ focused . _2 . _Wrapped |
163 | doMove moveRight | 177 | doEdit . delete $ -1 |
164 | EvKey KEnter [] -> continue . actOn st $ do | 178 | unless (maybe False ((==) <$> view _2 <*> view (_1 . to Seq.length)) focused') $ |
165 | doEdit $ insert 0 '\n' | 179 | doMove moveLeft |
166 | doMove moveRight | 180 | EvKey (KChar c) [] -> continue . actOn st $ do |
167 | other -> suspendAndResume $ do | 181 | doEdit $ insert 0 c |
168 | traceIO $ "Unhandled event:\n\t" ++ show other | 182 | doMove moveRight |
169 | return st | 183 | EvKey KEnter [] -> continue . actOn st $ do |
170 | -- where | 184 | doEdit $ insert 0 '\n' |
171 | -- editorMovement f = continue $ st & focused . _Just . editContentsL %~ f | 185 | doMove moveRight |
186 | EvKey (KChar 'p') [MCtrl] | ||
187 | | istActive -> do | ||
188 | void . liftIO . evaluate . force . ($ st) $ (,,) <$> view left <*> view right <*> view complement | ||
189 | continue $ st & active .~ False | ||
190 | | otherwise -> do | ||
191 | let st' = actOn st $ do | ||
192 | active .= True | ||
193 | doEdit mempty | ||
194 | before <- liftIO getCPUTime | ||
195 | void . liftIO . evaluate . force . ($ st') $ (,,) <$> view left <*> view right <*> view complement | ||
196 | after <- liftIO getCPUTime | ||
197 | suspendAndResume $ do | ||
198 | printf "Resume took %.12fs\n" (fromInteger (after - before) * 1e-12 :: Double) | ||
199 | return st' | ||
200 | EvKey (KChar 'o') [MCtrl] -> do | ||
201 | lBrowser <- liftIO $ newFileBrowser selectNonDirectories LoadBrowser Nothing | ||
202 | continue $ st & loadBrowser .~ Just lBrowser | ||
203 | other -> suspendAndResume $ do | ||
204 | traceIO $ "Unhandled event:\n\t" ++ show other | ||
205 | return st | ||
206 | -- where | ||
207 | -- editorMovement f = continue $ st & focused . _Just . editContentsL %~ f | ||
208 | | Just lBrowser <- istLoadBrowser = do | ||
209 | lBrowser' <- handleFileBrowserEvent ev lBrowser | ||
210 | case fileBrowserSelection lBrowser' of | ||
211 | [] -> continue $ st &?~ loadBrowser .= Just lBrowser' | ||
212 | (FileInfo{..} : _) -> do | ||
213 | insEdit <- divInit . view charseq <$> liftIO (Text.readFile fileInfoFilePath) | ||
214 | let st' = actOn st $ do | ||
215 | doEdit $ (insEdit :: StringEdits Natural Char) & stringEdits . sePos %~ fromIntegral | ||
216 | loadBrowser .= Nothing | ||
217 | continue st' | ||
218 | |||
172 | appHandleEvent st _ = continue st | 219 | appHandleEvent st _ = continue st |
173 | 220 | ||
174 | doMove = zoom $ focused . _2 . _Wrapped | 221 | doMove = zoom $ focused . _2 . _Wrapped |
@@ -259,9 +306,10 @@ doEdit relativeEdit = void . runMaybeT $ do | |||
259 | | otherwise = currentPos | 306 | | otherwise = currentPos |
260 | aL . _2 %= (<> Last (newContent, currentPos')) | 307 | aL . _2 %= (<> Last (newContent, currentPos')) |
261 | absoluteEdit' <- uses (aL . _3) (absoluteEdit `mappend`) | 308 | absoluteEdit' <- uses (aL . _3) (absoluteEdit `mappend`) |
262 | bEdits <- prop direction absoluteEdit' | 309 | bRes <- runMaybeT $ do |
263 | bDom <- use $ bL . _2 . _Wrapped . _1 | 310 | guard =<< use active |
264 | case bDom `apply` bEdits of | 311 | (,) <$> use (bL . _2 . _Wrapped . _1) <*> prop direction absoluteEdit' |
312 | case uncurry apply =<< bRes of | ||
265 | Nothing -> do | 313 | Nothing -> do |
266 | bL . _1 %= (<> Last Invalid) | 314 | bL . _1 %= (<> Last Invalid) |
267 | aL . _3 .= absoluteEdit' | 315 | aL . _3 .= absoluteEdit' |