Skip to content

Commit

Permalink
allow menu items to span multiple lines
Browse files Browse the repository at this point in the history
  • Loading branch information
tek committed Jul 29, 2023
1 parent 47f54d1 commit 32e660c
Show file tree
Hide file tree
Showing 40 changed files with 1,419 additions and 367 deletions.
48 changes: 24 additions & 24 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,28 @@
streamly = hackage "0.8.2" "0jhsdd71kqw0k0aszg1qb1l0wbxl1r73hsmkdgch4vlx43snlc8a";
};

cabal = {
license = "BSD-2-Clause-Patent";
license-file = "LICENSE";
author = "Torsten Schmits";
meta = {
maintainer = "hackage@tryp.io";
category = "Neovim";
github = "tek/ribosome";
extra-source-files = ["readme.md" "changelog.md"];
};
ghc-options = ["-fplugin=Polysemy.Plugin"];
prelude = {
enable = true;
package = {
name = "prelate";
version = "^>= 0.6";
};
module = "Prelate";
};
dependencies = ["polysemy" "polysemy-plugin"];
};

buildInputs = pkgs: [pkgs.neovim pkgs.tmux pkgs.xterm];

packages.ribosome-host = {
Expand Down Expand Up @@ -292,28 +314,6 @@

};

cabal = {
license = "BSD-2-Clause-Patent";
license-file = "LICENSE";
author = "Torsten Schmits";
meta = {
maintainer = "hackage@tryp.io";
category = "Neovim";
github = "tek/ribosome";
extra-source-files = ["readme.md" "changelog.md"];
};
ghc-options = ["-fplugin=Polysemy.Plugin"];
prelude = {
enable = true;
package = {
name = "prelate";
version = "^>= 0.6";
};
module = "Prelate";
};
dependencies = ["polysemy" "polysemy-plugin"];
};

envs.dev = {
buildInputs = pkgs: [pkgs.neovim pkgs.tmux pkgs.xterm];
env = { RIBOSOME_ROOT = builtins.toPath self; };
Expand All @@ -324,8 +324,8 @@
}) // {

lib = hix.lib.extend (_: super: {
modules = {projectModules ? [], extraModules ? []}:
super.modules { inherit projectModules; extraModules = extraModules ++ [(import ./ops/api.nix self)]; };
flakeWith = {projectModules ? [], extraModules ? []}:
super.flakeWith { inherit projectModules; extraModules = extraModules ++ [(import ./ops/api.nix self)]; };
});
};

Expand Down
3 changes: 3 additions & 0 deletions packages/menu/changelog.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
# Unreleased

* Add support for multiline menu items.
23 changes: 18 additions & 5 deletions packages/menu/lib/Ribosome/Menu/Action.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
module Ribosome.Menu.Action where

import Ribosome.Menu.Class.MenuState (MenuState, MenuState (Item, Mode, mode))
import qualified Ribosome.Menu.Class.MenuMode as MenuMode
import Ribosome.Menu.Class.MenuState (MenuState (Item, Mode, mode))
import Ribosome.Menu.Combinators (numVisible, overEntries)
import Ribosome.Menu.Data.CursorIndex (CursorIndex (CursorIndex))
import qualified Ribosome.Menu.Data.MenuAction as MenuAction
import Ribosome.Menu.Data.MenuAction (MenuAction)
import Ribosome.Menu.Data.MenuItem (MenuItem)
import Ribosome.Menu.Effect.Menu (Menu, basicState, menuState, modifyCursor, readCursor, viewState)
import Ribosome.Menu.ItemLens (focus)
import Ribosome.Menu.Lens (use, (%=), (.=))
import Ribosome.Menu.Prompt.Data.Prompt (Prompt)

Expand Down Expand Up @@ -53,7 +54,11 @@ cycleMenu ::
MenuSem s r ()
cycleMenu offset = do
count <- viewState (to numVisible)
modifyCursor \ current -> fromMaybe 0 ((current + fromIntegral offset) `mod` fromIntegral count)
modifyCursor \ current ->
let
new :: Int
new = fromIntegral current + offset
in fromIntegral (fromMaybe 0 (new `mod` count))

menuCycle ::
MenuState s =>
Expand All @@ -72,9 +77,9 @@ toggleSelected ::
MenuSem s r ()
toggleSelected = do
basicState do
CursorIndex cur <- readCursor
cur <- readCursor
#entries %= overEntries \ index ->
if index == cur
if index == fromIntegral cur
then #selected %~ not
else id
cycleMenu 1
Expand Down Expand Up @@ -118,3 +123,11 @@ menuCycleFilter = do
cur <- use mode
mode .= (MenuMode.cycleFilter @(Item s) cur)
menuRender

