handleEditorEvent: handle mouse click events to place the cursor (adds Eq constraint to handleEditorEvent)

This commit is contained in:
Jonathan Daugherty 2022-07-09 08:30:42 -07:00
parent 65645be3d2
commit 8eb41ca8c3
2 changed files with 12 additions and 9 deletions

View File

@ -3,7 +3,7 @@
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Lens.Micro ((^.), (&), (.~), (%~))
import Lens.Micro ((^.), (&), (.~))
import Lens.Micro.TH (makeLenses)
import Control.Monad (void)
#if !(MIN_VERSION_base(4,11,0))
@ -20,8 +20,6 @@ import qualified Brick.Widgets.Edit as E
import qualified Brick.Widgets.Center as C
import qualified Brick.Widgets.Border as B
import Brick.Widgets.Core
import Data.Text.Zipper (moveCursor)
import Data.Tuple (swap)
data Name = Info | Button1 | Button2 | Button3 | Prose | TextBox
deriving (Show, Ord, Eq)
@ -86,10 +84,11 @@ infoLayer st = T.Widget T.Fixed T.Fixed $ do
C.hCenter $ str msg
appEvent :: St -> T.BrickEvent Name e -> T.EventM Name (T.Next St)
appEvent st (T.MouseDown n _ _ loc) = do
let T.Location pos = loc
M.continue $ st & lastReportedClick .~ Just (n, loc)
& edit %~ E.applyEdit (if n == TextBox then moveCursor (swap pos) else id)
appEvent st ev@(T.MouseDown n _ _ loc) =
M.continue =<< T.handleEventLensed (st & lastReportedClick .~ Just (n, loc))
edit
E.handleEditorEvent
ev
appEvent st (T.MouseUp {}) = M.continue $ st & lastReportedClick .~ Nothing
appEvent st (T.VtyEvent (V.EvMouseUp {})) = M.continue $ st & lastReportedClick .~ Nothing
appEvent st (T.VtyEvent (V.EvKey V.KUp [V.MCtrl])) = M.vScrollBy (M.viewportScroll Prose) (-1) >> M.continue st

View File

@ -53,6 +53,7 @@ import qualified Data.Text.Encoding as T
import qualified Data.Text.Zipper as Z hiding ( textZipper )
import qualified Data.Text.Zipper.Generic as Z
import qualified Data.Text.Zipper.Generic.Words as Z
import Data.Tuple (swap)
import Brick.Types
import Brick.Widgets.Core
@ -114,14 +115,17 @@ instance DecodeUtf8 T.Text where
instance DecodeUtf8 String where
decodeUtf8 bs = T.unpack <$> decodeUtf8 bs
handleEditorEvent :: (DecodeUtf8 t, Eq t, Z.GenericTextZipper t)
handleEditorEvent :: (Eq n, DecodeUtf8 t, Eq t, Z.GenericTextZipper t)
=> BrickEvent n e
-> Editor t n
-> EventM n (Editor t n)
handleEditorEvent e ed = return $ applyEdit f ed
where
f = case e of
VtyEvent ev -> handleVtyEvent ev
VtyEvent ev ->
handleVtyEvent ev
MouseDown n _ _ (Location pos) | n == getName ed ->
Z.moveCursor (swap pos)
_ -> id
handleVtyEvent ev = case ev of
EvPaste bs -> case decodeUtf8 bs of