Skip to content

Commit

Permalink
Fix bug where directories can be copied (and then fail)
Browse files Browse the repository at this point in the history
  • Loading branch information
akazukin5151 committed Aug 25, 2021
1 parent fcdd8cd commit 3e1f4d3
Show file tree
Hide file tree
Showing 2 changed files with 76 additions and 60 deletions.
94 changes: 43 additions & 51 deletions src/kpxhs/ViewEvents/BrowserEvents.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,23 +2,22 @@

module ViewEvents.BrowserEvents (browserEvent) where

import Brick.BChan (writeBChan)
import qualified Brick.Main as M
import qualified Brick.Types as T
import Brick.Util (clamp)
import Brick.Widgets.Core (str, txt)
import qualified Brick.Widgets.Edit as E
import qualified Brick.Widgets.List as L
import Control.Concurrent (forkIO)
import Control.Monad (void)
import Data.Map.Strict ((!?))
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as TT
import qualified Graphics.Vty as V
import Lens.Micro ((%~), (&), (.~), (?~), (^.))
import System.Exit (ExitCode (ExitSuccess))
import Brick.BChan (writeBChan)
import qualified Brick.Main as M
import qualified Brick.Types as T
import Brick.Util (clamp)
import Brick.Widgets.Core (str, txt)
import qualified Brick.Widgets.Edit as E
import qualified Brick.Widgets.List as L
import Control.Concurrent (forkIO)
import Control.Monad (void)
import Data.Map.Strict ((!?))
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Graphics.Vty as V
import Lens.Micro ((%~), (&), (.~), (?~), (^.))
import System.Exit (ExitCode (ExitSuccess))

import Common
( dirsToStr
Expand Down Expand Up @@ -51,10 +50,13 @@ import ViewEvents.Common
, getCreds
, handleClipCount
, handleCopy
, isCopyable
, isDir
, liftContinue1
, liftContinue2
, prepareExit
, processInput
, processSelected
, runCmd
, updateFooter
)
Expand All @@ -66,9 +68,9 @@ browserEvent =
case e of
T.VtyEvent (V.EvKey V.KEsc []) -> handleEsc st
T.VtyEvent (V.EvKey V.KEnter []) -> handleEnter st
T.VtyEvent (V.EvKey (V.KChar 'p') []) ->
T.VtyEvent (V.EvKey (V.KChar 'p') []) | isCopyable st ->
liftContinue2 copyEntryFromBrowser st CopyPassword
T.VtyEvent (V.EvKey (V.KChar 'u') []) ->
T.VtyEvent (V.EvKey (V.KChar 'u') []) | isCopyable st ->
liftContinue2 copyEntryFromBrowser st CopyUsername
T.VtyEvent ev -> M.continue $ handleNav ev st
T.AppEvent ev -> liftContinue2 handleAppEvent st ev
Expand All @@ -83,18 +85,6 @@ handleEsc st =
_ -> M.continue $ goUpParent st


-- If there is "go up to parent" then check for that first
isDir :: State -> Bool
isDir st = fromMaybe False (processSelected f st)
where
f entry = TT.last entry == '/'

processSelected :: (Text -> a) -> State -> Maybe a
processSelected f st = do
(_, entry) <- L.listSelectedElement $ st ^. visibleEntries
pure $ f entry


-- | This tree of functions will run a shell command in the background
-- (After trying the cache first)
-- The output of the shell command will be handled later,
Expand Down Expand Up @@ -182,6 +172,7 @@ goUpParent st =
st & visibleEntries .~ toBrowserList entries
& searchField .~ E.editor SearchField (Just 1) ""
& currentDir %~ initOrDef []
& updateFooter
where
entries = fromMaybe ["Failed to get entries!"] $ maybeGetEntries st

Expand Down Expand Up @@ -223,27 +214,28 @@ copyEntryFromBrowser st ctype =
f entry = copyEntryCommon st entry ctype

