module Hum.Rebuild where
import Hum.Types
import Control.Lens
import Brick.Widgets.List
import Network.MPD ( withMPD )
import qualified Network.MPD as MPD
import qualified Data.Vector as V
songsOfArtist :: Maybe MPD.Value -> IO (V.Vector MPD.Song)
songsOfArtist :: Maybe Value -> IO (Vector Song)
songsOfArtist Maybe Value
martist = [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD
(Query -> MPD [Song]
forall (m :: * -> *). MonadMPD m => Query -> m [Song]
MPD.find (Metadata
MPD.AlbumArtist Metadata -> Value -> Query
MPD.=? Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"" Maybe Value
martist))
songsOfAlbum :: Maybe MPD.Value -> IO (V.Vector MPD.Song)
songsOfAlbum :: Maybe Value -> IO (Vector Song)
songsOfAlbum Maybe Value
malbum = [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD
(Query -> MPD [Song]
forall (m :: * -> *). MonadMPD m => Query -> m [Song]
MPD.find (Metadata
MPD.Album Metadata -> Value -> Query
MPD.=? Value -> Maybe Value -> Value
forall a. a -> Maybe a -> a
fromMaybe Value
"" Maybe Value
malbum))
albumsOfArtist :: Maybe MPD.Value -> IO (V.Vector MPD.Value)
albumsOfArtist :: Maybe Value -> IO (Vector Value)
albumsOfArtist Maybe Value
martist =
[Value] -> Vector Value
forall a. [a] -> Vector a
V.fromList ([Value] -> Vector Value)
-> (Either MPDError [Value] -> [Value])
-> Either MPDError [Value]
-> Vector Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Either MPDError [Value] -> [Value]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Value] -> Vector Value)
-> IO (Either MPDError [Value]) -> IO (Vector Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Value] -> IO (Either MPDError [Value])
forall a. MPD a -> IO (Response a)
withMPD (Metadata -> Maybe Value -> MPD [Value]
forall (m :: * -> *).
MonadMPD m =>
Metadata -> Maybe Value -> m [Value]
MPD.list Metadata
MPD.Album Maybe Value
martist)
rebuildLib :: MonadIO m => HState -> m HState
rebuildLib :: HState -> m HState
rebuildLib HState
s = do
Vector Value
artistsVec <- IO (Vector Value) -> m (Vector Value)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO ([Value] -> Vector Value
forall a. [a] -> Vector a
V.fromList ([Value] -> Vector Value)
-> (Either MPDError [Value] -> [Value])
-> Either MPDError [Value]
-> Vector Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> Either MPDError [Value] -> [Value]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Value] -> Vector Value)
-> IO (Either MPDError [Value]) -> IO (Vector Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Value] -> IO (Either MPDError [Value])
forall a. MPD a -> IO (Response a)
withMPD
(Metadata -> Maybe Value -> MPD [Value]
forall (m :: * -> *).
MonadMPD m =>
Metadata -> Maybe Value -> m [Value]
MPD.list Metadata
MPD.AlbumArtist Maybe Value
forall a. Maybe a
Nothing))
let artists' :: GenericList Name Vector Value
artists' = Name -> Vector Value -> Int -> GenericList Name Vector Value
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
ArtistsList Vector Value
artistsVec Int
1
Vector Value
albumsVec <- IO (Vector Value) -> m (Vector Value)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Value) -> m (Vector Value))
-> IO (Vector Value) -> m (Vector Value)
forall a b. (a -> b) -> a -> b
$ Maybe Value -> IO (Vector Value)
albumsOfArtist ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
artists')
let albums' :: GenericList Name Vector Value
albums' = Name -> Vector Value -> Int -> GenericList Name Vector Value
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
AlbumsList Vector Value
albumsVec Int
1
Vector Song
songsVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> m (Vector Song))
-> IO (Vector Song) -> m (Vector Song)
forall a b. (a -> b) -> a -> b
$ Maybe Value -> IO (Vector Song)
songsOfAlbum ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
albums')
let songs' :: GenericList Name Vector Song
songs' = Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
SongsList Vector Song
songsVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m HState
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState
-> Identity HState
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))
-> HState -> Identity HState)
-> GenericList Name Vector Value -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Value
artists'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState
-> Identity HState
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)
albumsL ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState -> Identity HState)
-> GenericList Name Vector Value -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Value
albums'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HState
-> Identity HState
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))
-> HState -> Identity HState)
-> GenericList Name Vector Song -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Song
songs'
rebuildLibArtists :: MonadIO m => HState -> m HState
rebuildLibArtists :: HState -> m HState
rebuildLibArtists HState
s = do
let artists' :: GenericList Name Vector Value
artists' = HState
s HState
-> Getting
(GenericList Name Vector Value)
HState
(GenericList Name Vector Value)
-> GenericList Name Vector Value
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HState -> Const (GenericList Name Vector Value) HState
Lens' HState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HState -> Const (GenericList Name Vector Value) HState)
-> ((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)
HState
(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 Value
albumsVec <- IO (Vector Value) -> m (Vector Value)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Value) -> m (Vector Value))
-> IO (Vector Value) -> m (Vector Value)
forall a b. (a -> b) -> a -> b
$ Maybe Value -> IO (Vector Value)
albumsOfArtist ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
artists')
let albums' :: GenericList Name Vector Value
albums' = Name -> Vector Value -> Int -> GenericList Name Vector Value
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
AlbumsList Vector Value
albumsVec Int
1
Vector Song
songsVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> m (Vector Song))
-> IO (Vector Song) -> m (Vector Song)
forall a b. (a -> b) -> a -> b
$ Maybe Value -> IO (Vector Song)
songsOfAlbum ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
albums')
let songs' :: GenericList Name Vector Song
songs' = Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
SongsList Vector Song
songsVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m HState
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState
-> Identity HState
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))
-> HState -> Identity HState)
-> GenericList Name Vector Value -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Value
artists'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState
-> Identity HState
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)
albumsL ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState -> Identity HState)
-> GenericList Name Vector Value -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Value
albums'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HState
-> Identity HState
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))
-> HState -> Identity HState)
-> GenericList Name Vector Song -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Song
songs'
rebuildLibAlbums :: MonadIO m => HState -> m HState
rebuildLibAlbums :: HState -> m HState
rebuildLibAlbums HState
s = do
let albums' :: GenericList Name Vector Value
albums' = HState
s HState
-> Getting
(GenericList Name Vector Value)
HState
(GenericList Name Vector Value)
-> GenericList Name Vector Value
forall s a. s -> Getting a s a -> a
^. (LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HState -> Const (GenericList Name Vector Value) HState
Lens' HState LibraryState
libraryL ((LibraryState
-> Const (GenericList Name Vector Value) LibraryState)
-> HState -> Const (GenericList Name Vector Value) HState)
-> ((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)
HState
(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)
albumsL
Vector Song
songsVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> m (Vector Song))
-> IO (Vector Song) -> m (Vector Song)
forall a b. (a -> b) -> a -> b
$ Maybe Value -> IO (Vector Song)
songsOfAlbum ((Int, Value) -> Value
forall a b. (a, b) -> b
snd ((Int, Value) -> Value) -> Maybe (Int, Value) -> Maybe Value
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GenericList Name Vector Value -> Maybe (Int, Value)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector Value
albums')
let songs' :: GenericList Name Vector Song
songs' = Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
SongsList Vector Song
songsVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m HState
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState
-> Identity HState
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)
albumsL ((GenericList Name Vector Value
-> Identity (GenericList Name Vector Value))
-> HState -> Identity HState)
-> GenericList Name Vector Value -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Value
albums' HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (LibraryState -> Identity LibraryState)
-> HState -> Identity HState
Lens' HState LibraryState
libraryL ((LibraryState -> Identity LibraryState)
-> HState -> Identity HState)
-> ((GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> LibraryState -> Identity LibraryState)
-> (GenericList Name Vector Song
-> Identity (GenericList Name Vector Song))
-> HState
-> Identity HState
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))
-> HState -> Identity HState)
-> GenericList Name Vector Song -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector Song
songs'
rebuildPl :: MonadIO m => HState -> m HState
rebuildPl :: HState -> m HState
rebuildPl HState
s = do
Vector PlaylistName
plListVec <- IO (Vector PlaylistName) -> m (Vector PlaylistName)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector PlaylistName) -> m (Vector PlaylistName))
-> IO (Vector PlaylistName) -> m (Vector PlaylistName)
forall a b. (a -> b) -> a -> b
$ [PlaylistName] -> Vector PlaylistName
forall a. [a] -> Vector a
V.fromList ([PlaylistName] -> Vector PlaylistName)
-> (Either MPDError [PlaylistName] -> [PlaylistName])
-> Either MPDError [PlaylistName]
-> Vector PlaylistName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PlaylistName] -> Either MPDError [PlaylistName] -> [PlaylistName]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [PlaylistName] -> Vector PlaylistName)
-> IO (Either MPDError [PlaylistName]) -> IO (Vector PlaylistName)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [PlaylistName] -> IO (Either MPDError [PlaylistName])
forall a. MPD a -> IO (Response a)
withMPD MPD [PlaylistName]
forall (m :: * -> *). MonadMPD m => m [PlaylistName]
MPD.listPlaylists
let plList' :: GenericList Name Vector PlaylistName
plList' = Name
-> Vector PlaylistName
-> Int
-> GenericList Name Vector PlaylistName
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
PlaylistList Vector PlaylistName
plListVec Int
1
Vector Song
plSongsVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> m (Vector Song))
-> IO (Vector Song) -> m (Vector Song)
forall a b. (a -> b) -> a -> b
$ [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD
(PlaylistName -> MPD [Song]
forall (m :: * -> *). MonadMPD m => PlaylistName -> m [Song]
MPD.listPlaylistInfo
(PlaylistName
-> ((Int, PlaylistName) -> PlaylistName)
-> Maybe (Int, PlaylistName)
-> PlaylistName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PlaylistName
"<no playlists>" (Int, PlaylistName) -> PlaylistName
forall a b. (a, b) -> b
snd (GenericList Name Vector PlaylistName -> Maybe (Int, PlaylistName)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector PlaylistName
plList'))
)
let plSongs' :: GenericList Name Vector (Song, Bool)
plSongs' = (, Bool
False) (Song -> (Song, Bool))
-> GenericList Name Vector Song
-> GenericList Name Vector (Song, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
PlaylistSongs Vector Song
plSongsVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m HState
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState
Lens' HState PlaylistsState
playlistsL ((PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState)
-> ((GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> PlaylistsState -> Identity PlaylistsState)
-> (GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> PlaylistsState -> Identity PlaylistsState
Lens' PlaylistsState (GenericList Name Vector PlaylistName)
plListL ((GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> HState -> Identity HState)
-> GenericList Name Vector PlaylistName -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector PlaylistName
plList'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState
Lens' HState PlaylistsState
playlistsL ((PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState)
-> ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> PlaylistsState -> Identity PlaylistsState)
-> (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)))
-> PlaylistsState -> Identity PlaylistsState
Lens' PlaylistsState (GenericList Name Vector (Song, Bool))
plSongsL ((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)
plSongs'
rebuildPlList :: MonadIO m => HState -> m HState
rebuildPlList :: HState -> m HState
rebuildPlList HState
s = do
let plList' :: GenericList Name Vector PlaylistName
plList' = HState
s HState
-> Getting
(GenericList Name Vector PlaylistName)
HState
(GenericList Name Vector PlaylistName)
-> GenericList Name Vector PlaylistName
forall s a. s -> Getting a s a -> a
^. (PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState)
-> HState -> Const (GenericList Name Vector PlaylistName) HState
Lens' HState PlaylistsState
playlistsL ((PlaylistsState
-> Const (GenericList Name Vector PlaylistName) PlaylistsState)
-> HState -> Const (GenericList Name Vector PlaylistName) HState)
-> ((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)
HState
(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
Vector Song
plSongsVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
([Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD
(PlaylistName -> MPD [Song]
forall (m :: * -> *). MonadMPD m => PlaylistName -> m [Song]
MPD.listPlaylistInfo
(PlaylistName
-> ((Int, PlaylistName) -> PlaylistName)
-> Maybe (Int, PlaylistName)
-> PlaylistName
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PlaylistName
"<no playlists>" (Int, PlaylistName) -> PlaylistName
forall a b. (a, b) -> b
snd (GenericList Name Vector PlaylistName -> Maybe (Int, PlaylistName)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
listSelectedElement GenericList Name Vector PlaylistName
plList'))
)
)
let plSongs' :: GenericList Name Vector (Song, Bool)
plSongs' = (, Bool
False) (Song -> (Song, Bool))
-> GenericList Name Vector Song
-> GenericList Name Vector (Song, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
PlaylistSongs Vector Song
plSongsVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m HState
forall a b. (a -> b) -> a -> b
$ HState
s HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState
Lens' HState PlaylistsState
playlistsL ((PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState)
-> ((GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> PlaylistsState -> Identity PlaylistsState)
-> (GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> HState
-> Identity HState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> PlaylistsState -> Identity PlaylistsState
Lens' PlaylistsState (GenericList Name Vector PlaylistName)
plListL ((GenericList Name Vector PlaylistName
-> Identity (GenericList Name Vector PlaylistName))
-> HState -> Identity HState)
-> GenericList Name Vector PlaylistName -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector PlaylistName
plList'
HState -> (HState -> HState) -> HState
forall a b. a -> (a -> b) -> b
& (PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState
Lens' HState PlaylistsState
playlistsL ((PlaylistsState -> Identity PlaylistsState)
-> HState -> Identity HState)
-> ((GenericList Name Vector (Song, Bool)
-> Identity (GenericList Name Vector (Song, Bool)))
-> PlaylistsState -> Identity PlaylistsState)
-> (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)))
-> PlaylistsState -> Identity PlaylistsState
Lens' PlaylistsState (GenericList Name Vector (Song, Bool))
plSongsL ((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)
plSongs'
rebuildQueue :: MonadIO m => HState -> m HState
rebuildQueue :: HState -> m HState
rebuildQueue HState
s = do
Vector Song
queueVec <- IO (Vector Song) -> m (Vector Song)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Vector Song) -> m (Vector Song))
-> IO (Vector Song) -> m (Vector Song)
forall a b. (a -> b) -> a -> b
$ [Song] -> Vector Song
forall a. [a] -> Vector a
V.fromList ([Song] -> Vector Song)
-> (Either MPDError [Song] -> [Song])
-> Either MPDError [Song]
-> Vector Song
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Song] -> Either MPDError [Song] -> [Song]
forall b a. b -> Either a b -> b
fromRight [] (Either MPDError [Song] -> Vector Song)
-> IO (Either MPDError [Song]) -> IO (Vector Song)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MPD [Song] -> IO (Either MPDError [Song])
forall a. MPD a -> IO (Response a)
withMPD (Maybe Int -> MPD [Song]
forall (m :: * -> *). MonadMPD m => Maybe Int -> m [Song]
MPD.playlistInfo Maybe Int
forall a. Maybe a
Nothing)
let queue' :: GenericList Name Vector (Song, Bool)
queue' = (, Bool
False) (Song -> (Song, Bool))
-> GenericList Name Vector Song
-> GenericList Name Vector (Song, Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Name -> Vector Song -> Int -> GenericList Name Vector Song
forall (t :: * -> *) n e.
Foldable t =>
n -> t e -> Int -> GenericList n t e
list Name
QueueList Vector Song
queueVec Int
1
HState -> m HState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HState -> m HState) -> HState -> m 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) -> HState -> HState
forall s t a b. ASetter s t a b -> b -> s -> t
.~ GenericList Name Vector (Song, Bool)
queue'