module Hum.Views.Help where
import Prelude hiding ( Down )
import Hum.Types
import Brick.Types
import Graphics.Vty.Input.Events
import Brick.Main
import Brick.Widgets.Core
import Brick.Widgets.Search
import Control.Lens
import Text.Regex.TDFA.Text
import Text.Regex.TDFA
drawViewHelp :: HumState -> Widget Name
drawViewHelp :: HumState -> Widget Name
drawViewHelp HumState
st = Name -> ViewportType -> Widget Name -> Widget Name
forall n.
(Ord n, Show n) =>
n -> ViewportType -> Widget n -> Widget n
viewport Name
Help ViewportType
Vertical (HumState -> Widget Name
helpW HumState
st)
helpW :: HumState -> Widget Name
helpW :: HumState -> Widget Name
helpW HumState
st =
let htx :: Text
htx = HumState
st HumState -> Getting Text HumState Text -> Text
forall s a. s -> Getting a s a -> a
^. (HelpState -> Const Text HelpState)
-> HumState -> Const Text HumState
Lens' HumState HelpState
helpL ((HelpState -> Const Text HelpState)
-> HumState -> Const Text HumState)
-> ((Text -> Const Text Text) -> HelpState -> Const Text HelpState)
-> Getting Text HumState Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Const Text Text) -> HelpState -> Const Text HelpState
Lens' HelpState Text
helpTextL
hi :: Int
hi = HumState
st HumState -> Getting Int HumState Int -> Int
forall s a. s -> Getting a s a -> a
^. (HelpState -> Const Int HelpState)
-> HumState -> Const Int HumState
Lens' HumState HelpState
helpL ((HelpState -> Const Int HelpState)
-> HumState -> Const Int HumState)
-> ((Int -> Const Int Int) -> HelpState -> Const Int HelpState)
-> Getting Int HumState Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int) -> HelpState -> Const Int HelpState
Lens' HelpState Int
helpSearchIntL
mterm :: Maybe Text
mterm = (NonEmpty Text -> Text) -> [Text] -> Maybe Text
forall a b. (NonEmpty a -> b) -> [a] -> Maybe b
viaNonEmpty NonEmpty Text -> Text
forall (f :: * -> *) a. IsNonEmpty f a a "head" => f a -> a
head (HumState
st HumState -> Getting [Text] HumState [Text] -> [Text]
forall s a. s -> Getting a s a -> a
^. (ExState -> Const [Text] ExState)
-> HumState -> Const [Text] HumState
Lens' HumState ExState
exL ((ExState -> Const [Text] ExState)
-> HumState -> Const [Text] HumState)
-> (([Text] -> Const [Text] [Text])
-> ExState -> Const [Text] ExState)
-> Getting [Text] HumState [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Const [Text] [Text]) -> ExState -> Const [Text] ExState
Lens' ExState [Text]
searchHistoryL)
mterm' :: Maybe Text
mterm' = if Maybe Text
mterm Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"" then Maybe Text
forall a. Maybe a
Nothing else Maybe Text
mterm
eterm :: Either String Regex
eterm = Either String Regex
-> (Text -> Either String Regex)
-> Maybe Text
-> Either String Regex
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (String -> Either String Regex
forall a b. a -> Either a b
Left String
"empty") (CompOption -> ExecOption -> Text -> Either String Regex
compile CompOption
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
compOpt
defaultCompOpt{caseSensitive :: Bool
caseSensitive = Bool
False} ExecOption
forall regex compOpt execOpt.
RegexOptions regex compOpt execOpt =>
execOpt
defaultExecOpt) Maybe Text
mterm'
in (String -> Widget Name)
-> (Regex -> Widget Name) -> Either String Regex -> Widget Name
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\String
_ -> Text -> Widget Name
forall n. Text -> Widget n
txt Text
htx) (\Regex
term -> Int -> Regex -> Text -> Widget Name
forall n. Int -> Regex -> Text -> Widget n
regexW Int
hi Regex
term Text
htx) Either String Regex
eterm
helpW' :: HumState -> Widget Name
helpW' :: HumState -> Widget Name
helpW' HumState
st =
let htx :: Text
htx = HumState
st HumState -> Getting Text HumState Text -> Text
forall s a. s -> Getting a s a -> a
^. (HelpState -> Const Text HelpState)
-> HumState -> Const Text HumState
Lens' HumState HelpState
helpL ((HelpState -> Const Text HelpState)
-> HumState -> Const Text HumState)
-> ((Text -> Const Text Text) -> HelpState -> Const Text HelpState)
-> Getting Text HumState Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Const Text Text) -> HelpState -> Const Text HelpState
Lens' HelpState Text
helpTextL
hi :: Int
hi = HumState
st HumState -> Getting Int HumState Int -> Int
forall s a. s -> Getting a s a -> a
^. (HelpState -> Const Int HelpState)
-> HumState -> Const Int HumState
Lens' HumState HelpState
helpL ((HelpState -> Const Int HelpState)
-> HumState -> Const Int HumState)
-> ((Int -> Const Int Int) -> HelpState -> Const Int HelpState)
-> Getting Int HumState Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Const Int Int) -> HelpState -> Const Int HelpState
Lens' HelpState Int
helpSearchIntL
mterm :: Maybe Text
mterm = (NonEmpty Text -> Text) -> [Text] -> Maybe Text
forall a b. (NonEmpty a -> b) -> [a] -> Maybe b
viaNonEmpty NonEmpty Text -> Text
forall (f :: * -> *) a. IsNonEmpty f a a "head" => f a -> a
head (HumState
st HumState -> Getting [Text] HumState [Text] -> [Text]
forall s a. s -> Getting a s a -> a
^. (ExState -> Const [Text] ExState)
-> HumState -> Const [Text] HumState
Lens' HumState ExState
exL ((ExState -> Const [Text] ExState)
-> HumState -> Const [Text] HumState)
-> (([Text] -> Const [Text] [Text])
-> ExState -> Const [Text] ExState)
-> Getting [Text] HumState [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Const [Text] [Text]) -> ExState -> Const [Text] ExState
Lens' ExState [Text]
searchHistoryL)
mterm' :: Maybe Text
mterm' = if Maybe Text
mterm Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"" then Maybe Text
forall a. Maybe a
Nothing else Maybe Text
mterm
in Widget Name -> (Text -> Widget Name) -> Maybe Text -> Widget Name
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> Widget Name
forall n. Text -> Widget n
txt Text
htx) (\Text
term -> Int -> Text -> Text -> Widget Name
forall n. Int -> Text -> Text -> Widget n
searchW Int
hi Text
term Text
htx) Maybe Text
mterm'
helpText' :: Text
helpText' :: Text
helpText' = [Text] -> Text
forall t. IsText t "unlines" => [t] -> t
unlines
[
Text
"Change views:"
, Text
" 1 - queue"
, Text
" 2 - library"
, Text
" 3 - playlists"
, Text
""
, Text
"General bindings:"
, Text
" t - play/pause toggle"
, Text
" , - previous song"
, Text
" . - next song"
, Text
" [ and ] - skip 5 second in either direction"
, Text
" { and } - skip 30 second in either direction"
, Text
" hjkl - vim movements"
, Text
" / and ? - forwards and backwards search"
, Text
" n and N - move to next and previous match of search"
, Text
" : - execute commands"
, Text
" q - quit"
, Text
" s - toggle single mode in mpd"
, Text
" c - toggle consume mode in mpd"
, Text
" x - toggle crossfade mode in mpd"
, Text
" r - toggle repeat mode in mpd"
, Text
" z - toggle random mode in mpd"
, Text
""
, Text
"Queue keybindings:"
, Text
" SPC - select song"
, Text
" y and d - yank and delete the selected songs"
, Text
" p - paste selected song"
, Text
" a - add selected songs to playlist"
, Text
""
, Text
"Library and Playlists keybindigns:"
, Text
" SPC - add song/song collection to queue"
, Text
" RET - add song/song collection to queue, and start playing the first one"
, Text
" ` - toggle sort of the album column between release order and alphabetical order"
, Text
""
, Text
"Playlists keybindigns:"
, Text
" On playlist contents:"
, Text
" e - make playlist editable, press again to get save prompt."
, Text
" editing a playlist is the same as editing the queue"
, Text
""
, Text
" On list of playlists:"
, Text
" e - rename playlist"
, Text
" y and p - copy and paste playlists (with -copy added to the name)"
, Text
" d - delete playlist (with prompt)"
, Text
""
, Text
"commands:"
, Text
":help - gets you this"
, Text
":q - quits"
, Text
":save $name - saves the queue to a playlist called $name"
]
helpSearch
:: Bool
-> HumState
-> EventM Name HumState
helpSearch :: Bool -> HumState -> EventM Name HumState
helpSearch Bool
dir HumState
st =
HumState -> EventM Name HumState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HumState -> EventM Name HumState)
-> HumState -> EventM Name HumState
forall a b. (a -> b) -> a -> b
$ if Bool
dir
then HumState
st HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (HelpState -> Identity HelpState) -> HumState -> Identity HumState
Lens' HumState HelpState
helpL ((HelpState -> Identity HelpState)
-> HumState -> Identity HumState)
-> ((Int -> Identity Int) -> HelpState -> Identity HelpState)
-> (Int -> Identity Int)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Identity Int) -> HelpState -> Identity HelpState
Lens' HelpState Int
helpSearchIntL ((Int -> Identity Int) -> HumState -> Identity HumState)
-> (Int -> Int) -> HumState -> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (\Int
x->Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
else HumState
st HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (HelpState -> Identity HelpState) -> HumState -> Identity HumState
Lens' HumState HelpState
helpL ((HelpState -> Identity HelpState)
-> HumState -> Identity HumState)
-> ((Int -> Identity Int) -> HelpState -> Identity HelpState)
-> (Int -> Identity Int)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Identity Int) -> HelpState -> Identity HelpState
Lens' HelpState Int
helpSearchIntL ((Int -> Identity Int) -> HumState -> Identity HumState)
-> (Int -> Int) -> HumState -> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (\Int
x->Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
handleEventHelp
:: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventHelp :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventHelp HumState
s BrickEvent Name HumEvent
e = case BrickEvent Name HumEvent
e of
VtyEvent Event
vtye -> case Event
vtye of
EvKey (KChar Char
'j') [] -> ViewportScroll Name -> Int -> EventM Name ()
forall n. ViewportScroll n -> Int -> EventM n ()
vScrollBy (Name -> ViewportScroll Name
forall n. n -> ViewportScroll n
viewportScroll Name
Help) Int
1 EventM Name ()
-> EventM Name (Next HumState) -> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
EvKey (KChar Char
'k') [] -> ViewportScroll Name -> Int -> EventM Name ()
forall n. ViewportScroll n -> Int -> EventM n ()
vScrollBy (Name -> ViewportScroll Name
forall n. n -> ViewportScroll n
viewportScroll Name
Help) (-Int
1) EventM Name ()
-> EventM Name (Next HumState) -> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
EvKey (KChar Char
'n') [] -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> EventM Name HumState -> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HumState -> EventM Name HumState
helpSearch (HumState
s HumState -> Getting Bool HumState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (ExState -> Const Bool ExState) -> HumState -> Const Bool HumState
Lens' HumState ExState
exL ((ExState -> Const Bool ExState)
-> HumState -> Const Bool HumState)
-> ((Bool -> Const Bool Bool) -> ExState -> Const Bool ExState)
-> Getting Bool HumState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> ExState -> Const Bool ExState
Lens' ExState Bool
searchDirectionL) HumState
s
EvKey (KChar Char
'N') [] -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> EventM Name HumState -> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HumState -> EventM Name HumState
helpSearch (HumState
s HumState -> Getting Bool HumState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (ExState -> Const Bool ExState) -> HumState -> Const Bool HumState
Lens' HumState ExState
exL ((ExState -> Const Bool ExState)
-> HumState -> Const Bool HumState)
-> ((Bool -> Const Bool Bool) -> ExState -> Const Bool ExState)
-> Getting Bool HumState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> ExState -> Const Bool ExState
Lens' ExState Bool
searchDirectionL Bool -> (Bool -> Bool) -> Bool
forall a b. a -> (a -> b) -> b
& Bool -> Bool
not) HumState
s
EvKey (KChar Char
'G') [] -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
EvKey (KChar Char
'g') [] -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
Event
_ -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
BrickEvent Name HumEvent
_ -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s