kino/src/UI/Widgets.hs

96 lines
3.1 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
{-|
Module : UI.Widgets
Description : This is the code which builds the Brick frontend
-}
module UI.Widgets where
import Brick
import Brick.Main
import Brick.Widgets.Center
import Brick.Widgets.Border
import Brick.Widgets.Edit
import Brick.AttrMap (attrMap)
import Graphics.Vty (defAttr)
import Graphics.Vty.Input.Events
import Control.Monad.IO.Class (liftIO)
import qualified Data.Text as T
import Lens.Micro
import Data.Maybe
import JSONTypes
import Request
import Misc
import AppTypes
import Torrent
-- | Wrap a widget in the selected attribute
select :: Widget Ident -> Widget Ident
select = withAttr (attrName "selected")
-- | Given a movie and a tuple of widgets and state, append the
-- movie to the widgets. Used by movieWidgets
widgetCons :: JSONMovie -> (Widget Ident, AppS) -> (Widget Ident, AppS)
widgetCons m (w, s) =
embed $ if Just m == (s ^. appDetails)
then select . visible $
if s ^. appExpanded
then expandedWidget s m
else movieWidget s m
else movieWidget s m
where
embed x = (x <=> w, s)
-- | Returns a big list of all movies
movieWidgets :: AppS -> Widget Ident
movieWidgets s = let (items, _) = foldr widgetCons (emptyWidget, s) (moviesMovies (s ^. appListing))
in items
-- | Returns a single movie listing
movieWidget :: AppS -> JSONMovie -> Widget Ident
movieWidget s m = txt (movieTitle m) <+> padLeft Max (str (show (movieYear m)))
-- | Returns an expanded movie listing showing additional info
expandedWidget :: AppS -> JSONMovie -> Widget Ident
expandedWidget s m = movieWidget s m
<=> (padRight (Pad 3) (str "Rating") <+> str (show (movieRating m)))
<=> (padRight (Pad 1) (str "Language") <+> txt (movieLanguage m))
<=> (padRight (Pad 3) (str "Genres") <+> txt (T.intercalate ", " (movieGenres m)))
<=> (padRight (Pad 2) (str "Magnets") <+> str (listTorrents m))
<=> (padRight (Pad 2) (str "Summary") <+> txtWrap (movieSummary m))
-- | The search mode widget. Uses the brick built in Editor widget
searchWidget :: AppS -> Widget Ident
searchWidget s = center $ border $
padAll 1 (editorRenderer (s ^. appEditor))
<=> padAll 1 (hCenter (str "[Press enter to search]"))
editorRenderer :: Editor T.Text Ident -> Widget Ident
editorRenderer e = renderEditor render True e
where
render :: [T.Text] -> Widget Ident
render [] = txt "Enter query term" $> withAttr editAttr
render [""] = txt "Enter query term" $> withAttr editAttr
render (t:_) = txt t
-- | The browse mode widget which returns a full listing of movies
-- or reports that there are no movies to list
browseWidget :: AppS -> Widget Ident
browseWidget s =
str "Title" <+> padLeft Max (str "Year")
<=> viewport Listing Vertical (movieWidgets s)
-- | The message widget which simply shows a message and informs
-- the user of how to escape
messageWidget :: AppS -> Widget Ident
messageWidget s = center $ border $
padAll 1 (hCenter (str (fromMaybe "Unkown Error!" (s ^. appMessage))))
<=> padAll 1 (hCenter (str ("[Press any key to " <> action <> "]")))
where
action = if s ^. appContinue
then "continue"
else "exit"