menuFocusItem ::
MenuState s =>
MenuWidget s r (Maybe (MenuItem (Item s)))
menuFocusItem =
menuState do
selection <- use focus
menuSuccess selection
4 changes: 2 additions & 2 deletions packages/menu/lib/Ribosome/Menu/Class/MenuState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,13 +74,13 @@ entries =

itemCount ::
MenuState s =>
Lens s s Int Int
Lens s s Word Word
itemCount =
core . #itemCount

entryCount ::
MenuState s =>
Lens s s Int Int
Lens s s Word Word
entryCount =
core . #entryCount

Expand Down
5 changes: 2 additions & 3 deletions packages/menu/lib/Ribosome/Menu/Data/CursorIndex.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,9 @@
module Ribosome.Menu.Data.CursorIndex where

newtype CursorIndex =
CursorIndex { unCursorIndex :: Int }
CursorIndex { unCursorIndex :: Word }
deriving stock (Eq, Show, Generic)
deriving newtype (Num, Real, Enum, Integral, Ord)

instance Default CursorIndex where
def =
0
def = 0
2 changes: 1 addition & 1 deletion packages/menu/lib/Ribosome/Menu/Data/CursorLine.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Ribosome.Menu.Data.CursorLine where

newtype CursorLine =
CursorLine { unCursorLine :: Int }
CursorLine { unCursorLine :: Word }
deriving stock (Eq, Show, Generic)
deriving newtype (Num, Real, Enum, Integral, Ord)
46 changes: 29 additions & 17 deletions packages/menu/lib/Ribosome/Menu/Data/Entry.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,45 +3,57 @@ module Ribosome.Menu.Data.Entry where
import qualified Data.IntMap.Strict as IntMap
import Data.Semigroup (Sum (Sum, getSum))

import Ribosome.Host.Data.Tuple (dup)
import qualified Ribosome.Menu.Data.MenuItem
import Ribosome.Menu.Data.MenuItem (MenuItem, simpleMenuItem)
import Ribosome.Menu.Data.MenuItem (MenuItem, simpleMenuItem, simpleMenuItemLines)

-- TODO use ItemIndex, which refers to the original insertion index.
-- EntryIndex refers to the effective visible item list, not to be used here.
data Entry a =
Entry {
item :: MenuItem a,
index :: Int,
index :: Word,
selected :: Bool
}
deriving stock (Eq, Show, Generic)

instance Eq a => Ord (Entry a) where
compare =
comparing (.index) <> comparing ((.render) . (.item))
comparing (.index) <> comparing (.item.render)

type Entries a =
IntMap (Seq (Entry a))

tuple :: Entry a -> (Int, MenuItem a)
tuple Entry {..} =
(index, item)

insertFiltered :: Int -> Entry a -> Entries a -> Entries a
insertFiltered i it =
IntMap.insertWith (flip (<>)) i (pure it)

fromList :: [(Int, Entry a)] -> Entries a
fromList =
IntMap.fromListWith (flip (<>)) . fmap (second pure)

intEntries :: [(Int, Int)] -> Entries Int
intEntries :: [(Int, Word)] -> Entries Word
intEntries nums =
fromList [(score, Entry (simpleMenuItem i (show i)) i False) | (score, i) <- nums]

simpleIntEntries :: [Int] -> Entries Int
multi :: Word -> NonEmpty Text -> Entry Word
multi i ls =
Entry (simpleMenuItemLines i ls) i False

multis :: [(Int, Word, NonEmpty Text)] -> Entries Word
multis es =
fromList [(score, multi i ls) | (score, i, ls) <- es]

simpleIntEntries :: [Word] -> Entries Word
simpleIntEntries =
intEntries . fmap dup
intEntries . fmap \ i -> (fromIntegral i, i)

entriesLength :: Entries a -> Int
entriesLength :: Entries a -> Word
entriesLength =
getSum . foldMap (Sum . length)
fromIntegral . getSum . foldMap (Sum . length)

entryLineCount :: Entry a -> Word
entryLineCount e = fromIntegral (length e.item.render)

-- | Calculate the total number of lines in an 'Entry' list.
entriesLineCount ::
Foldable t =>
t (Entry a) ->
Word
entriesLineCount =
getSum . foldMap (Sum . entryLineCount)
24 changes: 20 additions & 4 deletions packages/menu/lib/Ribosome/Menu/Data/MenuItem.hs
Original file line number Diff line number Diff line change
@@ -1,21 +1,37 @@
module Ribosome.Menu.Data.MenuItem where
module Ribosome.Menu.Data.MenuItem (
module Ribosome.Menu.Data.MenuItem,
MenuItem (MenuItem, ..),
) where

import qualified Data.IntMap.Strict as IntMap
import qualified Data.Text as Text

