module Hum.UI where
import Brick.Main
import Brick.Types
import qualified Brick.BChan as BC
import Brick.Widgets.Core
import Brick.Widgets.List
import Brick.Widgets.Edit
import Graphics.Vty.Input.Events
import Network.MPD ( withMPD )
import qualified Network.MPD as MPD
import Hum.Types
import qualified Data.Vector as V
import qualified Data.Text as T
import Hum.Attributes
import Hum.Views
import Hum.Modes
import Hum.Rebuild
import Control.Lens
import System.Directory
app :: App HumState HumEvent Name
app :: App HumState HumEvent Name
app = App :: forall s e n.
(s -> [Widget n])
-> (s -> [CursorLocation n] -> Maybe (CursorLocation n))
-> (s -> BrickEvent n e -> EventM n (Next s))
-> (s -> EventM n s)
-> (s -> AttrMap)
-> App s e n
App { appDraw :: HumState -> [Widget Name]
appDraw = HumState -> [Widget Name]
drawUI
, appChooseCursor :: HumState -> [CursorLocation Name] -> Maybe (CursorLocation Name)
appChooseCursor = HumState -> [CursorLocation Name] -> Maybe (CursorLocation Name)
chooseCursor
, appHandleEvent :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
appHandleEvent = HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEvent
, appStartEvent :: HumState -> EventM Name HumState
appStartEvent = HumState -> EventM Name HumState
humStartEvent
, appAttrMap :: HumState -> AttrMap
appAttrMap = AttrMap -> HumState -> AttrMap
forall a b. a -> b -> a
const AttrMap
humAttrMap
}
drawUI :: HumState -> [Widget Name]
drawUI :: HumState -> [Widget Name]
drawUI HumState
st =
[if HumState
st HumState -> Getting Mode HumState Mode -> Mode
forall s a. s -> Getting a s a -> a
^. Getting Mode HumState Mode
Lens' HumState Mode
modeL Mode -> Mode -> Bool
forall a. Eq a => a -> a -> Bool
== Mode
PromptMode then HumState -> Widget Name
drawPrompt HumState
st else Widget Name
forall n. Widget n
emptyWidget,
HumState -> Widget Name
drawNowPlaying HumState
st
Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> (case HumState -> View
hview HumState
st of
View
QueueView -> HumState -> Widget Name
drawViewQueue HumState
st
View
LibraryView -> HumState -> Widget Name
drawViewLibrary HumState
st
View
PlaylistsView -> HumState -> Widget Name
drawViewPlaylists HumState
st
View
HelpView -> HumState -> Widget Name
drawViewHelp HumState
st
)
Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> if HumState
st HumState -> Getting Bool HumState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (Focus -> Const Bool Focus) -> HumState -> Const Bool HumState
Lens' HumState Focus
focusL ((Focus -> Const Bool Focus) -> HumState -> Const Bool HumState)
-> ((Bool -> Const Bool Bool) -> Focus -> Const Bool Focus)
-> Getting Bool HumState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> Focus -> Const Bool Focus
Lens' Focus Bool
focExL
then Text -> Widget Name
forall n. Text -> Widget n
txt (HumState
st HumState -> Getting ExSubMode HumState ExSubMode -> ExSubMode
forall s a. s -> Getting a s a -> a
^. (ExState -> Const ExSubMode ExState)
-> HumState -> Const ExSubMode HumState
Lens' HumState ExState
exL ((ExState -> Const ExSubMode ExState)
-> HumState -> Const ExSubMode HumState)
-> ((ExSubMode -> Const ExSubMode ExSubMode)
-> ExState -> Const ExSubMode ExState)
-> Getting ExSubMode HumState ExSubMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExSubMode -> Const ExSubMode ExSubMode)
-> ExState -> Const ExSubMode ExState
Lens' ExState ExSubMode
exPrefixL ExSubMode -> (ExSubMode -> Text) -> Text
forall a b. a -> (a -> b) -> b
& ExSubMode -> Text
exPrefixTxt) Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> ([Text] -> Widget Name) -> Bool -> Editor Text Name -> Widget Name
forall n t.
(Ord n, Show n, Monoid t, TextWidth t, GenericTextZipper t) =>
([t] -> Widget n) -> Bool -> Editor t n -> Widget n
renderEditor
(Text -> Widget Name
forall n. Text -> Widget n
txt (Text -> Widget Name) -> ([Text] -> Text) -> [Text] -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines)
(HumState
st HumState -> Getting Bool HumState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (Focus -> Const Bool Focus) -> HumState -> Const Bool HumState
Lens' HumState Focus
focusL ((Focus -> Const Bool Focus) -> HumState -> Const Bool HumState)
-> ((Bool -> Const Bool Bool) -> Focus -> Const Bool Focus)
-> Getting Bool HumState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> Focus -> Const Bool Focus
Lens' Focus Bool
focExL)
(HumState
st HumState
-> Getting (Editor Text Name) HumState (Editor Text Name)
-> Editor Text Name
forall s a. s -> Getting a s a -> a
^. (ExState -> Const (Editor Text Name) ExState)
-> HumState -> Const (Editor Text Name) HumState
Lens' HumState ExState
exL ((ExState -> Const (Editor Text Name) ExState)
-> HumState -> Const (Editor Text Name) HumState)
-> ((Editor Text Name
-> Const (Editor Text Name) (Editor Text Name))
-> ExState -> Const (Editor Text Name) ExState)
-> Getting (Editor Text Name) HumState (Editor Text Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Editor Text Name -> Const (Editor Text Name) (Editor Text Name))
-> ExState -> Const (Editor Text Name) ExState
Lens' ExState (Editor Text Name)
exEditorL)
else Text -> Widget Name
forall n. Text -> Widget n
txt Text
" "
]
chooseCursor :: HumState -> [CursorLocation Name] -> Maybe (CursorLocation Name)
chooseCursor :: HumState -> [CursorLocation Name] -> Maybe (CursorLocation Name)
chooseCursor HumState
st [CursorLocation Name]
ls
| HumState
st HumState -> Getting Bool HumState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (Focus -> Const Bool Focus) -> HumState -> Const Bool HumState
Lens' HumState Focus
focusL ((Focus -> Const Bool Focus) -> HumState -> Const Bool HumState)
-> ((Bool -> Const Bool Bool) -> Focus -> Const Bool Focus)
-> Getting Bool HumState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> Focus -> Const Bool Focus
Lens' Focus Bool
focExL = (CursorLocation Name -> Bool)
-> [CursorLocation Name] -> Maybe (CursorLocation Name)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Name -> CursorLocation Name -> Bool
forall n1. Eq n1 => n1 -> CursorLocation n1 -> Bool
isCurrent Name
ExEditor) [CursorLocation Name]
ls
| HumState
st HumState -> Getting PromptType HumState PromptType -> PromptType
forall s a. s -> Getting a s a -> a
^. (Prompts -> Const PromptType Prompts)
-> HumState -> Const PromptType HumState
Lens' HumState Prompts
promptsL ((Prompts -> Const PromptType Prompts)
-> HumState -> Const PromptType HumState)
-> ((PromptType -> Const PromptType PromptType)
-> Prompts -> Const PromptType Prompts)
-> Getting PromptType HumState PromptType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PromptType -> Const PromptType PromptType)
-> Prompts -> Const PromptType Prompts
Lens' Prompts PromptType
currentPromptL PromptType -> PromptType -> Bool
forall a. Eq a => a -> a -> Bool
== PromptType
TextPrompt = (CursorLocation Name -> Bool)
-> [CursorLocation Name] -> Maybe (CursorLocation Name)
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Name -> CursorLocation Name -> Bool
forall n1. Eq n1 => n1 -> CursorLocation n1 -> Bool
isCurrent Name
TextPromptEditor) [CursorLocation Name]
ls
| Bool
otherwise = Maybe (CursorLocation Name)
forall a. Maybe a
Nothing
where
isCurrent :: n1 -> CursorLocation n1 -> Bool
isCurrent n1
n CursorLocation n1
cl = CursorLocation n1
cl CursorLocation n1
-> Getting (Maybe n1) (CursorLocation n1) (Maybe n1) -> Maybe n1
forall s a. s -> Getting a s a -> a
^. Getting (Maybe n1) (CursorLocation n1) (Maybe n1)
forall n1 n2.
Lens (CursorLocation n1) (CursorLocation n2) (Maybe n1) (Maybe n2)
cursorLocationNameL Maybe n1 -> Maybe n1 -> Bool
forall a. Eq a => a -> a -> Bool
== n1 -> Maybe n1
forall a. a -> Maybe a
Just n1
n
buildInitialState :: BC.BChan HumEvent -> IO HumState
buildInitialState :: BChan HumEvent -> IO HumState
buildInitialState BChan HumEvent
chan = do
FilePath
configDir <- XdgDirectory -> FilePath -> IO FilePath
getXdgDirectory XdgDirectory
XdgConfig FilePath
"hum"
()
_ <- Bool -> FilePath -> IO ()
createDirectoryIfMissing Bool
True FilePath
configDir
let mode :: Mode
mode = Mode
NormalMode
let ex :: ExState
ex = ExState :: ExSubMode
-> Editor Text Name -> Bool -> [Text] -> [Text] -> ExState
ExState { exPrefix :: ExSubMode
exPrefix = ExSubMode
Cmd
, exEditor :: Editor Text Name
exEditor = Name -> Maybe Int -> Text -> Editor Text Name
forall n. n -> Maybe Int -> Text -> Editor Text n
editorText Name
ExEditor (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) Text
""
, searchDirection :: Bool
searchDirection = Bool
True
, searchHistory :: [Text]
searchHistory = []
, cmdHistory :: [Text]
cmdHistory = []
}
Maybe Song
currentSong <- Maybe Song -> Either MPDError (Maybe Song) -> Maybe Song
forall b a. b -> Either a b -> b
fromRight Maybe Song
forall a. Maybe a
Nothing (Either MPDError (Maybe Song) -> Maybe Song)
-> IO (Either MPDError (Maybe Song)) -> IO (Maybe Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD (Maybe Song) -> IO (Either MPDError (Maybe Song))
forall a. MPD a -> IO (Response a)
withMPD MPD (Maybe Song)
forall (m :: * -> *). MonadMPD m => m (Maybe Song)
MPD.currentSong
Maybe Status
status <- Maybe Status -> Either MPDError (Maybe Status) -> Maybe Status
forall b a. b -> Either a b -> b
fromRight Maybe Status
forall a. Maybe a
Nothing (Either MPDError (Maybe Status) -> Maybe Status)
-> IO (Either MPDError (Maybe Status)) -> IO (Maybe Status)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Status -> Maybe Status
forall a. a -> Maybe a
Just (Status -> Maybe Status)
-> IO (Either MPDError Status)
-> IO (Either MPDError (Maybe Status))
forall (f :: * -> *) (g :: * -> *) a b.
(Functor f, Functor g) =>
(a -> b) -> f (g a) -> f (g b)
<<$>> MPD Status -> IO (Either MPDError Status)
forall a. MPD a -> IO (Response a)
withMPD MPD Status
forall (m :: * -> *). MonadMPD m => m Status
MPD.status)
let hview :: View
hview = View
QueueView
let focus :: Focus
focus = Focus :: FocQueue -> FocLib -> FocPlay -> Bool -> Focus
Focus { focQueue :: FocQueue
focQueue = FocQueue
FocQueue
, focLib :: FocLib
focLib = FocLib
FocArtists
, focPlay :: FocPlay
focPlay = FocPlay
FocPlaylists
, focEx :: Bool
focEx = Bool
False
}
let clipboard :: Clipboard
clipboard = Clipboard :: SongList -> Maybe PlaylistName -> Clipboard
Clipboard { clSongs :: SongList
clSongs = Name -> Vector (Song, Bool) -> Int -> SongList
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
ClSongs Vector (Song, Bool)
forall a. Vector a
V.empty Int
1
, clPlName :: Maybe PlaylistName
clPlName = Maybe PlaylistName
forall a. Maybe a
Nothing}
Vector Song
queueVec <- [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD (Maybe Int -> MPD [Song]
forall (m :: * -> *). MonadMPD m => Maybe Int -> m [Song]
MPD.playlistInfo Maybe Int
forall a. Maybe a
Nothing)
let queue :: SongList
queue = (, Bool
False) (Song -> (Song, Bool)) -> GenericList Name Vector Song -> SongList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
QueueList Vector Song
queueVec Int
1
Vector Value
artistsVec <- [Value] -> Vector Value
forall a. [a] -> Vector a
V.fromList ([Value] -> Vector Value)
-> (Either MPDError [Value] -> [Value])
-> Either MPDError [Value]
-> Vector Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Either MPDError [Value] -> [Value]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Value] -> Vector Value)
-> IO (Either MPDError [Value]) -> IO (Vector Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Value] -> IO (Either MPDError [Value])
forall a. MPD a -> IO (Response a)
withMPD (Metadata -> Query -> MPD [Value]
forall (m :: * -> *). MonadMPD m => Metadata -> Query -> m [Value]
MPD.list Metadata
MPD.AlbumArtist Query
forall a. Monoid a => a
mempty)
let artists :: GenericList Name Vector Value
artists = Name -> Vector Value -> Int -> GenericList Name Vector Value
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
ArtistsList Vector Value
artistsVec Int
1
let yalbumSort :: Bool
yalbumSort = Bool
True
Vector (Value, Value)
yalbumsVec <- IO (Vector (Value, Value))
-> (Value -> IO (Vector (Value, Value)))
-> Maybe Value
-> IO (Vector (Value, Value))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Vector (Value, Value) -> IO (Vector (Value, Value))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Vector (Value, Value)
forall (f :: * -> *) a. Alternative f => f a
empty) (Bool -> Value -> IO (Vector (Value, Value))
yalbumsOfArtist Bool
yalbumSort) ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
artists)
let yalbums :: GenericList Name Vector (Value, Value)
yalbums = Name
-> Vector (Value, Value)
-> Int
-> GenericList Name Vector (Value, Value)
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
YalbumsList Vector (Value, Value)
yalbumsVec Int
1
Vector Song
songsVec <- IO (Vector Song)
-> (Value -> IO (Vector Song)) -> Maybe Value -> IO (Vector Song)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Vector Song -> IO (Vector Song)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Vector Song
forall (f :: * -> *) a. Alternative f => f a
empty) Value -> IO (Vector Song)
songsOfAlbum ((Value, Value) -> Value
forall a b. (a, b) -> b
snd ((Value, Value) -> Value)
-> ((Int, (Value, Value)) -> (Value, Value))
-> (Int, (Value, Value))
-> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, (Value, Value)) -> (Value, Value)
forall a b. (a, b) -> b
snd ((Int, (Value, Value)) -> Value)
-> Maybe (Int, (Value, Value)) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector (Value, Value)
-> Maybe (Int, (Value, Value))
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector (Value, Value)
yalbums)
let songs :: GenericList Name Vector Song
songs = Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
SongsList Vector Song
songsVec Int
1
let library :: LibraryState
library = LibraryState :: GenericList Name Vector Value
-> GenericList Name Vector (Value, Value)
-> Bool
-> GenericList Name Vector Song
-> LibraryState
LibraryState { GenericList Name Vector Value
artists :: GenericList Name Vector Value
artists :: GenericList Name Vector Value
artists, GenericList Name Vector (Value, Value)
yalbums :: GenericList Name Vector (Value, Value)
yalbums :: GenericList Name Vector (Value, Value)
yalbums, Bool
yalbumSort :: Bool
yalbumSort :: Bool
yalbumSort, GenericList Name Vector Song
songs :: GenericList Name Vector Song
songs :: GenericList Name Vector Song
songs }
Vector PlaylistName
plListVec <- [PlaylistName] -> Vector PlaylistName
forall a. [a] -> Vector a
V.fromList ([PlaylistName] -> Vector PlaylistName)
-> (Either MPDError [PlaylistName] -> [PlaylistName])
-> Either MPDError [PlaylistName]
-> Vector PlaylistName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PlaylistName] -> [PlaylistName]
forall a. Ord a => [a] -> [a]
sort ([PlaylistName] -> [PlaylistName])
-> (Either MPDError [PlaylistName] -> [PlaylistName])
-> Either MPDError [PlaylistName]
-> [PlaylistName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PlaylistName] -> Either MPDError [PlaylistName] -> [PlaylistName]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [PlaylistName] -> Vector PlaylistName)
-> IO (Either MPDError [PlaylistName]) -> IO (Vector PlaylistName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [PlaylistName] -> IO (Either MPDError [PlaylistName])
forall a. MPD a -> IO (Response a)
withMPD MPD [PlaylistName]
forall (m :: * -> *). MonadMPD m => m [PlaylistName]
MPD.listPlaylists
let plList :: GenericList Name Vector PlaylistName
plList = Name
-> Vector PlaylistName
-> Int
-> GenericList Name Vector PlaylistName
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
PlaylistList Vector PlaylistName
plListVec Int
1
Vector Song
plSongsVec <- [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD
( PlaylistName -> MPD [Song]
forall (m :: * -> *). MonadMPD m => PlaylistName -> m [Song]
MPD.listPlaylistInfo
(PlaylistName -> MPD [Song]) -> PlaylistName -> MPD [Song]
forall a b. (a -> b) -> a -> b
$ PlaylistName
-> ((Int, PlaylistName) -> PlaylistName)
-> Maybe (Int, PlaylistName)
-> PlaylistName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PlaylistName
"<no playlists>" (Int, PlaylistName) -> PlaylistName
forall a b. (a, b) -> b
snd (GenericList Name Vector PlaylistName -> Maybe (Int, PlaylistName)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector PlaylistName
plList)
)
let plSongs :: SongList
plSongs = (, Bool
False) (Song -> (Song, Bool)) -> GenericList Name Vector Song -> SongList
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
PlaylistSongs Vector Song
plSongsVec Int
1
let playlists :: PlaylistsState
playlists = PlaylistsState :: GenericList Name Vector PlaylistName -> SongList -> PlaylistsState
PlaylistsState { GenericList Name Vector PlaylistName
plList :: GenericList Name Vector PlaylistName
plList :: GenericList Name Vector PlaylistName
plList, SongList
plSongs :: SongList
plSongs :: SongList
plSongs }
let editable :: Bool
editable = Bool
False
let prompts :: Prompts
prompts = Prompts :: PromptType
-> Text
-> List Name (Maybe PlaylistName)
-> Editor Text Name
-> (Bool -> HumState -> EventM Name HumState)
-> Prompts
Prompts
{ currentPrompt :: PromptType
currentPrompt = PromptType
PlSelectPrompt
, promptTitle :: Text
promptTitle = Text
""
, textPrompt :: Editor Text Name
textPrompt = Name -> Maybe Int -> Text -> Editor Text Name
forall n. n -> Maybe Int -> Text -> Editor Text n
editorText Name
TextPromptEditor (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
1) Text
""
, plSelectPrompt :: List Name (Maybe PlaylistName)
plSelectPrompt = Int
-> Maybe PlaylistName
-> List Name (Maybe PlaylistName)
-> List Name (Maybe PlaylistName)
forall (t :: * -> *) e n.
(Splittable t, Applicative t, Semigroup (t e)) =>
Int -> e -> GenericList n t e -> GenericList n t e
listInsert Int
0 Maybe PlaylistName
forall a. Maybe a
Nothing (PlaylistName -> Maybe PlaylistName
forall a. a -> Maybe a
Just (PlaylistName -> Maybe PlaylistName)
-> GenericList Name Vector PlaylistName
-> List Name (Maybe PlaylistName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector PlaylistName
plList)
, exitPromptFunc :: Bool -> HumState -> EventM Name HumState
exitPromptFunc = \Bool
_ HumState
s -> 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
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Mode -> Identity Mode) -> HumState -> Identity HumState
Lens' HumState Mode
modeL ((Mode -> Identity Mode) -> HumState -> Identity HumState)
-> Mode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Mode
NormalMode
}
let help :: HelpState
help = HelpState :: Text -> Int -> HelpState
HelpState
{ helpText :: Text
helpText = Text
helpText'
, helpSearchInt :: Int
helpSearchInt = Int
0
}
HumState -> IO HumState
forall (f :: * -> *) a. Applicative f => a -> f a
pure HumState :: BChan HumEvent
-> View
-> Maybe Status
-> Mode
-> ExState
-> Maybe Song
-> SongList
-> LibraryState
-> PlaylistsState
-> Clipboard
-> Focus
-> Bool
-> Prompts
-> HelpState
-> HumState
HumState { BChan HumEvent
chan :: BChan HumEvent
chan :: BChan HumEvent
chan
, View
hview :: View
hview :: View
hview
, Mode
mode :: Mode
mode :: Mode
mode
, ExState
ex :: ExState
ex :: ExState
ex
, Maybe Status
status :: Maybe Status
status :: Maybe Status
status
, Maybe Song
currentSong :: Maybe Song
currentSong :: Maybe Song
currentSong
, SongList
queue :: SongList
queue :: SongList
queue
, Clipboard
clipboard :: Clipboard
clipboard :: Clipboard
clipboard
, LibraryState
library :: LibraryState
library :: LibraryState
library
, PlaylistsState
playlists :: PlaylistsState
playlists :: PlaylistsState
playlists
, HelpState
help :: HelpState
help :: HelpState
help
, Focus
focus :: Focus
focus :: Focus
focus
, Bool
editable :: Bool
editable :: Bool
editable
, Prompts
prompts :: Prompts
prompts :: Prompts
prompts
}
humStartEvent :: HumState -> EventM Name HumState
humStartEvent :: HumState -> EventM Name HumState
humStartEvent = HumState -> EventM Name HumState
forall (f :: * -> *) a. Applicative f => a -> f a
pure
handleEvent :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEvent :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEvent HumState
s BrickEvent Name HumEvent
e = case BrickEvent Name HumEvent
e of
VtyEvent Event
vtye -> case HumState
s HumState -> Getting Mode HumState Mode -> Mode
forall s a. s -> Getting a s a -> a
^. Getting Mode HumState Mode
Lens' HumState Mode
modeL of
Mode
ExMode -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleExEvent HumState
s BrickEvent Name HumEvent
e
Mode
PromptMode -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handlePromptEvent HumState
s BrickEvent Name HumEvent
e
Mode
NormalMode -> case Event
vtye of
EvKey (KChar Char
'q') [] -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
halt HumState
s
EvKey (KChar Char
't') [] -> do
Either MPDError PlaybackState
st <- IO (Either MPDError PlaybackState)
-> EventM Name (Either MPDError PlaybackState)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ((Status -> PlaybackState
MPD.stState (Status -> PlaybackState)
-> Either MPDError Status -> Either MPDError PlaybackState
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Either MPDError Status -> Either MPDError PlaybackState)
-> IO (Either MPDError Status)
-> IO (Either MPDError PlaybackState)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD Status -> IO (Either MPDError Status)
forall a. MPD a -> IO (Response a)
withMPD MPD Status
forall (m :: * -> *). MonadMPD m => m Status
MPD.status)
Response ()
_ <- case Either MPDError PlaybackState
st of
Left MPDError
_ -> IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> MPD ()
forall (m :: * -> *). MonadMPD m => Bool -> m ()
MPD.pause Bool
True)
Right PlaybackState
_ -> IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ MPD ()
forall (m :: * -> *). MonadMPD m => m ()
MPD.toggle)
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
EvKey (KChar Char
's') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> MPD ()
forall (m :: * -> *). MonadMPD m => Bool -> m ()
MPD.single (Bool -> (Status -> Bool) -> Maybe Status -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool) -> (Status -> Bool) -> Status -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Bool
MPD.stSingle) (HumState -> Maybe Status
status HumState
s)))
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'c') [] -> do
Response ()
_ <-
IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
( MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD
(MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> MPD ()
forall (m :: * -> *). MonadMPD m => Bool -> m ()
MPD.consume (Bool -> (Status -> Bool) -> Maybe Status -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool) -> (Status -> Bool) -> Status -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Bool
MPD.stConsume) (HumState -> Maybe Status
status HumState
s))
)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'x') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Seconds -> MPD ()
forall (m :: * -> *). MonadMPD m => Seconds -> m ()
MPD.crossfade
( (\case
Seconds
0 -> Seconds
5
Seconds
_ -> Seconds
0
)
(Seconds -> Seconds) -> Seconds -> Seconds
forall a b. (a -> b) -> a -> b
$ Seconds -> (Status -> Seconds) -> Maybe Status -> Seconds
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Seconds
0 Status -> Seconds
MPD.stXFadeWidth (HumState -> Maybe Status
status HumState
s)
)
)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'r') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> MPD ()
forall (m :: * -> *). MonadMPD m => Bool -> m ()
MPD.repeat (Bool -> (Status -> Bool) -> Maybe Status -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool) -> (Status -> Bool) -> Status -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Bool
MPD.stRepeat) (HumState -> Maybe Status
status HumState
s)))
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'z') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> MPD ()
forall (m :: * -> *). MonadMPD m => Bool -> m ()
MPD.random (Bool -> (Status -> Bool) -> Maybe Status -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False (Bool -> Bool
not (Bool -> Bool) -> (Status -> Bool) -> Status -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Status -> Bool
MPD.stRandom) (HumState -> Maybe Status
status HumState
s)))
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'/') [] ->
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Mode -> Identity Mode) -> HumState -> Identity HumState
Lens' HumState Mode
modeL ((Mode -> Identity Mode) -> HumState -> Identity HumState)
-> Mode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Mode
ExMode
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (ExState -> Identity ExState) -> HumState -> Identity HumState
Lens' HumState ExState
exL ((ExState -> Identity ExState) -> HumState -> Identity HumState)
-> ((ExSubMode -> Identity ExSubMode)
-> ExState -> Identity ExState)
-> (ExSubMode -> Identity ExSubMode)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExSubMode -> Identity ExSubMode) -> ExState -> Identity ExState
Lens' ExState ExSubMode
exPrefixL ((ExSubMode -> Identity ExSubMode)
-> HumState -> Identity HumState)
-> ExSubMode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ExSubMode
FSearch
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (ExState -> Identity ExState) -> HumState -> Identity HumState
Lens' HumState ExState
exL ((ExState -> Identity ExState) -> HumState -> Identity HumState)
-> ((Bool -> Identity Bool) -> ExState -> Identity ExState)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> ExState -> Identity ExState
Lens' ExState Bool
searchDirectionL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Focus -> Identity Focus) -> HumState -> Identity HumState
Lens' HumState Focus
focusL ((Focus -> Identity Focus) -> HumState -> Identity HumState)
-> ((Bool -> Identity Bool) -> Focus -> Identity Focus)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> Focus -> Identity Focus
Lens' Focus Bool
focExL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
EvKey (KChar Char
'?') [] ->
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Mode -> Identity Mode) -> HumState -> Identity HumState
Lens' HumState Mode
modeL ((Mode -> Identity Mode) -> HumState -> Identity HumState)
-> Mode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Mode
ExMode
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (ExState -> Identity ExState) -> HumState -> Identity HumState
Lens' HumState ExState
exL ((ExState -> Identity ExState) -> HumState -> Identity HumState)
-> ((ExSubMode -> Identity ExSubMode)
-> ExState -> Identity ExState)
-> (ExSubMode -> Identity ExSubMode)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExSubMode -> Identity ExSubMode) -> ExState -> Identity ExState
Lens' ExState ExSubMode
exPrefixL ((ExSubMode -> Identity ExSubMode)
-> HumState -> Identity HumState)
-> ExSubMode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ExSubMode
BSearch
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (ExState -> Identity ExState) -> HumState -> Identity HumState
Lens' HumState ExState
exL ((ExState -> Identity ExState) -> HumState -> Identity HumState)
-> ((Bool -> Identity Bool) -> ExState -> Identity ExState)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> ExState -> Identity ExState
Lens' ExState Bool
searchDirectionL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Focus -> Identity Focus) -> HumState -> Identity HumState
Lens' HumState Focus
focusL ((Focus -> Identity Focus) -> HumState -> Identity HumState)
-> ((Bool -> Identity Bool) -> Focus -> Identity Focus)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> Focus -> Identity Focus
Lens' Focus Bool
focExL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
EvKey (KChar Char
':') [] ->
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Mode -> Identity Mode) -> HumState -> Identity HumState
Lens' HumState Mode
modeL ((Mode -> Identity Mode) -> HumState -> Identity HumState)
-> Mode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Mode
ExMode
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (ExState -> Identity ExState) -> HumState -> Identity HumState
Lens' HumState ExState
exL ((ExState -> Identity ExState) -> HumState -> Identity HumState)
-> ((ExSubMode -> Identity ExSubMode)
-> ExState -> Identity ExState)
-> (ExSubMode -> Identity ExSubMode)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExSubMode -> Identity ExSubMode) -> ExState -> Identity ExState
Lens' ExState ExSubMode
exPrefixL ((ExSubMode -> Identity ExSubMode)
-> HumState -> Identity HumState)
-> ExSubMode -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ ExSubMode
Cmd
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Focus -> Identity Focus) -> HumState -> Identity HumState
Lens' HumState Focus
focusL ((Focus -> Identity Focus) -> HumState -> Identity HumState)
-> ((Bool -> Identity Bool) -> Focus -> Identity Focus)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> Focus -> Identity Focus
Lens' Focus Bool
focExL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
True
EvKey (KChar Char
'.') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD MPD ()
forall (m :: * -> *). MonadMPD m => m ()
MPD.next)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
',') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD MPD ()
forall (m :: * -> *). MonadMPD m => m ()
MPD.previous)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
']') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> FractionalSeconds -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
Bool -> FractionalSeconds -> m ()
MPD.seekCur Bool
False FractionalSeconds
5)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'[') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> FractionalSeconds -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
Bool -> FractionalSeconds -> m ()
MPD.seekCur Bool
False (-FractionalSeconds
5))
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'}') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> FractionalSeconds -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
Bool -> FractionalSeconds -> m ()
MPD.seekCur Bool
False FractionalSeconds
30)
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'{') [] -> do
Response ()
_ <- IO (Response ()) -> EventM Name (Response ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (MPD () -> IO (Response ())
forall a. MPD a -> IO (Response a)
withMPD (MPD () -> IO (Response ())) -> MPD () -> IO (Response ())
forall a b. (a -> b) -> a -> b
$ Bool -> FractionalSeconds -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
Bool -> FractionalSeconds -> m ()
MPD.seekCur Bool
False (-FractionalSeconds
30))
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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
EvKey (KChar Char
'1') [] -> do
()
_ <- IO () -> EventM Name ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (BChan HumEvent -> HumEvent -> IO ()
forall a. BChan a -> a -> IO ()
BC.writeBChan (HumState -> BChan HumEvent
chan HumState
s) (Tick -> HumEvent
forall a b. a -> Either a b
Left Tick
Tick))
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Bool -> Identity Bool) -> HumState -> Identity HumState
Lens' HumState Bool
editableL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (View -> Identity View) -> HumState -> Identity HumState
Lens' HumState View
hviewL ((View -> Identity View) -> HumState -> Identity HumState)
-> View -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ View
QueueView
EvKey (KChar Char
'2') [] -> do
()
_ <- IO () -> EventM Name ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (BChan HumEvent -> HumEvent -> IO ()
forall a. BChan a -> a -> IO ()
BC.writeBChan (HumState -> BChan HumEvent
chan HumState
s) (Tick -> HumEvent
forall a b. a -> Either a b
Left Tick
Tick))
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Bool -> Identity Bool) -> HumState -> Identity HumState
Lens' HumState Bool
editableL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (View -> Identity View) -> HumState -> Identity HumState
Lens' HumState View
hviewL ((View -> Identity View) -> HumState -> Identity HumState)
-> View -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ View
LibraryView
EvKey (KChar Char
'3') [] -> do
()
_ <- IO () -> EventM Name ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (BChan HumEvent -> HumEvent -> IO ()
forall a. BChan a -> a -> IO ()
BC.writeBChan (HumState -> BChan HumEvent
chan HumState
s) (Tick -> HumEvent
forall a b. a -> Either a b
Left Tick
Tick))
HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue (HumState -> EventM Name (Next HumState))
-> HumState -> EventM Name (Next HumState)
forall a b. (a -> b) -> a -> b
$ HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Bool -> Identity Bool) -> HumState -> Identity HumState
Lens' HumState Bool
editableL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> Bool -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Bool
False
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (View -> Identity View) -> HumState -> Identity HumState
Lens' HumState View
hviewL ((View -> Identity View) -> HumState -> Identity HumState)
-> View -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ View
PlaylistsView
EvResize Int
_ Int
_ -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s
Event
_ -> case HumState -> View
hview HumState
s of
View
QueueView -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventQueue HumState
s BrickEvent Name HumEvent
e
View
LibraryView -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventLibrary HumState
s BrickEvent Name HumEvent
e
View
PlaylistsView -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventPlaylists HumState
s BrickEvent Name HumEvent
e
View
HelpView -> HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventHelp HumState
s BrickEvent Name HumEvent
e
(AppEvent (Left Tick
Tick)) -> 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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
(AppEvent (Right (Right [Subsystem]
subs)))
| Subsystem
MPD.PlaylistS Subsystem -> [Subsystem] -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` [Subsystem]
subs -> 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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus (HumState -> EventM Name HumState)
-> EventM Name HumState -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildQueue HumState
s
| Bool
otherwise -> 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
=<< HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s
BrickEvent Name HumEvent
_ -> HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue HumState
s