-- | module Hum.Views.Queue where import Hum.Types import Brick.Main import Graphics.Vty.Input.Events import Brick.Types import Brick.Widgets.Core import Brick.Widgets.Center import Brick.Widgets.List import Hum.Attributes import Hum.Utils import Hum.Rebuild import Hum.Views.Common import Network.MPD ( withMPD ) import qualified Network.MPD as MPD import qualified Data.Map.Strict as Map import Control.Lens drawViewQueue :: HState -> Widget Name drawViewQueue st = let vsize = case join $ Map.lookup Queue $ extentMap st of Just e -> snd . extentSize $ e Nothing -> 60 in reportExtent Queue $ hCenter ( viewport Queue Vertical -- . visible . vLimit vsize . center $ hCenter header <=> hCenter (renderList (const (queueRow st)) ((focQueue . focus $ st) == FocQueue) (queue st) ) ) where {-songIdx = column (Just (Col 4)) Max (Pad 1) $ txt "Inx" songId = column (Just (Col 3)) Max (Pad 1) $ txt "ID"-} album = withAttr queueAlbumAttr $ column (Just (Per 25)) (Pad 1) Max $ txt "Album" track = withAttr queueTrackAttr $ column (Just (Col 3)) Max (Pad 1) $ txt "#" title = withAttr queueTitleAttr $ column Nothing Max Max $ txt "Title" artist = withAttr queueArtistAttr $ column (Just (Per 25)) Max (Pad 1) $ txt "Artist" time = withAttr queueTimeAttr $ column (Just (Col 5)) Max (Pad 1) $ txt "Time" header = withDefAttr headerAttr ({-songIdx <+> songId <+>-} album <+> track <+> title <+> artist <+> time) queueRow :: HState -> (MPD.Song, Highlight) -> Widget n queueRow st (song, hl) = (if hl then highlightOverQueueAttrs else id) . (if Just (MPD.sgIndex song) == (MPD.sgIndex <$> nowPlaying) then withDefAttr queueNowPlayingAttr else id ) $ hCenter ( {-songIdx <+> songId <+> -} album <+> track <+> title <+> artist <+> time) where nowPlaying = currentSong st {-songIdx = column (Just (Col 4)) Max (Pad 1) $ txt $ maybe "?" show $ MPD.sgIndex song songId = column (Just (Col 3)) Max (Pad 1) $ txt $ maybe "?" (\(MPD.Id x) -> show x) $ MPD.sgId song-} album = withAttr queueAlbumAttr $ column (Just (Per 25)) (Pad 1) Max $ txt $ meta "" MPD.Album song track = withAttr queueTrackAttr $ column (Just (Col 3)) Max (Pad 1) $ txt $ meta "?" MPD.Track song title = withAttr queueTitleAttr $ column Nothing Max Max $ txt $ meta "" MPD.Title song artist = withAttr queueArtistAttr $ column (Just (Per 25)) Max (Pad 1) $ txt $ meta "" MPD.Artist song time = withAttr queueTimeAttr $ column (Just (Col 5)) Max (Pad 1) $ txt $ secondsToTime $ MPD.sgLength song pasteDeleteCleanup :: HState -> SongList -> EventM Name HState pasteDeleteCleanup s clSongs' = do let mi = listSelected (queue s) extentMap <- updateExtentMap currentSong <- liftIO (fromRight Nothing <$> withMPD MPD.currentSong) status <- liftIO (fromRight Nothing <$> (Just <<$>> withMPD MPD.status)) s' <- rebuildQueue s pure (s' & queueL %~ maybe id listMoveTo mi & clipboardL . clSongsL .~ clSongs') { currentSong , status , extentMap } queueSearch :: Bool -> HState -> EventM Name HState queueSearch direction s = let dir = if direction then id else listReverse searchkey = fromMaybe "" ((s ^. exL . searchHistoryL) !!? 0) in if searchkey == "" then pure s else do extentMap <- updateExtentMap pure $ s { extentMap } & queueL %~ ( dir . listFindBy ( songSearch searchkey [MPD.Title, MPD.Album, MPD.Artist] . fst ) . dir ) queueAddToPl :: HState -> String -> EventM Name HState queueAddToPl s plName = let songs = (s ^. queueL) & getHighlighted & listElements <&> fst in songBulkAddtoPl plName songs s handleEventQueue :: HState -> BrickEvent Name HumEvent -> EventM Name (Next HState) handleEventQueue s e = case e of VtyEvent vtye -> case vtye of EvKey (KChar 'j') [] -> do extentMap <- updateExtentMap continue s { queue = listMoveDown $ queue s, extentMap } EvKey (KChar 'k') [] -> do extentMap <- updateExtentMap continue s { queue = listMoveUp $ queue s, extentMap } EvKey (KChar 'n') [] -> continue =<< queueSearch (s ^. exL . searchDirectionL) s EvKey (KChar 'N') [] -> continue =<< queueSearch (s ^. exL . searchDirectionL & not) s EvKey (KChar 'a') [] -> continue $ s & modeL .~ PromptMode & promptsL . currentPromptL .~ PlSelectPrompt & promptsL . promptTitleL .~ "Add selected Item(s) to:" EvKey KEnter [] -> do let maybeSelectedId = MPD.sgId . fst . snd =<< listSelectedElement (queue s) traverse_ (\sel -> liftIO (withMPD $ MPD.playId sel)) maybeSelectedId song <- liftIO (withMPD MPD.currentSong) continue s { currentSong = fromRight Nothing song, queue = queue s } EvKey (KChar ' ') [] -> continue $ s & queueL %~ (listMoveDown . listToggleHighlight) EvKey (KChar 'd') [] -> do let clSongs' = getHighlighted (queue s) _ <- liftIO (withMPD $ deleteHighlightedfromQ (queue s)) continue =<< pasteDeleteCleanup s clSongs' EvKey (KChar 'D') [] -> do let clip = queue s _ <- liftIO (withMPD $ deleteAll (queue s)) continue =<< pasteDeleteCleanup s clip EvKey (KChar 'y') [] -> continue $ s & clipboardL . clSongsL .~ (s ^. queueL & getHighlighted) EvKey (KChar 'p') [] -> do let clip = s ^. clipboardL . clSongsL _ <- liftIO (withMPD $ pasteSongstoQ clip (queue s)) continue =<< pasteDeleteCleanup s clip EvKey (KChar 'G') [] -> do extentMap <- updateExtentMap continue s { queue = listMoveTo (length . queue $ s) $ queue s , extentMap } EvKey (KChar 'g') [] -> do -- TODO change this to 'gg', somehow extentMap <- updateExtentMap continue s { queue = listMoveTo 0 $ queue s, extentMap } _ -> continue s _ -> continue s