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 Control.Lens
drawViewQueue :: HumState -> Widget Name
drawViewQueue :: HumState -> Widget Name
drawViewQueue HumState
st = 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
$
Size -> Size -> RenderM Name (Result Name) -> Widget Name
forall n. Size -> Size -> RenderM n (Result n) -> Widget n
Widget Size
Greedy Size
Greedy (RenderM Name (Result Name) -> Widget Name)
-> RenderM Name (Result Name) -> Widget Name
forall a b. (a -> b) -> a -> b
$ do
Context
ctx <- RenderM Name Context
forall n. RenderM n Context
getContext
let vsize :: Int
vsize = Context
ctx Context -> Getting Int Context Int -> Int
forall s a. s -> Getting a s a -> a
^. Getting Int Context Int
Lens' Context Int
windowHeightL Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
6
Widget Name -> RenderM Name (Result Name)
forall n. Widget n -> RenderM n (Result n)
render (Widget Name -> RenderM Name (Result Name))
-> Widget Name -> RenderM Name (Result Name)
forall a b. (a -> b) -> a -> b
$ Widget Name -> Widget Name
forall n. Widget n -> Widget n
hCenter
( 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 (HumState -> (Song, Bool) -> Widget Name
forall n. HumState -> (Song, Bool) -> Widget n
queueRow HumState
st))
((Focus -> FocQueue
focQueue (Focus -> FocQueue) -> (HumState -> Focus) -> HumState -> FocQueue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HumState -> Focus
focus (HumState -> FocQueue) -> HumState -> FocQueue
forall a b. (a -> b) -> a -> b
$ HumState
st) FocQueue -> FocQueue -> Bool
forall a. Eq a => a -> a -> Bool
== FocQueue
FocQueue)
(HumState -> GenericList Name Vector (Song, Bool)
queue HumState
st)
)
)
where
album :: Widget n
album =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
albumAttr (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
trackAttr (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
titleAttr (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
artistAttr (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
timeAttr (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 :: HumState -> (MPD.Song, Highlight) -> Widget n
queueRow :: HumState -> (Song, Bool) -> Widget n
queueRow HumState
st (Song
song, Bool
hl) =
(if Bool
hl then Widget n -> Widget n
forall n. Widget n -> Widget n
highlightOverAttrs 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 = HumState -> Maybe Song
currentSong HumState
st
album :: Widget n
album =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
albumAttr (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
trackAttr (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
titleAttr (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
artistAttr (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
timeAttr
(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
queueSearch
:: Bool
-> HumState
-> EventM Name HumState
queueSearch :: Bool -> HumState -> EventM Name HumState
queueSearch Bool
direction HumState
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
"" ((HumState
s 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) [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 HumState -> EventM Name HumState
forall (f :: * -> *) a. Applicative f => a -> f a
pure HumState
s
else do
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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL
((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
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
:: HumState
-> String
-> EventM Name HumState
queueAddToPl :: HumState -> String -> EventM Name HumState
queueAddToPl HumState
s String
plName =
let songs :: Vector Song
songs =
(HumState
s HumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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))
HumState
(GenericList Name Vector (Song, Bool))
Lens' HumState (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 (t :: * -> *) n e.
(Filterable t, Traversable 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 -> HumState -> EventM Name HumState
forall n. String -> Vector Song -> HumState -> EventM n HumState
songBulkAddtoPl String
plName Vector Song
songs HumState
s
handleEventQueue
:: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventQueue :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventQueue HumState
s BrickEvent Name HumEvent
e = case BrickEvent Name HumEvent
e of
VtyEvent Event
vtye -> case Event
vtye of
EvKey (KChar Char
'j') [] -> 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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
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
EvKey (KChar Char
'k') [] -> 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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
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
listMoveUp
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
queueSearch (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
queueSearch (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
'a') [] ->
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
PromptMode
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Prompts -> Identity Prompts) -> HumState -> Identity HumState
Lens' HumState Prompts
promptsL ((Prompts -> Identity Prompts) -> HumState -> Identity HumState)
-> ((List Name (Maybe PlaylistName)
-> Identity (List Name (Maybe PlaylistName)))
-> Prompts -> Identity Prompts)
-> (List Name (Maybe PlaylistName)
-> Identity (List Name (Maybe PlaylistName)))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (List Name (Maybe PlaylistName)
-> Identity (List Name (Maybe PlaylistName)))
-> Prompts -> Identity Prompts
Lens' Prompts (List Name (Maybe PlaylistName))
plSelectPromptL ((List Name (Maybe PlaylistName)
-> Identity (List Name (Maybe PlaylistName)))
-> HumState -> Identity HumState)
-> List Name (Maybe PlaylistName) -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ 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
<$> (HumState
s HumState
-> Getting
(GenericList Name Vector PlaylistName)
HumState
(GenericList Name Vector PlaylistName)
-> GenericList Name Vector PlaylistName
forall s a. s -> Getting a s a -> a
^. (PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState)
-> HumState
-> Const (GenericList Name Vector PlaylistName) HumState
Lens' HumState PlaylistsState
playlistsL ((PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState)
-> HumState
-> Const (GenericList Name Vector PlaylistName) HumState)
-> ((GenericList Name Vector PlaylistName
-> Const
(GenericList Name Vector PlaylistName)
(GenericList Name Vector PlaylistName))
-> PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState)
-> Getting
(GenericList Name Vector PlaylistName)
HumState
(GenericList Name Vector PlaylistName)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector PlaylistName
-> Const
(GenericList Name Vector PlaylistName)
(GenericList Name Vector PlaylistName))
-> PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState
Lens' PlaylistsState (GenericList Name Vector PlaylistName)
plListL))
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Prompts -> Identity Prompts) -> HumState -> Identity HumState
Lens' HumState Prompts
promptsL ((Prompts -> Identity Prompts) -> HumState -> Identity HumState)
-> ((PromptType -> Identity PromptType)
-> Prompts -> Identity Prompts)
-> (PromptType -> Identity PromptType)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PromptType -> Identity PromptType) -> Prompts -> Identity Prompts
Lens' Prompts PromptType
currentPromptL ((PromptType -> Identity PromptType)
-> HumState -> Identity HumState)
-> PromptType -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ PromptType
PlSelectPrompt
HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Prompts -> Identity Prompts) -> HumState -> Identity HumState
Lens' HumState Prompts
promptsL ((Prompts -> Identity Prompts) -> HumState -> Identity HumState)
-> ((Text -> Identity Text) -> Prompts -> Identity Prompts)
-> (Text -> Identity Text)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> Prompts -> Identity Prompts
Lens' Prompts Text
promptTitleL ((Text -> Identity Text) -> HumState -> Identity HumState)
-> Text -> HumState -> HumState
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 (HumState -> GenericList Name Vector (Song, Bool)
queue HumState
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
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus HumState
s EventM Name HumState
-> (HumState -> EventM Name (Next HumState))
-> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue
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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
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' = HumState
s HumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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))
HumState
(GenericList Name Vector (Song, Bool))
Lens' HumState (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 (t :: * -> *) n e.
(Filterable t, Traversable t) =>
GenericList n t (e, Bool) -> GenericList n t (e, Bool)
getHighlighted
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 (HumState
s HumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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))
HumState
(GenericList Name Vector (Song, Bool))
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL))
let s' :: HumState
s' = HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Clipboard -> Identity Clipboard) -> HumState -> Identity HumState
Lens' HumState Clipboard
clipboardL ((Clipboard -> Identity Clipboard)
-> HumState -> Identity HumState)
-> ((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)))
-> HumState
-> Identity HumState
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)))
-> HumState -> Identity HumState)
-> GenericList Name Vector (Song, Bool) -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector (Song, Bool)
clSongs'
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildQueue HumState
s' EventM Name HumState
-> (HumState -> EventM Name HumState) -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus EventM Name HumState
-> (HumState -> EventM Name (Next HumState))
-> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue
EvKey (KChar Char
'D') [] -> do
let clSongs' :: GenericList Name Vector (Song, Bool)
clSongs' = HumState
sHumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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))
HumState
(GenericList Name Vector (Song, Bool))
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL
let s' :: HumState
s' = HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (Clipboard -> Identity Clipboard) -> HumState -> Identity HumState
Lens' HumState Clipboard
clipboardL ((Clipboard -> Identity Clipboard)
-> HumState -> Identity HumState)
-> ((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)))
-> HumState
-> Identity HumState
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)))
-> HumState -> Identity HumState)
-> GenericList Name Vector (Song, Bool) -> HumState -> HumState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector (Song, Bool)
clSongs'
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.clear)
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildQueue HumState
s' EventM Name HumState
-> (HumState -> EventM Name HumState) -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus EventM Name HumState
-> (HumState -> EventM Name (Next HumState))
-> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue
EvKey (KChar Char
'y') [] -> 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
-> Lens' HumState (GenericList Name Vector (Song, Bool))
-> HumState
yankHighlighted HumState
s Lens' HumState (GenericList Name Vector (Song, Bool))
queueL
EvKey (KChar Char
'p') [] -> do
let clSongs' :: GenericList Name Vector (Song, Bool)
clSongs' = HumState
s HumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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)
-> HumState
-> Const (GenericList Name Vector (Song, Bool)) HumState
Lens' HumState Clipboard
clipboardL ((Clipboard
-> Const (GenericList Name Vector (Song, Bool)) Clipboard)
-> HumState
-> Const (GenericList Name Vector (Song, Bool)) HumState)
-> ((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))
HumState
(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)
clSongs' (HumState
s HumState
-> Getting
(GenericList Name Vector (Song, Bool))
HumState
(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))
HumState
(GenericList Name Vector (Song, Bool))
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL))
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildQueue HumState
s EventM Name HumState
-> (HumState -> EventM Name HumState) -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildStatus EventM Name HumState
-> (HumState -> EventM Name (Next HumState))
-> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= HumState -> EventM Name (Next HumState)
forall s n. s -> EventM n (Next s)
continue
EvKey (KChar Char
'G') [] -> 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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ 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
1)
EvKey (KChar Char
'g') [] -> 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
& (GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState
Lens' HumState (GenericList Name Vector (Song, Bool))
queueL ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Song, Bool)
-> GenericList Name Vector (Song, Bool))
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ 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
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