module Hum.Views.Library where
import Hum.Types
import Brick.Types
import Graphics.Vty.Input.Events
import Brick.Main
import Brick.Widgets.Core
import Brick.Widgets.Center
import Brick.Widgets.Border
import Control.Lens
import Brick.Widgets.List
import Hum.Attributes
import Hum.Views.Common
import Hum.Rebuild
import qualified Data.Text as T
import qualified Data.Vector as V
import qualified Network.MPD as MPD
import Hum.Utils
drawLibraryLeft :: HumState -> Widget Name
drawLibraryLeft :: HumState -> Widget Name
drawLibraryLeft HumState
st = Name -> Widget Name -> Widget Name
forall n. n -> Widget n -> Widget n
reportExtent Name
LibraryLeft (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
( Widget Name -> Widget Name
forall n. Widget n -> Widget n
visible
(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
forall n. Widget n
hBorder
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 -> Text -> Widget Name)
-> Bool -> GenericList Name Vector Text -> 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 ((Text -> Widget Name) -> Bool -> Text -> Widget Name
forall a b. a -> b -> a
const ((Text -> Widget Name) -> Bool -> Text -> Widget Name)
-> (Text -> Widget Name) -> Bool -> Text -> Widget Name
forall a b. (a -> b) -> a -> b
$ HumState -> Name -> Text -> Widget Name
forall n. HumState -> Name -> Text -> Widget n
libraryRow HumState
st Name
LibraryLeft)
((Focus -> FocLib
focLib (Focus -> FocLib) -> (HumState -> Focus) -> HumState -> FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HumState -> Focus
focus (HumState -> FocLib) -> HumState -> FocLib
forall a b. (a -> b) -> a -> b
$ HumState
st) FocLib -> FocLib -> Bool
forall a. Eq a => a -> a -> Bool
== FocLib
FocArtists)
(Value -> Text
forall a. ToString a => a -> Text
MPD.toText (Value -> Text)
-> GenericList Name Vector Value -> GenericList Name Vector Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> HumState
st HumState
-> Getting
(GenericList Name Vector Value)
HumState
(GenericList Name Vector Value)
-> GenericList Name Vector Value
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HumState -> Const (GenericList Name Vector Value) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HumState -> Const (GenericList Name Vector Value) HumState)
-> ((GenericList Name Vector Value
-> Const
(GenericList Name Vector Value) (GenericList Name Vector Value))
-> LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> Getting
(GenericList Name Vector Value)
HumState
(GenericList Name Vector Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Value
-> Const
(GenericList Name Vector Value) (GenericList Name Vector Value))
-> LibraryState
-> Const (GenericList Name Vector Value) LibraryState
Lens' LibraryState (GenericList Name Vector Value)
artistsL)
)
)
drawLibraryMid :: HumState -> Widget Name
drawLibraryMid :: HumState -> Widget Name
drawLibraryMid HumState
st = Name -> Widget Name -> Widget Name
forall n. n -> Widget n -> Widget n
reportExtent Name
LibraryMid (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
( Widget Name -> Widget Name
forall n. Widget n -> Widget n
visible
(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
forall n. Widget n
hBorder
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 -> (Value, Value) -> Widget Name)
-> Bool -> GenericList Name Vector (Value, Value) -> 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 (((Value, Value) -> Widget Name)
-> Bool -> (Value, Value) -> Widget Name
forall a b. a -> b -> a
const (((Value, Value) -> Widget Name)
-> Bool -> (Value, Value) -> Widget Name)
-> ((Value, Value) -> Widget Name)
-> Bool
-> (Value, Value)
-> Widget Name
forall a b. (a -> b) -> a -> b
$ (Value, Value) -> Widget Name
forall n. (Value, Value) -> Widget n
libraryAlbumRow)
((Focus -> FocLib
focLib (Focus -> FocLib) -> (HumState -> Focus) -> HumState -> FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HumState -> Focus
focus (HumState -> FocLib) -> HumState -> FocLib
forall a b. (a -> b) -> a -> b
$ HumState
st) FocLib -> FocLib -> Bool
forall a. Eq a => a -> a -> Bool
== FocLib
FocAlbums)
(HumState
st HumState
-> Getting
(GenericList Name Vector (Value, Value))
HumState
(GenericList Name Vector (Value, Value))
-> GenericList Name Vector (Value, Value)
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> HumState
-> Const (GenericList Name Vector (Value, Value)) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> HumState
-> Const (GenericList Name Vector (Value, Value)) HumState)
-> ((GenericList Name Vector (Value, Value)
-> Const
(GenericList Name Vector (Value, Value))
(GenericList Name Vector (Value, Value)))
-> LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> Getting
(GenericList Name Vector (Value, Value))
HumState
(GenericList Name Vector (Value, Value))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Value, Value)
-> Const
(GenericList Name Vector (Value, Value))
(GenericList Name Vector (Value, Value)))
-> LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState
Lens' LibraryState (GenericList Name Vector (Value, Value))
yalbumsL)
)
)
drawLibraryRight :: HumState -> Widget Name
drawLibraryRight :: HumState -> Widget Name
drawLibraryRight HumState
st = Name -> Widget Name -> Widget Name
forall n. n -> Widget n -> Widget n
reportExtent Name
LibraryRight (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
( Widget Name -> Widget Name
forall n. Widget n -> Widget n
visible
(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
forall n. Widget n
hBorder
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 -> Widget Name)
-> Bool -> GenericList Name Vector Song -> 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 -> Widget Name) -> Bool -> Song -> Widget Name
forall a b. a -> b -> a
const ((Song -> Widget Name) -> Bool -> Song -> Widget Name)
-> (Song -> Widget Name) -> Bool -> Song -> Widget Name
forall a b. (a -> b) -> a -> b
$ HumState -> Song -> Widget Name
forall n. HumState -> Song -> Widget n
librarySongRow HumState
st)
((Focus -> FocLib
focLib (Focus -> FocLib) -> (HumState -> Focus) -> HumState -> FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HumState -> Focus
focus (HumState -> FocLib) -> HumState -> FocLib
forall a b. (a -> b) -> a -> b
$ HumState
st) FocLib -> FocLib -> Bool
forall a. Eq a => a -> a -> Bool
== FocLib
FocSongs)
(HumState
st HumState
-> Getting
(GenericList Name Vector Song)
HumState
(GenericList Name Vector Song)
-> GenericList Name Vector Song
forall s a. s -> Getting a s a -> a
^. (LibraryState -> Const (GenericList Name Vector Song) LibraryState)
-> HumState -> Const (GenericList Name Vector Song) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Song) LibraryState)
-> HumState -> Const (GenericList Name Vector Song) HumState)
-> ((GenericList Name Vector Song
-> Const
(GenericList Name Vector Song) (GenericList Name Vector Song))
-> LibraryState
-> Const (GenericList Name Vector Song) LibraryState)
-> Getting
(GenericList Name Vector Song)
HumState
(GenericList Name Vector Song)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Song
-> Const
(GenericList Name Vector Song) (GenericList Name Vector Song))
-> LibraryState
-> Const (GenericList Name Vector Song) LibraryState
Lens' LibraryState (GenericList Name Vector Song)
songsL)
)
)
libraryRow :: HumState -> Name -> T.Text -> Widget n
libraryRow :: HumState -> Name -> Text -> Widget n
libraryRow HumState
_ Name
name Text
val =
AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr
(case Name
name of
Name
LibraryLeft -> AttrName
artistAttr
Name
LibraryMid -> AttrName
albumAttr
Name
_ -> AttrName
listAttr
)
(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 (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
val
libraryAlbumRow :: (MPD.Value,MPD.Value) -> Widget n
libraryAlbumRow :: (Value, Value) -> Widget n
libraryAlbumRow (Value
yr,Value
al) =
let year :: Text
year = Value -> Text
forall a. ToString a => a -> Text
MPD.toText Value
yr
album :: Text
album = Value -> Text
forall a. ToString a => a -> Text
MPD.toText Value
al
yearW :: Widget n
yearW = AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
dateAttr (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
7)) Padding
Max Padding
Max (Widget n -> Widget n) -> Widget n -> Widget n
forall a b. (a -> b) -> a -> b
$
if Text -> Bool
T.null Text
year
then Text -> Widget n
forall n. Text -> Widget n
txt Text
" "
else Text -> Widget n
forall n. Text -> Widget n
txt Text
"(" Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Text -> Widget n
forall n. Text -> Widget n
txt (Int -> Text -> Text
T.take Int
4 Text
year) Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Text -> Widget n
forall n. Text -> Widget n
txt Text
")"
albumW :: Widget n
albumW = 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 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
album
in Widget n
forall n. Widget n
yearW Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
albumW
librarySongRow :: HumState -> MPD.Song -> Widget n
librarySongRow :: HumState -> Song -> Widget n
librarySongRow HumState
st Song
song =
let pathsInQueue :: Vector Path
pathsInQueue =
(Song -> Path
MPD.sgFilePath (Song -> Path) -> Vector Song -> Vector Path
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Vector Song -> Vector Path)
-> (HumState -> Vector Song) -> HumState -> Vector Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Song, Bool) -> Song
forall a b. (a, b) -> a
fst ((Song, Bool) -> Song) -> Vector (Song, Bool) -> Vector Song
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (Vector (Song, Bool) -> Vector Song)
-> (HumState -> Vector (Song, Bool)) -> HumState -> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector (Song, Bool) -> Vector (Song, Bool)
forall n (t :: * -> *) e. GenericList n t e -> t e
listElements (GenericList Name Vector (Song, Bool) -> Vector (Song, Bool))
-> (HumState -> GenericList Name Vector (Song, Bool))
-> HumState
-> Vector (Song, Bool)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HumState -> GenericList Name Vector (Song, Bool)
queue (HumState -> Vector Path) -> HumState -> Vector Path
forall a b. (a -> b) -> a -> b
$ HumState
st
title :: Text
title = Text -> Metadata -> Song -> Text
meta (Path -> Text
forall a. ToString a => a -> Text
MPD.toText (Path -> Text) -> (Song -> Path) -> Song -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Song -> Path
MPD.sgFilePath (Song -> Text) -> Song -> Text
forall a b. (a -> b) -> a -> b
$ Song
song) Metadata
MPD.Title Song
song
titleW :: Widget n
titleW = 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
track :: Text
track = Text -> Metadata -> Song -> Text
meta Text
"-" Metadata
MPD.Track Song
song
trackW :: Widget n
trackW = 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
track
in (if Song -> Path
MPD.sgFilePath Song
song Path -> Vector Path -> Bool
forall (f :: * -> *) a.
(Foldable f, DisallowElem f, Eq a) =>
a -> f a -> Bool
`elem` Vector Path
pathsInQueue
then AttrName -> Widget n -> Widget n
forall n. AttrName -> Widget n -> Widget n
withAttr AttrName
titleBoldAttr
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
forall n. Widget n
trackW Widget n -> Widget n -> Widget n
forall n. Widget n -> Widget n -> Widget n
<+> Widget n
forall n. Widget n
titleW
libraryMoveRight :: FocLib -> FocLib
libraryMoveRight :: FocLib -> FocLib
libraryMoveRight FocLib
FocArtists = FocLib
FocAlbums
libraryMoveRight FocLib
_ = FocLib
FocSongs
libraryMoveLeft :: FocLib -> FocLib
libraryMoveLeft :: FocLib -> FocLib
libraryMoveLeft FocLib
FocSongs = FocLib
FocAlbums
libraryMoveLeft FocLib
_ = FocLib
FocArtists
drawViewLibrary :: HumState -> Widget Name
drawViewLibrary :: HumState -> Widget Name
drawViewLibrary HumState
st =
HumState -> Widget Name
drawLibraryLeft HumState
st Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> HumState -> Widget Name
drawLibraryMid HumState
st Widget Name -> Widget Name -> Widget Name
forall n. Widget n -> Widget n -> Widget n
<+> HumState -> Widget Name
drawLibraryRight HumState
st
libraryMove
:: (forall e . List Name e -> List Name e)
-> HumState
-> EventM Name HumState
libraryMove :: (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove forall e. List Name e -> List Name e
moveFunc HumState
s =
let libfoc :: FocLib
libfoc = HumState
s HumState -> Getting FocLib HumState FocLib -> FocLib
forall s a. s -> Getting a s a -> a
^. (Focus -> Const FocLib Focus) -> HumState -> Const FocLib HumState
Lens' HumState Focus
focusL ((Focus -> Const FocLib Focus)
-> HumState -> Const FocLib HumState)
-> ((FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus)
-> Getting FocLib HumState FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus
Lens' Focus FocLib
focLibL
in case FocLib
libfoc of
FocLib
FocArtists -> HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildLibArtists (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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector Value)
artistsL ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HumState -> Identity HumState)
-> (GenericList Name Vector Value -> GenericList Name Vector Value)
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ GenericList Name Vector Value -> GenericList Name Vector Value
forall e. List Name e -> List Name e
moveFunc
FocLib
FocAlbums -> HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildLibAlbums (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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector (Value, Value))
yalbumsL ((GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall e. List Name e -> List Name e
moveFunc
FocLib
FocSongs -> 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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector Song)
songsL ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HumState -> Identity HumState)
-> (GenericList Name Vector Song -> GenericList Name Vector Song)
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ GenericList Name Vector Song -> GenericList Name Vector Song
forall e. List Name e -> List Name e
moveFunc
libraryAddtoQ
:: Bool
-> HumState
-> EventM Name HumState
libraryAddtoQ :: Bool -> HumState -> EventM Name HumState
libraryAddtoQ Bool
play HumState
s =
let libfoc :: FocLib
libfoc = HumState
s HumState -> Getting FocLib HumState FocLib -> FocLib
forall s a. s -> Getting a s a -> a
^. (Focus -> Const FocLib Focus) -> HumState -> Const FocLib HumState
Lens' HumState Focus
focusL ((Focus -> Const FocLib Focus)
-> HumState -> Const FocLib HumState)
-> ((FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus)
-> Getting FocLib HumState FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus
Lens' Focus FocLib
focLibL
in
case FocLib
libfoc of
FocLib
FocArtists -> do
let martist :: Maybe Value
martist = (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 (HumState
s HumState
-> Getting
(GenericList Name Vector Value)
HumState
(GenericList Name Vector Value)
-> GenericList Name Vector Value
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HumState -> Const (GenericList Name Vector Value) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HumState -> Const (GenericList Name Vector Value) HumState)
-> ((GenericList Name Vector Value
-> Const
(GenericList Name Vector Value) (GenericList Name Vector Value))
-> LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> Getting
(GenericList Name Vector Value)
HumState
(GenericList Name Vector Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Value
-> Const
(GenericList Name Vector Value) (GenericList Name Vector Value))
-> LibraryState
-> Const (GenericList Name Vector Value) LibraryState
Lens' LibraryState (GenericList Name Vector Value)
artistsL)
Vector Song
songs <-IO (Vector Song) -> EventM Name (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> EventM Name (Vector Song))
-> IO (Vector Song) -> EventM Name (Vector Song)
forall a b. (a -> b) -> a -> b
$ 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)
songsOfArtist Maybe Value
martist
Bool -> Vector Song -> HumState -> EventM Name HumState
forall n. Bool -> Vector Song -> HumState -> EventM n HumState
songBulkAddtoQ Bool
play Vector Song
songs HumState
s
FocLib
FocAlbums -> do
let malbum :: Maybe Value
malbum = (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 (HumState
s HumState
-> Getting
(GenericList Name Vector (Value, Value))
HumState
(GenericList Name Vector (Value, Value))
-> GenericList Name Vector (Value, Value)
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> HumState
-> Const (GenericList Name Vector (Value, Value)) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> HumState
-> Const (GenericList Name Vector (Value, Value)) HumState)
-> ((GenericList Name Vector (Value, Value)
-> Const
(GenericList Name Vector (Value, Value))
(GenericList Name Vector (Value, Value)))
-> LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState)
-> Getting
(GenericList Name Vector (Value, Value))
HumState
(GenericList Name Vector (Value, Value))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Value, Value)
-> Const
(GenericList Name Vector (Value, Value))
(GenericList Name Vector (Value, Value)))
-> LibraryState
-> Const (GenericList Name Vector (Value, Value)) LibraryState
Lens' LibraryState (GenericList Name Vector (Value, Value))
yalbumsL)
Vector Song
songs <- IO (Vector Song) -> EventM Name (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> EventM Name (Vector Song))
-> IO (Vector Song) -> EventM Name (Vector Song)
forall a b. (a -> b) -> a -> b
$ 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 Maybe Value
malbum
Bool -> Vector Song -> HumState -> EventM Name HumState
forall n. Bool -> Vector Song -> HumState -> EventM n HumState
songBulkAddtoQ Bool
play Vector Song
songs HumState
s
FocLib
FocSongs -> do
let songs :: Vector Song
songs = Vector Song -> (Song -> Vector Song) -> Maybe Song -> Vector Song
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Vector Song
forall a. Vector a
V.empty Song -> Vector Song
forall a. a -> Vector a
V.singleton (Maybe Song -> Vector Song) -> Maybe Song -> Vector Song
forall a b. (a -> b) -> a -> b
$ (Int, Song) -> Song
forall a b. (a, b) -> b
snd ((Int, Song) -> Song) -> Maybe (Int, Song) -> Maybe Song
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Song -> Maybe (Int, Song)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement
(HumState
s HumState
-> Getting
(GenericList Name Vector Song)
HumState
(GenericList Name Vector Song)
-> GenericList Name Vector Song
forall s a. s -> Getting a s a -> a
^. (LibraryState -> Const (GenericList Name Vector Song) LibraryState)
-> HumState -> Const (GenericList Name Vector Song) HumState
Lens' HumState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Song) LibraryState)
-> HumState -> Const (GenericList Name Vector Song) HumState)
-> ((GenericList Name Vector Song
-> Const
(GenericList Name Vector Song) (GenericList Name Vector Song))
-> LibraryState
-> Const (GenericList Name Vector Song) LibraryState)
-> Getting
(GenericList Name Vector Song)
HumState
(GenericList Name Vector Song)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Song
-> Const
(GenericList Name Vector Song) (GenericList Name Vector Song))
-> LibraryState
-> Const (GenericList Name Vector Song) LibraryState
Lens' LibraryState (GenericList Name Vector Song)
songsL)
Bool -> Vector Song -> HumState -> EventM Name HumState
forall n. Bool -> Vector Song -> HumState -> EventM n HumState
songBulkAddtoQ Bool
play Vector Song
songs HumState
s
librarySearch
:: Bool
-> HumState
-> EventM Name HumState
librarySearch :: Bool -> HumState -> EventM Name HumState
librarySearch Bool
direction HumState
s =
let libfoc :: FocLib
libfoc = HumState
s HumState -> Getting FocLib HumState FocLib -> FocLib
forall s a. s -> Getting a s a -> a
^. (Focus -> Const FocLib Focus) -> HumState -> Const FocLib HumState
Lens' HumState Focus
focusL ((Focus -> Const FocLib Focus)
-> HumState -> Const FocLib HumState)
-> ((FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus)
-> Getting FocLib HumState FocLib
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocLib -> Const FocLib FocLib) -> Focus -> Const FocLib Focus
Lens' Focus FocLib
focLibL
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 case FocLib
libfoc of
FocLib
FocArtists -> do
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildLibArtists
(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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL
((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector Value)
artistsL
((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HumState -> Identity HumState)
-> (GenericList Name Vector Value -> GenericList Name Vector Value)
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (GenericList Name Vector Value -> GenericList Name Vector Value
forall n e. GenericList n Vector e -> GenericList n Vector e
dir (GenericList Name Vector Value -> GenericList Name Vector Value)
-> (GenericList Name Vector Value -> GenericList Name Vector Value)
-> GenericList Name Vector Value
-> GenericList Name Vector Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Bool)
-> GenericList Name Vector Value -> GenericList Name Vector Value
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listFindBy (Text -> Value -> Bool
forall a. ToString a => Text -> a -> Bool
stringySearch Text
searchkey) (GenericList Name Vector Value -> GenericList Name Vector Value)
-> (GenericList Name Vector Value -> GenericList Name Vector Value)
-> GenericList Name Vector Value
-> GenericList Name Vector Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector Value -> GenericList Name Vector Value
forall n e. GenericList n Vector e -> GenericList n Vector e
dir)
FocLib
FocAlbums -> do
HumState -> EventM Name HumState
forall (m :: * -> *). MonadIO m => HumState -> m HumState
rebuildLibAlbums
(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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL
((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector (Value, Value))
yalbumsL
((GenericList Name Vector (Value, Value)
-> Identity (GenericList Name Vector (Value, Value)))
-> HumState -> Identity HumState)
-> (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall n e. GenericList n Vector e -> GenericList n Vector e
dir (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Value, Value) -> Bool)
-> GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
(e -> Bool) -> GenericList n t e -> GenericList n t e
listFindBy (Text -> Value -> Bool
forall a. ToString a => Text -> a -> Bool
stringySearch Text
searchkey (Value -> Bool)
-> ((Value, Value) -> Value) -> (Value, Value) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value, Value) -> Value
forall a b. (a, b) -> b
snd) (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> (GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value))
-> GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector (Value, Value)
-> GenericList Name Vector (Value, Value)
forall n e. GenericList n Vector e -> GenericList n Vector e
dir)
FocLib
FocSongs -> 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
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL
((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState
Lens' LibraryState (GenericList Name Vector Song)
songsL
((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HumState -> Identity HumState)
-> (GenericList Name Vector Song -> GenericList Name Vector Song)
-> HumState
-> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ (GenericList Name Vector Song -> GenericList Name Vector Song
forall n e. GenericList n Vector e -> GenericList n Vector e
dir (GenericList Name Vector Song -> GenericList Name Vector Song)
-> (GenericList Name Vector Song -> GenericList Name Vector Song)
-> GenericList Name Vector Song
-> GenericList Name Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Song -> Bool)
-> GenericList Name Vector Song -> GenericList Name Vector Song
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]) (GenericList Name Vector Song -> GenericList Name Vector Song)
-> (GenericList Name Vector Song -> GenericList Name Vector Song)
-> GenericList Name Vector Song
-> GenericList Name Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenericList Name Vector Song -> GenericList Name Vector Song
forall n e. GenericList n Vector e -> GenericList n Vector e
dir)
handleEventLibrary
:: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventLibrary :: HumState -> BrickEvent Name HumEvent -> EventM Name (Next HumState)
handleEventLibrary 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))
-> EventM Name HumState -> EventM Name (Next HumState)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove forall e. List Name e -> List Name e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveDown HumState
s
EvKey (KChar Char
'k') [] -> 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
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove forall e. List Name e -> List Name e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveUp HumState
s
EvKey (KChar Char
'l') [] -> 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
& (Focus -> Identity Focus) -> HumState -> Identity HumState
Lens' HumState Focus
focusL ((Focus -> Identity Focus) -> HumState -> Identity HumState)
-> ((FocLib -> Identity FocLib) -> Focus -> Identity Focus)
-> (FocLib -> Identity FocLib)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocLib -> Identity FocLib) -> Focus -> Identity Focus
Lens' Focus FocLib
focLibL ((FocLib -> Identity FocLib) -> HumState -> Identity HumState)
-> (FocLib -> FocLib) -> HumState -> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ FocLib -> FocLib
libraryMoveRight
EvKey (KChar Char
'h') [] -> 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
& (Focus -> Identity Focus) -> HumState -> Identity HumState
Lens' HumState Focus
focusL ((Focus -> Identity Focus) -> HumState -> Identity HumState)
-> ((FocLib -> Identity FocLib) -> Focus -> Identity Focus)
-> (FocLib -> Identity FocLib)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FocLib -> Identity FocLib) -> Focus -> Identity Focus
Lens' Focus FocLib
focLibL ((FocLib -> Identity FocLib) -> HumState -> Identity HumState)
-> (FocLib -> FocLib) -> HumState -> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ FocLib -> FocLib
libraryMoveLeft
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
librarySearch (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
librarySearch (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 Key
KEnter [] ->
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
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove forall e. List Name e -> List Name e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveDown (HumState -> EventM Name HumState)
-> EventM Name HumState -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HumState -> EventM Name HumState
libraryAddtoQ Bool
True HumState
s
EvKey (KChar Char
' ') [] ->
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
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove forall e. List Name e -> List Name e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
GenericList n t e -> GenericList n t e
listMoveDown (HumState -> EventM Name HumState)
-> EventM Name HumState -> EventM Name HumState
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Bool -> HumState -> EventM Name HumState
libraryAddtoQ Bool
False HumState
s
EvKey (KChar Char
'G') [] -> 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
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove (Int -> GenericList Name Vector e -> GenericList Name Vector e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
listMoveTo (-Int
1)) HumState
s
EvKey (KChar Char
'g') [] -> 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
=<< (forall e. List Name e -> List Name e)
-> HumState -> EventM Name HumState
libraryMove (Int -> GenericList Name Vector e -> GenericList Name Vector e
forall (t :: * -> *) n e.
(Foldable t, Splittable t) =>
Int -> GenericList n t e -> GenericList n t e
listMoveTo Int
0) HumState
s
EvKey (KChar Char
'`') [] -> 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
rebuildLibArtists (HumState
s HumState -> (HumState -> HumState) -> HumState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState
Lens' HumState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HumState -> Identity HumState)
-> ((Bool -> Identity Bool)
-> LibraryState -> Identity LibraryState)
-> (Bool -> Identity Bool)
-> HumState
-> Identity HumState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bool -> Identity Bool) -> LibraryState -> Identity LibraryState
Lens' LibraryState Bool
yalbumSortL ((Bool -> Identity Bool) -> HumState -> Identity HumState)
-> (Bool -> Bool) -> HumState -> HumState
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Bool -> Bool
not)
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