module Hum.Views.Queue where
import Hum.Types
import Brick.Main
import Graphics.Vty.Input.Events
import Brick.Types
import Brick.Widgets.Core
import Brick.Widgets.Center
import Brick.Widgets.List
import Hum.Attributes
import Hum.Utils
import Hum.Rebuild
import Hum.Views.Common
import Network.MPD ( withMPD )
import qualified Network.MPD as MPD
import qualified Data.Map.Strict as Map
import Control.Lens
drawViewQueue :: HState -> Widget Name
drawViewQueue :: HState -> Widget Name
drawViewQueue HState
st =
let vsize :: Int
vsize = case Maybe (Maybe (Extent Name)) -> Maybe (Extent Name)
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe (Extent Name)) -> Maybe (Extent Name))
-> Maybe (Maybe (Extent Name)) -> Maybe (Extent Name)
forall a b. (a -> b) -> a -> b
$ Name
-> Map Name (Maybe (Extent Name)) -> Maybe (Maybe (Extent Name))
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name
Queue (Map Name (Maybe (Extent Name)) -> Maybe (Maybe (Extent Name)))
-> Map Name (Maybe (Extent Name)) -> Maybe (Maybe (Extent Name))
forall a b. (a -> b) -> a -> b
$ HState -> Map Name (Maybe (Extent Name))
extentMap HState
st of
Just Extent Name
e -> (Int, Int) -> Int
forall a b. (a, b) -> b
snd ((Int, Int) -> Int)
-> (Extent Name -> (Int, Int)) -> Extent Name -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Extent Name -> (Int, Int)
forall n. Extent n -> (Int, Int)
extentSize (Extent Name -> Int) -> Extent Name -> Int
forall a b. (a -> b) -> a -> b
$ Extent Name
e
Maybe (Extent Name)
Nothing -> Int
60
in Name -> Widget Name -> Widget Name
forall n. n -> Widget n -> Widget n
reportExtent Name
Queue (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Widget Name -> Widget Name
forall n. Widget n -> Widget n
hCenter
( Name -> ViewportType -> Widget Name -> Widget Name
forall n.
(Ord n, Show n) =>
n -> ViewportType -> Widget n -> Widget n
viewport Name
Queue ViewportType
Vertical
(Widget Name -> Widget Name)
-> (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Widget Name -> Widget Name
forall n. Int -> Widget n -> Widget n
vLimit Int
vsize
(Widget Name -> Widget Name)
-> (Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Widget Name -> Widget Name
forall n. Widget n -> Widget n
center
(Widget Name -> Widget Name) -> Widget Name -> Widget Name
forall a b. (a -> b) -> a -> b
$ Widget Name -> Widget Name
forall n. Widget n -> Widget n
hCenter Widget Name
forall n. Widget n
header
Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<=> Widget Name -> Widget Name
forall n. Widget n -> Widget n
hCenter
((Bool -> (Song, Bool) -> Widget Name)
-> Bool -> GenericList Name Vector (Song, Bool) -> Widget Name
forall (t :: * -> *) n e.
(Traversable t, Splittable t, Ord n, Show n) =>
(Bool -> e -> Widget n) -> Bool -> GenericList n t e -> Widget n
renderList (((Song, Bool) -> Widget Name)
-> Bool -> (Song, Bool) -> Widget Name
forall a b. a -> b -> a
const (HState -> (Song, Bool) -> Widget Name
forall n. HState -> (Song, Bool) -> Widget n
queueRow HState
st))
((Focus -> FocQueue
focQueue (Focus -> FocQueue) -> (HState -> Focus) -> HState -> FocQueue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HState -> Focus
focus (HState -> FocQueue) -> HState -> FocQueue
forall a b. (a -> b) -> a -> b
$ HState
st) FocQueue -> FocQueue -> Bool
forall a. Eq a => a -> a -> Bool
== FocQueue
FocQueue)
(HState -> GenericList Name Vector (Song, Bool)
queue HState
st)
)
)
where
album :: Widget n
album =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueAlbumAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Per Int
25)) (Int -> Padding
Pad Int
1) Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt Text
"Album"
track :: Widget n
track = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTrackAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Col Int
3)) Padding
Max (Int -> Padding
Pad Int
1) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt Text
"#"
title :: Widget n
title = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTitleAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column Maybe PerCol
forall a. Maybe a
Nothing Padding
Max Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt Text
"Title"
artist :: Widget n
artist =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueArtistAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Per Int
25)) Padding
Max (Int -> Padding
Pad Int
1) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt Text
"Artist"
time :: Widget n
time =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTimeAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Col Int
5)) Padding
Max (Int -> Padding
Pad Int
1) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt Text
"Time"
header :: Widget n
header = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
headerAttr
(
Widget n
forall n. Widget n
album Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
track Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
title Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
artist Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
time)
queueRow :: HState -> (MPD.Song, Highlight) -> Widget n
queueRow :: HState -> (Song, Bool) -> Widget n
queueRow HState
st (Song
song, Bool
hl) =
(if Bool
hl then Widget n -> Widget n
forall n. Widget n -> Widget n
highlightOverQueueAttrs else Widget n -> Widget n
forall a. a -> a
id)
(Widget n -> Widget n)
-> (Widget n -> Widget n) -> Widget n -> Widget n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Maybe Int -> Maybe (Maybe Int)
forall a. a -> Maybe a
Just (Song -> Maybe Int
MPD.sgIndex Song
song) Maybe (Maybe Int) -> Maybe (Maybe Int) -> Bool
forall a. Eq a => a -> a -> Bool
== (Song -> Maybe Int
MPD.sgIndex (Song -> Maybe Int) -> Maybe Song -> Maybe (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe Song
nowPlaying)
then AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withDefAttr AttrName
queueNowPlayingAttr
else Widget n -> Widget n
forall a. a -> a
id
)
(Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Widget n -> Widget n
forall n. Widget n -> Widget n
hCenter (
Widget n
forall n. Widget n
album Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
track Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
title Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
artist Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
time)
where
nowPlaying :: Maybe Song
nowPlaying = HState -> Maybe Song
currentSong HState
st
album :: Widget n
album =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueAlbumAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Per Int
25)) (Int -> Padding
Pad Int
1) Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Metadata -> Song -> Text
meta
Text
"<no album>"
Metadata
MPD.Album
Song
song
track :: Widget n
track =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTrackAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Col Int
3)) Padding
Max (Int -> Padding
Pad Int
1) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Metadata -> Song -> Text
meta
Text
"?"
Metadata
MPD.Track
Song
song
title :: Widget n
title = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTitleAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column Maybe PerCol
forall a. Maybe a
Nothing Padding
Max Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Metadata -> Song -> Text
meta
Text
"<no title>"
Metadata
MPD.Title
Song
song
artist :: Widget n
artist =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueArtistAttr (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Per Int
25)) Padding
Max (Int -> Padding
Pad Int
1) (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt (Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Metadata -> Song -> Text
meta
Text
"<no artist>"
Metadata
MPD.Artist
Song
song
time :: Widget n
time =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
queueTimeAttr
(Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
forall n.
Maybe PerCol -> Padding -> Padding -> Widget n -> Widget n
column (PerCol -> Maybe PerCol
forall a. a -> Maybe a
Just (Int -> PerCol
Col Int
5)) Padding
Max (Int -> Padding
Pad Int
1)
(Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$ Text -> Widget n
forall n. Text -> Widget n
txt
(Text -> Widget n) -> Text -> Widget n
forall a b. (a -> b) -> a -> b
$ Integer -> Text
secondsToTime
(Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ Song -> Integer
MPD.sgLength Song
song
pasteDeleteCleanup :: HState -> SongList -> EventM Name HState
pasteDeleteCleanup :: HState
-> GenericList Name Vector (Song, Bool) -> EventM Name HState
pasteDeleteCleanup HState
s GenericList Name Vector (Song, Bool)
clSongs' = do
let mi :: Maybe Int
mi = GenericList Name Vector (Song, Bool) -> Maybe Int
forall n (t :: * -> *) e. GenericList n t e -> Maybe Int
listSelected (HState -> GenericList Name Vector (Song, Bool)
queue HState
s)
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
Maybe Song
currentSong <- IO (Maybe Song) -> EventM Name (Maybe Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (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 <- IO (Maybe Status) -> EventM Name (Maybe Status)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (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))
HState
s' <- HState -> EventM Name HState
forall (m :: * -> *). MonadIO m => HState -> m HState
rebuildQueue HState
s
HState -> EventM Name HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState
s' HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState
Lens' HState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HState
-> HState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> (Int
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> Maybe Int
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall a. a -> a
id Int
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
listMoveTo Maybe Int
mi
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (Clipboard -> Identity Clipboard) -> HState -> Identity HState
Lens' HState Clipboard
clipboardL ((Clipboard -> Identity Clipboard) -> HState -> Identity HState)
-> ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> Clipboard -> Identity Clipboard)
-> (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> Clipboard -> Identity Clipboard
Lens' Clipboard (GenericList Name Vector (Song, Bool))
clSongsL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState)
-> GenericList Name Vector (Song, Bool) -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector (Song, Bool)
clSongs') { Maybe Song
currentSong :: Maybe Song
currentSong :: Maybe Song
currentSong
, Maybe Status
status :: Maybe Status
status :: Maybe Status
status
, Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap
}
queueSearch :: Bool -> HState -> EventM Name HState
queueSearch :: Bool -> HState -> EventM Name HState
queueSearch Bool
direction HState
s =
let
dir :: GenericList n Vector e -> GenericList n Vector e
dir = if Bool
direction then GenericList n Vector e -> GenericList n Vector e
forall a. a -> a
id else GenericList n Vector e -> GenericList n Vector e
forall (t :: * -> *) n e.
(Reversible t, Foldable t) =>
GenericList n t e -> GenericList n t e
listReverse
searchkey :: Text
searchkey = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" ((HState
s HState -> Getting [Text] HState [Text] -> [Text]
forall s a. s -> Getting a s a -> a
^. (ExState -> Const [Text] ExState) -> HState -> Const [Text] HState
Lens' HState ExState
exL ((ExState -> Const [Text] ExState)
-> HState -> Const [Text] HState)
-> (([Text] -> Const [Text] [Text])
-> ExState -> Const [Text] ExState)
-> Getting [Text] HState [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Text] -> Const [Text] [Text]) -> ExState -> Const [Text] ExState
Lens' ExState [Text]
searchHistoryL) [Text] -> Int -> Maybe Text
forall a. [a] -> Int -> Maybe a
!!? Int
0)
in
if Text
searchkey Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
""
then HState -> EventM Name HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure HState
s
else do
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
HState -> EventM Name HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(HState -> EventM Name HState) -> HState -> EventM Name HState
forall a b. (a -> b) -> a -> b
$ HState
s { Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap }
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState
Lens' HState (GenericList Name Vector (Song, Bool))
queueL
((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HState
-> HState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ ( GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall n e. GenericList n Vector e -> GenericList n Vector e
dir
(GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Song, Bool) -> Bool)
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listFindBy
( Text -> [Metadata] -> Song -> Bool
songSearch Text
searchkey [Metadata
MPD.Title, Metadata
MPD.Album, Metadata
MPD.Artist]
(Song -> Bool) -> ((Song, Bool) -> Song) -> (Song, Bool) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Song, Bool) -> Song
forall a b. (a, b) -> a
fst
)
(GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall n e. GenericList n Vector e -> GenericList n Vector e
dir
)
queueAddToPl :: HState -> String -> EventM Name HState
queueAddToPl :: HState -> String -> EventM Name HState
queueAddToPl HState
s String
plName =
let songs :: Vector Song
songs =
(HState
s HState
-> Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
Lens' HState (GenericList Name Vector (Song, Bool))
queueL)
GenericList Name Vector (Song, Bool)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
forall a b. a -> (a -> b) -> b
& GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall e (t :: * -> *) n.
(Eq e, Filterable t, Foldable t, Splittable t) =>
GenericList n t (e, Bool) -> GenericList n t (e, Bool)
getHighlighted
GenericList Name Vector (Song, Bool)
-> (GenericList Name Vector (Song, Bool) -> Vector (Song, Bool))
-> Vector (Song, Bool)
forall a b. a -> (a -> b) -> b
& GenericList Name Vector (Song, Bool) -> Vector (Song, Bool)
forall n (t :: * -> *) e. GenericList n t e -> t e
listElements
Vector (Song, Bool) -> ((Song, Bool) -> Song) -> Vector Song
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> (Song, Bool) -> Song
forall a b. (a, b) -> a
fst
in String -> Vector Song -> HState -> EventM Name HState
forall n. String -> Vector Song -> HState -> EventM n HState
songBulkAddtoPl String
plName Vector Song
songs HState
s
handleEventQueue
:: HState -> BrickEvent Name HumEvent -> EventM Name (Next HState)
handleEventQueue :: HState -> BrickEvent Name HumEvent -> EventM Name (Next HState)
handleEventQueue HState
s BrickEvent Name HumEvent
e = case BrickEvent Name HumEvent
e of
VtyEvent Event
vtye -> case Event
vtye of
EvKey (KChar Char
'j') [] -> do
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s { queue :: GenericList Name Vector (Song, Bool)
queue = GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveDown (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall a b. (a -> b) -> a -> b
$ HState -> GenericList Name Vector (Song, Bool)
queue HState
s, Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap }
EvKey (KChar Char
'k') [] -> do
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s { queue :: GenericList Name Vector (Song, Bool)
queue = GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveUp (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall a b. (a -> b) -> a -> b
$ HState -> GenericList Name Vector (Song, Bool)
queue HState
s, Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap }
EvKey (KChar Char
'n') [] -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> EventM Name HState -> EventM Name (Next HState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HState -> EventM Name HState
queueSearch (HState
s HState -> Getting Bool HState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (ExState -> Const Bool ExState) -> HState -> Const Bool HState
Lens' HState ExState
exL ((ExState -> Const Bool ExState) -> HState -> Const Bool HState)
-> ((Bool -> Const Bool Bool) -> ExState -> Const Bool ExState)
-> Getting Bool HState Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Const Bool Bool) -> ExState -> Const Bool ExState
Lens' ExState Bool
searchDirectionL) HState
s
EvKey (KChar Char
'N') [] -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> EventM Name HState -> EventM Name (Next HState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HState -> EventM Name HState
queueSearch (HState
s HState -> Getting Bool HState Bool -> Bool
forall s a. s -> Getting a s a -> a
^. (ExState -> Const Bool ExState) -> HState -> Const Bool HState
Lens' HState ExState
exL ((ExState -> Const Bool ExState) -> HState -> Const Bool HState)
-> ((Bool -> Const Bool Bool) -> ExState -> Const Bool ExState)
-> Getting Bool HState 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) HState
s
EvKey (KChar Char
'a') [] -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> HState -> EventM Name (Next HState)
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (Mode -> Identity Mode) -> HState -> Identity HState
Lens' HState Mode
modeL ((Mode -> Identity Mode) -> HState -> Identity HState)
-> Mode -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Mode
PromptMode
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (Prompts -> Identity Prompts) -> HState -> Identity HState
Lens' HState Prompts
promptsL ((Prompts -> Identity Prompts) -> HState -> Identity HState)
-> ((PromptType -> Identity PromptType)
-> Prompts -> Identity Prompts)
-> (PromptType -> Identity PromptType)
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PromptType -> Identity PromptType) -> Prompts -> Identity Prompts
Lens' Prompts PromptType
currentPromptL ((PromptType -> Identity PromptType) -> HState -> Identity HState)
-> PromptType -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ PromptType
PlSelectPrompt
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (Prompts -> Identity Prompts) -> HState -> Identity HState
Lens' HState Prompts
promptsL ((Prompts -> Identity Prompts) -> HState -> Identity HState)
-> ((Text -> Identity Text) -> Prompts -> Identity Prompts)
-> (Text -> Identity Text)
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Prompts -> Identity Prompts
Lens' Prompts Text
promptTitleL ((Text -> Identity Text) -> HState -> Identity HState)
-> Text -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Text
"Add selected Item(s) to:"
EvKey Key
KEnter [] -> do
let maybeSelectedId :: Maybe Id
maybeSelectedId =
Song -> Maybe Id
MPD.sgId (Song -> Maybe Id)
-> ((Int, (Song, Bool)) -> Song) -> (Int, (Song, Bool)) -> Maybe Id
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Song, Bool) -> Song
forall a b. (a, b) -> a
fst ((Song, Bool) -> Song)
-> ((Int, (Song, Bool)) -> (Song, Bool))
-> (Int, (Song, Bool))
-> Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, (Song, Bool)) -> (Song, Bool)
forall a b. (a, b) -> b
snd ((Int, (Song, Bool)) -> Maybe Id)
-> Maybe (Int, (Song, Bool)) -> Maybe Id
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< GenericList Name Vector (Song, Bool) -> Maybe (Int, (Song, Bool))
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement (HState -> GenericList Name Vector (Song, Bool)
queue HState
s)
(Id -> EventM Name (Response ())) -> Maybe Id -> EventM Name ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\Id
sel -> 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
$ Id -> MPD ()
forall (m :: * -> *). MonadMPD m => Id -> m ()
MPD.playId Id
sel)) Maybe Id
maybeSelectedId
Either MPDError (Maybe Song)
song <- IO (Either MPDError (Maybe Song))
-> EventM Name (Either MPDError (Maybe Song))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (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)
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s { currentSong :: 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)
song, queue :: GenericList Name Vector (Song, Bool)
queue = HState -> GenericList Name Vector (Song, Bool)
queue HState
s }
EvKey (KChar Char
' ') [] -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> HState -> EventM Name (Next HState)
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState
Lens' HState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HState
-> HState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveDown (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
Traversable t =>
GenericList n t (e, Bool) -> GenericList n t (e, Bool)
listToggleHighlight)
EvKey (KChar Char
'd') [] -> do
let clSongs' :: GenericList Name Vector (Song, Bool)
clSongs' = GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall e (t :: * -> *) n.
(Eq e, Filterable t, Foldable t, Splittable t) =>
GenericList n t (e, Bool) -> GenericList n t (e, Bool)
getHighlighted (HState -> GenericList Name Vector (Song, Bool)
queue HState
s)
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
$ GenericList Name Vector (Song, Bool) -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
GenericList Name Vector (Song, Bool) -> m ()
deleteHighlightedfromQ (HState -> GenericList Name Vector (Song, Bool)
queue HState
s))
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> EventM Name HState -> EventM Name (Next HState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HState
-> GenericList Name Vector (Song, Bool) -> EventM Name HState
pasteDeleteCleanup HState
s GenericList Name Vector (Song, Bool)
clSongs'
EvKey (KChar Char
'D') [] -> do
let clip :: GenericList Name Vector (Song, Bool)
clip = HState -> GenericList Name Vector (Song, Bool)
queue HState
s
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
$ GenericList Name Vector (Song, Bool) -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
GenericList Name Vector (Song, Bool) -> m ()
deleteAll (HState -> GenericList Name Vector (Song, Bool)
queue HState
s))
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> EventM Name HState -> EventM Name (Next HState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HState
-> GenericList Name Vector (Song, Bool) -> EventM Name HState
pasteDeleteCleanup HState
s GenericList Name Vector (Song, Bool)
clip
EvKey (KChar Char
'y') [] -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> HState -> EventM Name (Next HState)
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (Clipboard -> Identity Clipboard) -> HState -> Identity HState
Lens' HState Clipboard
clipboardL ((Clipboard -> Identity Clipboard) -> HState -> Identity HState)
-> ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> Clipboard -> Identity Clipboard)
-> (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> Clipboard -> Identity Clipboard
Lens' Clipboard (GenericList Name Vector (Song, Bool))
clSongsL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HState -> Identity HState)
-> GenericList Name Vector (Song, Bool) -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ (HState
s HState
-> Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
forall s a. s -> Getting a s a -> a
^. Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
Lens' HState (GenericList Name Vector (Song, Bool))
queueL GenericList Name Vector (Song, Bool)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
forall a b. a -> (a -> b) -> b
& GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall e (t :: * -> *) n.
(Eq e, Filterable t, Foldable t, Splittable t) =>
GenericList n t (e, Bool) -> GenericList n t (e, Bool)
getHighlighted)
EvKey (KChar Char
'p') [] -> do
let clip :: GenericList Name Vector (Song, Bool)
clip = HState
s HState
-> Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
forall s a. s -> Getting a s a -> a
^. (Clipboard
-> Const (GenericList Name Vector (Song, Bool)) Clipboard)
-> HState -> Const (GenericList Name Vector (Song, Bool)) HState
Lens' HState Clipboard
clipboardL ((Clipboard
-> Const (GenericList Name Vector (Song, Bool)) Clipboard)
-> HState -> Const (GenericList Name Vector (Song, Bool)) HState)
-> ((GenericList Name Vector (Song, Bool)
-> Const
(GenericList Name Vector (Song, Bool))
(GenericList Name Vector (Song, Bool)))
-> Clipboard
-> Const (GenericList Name Vector (Song, Bool)) Clipboard)
-> Getting
(GenericList Name Vector (Song, Bool))
HState
(GenericList Name Vector (Song, Bool))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Song, Bool)
-> Const
(GenericList Name Vector (Song, Bool))
(GenericList Name Vector (Song, Bool)))
-> Clipboard
-> Const (GenericList Name Vector (Song, Bool)) Clipboard
Lens' Clipboard (GenericList Name Vector (Song, Bool))
clSongsL
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
$ GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool) -> MPD ()
forall (m :: * -> *).
MonadMPD m =>
GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool) -> m ()
pasteSongstoQ GenericList Name Vector (Song, Bool)
clip (HState -> GenericList Name Vector (Song, Bool)
queue HState
s))
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue (HState -> EventM Name (Next HState))
-> EventM Name HState -> EventM Name (Next HState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< HState
-> GenericList Name Vector (Song, Bool) -> EventM Name HState
pasteDeleteCleanup HState
s GenericList Name Vector (Song, Bool)
clip
EvKey (KChar Char
'G') [] -> do
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s { queue :: GenericList Name Vector (Song, Bool)
queue = Int
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
listMoveTo (GenericList Name Vector (Song, Bool) -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (GenericList Name Vector (Song, Bool) -> Int)
-> (HState -> GenericList Name Vector (Song, Bool))
-> HState
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HState -> GenericList Name Vector (Song, Bool)
queue (HState -> Int) -> HState -> Int
forall a b. (a -> b) -> a -> b
$ HState
s) (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall a b. (a -> b) -> a -> b
$ HState -> GenericList Name Vector (Song, Bool)
queue HState
s
, Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap
}
EvKey (KChar Char
'g') [] -> do
Map Name (Maybe (Extent Name))
extentMap <- EventM Name (Map Name (Maybe (Extent Name)))
updateExtentMap
HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s { queue :: GenericList Name Vector (Song, Bool)
queue = Int
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
listMoveTo Int
0 (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool)
forall a b. (a -> b) -> a -> b
$ HState -> GenericList Name Vector (Song, Bool)
queue HState
s, Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap :: Map Name (Maybe (Extent Name))
extentMap }
Event
_ -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s
BrickEvent Name HumEvent
_ -> HState -> EventM Name (Next HState)
forall s n. s -> EventM n (Next s)
continue HState
s