Skip to content

Commit

Permalink
better bottom menu
Browse files Browse the repository at this point in the history
  • Loading branch information
pasqu4le committed Apr 11, 2018
1 parent 283e238 commit 7251084
Show file tree
Hide file tree
Showing 8 changed files with 158 additions and 100 deletions.
29 changes: 19 additions & 10 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -19,31 +19,42 @@ Clifm is a [brick](https://github.com/jtdaugherty/brick) application, that in tu

If your terminal supports a mouse you can use it to change Tab/Pane, click a button on the bottom or change your selection, but only using the keyboard you can perform every possible action. This is the list of all the keybindings:

#### Bottom menu
- L: open Se**l**ection menu
- A: open T**a**b menu
- P: open **P**ane menu
- BackSpace: go **back** to main menu
- Esc/Q: **Q**uit

#### Selection
- Enter: Open directory/run executable file/open readable file in editor
- Ctrl+(X/C): Cut/Copy the selected Item
- Up/Down Arrow: move the selection in the current Tab
- PageUp/PageDown: move the selection in the current Tab by one page at a time
- Home/End: move the selection in the current Tab to beginning or end of list
- Enter: Open directory/run executable file/open readable file in editor
- Tab/BackTab: Move to the next/previous tab
- Ctrl+(Left/Right Arrow): Swap current tab's position with the previous/next one
- Esc/Q: **Q**uit
- Ctrl+(X/C): Cut/Copy the selected Item
- Ctrl+V: Paste in the current Tab's directory
- Ctrl+R: **R**ename the selected Item
- Ctrl+D: **D**elete the selected Item
- Ctrl+O: **O**pen the selected directory in a New Tab
- S: **S**how info about the selected Item

#### Tabs
- Tab/BackTab: Move to the next/previous tab
- Ctrl+(Left/Right Arrow): Swap current tab's position with the previous/next one
- Ctrl+V: Paste in the current Tab's directory
- Ctrl+S: **S**earch for a file/folder in the current Tab's directory
- K: **K**ill (close) the current Tab
- S: **S**how info about the selected Item
- M: **M**ake a new directory
- T: **T**ouch (create an empty) file
- G: **G**o to another directory
- E: Open **E**mpty Tab
- R: **R**efresh the current Tab
- O: **O**rder by file name/file size/access time/modification time
- I: **I**nvert order

#### Panes
- Left/Right Arrow: Focus on the previous/next Pane
- Ctrl+E: Open **E**mpty Pane
- Ctrl+K: **K**ill (close) the current Pane
- Left/Right Arrow: Focus on the previous/next Pane

The actions above will not work only if a prompt is up, or you try to do something not possible.

Expand Down Expand Up @@ -94,7 +105,5 @@ Complete explanation from [Brick.Themes](https://hackage.haskell.org/package/bri
> Attribute names with multiple components (e.g. attr1 <> attr2) can be referenced in customization files by separating the names with a dot. For example, the attribute name "list" <> "selected" can be referenced by using the string "list.selected".
## TODOs
- better bottom menu (avoid too many buttons at once)
- more settings (using command line arguments)
- mc directory comparison (need to solve the next point first)
- find a way to read correctly a directory size in reasonable time
4 changes: 2 additions & 2 deletions clifm.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ name: clifm
-- PVP summary: +-+------- breaking API changes
-- | | +----- non-breaking API additions
-- | | | +--- code changes with no API change
version: 0.3.0.0
version: 0.3.1.0

-- A short (one-line) description of the package.
synopsis: Command Line Interface File Manager
Expand Down Expand Up @@ -59,7 +59,7 @@ executable clifm
Widgets.Manager
Widgets.Pane
Widgets.Tab
Widgets.Clipboard
Widgets.Menu
Widgets.Prompt

-- LANGUAGE extensions used by modules in this package.
Expand Down
4 changes: 2 additions & 2 deletions src/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,13 +5,13 @@ import Brick.Widgets.Core (withDefAttr, str)
import Brick.Types (Widget)
import Brick.Themes (Theme, newTheme)
import Brick.AttrMap (AttrName, AttrMap, attrName, attrMap)
import Graphics.Vty (defAttr, withStyle, underline, black, yellow, white, blue, red)
import Graphics.Vty (Key(..), defAttr, withStyle, underline, black, yellow, white, blue, red)
import Brick.Util (on, fg, bg)
import Brick.Widgets.Edit (editFocusedAttr)
import Brick.Widgets.List (listSelectedFocusedAttr, listSelectedAttr)

-- data definitions
data Name = Button {charBind :: Char, withCtrl :: Bool} |
data Name = Button {keyBind :: Key, withCtrl :: Bool} |
LabelsRow {pnName :: PaneName} |
Label {pnName :: PaneName, labelNum :: Int} |
PromptEditor |
Expand Down
26 changes: 0 additions & 26 deletions src/Widgets/Clipboard.hs

This file was deleted.

46 changes: 16 additions & 30 deletions src/Widgets/Manager.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,16 +2,15 @@ module Widgets.Manager where
import Types
import Widgets.Pane
import Widgets.Tab
import Widgets.Clipboard
import Widgets.Menu
import Widgets.Prompt

import System.Process (callCommand)
import Control.Exception (try, SomeException)
import Data.Char (toUpper)
import Brick.Main (continue, halt, suspendAndResume)
import Brick.Widgets.Core ((<+>), str, hBox, vBox, vLimit, withBorderStyle, clickable)
import Brick.Widgets.Core ((<+>), str, hBox, vBox, vLimit, withBorderStyle)
import Brick.Types (Widget, BrickEvent(..), EventM, Next, ViewportType(..), Location(..))
import Brick.Widgets.Border (border, vBorder, hBorder, borderWithLabel)
import Brick.Widgets.Border (vBorder, hBorder)
import Brick.Widgets.Border.Style (unicodeBold)
import Brick.BChan (BChan)
import Graphics.Vty (Event(EvKey), Key(..), Modifier(MCtrl))
Expand All @@ -22,7 +21,7 @@ import Data.List.PointedList.Circular (next, previous)

data State = State {paneZipper :: PaneZipper,
lastPaneName :: PaneName,
clipboard :: Clipboard,
bottomMenu :: Menu,
prompt :: Maybe Prompt,
editorCommand :: String,
eventChan :: BChan (ThreadEvent Tab)
Expand All @@ -33,7 +32,7 @@ type PaneZipper = PointedList Pane
makeState :: FilePath -> String -> BChan (ThreadEvent Tab) -> IO State
makeState path editCom eChan = do
pane <- makePane 0 path
return $ State (singleton pane) 0 EmptyBoard Nothing editCom eChan
return $ State (singleton pane) 0 makeMenu Nothing editCom eChan

-- rendering functions
drawUi :: State -> [Widget Name]
Expand All @@ -46,31 +45,11 @@ renderMainUI state = vBox [panes, botSep, menu]
where
panes = renderPanes $ paneZipper state
botSep = withBorderStyle unicodeBold hBorder
menu = vLimit 3 $ renderMenu state
menu = vLimit 3 $ renderMenu (bottomMenu state) (currentPane state)

renderPanes :: PaneZipper -> Widget Name
renderPanes = hBox . intersperse vBorder . map renderPane . toList . withFocus

renderMenu :: State -> Widget Name
renderMenu st = hBox . (renderClipboard (clipboard st) :) . renderButtons . currentTab $ currentPane st

renderButtons :: Tab -> [Widget Name]
renderButtons tab = map renderButton $ tabButtons tab ++ indipendentButtons

renderButton :: (Widget Name, Char, Bool) -> Widget Name
renderButton (s, c, b) = clickable Button {charBind = c, withCtrl = b} $ btBr s
where btBr = if b then borderWithLabel (str $ "C-" ++ [toUpper c]) else border

indipendentButtons :: [(Widget Name, Char, Bool)]
indipendentButtons = [
(keybindStr "e" <+> str "mpty tab", 'e', False),
(keybindStr "g" <+> str "o to", 'g', False),
(keybindStr "k" <+> str "ill tab", 'k', False),
(keybindStr "e" <+> str "mpty pane", 'e', True),
(keybindStr "k" <+> str "ill pane", 'k', True),
(keybindStr "q" <+> str "uit", 'q', False)
]

-- event handling functions
handleEvent :: State -> BrickEvent Name (ThreadEvent Tab) -> EventM Name (Next State)
handleEvent state event = case prompt state of
Expand All @@ -87,6 +66,10 @@ handlePrompt ev pr state = do
handleMain :: BrickEvent Name (ThreadEvent Tab) -> State -> EventM Name (Next State)
handleMain (VtyEvent ev) = case ev of
EvKey KEsc [] -> halt
EvKey KBS [] -> updateMenu MainMenu
EvKey (KChar 'l') [] -> updateMenu SelectionMenu
EvKey (KChar 'a') [] -> updateMenu TabMenu
EvKey (KChar 'p') [] -> updateMenu PaneMenu
EvKey (KChar 'q') [] -> halt
EvKey (KChar 'x') [MCtrl] -> updateClipboard makeCutBoard
EvKey (KChar 'c') [MCtrl] -> updateClipboard makeCopyBoard
Expand All @@ -108,7 +91,7 @@ handleMain (VtyEvent ev) = case ev of
handleMain (MouseUp name _ (Location pos)) = case name of
EntryList {pnName = pName} -> updateCurrentPane (moveTabToRow $ snd pos) . focusOnPane pName
Label {pnName = pName, labelNum = n} -> updateCurrentPane (updateTabZipper (moveToNth n)) . focusOnPane pName
Button {charBind = c, withCtrl = b} -> handleMain . VtyEvent $ EvKey (KChar c) [MCtrl | b]
Button {keyBind = key, withCtrl = b} -> handleMain . VtyEvent $ EvKey key [MCtrl | b]
_ -> continue
handleMain _ = continue

Expand All @@ -118,9 +101,12 @@ updateCurrentPane func state = do
newPane <- func $ currentPane state
continue $ state {paneZipper = replace newPane $ paneZipper state, prompt = Nothing}

updateMenu :: MenuType -> State -> EventM Name (Next State)
updateMenu tp st = continue $ st {bottomMenu = changeMenu tp $ bottomMenu st}

updateClipboard :: (Entry -> Clipboard) -> State -> EventM Name (Next State)
updateClipboard f st = continue $ case selectedEntry . currentTab $ currentPane st of
(Just entry) -> st {clipboard=f entry}
(Just entry) -> st {bottomMenu = changeClipboard (f entry) $ bottomMenu st}
_ -> st

updatePrompt :: Prompt -> State -> EventM Name (Next State)
Expand All @@ -133,7 +119,7 @@ openPrompt func state = continue $ state {prompt = Just $ func tab pName}
pName = paneName $ currentPane state

openPromptWithClip :: (Clipboard -> Tab -> PaneName -> Prompt) -> State -> EventM Name (Next State)
openPromptWithClip func state = openPrompt (func $ clipboard state) state
openPromptWithClip func state = openPrompt (func . clipboard $ bottomMenu state) state

openTabEntry :: State -> EventM Name (Next State)
openTabEntry state = case selectedEntry . currentTab $ currentPane state of
Expand Down
118 changes: 118 additions & 0 deletions src/Widgets/Menu.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,118 @@
module Widgets.Menu where
import Types
import Widgets.Pane
import Widgets.Tab

import Data.Char (toUpper)
import System.FilePath (takeFileName)
import Brick.Widgets.Core ((<+>), str, hLimit, hBox, clickable)
import Brick.Types (Widget)
import Brick.Widgets.Border (borderWithLabel, border)
import Graphics.Vty (Event(EvKey), Key(..), Modifier(MCtrl))

data Menu = Menu {clipboard :: Clipboard, menuType :: MenuType}
data MenuType = MainMenu | SelectionMenu | TabMenu | PaneMenu
data Clipboard = CopyBoard {fromEntry :: Entry} | CutBoard {fromEntry :: Entry} | EmptyBoard

instance Show Clipboard where
show EmptyBoard = " -empty- "
show board = takeFileName . entryPath $ fromEntry board

-- creation functions
makeMenu :: Menu
makeMenu = Menu {clipboard = EmptyBoard, menuType = MainMenu}

makeCopyBoard :: Entry -> Clipboard
makeCopyBoard = CopyBoard

makeCutBoard :: Entry -> Clipboard
makeCutBoard = CutBoard

-- rendering functions
renderMenu :: Menu -> Pane -> Widget Name
renderMenu m = hBox . (renderClipboard (clipboard m) :) . renderButtons (menuType m)

renderButtons :: MenuType -> Pane -> [Widget Name]
renderButtons tp pane = map renderButton $ case tp of
MainMenu -> mainButtons
SelectionMenu -> (backButton :) . selectionButtons . selectedEntry $ currentTab pane
TabMenu -> (backButton :) . tabButtons $ currentTab pane
PaneMenu -> backButton : paneButtons

renderButton :: (Widget Name, Maybe String, Name) -> Widget Name
renderButton (bContent, bLabel, bName) = clickable bName $ case bLabel of
Just txt -> borderWithLabel (str txt) bContent
Nothing -> border bContent

mainButtons :: [(Widget Name, Maybe String, Name)]
mainButtons = [
(str "se" <+> keybindStr "l" <+> str "ection menu", Nothing, Button {keyBind = KChar 'l', withCtrl = False}),
(str "t" <+> keybindStr "a" <+> str "b menu", Nothing, Button {keyBind = KChar 'a', withCtrl = False}),
(keybindStr "p" <+> str "ane menu", Nothing, Button {keyBind = KChar 'p', withCtrl = False}),
(keybindStr "q" <+> str "uit", Nothing, Button {keyBind = KChar 'q', withCtrl = False})
]

selectionButtons :: Maybe Entry -> [(Widget Name, Maybe String, Name)]
selectionButtons e = case e of
Just FileEntry {} -> anySelectionButtons
Just DirEntry {} -> anySelectionButtons ++ [(keybindStr "o" <+> str "pen in new tab", ctrlText 'o', Button {keyBind = KChar 'o', withCtrl = True})]
_ -> []

anySelectionButtons :: [(Widget Name, Maybe String, Name)]
anySelectionButtons = [
(str "cut", ctrlText 'x', Button {keyBind = KChar 'x', withCtrl = True}),
(str "copy", ctrlText 'c', Button {keyBind = KChar 'c', withCtrl = True}),
(keybindStr "r" <+> str "ename", ctrlText 'r', Button {keyBind = KChar 'r', withCtrl = True}),
(keybindStr "d" <+> str "elete", ctrlText 'd', Button {keyBind = KChar 'd', withCtrl = True}),
(keybindStr "s" <+> str "how info", Nothing, Button {keyBind = KChar 's', withCtrl = False})
]

tabButtons :: Tab -> [(Widget Name, Maybe String, Name)]
tabButtons tab = case tab of
DirTab {entryOrder = order} -> dirTabButtons ++ entryTabButtons order ++ anyTabButtons
SearchTab {entryOrder = order} -> entryTabButtons order ++ anyTabButtons
_ -> anyTabButtons

dirTabButtons :: [(Widget Name, Maybe String, Name)]
dirTabButtons = [
(str "paste", ctrlText 'v', Button {keyBind = KChar 'v', withCtrl = True}),
(keybindStr "s" <+> str "earch", ctrlText 's', Button {keyBind = KChar 's', withCtrl = True}),
(keybindStr "m" <+> str "ake dir", Nothing, Button {keyBind = KChar 'm', withCtrl = False}),
(keybindStr "t" <+> str "ouch file", Nothing, Button {keyBind = KChar 't', withCtrl = False})
]

entryTabButtons :: EntryOrder -> [(Widget Name, Maybe String, Name)]
entryTabButtons order = [
(keybindStr "r" <+> str "efresh", Nothing, Button {keyBind = KChar 'r', withCtrl = False}),
(keybindStr "o" <+> str ("rder by " ++ (show . nextOrderType $ orderType order)), Nothing, Button {keyBind = KChar 'o', withCtrl = False}),
(keybindStr "i" <+> str "nvert order", Nothing, Button {keyBind = KChar 'i', withCtrl = False})
]

anyTabButtons :: [(Widget Name, Maybe String, Name)]
anyTabButtons = [
(keybindStr "g" <+> str "o to", Nothing, Button {keyBind = KChar 'g', withCtrl = False}),
(keybindStr "e" <+> str "mpty tab", Nothing, Button {keyBind = KChar 'e', withCtrl = False}),
(keybindStr "k" <+> str "ill tab", Nothing, Button {keyBind = KChar 'k', withCtrl = False})
]

paneButtons :: [(Widget Name, Maybe String, Name)]
paneButtons = [
(keybindStr "e" <+> str "mpty pane", ctrlText 'e', Button {keyBind = KChar 'e', withCtrl = True}),
(keybindStr "k" <+> str "ill pane", ctrlText 'k', Button {keyBind = KChar 'k', withCtrl = True})
]

ctrlText :: Char -> Maybe String
ctrlText c = Just $ "C-" ++ [toUpper c]

backButton :: (Widget Name, Maybe String, Name)
backButton = (str "<_", Nothing, Button {keyBind = KBS, withCtrl = False})

renderClipboard :: Clipboard -> Widget Name
renderClipboard = hLimit 24 . borderWithLabel (str "clipboard") . str . show

-- state changing functions
changeMenu :: MenuType -> Menu -> Menu
changeMenu tp menu = menu {menuType = tp}

changeClipboard :: Clipboard -> Menu -> Menu
changeClipboard cb menu = menu {clipboard = cb}
2 changes: 1 addition & 1 deletion src/Widgets/Prompt.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
module Widgets.Prompt where
import Types
import Widgets.Tab
import Widgets.Clipboard
import Widgets.Menu

import Data.Monoid ((<>))
import Data.Functor (($>))
Expand Down
29 changes: 0 additions & 29 deletions src/Widgets/Tab.hs
Original file line number Diff line number Diff line change
Expand Up @@ -181,35 +181,6 @@ renderEntryTime Nothing _ = str " -----------------"
renderEntryTime (Just tms) sel = str . format $ (if sel then fst else snd) tms
where format = formatTime defaultTimeLocale " %R %b %e %Y"

tabButtons :: Tab -> [(Widget Name, Char, Bool)]
tabButtons DirTab {entryOrder = order} = [
(str "cut", 'x', True),
(str "copy", 'c', True),
(str "paste", 'v', True),
(keybindStr "r" <+> str "ename", 'r', True),
(keybindStr "d" <+> str "elete", 'd', True),
(keybindStr "s" <+> str "earch", 's', True),
(keybindStr "m" <+> str "ake dir", 'm', False),
(keybindStr "t" <+> str "ouch file", 't', False),
(keybindStr "s" <+> str "how info", 's', False),
(keybindStr "r" <+> str "efresh", 'r', False),
(keybindStr "o" <+> str "pen in new tab", 'o', True),
(keybindStr "o" <+> str ("rder by " ++ (show . nextOrderType $ orderType order)), 'o', False),
(keybindStr "i" <+> str "nvert order", 'i', False)
]
tabButtons SearchTab {entryOrder = order} = [
(str "cut", 'x', True),
(str "copy", 'c', True),
(keybindStr "r" <+> str "ename", 'r', True),
(keybindStr "d" <+> str "elete", 'd', True),
(keybindStr "s" <+> str "how info", 's', False),
(keybindStr "r" <+> str "efresh", 'r', False),
(keybindStr "o" <+> str "pen in new tab", 'o', True),
(keybindStr "o" <+> str ("rder by " ++ (show . nextOrderType $ orderType order)), 'o', False),
(keybindStr "i" <+> str "nvert order", 'i', False)
]
tabButtons _ = []

-- event handling and state-changing functions
handleTabEvent :: Event -> Tab -> EventM Name Tab
handleTabEvent _ EmptyTab = return EmptyTab
Expand Down

0 comments on commit 7251084

Please sign in to comment.