did even more work on UI!

master
Rachel Lambda Samuelsson 2021-09-14 18:24:05 +02:00
parent 64aaf0fbc2
commit f71cee3ffa
3 changed files with 35 additions and 15 deletions

View File

@ -1,5 +1,6 @@
module Misc where module Misc where
infixl 3 !?
(!?) :: [a] -> Int -> Maybe a (!?) :: [a] -> Int -> Maybe a
[] !? i = Nothing [] !? i = Nothing
(x:xs) !? 0 = Just x (x:xs) !? 0 = Just x

View File

@ -40,13 +40,13 @@ runApp :: IO AppS
runApp = defaultMain app initialState runApp = defaultMain app initialState
startEvent :: AppS -> EventM Ident AppS startEvent :: AppS -> EventM Ident AppS
startEvent (AppS m c e p l d err) = do startEvent s = do
-- todo move unwrapping our response structure into a function -- todo move unwrapping our response structure into a function
response <- liftIO getMovies response <- liftIO getMovies
case response of pure $ case response of
(Left msg) -> pure (AppS m c e p l d (Just (T.unpack msg))) (Left msg) -> s & appError .~ Just (T.unpack msg)
(Right listing) -> do (Right listing) -> s & appListing .~ Just listing
pure (AppS m c e p (Just listing) (movies listing !? c) err) & appDetails .~ (movies listing !? s ^. appCursor)
draw :: AppS -> [Widget Ident] draw :: AppS -> [Widget Ident]
draw s = pure $ case s ^. appMode of draw s = pure $ case s ^. appMode of
@ -73,9 +73,19 @@ eventHandler s (VtyEvent (EvKey k _)) = do
Search -> undefined Search -> undefined
Browse -> case k of Browse -> case k of
(KChar 'q') -> halt s (KChar 'q') -> halt s
(KEsc) -> halt s
(KChar 'j') -> continue (scroll Down s) (KChar 'j') -> continue (scroll Down s)
(KChar 'k') -> continue (scroll Up s) (KChar 'k') -> continue (scroll Up s)
(KDown) -> continue (scroll Down s)
(KUp) -> continue (scroll Up s)
(KChar ' ') -> continue (s & appExpanded %~ not) (KChar ' ') -> continue (s & appExpanded %~ not)
(KEnter) -> continue (s & appExpanded %~ not)
(KChar '/') -> continue (s & appMode .~ Search)
(KChar 's') -> continue (s & appMode .~ Search)
_ -> continue s _ -> continue s
eventHandler s _ = continue s eventHandler s _ = continue s

View File

@ -1,8 +1,11 @@
{-# LANGUAGE OverloadedStrings #-}
module Widgets where module Widgets where
import Brick import Brick
import Brick.Main import Brick.Main
import Brick.Widgets.Center import Brick.Widgets.Center
import Brick.Widgets.Table
import Brick.AttrMap (attrMap) import Brick.AttrMap (attrMap)
import Graphics.Vty (defAttr) import Graphics.Vty (defAttr)
import Graphics.Vty.Input.Events import Graphics.Vty.Input.Events
@ -15,28 +18,34 @@ import Request
import Misc import Misc
import AppTypes import AppTypes
select :: Widget Ident -> Widget Ident
select = (withAttr (attrName "selected"))
widgetCons :: JSONMovie -> (Widget Ident, Int, AppS) -> (Widget Ident, Int, AppS) widgetCons :: JSONMovie -> (Widget Ident, Int, AppS) -> (Widget Ident, Int, AppS)
widgetCons m (w, i, s) = widgetCons m (w, i, s) =
if s ^. appCursor == i embed $ if s ^. appCursor == i
then embed . visible . select $ then select . visible $
if s ^. appExpanded if s ^. appExpanded
then expandedWidget s m i then expandedWidget s m
else movieWidget s m i else movieWidget s m
else embed (movieWidget s m i) else movieWidget s m
where where
embed x = (w <=> x, i+1, s) embed x = (w <=> x, i+1, s)
select = (withAttr (attrName "selected"))
movieWidgets :: AppS -> JSONListMovies -> Widget Ident movieWidgets :: AppS -> JSONListMovies -> Widget Ident
movieWidgets s m = let (items, _, _) = foldr widgetCons (emptyWidget, 0, s) (movies m) movieWidgets s m = let (items, _, _) = foldr widgetCons (emptyWidget, 0, s) (movies m)
in items in items
movieWidget :: AppS -> JSONMovie -> Int -> Widget Ident movieWidget :: AppS -> JSONMovie -> Widget Ident
movieWidget s m i = txt (movie_title m) <+> padLeft Max (str (show (movie_year m))) movieWidget s m = txt (movie_title m) <+> padLeft Max (str (show (movie_year m)))
expandedWidget :: AppS -> JSONMovie -> Int -> Widget Ident expandedWidget :: AppS -> JSONMovie -> Widget Ident
expandedWidget s m i = movieWidget s m i <=> txtWrap (movie_summary m) expandedWidget s m = movieWidget s m
<=> (padRight (Pad 3) (str "Rating") <+> str (show (movie_rating m)))
<=> (padRight (Pad 1) (str "Language") <+> txt (movie_language m))
<=> (padRight (Pad 3) (str "Genres") <+> txt (T.intercalate ", " (movie_genres m)))
<=> (padRight (Pad 2) (str "Summary") <+> txtWrap (movie_summary m))
searchWidget :: AppS -> Widget Ident searchWidget :: AppS -> Widget Ident
searchWidget = undefined searchWidget = undefined