data MenuItem a =
MenuItem {
UnsafeMenuItem {
meta :: a,
text :: Text,
render :: Text
lines :: Word,
render :: NonEmpty Text
}
deriving stock (Eq, Show, Ord, Functor, Generic)

pattern MenuItem :: a -> Text -> NonEmpty Text -> MenuItem a
pattern MenuItem {meta, text, render} <- UnsafeMenuItem {..}
where
MenuItem meta text render = UnsafeMenuItem {lines = fromIntegral (length render), ..}

{-# complete MenuItem #-}

type Items a =
IntMap (MenuItem a)

simpleMenuItem :: a -> Text -> MenuItem a
simpleMenuItem a t =
MenuItem a t t
MenuItem a t [t]

simpleMenuItemLines :: a -> NonEmpty Text -> MenuItem a
simpleMenuItemLines a t =
MenuItem a (Text.intercalate "\n" (toList t)) t

simpleItems :: [Text] -> Items ()
simpleItems =
Expand Down
6 changes: 3 additions & 3 deletions packages/menu/lib/Ribosome/Menu/Data/MenuStatus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ data MenuStatus =
filter :: Text,
middle :: Int -> Maybe Text,
bottom :: Int -> [Text],
itemCount :: Int,
entryCount :: Int,
cursor :: Int
itemCount :: Word,
entryCount :: Word,
cursor :: Word
}
deriving stock (Generic)
21 changes: 16 additions & 5 deletions packages/menu/lib/Ribosome/Menu/Data/MenuView.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,26 @@ module Ribosome.Menu.Data.MenuView where
import Ribosome.Menu.Data.CursorIndex (CursorIndex)
import Ribosome.Menu.Data.CursorLine (CursorLine)

newtype EntryIndex =
EntryIndex Word
deriving stock (Eq, Show, Generic)
deriving newtype (Num, Real, Enum, Integral, Ord)

data ViewRange =
ViewRange {
bottom :: EntryIndex,
top :: EntryIndex,
cursorLine :: CursorLine
}
deriving stock (Eq, Show, Generic)

data MenuView =
MenuView {
topIndex :: Int,
botIndex :: Int,
cursor :: CursorIndex,
cursorLine :: CursorLine
range :: Maybe ViewRange,
cursor :: CursorIndex
}
deriving stock (Eq, Show, Generic)

instance Default MenuView where
def =
MenuView 0 0 0 0
MenuView Nothing 0
63 changes: 40 additions & 23 deletions packages/menu/lib/Ribosome/Menu/Data/NvimMenuState.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,50 @@
module Ribosome.Menu.Data.NvimMenuState where

import Ribosome.Menu.Data.CursorIndex (CursorIndex)
import Ribosome.Menu.Data.CursorLine (CursorLine)
import Ribosome.Menu.Data.MenuView (MenuView)
import Ribosome.Menu.Data.Entry (Entry)
import Ribosome.Menu.Data.MenuView (EntryIndex, MenuView)

data NvimMenuState =
NvimMenuState {
view :: MenuView,
cursorIndex :: CursorIndex,
indexes :: [(Int, Bool)]
data PartialEntry a =
PartialEntry {
entry :: Entry a,
visibleLines :: Word
}
deriving stock (Eq, Show, Generic)

instance Default NvimMenuState where
def =
NvimMenuState def 0 def
data EntrySlice i =
EntrySlice {
full :: [Entry i],
indexBot :: EntryIndex,
indexTop :: EntryIndex,
partialBot :: Maybe (PartialEntry i),
partialTop :: Maybe (PartialEntry i)
}
|
OnlyPartialEntry {
entry :: PartialEntry i,
index :: EntryIndex
}
deriving stock (Eq, Show, Generic)

topIndex :: Lens' NvimMenuState Int
topIndex =
#view . #topIndex
sliceRange :: EntrySlice i -> (EntryIndex, EntryIndex)
sliceRange = \case
EntrySlice {..} -> (indexBot, indexTop)
OnlyPartialEntry {index} -> (index, index)

botIndex :: Lens' NvimMenuState Int
botIndex =
#view . #botIndex
data SliceIndexes =
SliceIndexes {
full :: [(Word, Bool)],
partialBot :: Maybe (Word, Word, Bool),
partialTop :: Maybe (Word, Word, Bool)
}
deriving stock (Eq, Show, Generic)
deriving anyclass (Default)

cursor :: Lens' NvimMenuState CursorIndex
cursor =
#view . #cursor
data NvimMenuState =
NvimMenuState {
view :: MenuView,
slice :: SliceIndexes
}
deriving stock (Eq, Show, Generic)

cursorLine :: Lens' NvimMenuState CursorLine
cursorLine =
#view . #cursorLine
instance Default NvimMenuState where
def = NvimMenuState def def
Loading

0 comments on commit 32e660c

Please sign in to comment.