kino/src/Kino/UI/Widgets.hs

114 lines
4.0 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
{-|
Module : Kino.UI.Widgets
Description : This is the code which builds the Brick frontend
This is the code which builds the Brick frontend
-}
module Kino.UI.Widgets (messageWidget, searchWidget, browseWidget, sortWidget) where
import Data.Maybe (fromMaybe)
import Brick
import Brick.Widgets.Center
import Brick.Widgets.Border
import Brick.Widgets.Edit
import Lens.Micro
import qualified Data.Text as T
import Kino.Types
import Kino.Misc
import Kino.Torrent
-- | Wrap a widget in the selected attribute
select :: Widget Ident -> Widget Ident
select = withAttr (attrName "selected")
-- | Given a state, a movie and a second widget, append the
-- movie to the widget second widget. Used by movieWidgets
widgetCons :: AppS -> JSONMovie -> Widget Ident -> Widget Ident
widgetCons s m w =
(<=> w) $ if Just m == (s ^. appDetails)
then select . visible $
if s ^. appExpanded
then expandedWidget m
else movieWidget m
else movieWidget m
-- | Returns a big list of all movies
movieWidgets :: AppS -> Widget Ident
movieWidgets s = foldr (widgetCons s) emptyWidget (moviesMovies (s ^. appListing))
-- | Returns a single movie listing
movieWidget :: JSONMovie -> Widget Ident
movieWidget m = txt (movieTitle m) <+> padLeft Max (str (show (movieYear m)))
-- | Returns an expanded movie listing showing additional info
expandedWidget :: JSONMovie -> Widget Ident
expandedWidget m = movieWidget 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 "Runtime") <+> str (show hours <> "h " <> show minutes <> "m"))
<=> (padRight (Pad 2) (str "Magnets") <+> str (listTorrents m))
<=> (padRight (Pad 2) (str "Summary") <+> txtWrap (movieSummary m))
where
(hours, minutes) = divMod (movieRuntime m) 60
-- | 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]"))
-- | Takes an editor and returns a widget to represent it
editorRenderer :: Editor T.Text Ident -> Widget Ident
editorRenderer = renderEditor txtRender True
where
txtRender :: [T.Text] -> Widget Ident
txtRender [] = txt "Enter query term" $> withAttr editAttr
txtRender [""] = txt "Enter query term" $> withAttr editAttr
txtRender (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)
<=> (str ("results: " <> results) <+> padLeft Max (str ("(" <> page <> "/" <> pages <> ")")))
where
listing = s ^. appListing
results = show (moviesCount listing)
pages = show ((moviesCount listing `div` moviesLimit listing) + 1)
page = show (s ^. appPage)
-- | 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"
-- | The sort widget which simply shows the different sorting modees
-- and informs the the user of how to set each one.
sortWidget :: Widget Ident
sortWidget = center $ border $ hCenter $
padAll 1 (str "Sort by:\n\
\(Tt) Title\n\
\(Yy) Year\n\
\(Rr) Rating\n\
\(Ss) Seeds\n\
\(Dd) Downloads\n\
\(Ll) Likes\n\
\(Uu) Upload Date\n\n\
\Upper case ascending\n\
\Lower case descending")
<=> padAll 1 (hCenter (str "[Press q to close this menu]"))