handleNav :: V.Event -> State -> State
handleNav e st =
st & visibleEntries %~ case e of
-- Keys from handleListEvent
V.EvKey V.KUp [] -> L.listMoveUp
V.EvKey V.KDown [] -> L.listMoveDown
V.EvKey V.KHome [] -> listMoveToBeginning
V.EvKey V.KEnd [] -> listMoveToEnd
V.EvKey V.KPageDown [] -> listMovePageDown
V.EvKey V.KPageUp [] -> listMovePageUp
-- WASD
V.EvKey (V.KChar 'w') [] -> L.listMoveUp
V.EvKey (V.KChar 's') [] -> L.listMoveDown
V.EvKey (V.KChar 'e') [] -> listMovePageDown
V.EvKey (V.KChar 'q') [] -> listMovePageUp
-- Vi
V.EvKey (V.KChar 'k') [] -> L.listMoveUp
V.EvKey (V.KChar 'j') [] -> L.listMoveDown
V.EvKey (V.KChar 'g') [] -> listMoveToBeginning
V.EvKey (V.KChar 'G') [] -> listMoveToEnd
_ -> id
handleNav e st = new_st & updateFooter
where
new_st = st & visibleEntries %~
case e of
-- Keys from handleListEvent
V.EvKey V.KUp [] -> L.listMoveUp
V.EvKey V.KDown [] -> L.listMoveDown
V.EvKey V.KHome [] -> listMoveToBeginning
V.EvKey V.KEnd [] -> listMoveToEnd
V.EvKey V.KPageDown [] -> listMovePageDown
V.EvKey V.KPageUp [] -> listMovePageUp
-- WASD
V.EvKey (V.KChar 'w') [] -> L.listMoveUp
V.EvKey (V.KChar 's') [] -> L.listMoveDown
V.EvKey (V.KChar 'e') [] -> listMovePageDown
V.EvKey (V.KChar 'q') [] -> listMovePageUp
-- Vi
V.EvKey (V.KChar 'k') [] -> L.listMoveUp
V.EvKey (V.KChar 'j') [] -> L.listMoveDown
V.EvKey (V.KChar 'g') [] -> listMoveToBeginning
V.EvKey (V.KChar 'G') [] -> listMoveToEnd
_ -> id
-- Default page up and down functions too fast for me
listMovePageUp l = listMoveBy (subtract 5) l
listMovePageDown l = listMoveBy (5 +) l
Expand Down
42 changes: 33 additions & 9 deletions src/kpxhs/ViewEvents/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,7 @@ import Control.Concurrent (forkIO, threadDelay)
import Control.Monad (void)
import Control.Monad.IO.Class (liftIO)
import Data.List (partition, sort)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as TT
import qualified Data.Text.Zipper as Z hiding (textZipper)
Expand All @@ -23,8 +24,9 @@ import System.Exit (ExitCode (ExitSuccess))
import System.Info (os)
import System.Process (callCommand, readProcessWithExitCode)

import Common (annotate, exit, initialFooter, tab)
import Types
import qualified Brick.Widgets.List as L
import Common (annotate, exit, initialFooter, tab)
import Types
( Action (Clip, Ls, Show)
, CmdOutput
, CopyType (CopyUsername)
Expand All @@ -44,6 +46,7 @@ import Types
, keyfileField
, passwordField
, previousView
, visibleEntries
)


Expand Down Expand Up @@ -185,16 +188,37 @@ updateFooter st = st & footer .~ viewDefaultFooter st
viewDefaultFooter :: State -> Widget Field
viewDefaultFooter st =
annotate $ case st^.activeView of
SearchView -> [exit, tab " focus list "]
EntryView -> [back, username, password]
SearchView -> [exit, tab " focus list "]
EntryView -> [back, username, password]
PasswordView -> initialFooter $ st ^. focusRing
ExitView -> [("", "")]
BrowserView ->
let extra = if isCopyable st then [username, password] else [] in
case st^.currentDir of
[] -> [exit, focus_search, username, password]
_ -> [back, focus_search, username, password]
PasswordView -> initialFooter $ st ^. focusRing
ExitView -> [("", "")]
[] -> [exit, focus_search] <> extra
_ -> [back, focus_search] <> extra
where
back = ("Esc", " back ")
username = ("u", " copy username ")
password = ("p", " copy password")
focus_search = ("Tab", " focus search ")

focus_search :: (Text, Text)
focus_search = ("Tab", " focus search ")

isDir :: State -> Bool
isDir st = fromMaybe False (processSelected f st)
where
f entry = TT.last entry == '/'

isGoUpToParent :: State -> Bool
isGoUpToParent st = fromMaybe False (processSelected f st)
where
f entry = entry == "-- (Go up parent) --"

isCopyable :: State -> Bool
isCopyable st = not (isDir st || isGoUpToParent st)

processSelected :: (Text -> a) -> State -> Maybe a
processSelected f st = do
(_, entry) <- L.listSelectedElement $ st ^. visibleEntries
pure $ f entry

0 comments on commit 3e1f4d3

Please sign in to comment.