added sorting modes
This commit is contained in:
parent
879fd536d6
commit
47454593d7
|
@ -40,7 +40,9 @@ defaultOptions = defaults & param "limit" .~ ["50"]
|
||||||
-- | Updates the state following a new movie request
|
-- | Updates the state following a new movie request
|
||||||
setMovies :: AppS -> IO AppS
|
setMovies :: AppS -> IO AppS
|
||||||
setMovies s = do
|
setMovies s = do
|
||||||
m <- getMovies ((s ^. appReqOpts) & param "page" .~ [T.pack (show (s ^. appPage))])
|
m <- getMovies $ (s ^. appReqOpts) & param "page" .~ [T.pack (show (s ^. appPage))]
|
||||||
|
& param "sort_by" .~ [T.pack (show (s ^. appSort))]
|
||||||
|
& param "order_by" .~ [T.pack (show (s ^. appSortMode))]
|
||||||
pure $ case m of
|
pure $ case m of
|
||||||
(Left e) -> displayMessage s True (displayException e)
|
(Left e) -> displayMessage s True (displayException e)
|
||||||
(Right r) -> case r of
|
(Right r) -> case r of
|
||||||
|
|
|
@ -72,7 +72,7 @@ instance FromJSON JSONMovie where
|
||||||
<*> v .: "year"
|
<*> v .: "year"
|
||||||
<*> v .: "rating"
|
<*> v .: "rating"
|
||||||
<*> v .: "runtime"
|
<*> v .: "runtime"
|
||||||
<*> v .: "genres"
|
<*> v .:? "genres" .!= []
|
||||||
<*> v .: "summary"
|
<*> v .: "summary"
|
||||||
<*> v .: "language"
|
<*> v .: "language"
|
||||||
<*> v .: "torrents"
|
<*> v .: "torrents"
|
||||||
|
@ -115,7 +115,26 @@ data SortOrder
|
||||||
| Downloads
|
| Downloads
|
||||||
| Likes
|
| Likes
|
||||||
| UploadDate
|
| UploadDate
|
||||||
deriving (Eq, Show)
|
deriving (Eq)
|
||||||
|
|
||||||
|
instance Show SortOrder where
|
||||||
|
show Title = "title"
|
||||||
|
show Year = "year"
|
||||||
|
show Rating = "rating"
|
||||||
|
show Seeds = "seeds"
|
||||||
|
show Downloads = "download_count"
|
||||||
|
show Likes = "like_count"
|
||||||
|
show UploadDate = "date_added"
|
||||||
|
|
||||||
|
-- | Used to choose how to sort
|
||||||
|
data SortMode
|
||||||
|
= Ascending
|
||||||
|
| Descending
|
||||||
|
deriving (Eq)
|
||||||
|
|
||||||
|
instance Show SortMode where
|
||||||
|
show Ascending = "asc"
|
||||||
|
show Descending = "desc"
|
||||||
|
|
||||||
-- | Used for scrolling
|
-- | Used for scrolling
|
||||||
data ScrollDirection = Up | Down
|
data ScrollDirection = Up | Down
|
||||||
|
@ -134,6 +153,7 @@ data AppS = AppS
|
||||||
, _appEditor :: Editor T.Text Ident -- ^ The state for the editor widget
|
, _appEditor :: Editor T.Text Ident -- ^ The state for the editor widget
|
||||||
, _appReqOpts :: WR.Options -- ^ The options to use to make our requests
|
, _appReqOpts :: WR.Options -- ^ The options to use to make our requests
|
||||||
, _appSort :: SortOrder -- ^ The order to display the listings in
|
, _appSort :: SortOrder -- ^ The order to display the listings in
|
||||||
|
, _appSortMode :: SortMode -- ^ If to sort ascending or descending
|
||||||
} deriving (Show)
|
} deriving (Show)
|
||||||
|
|
||||||
makeLenses ''AppS
|
makeLenses ''AppS
|
||||||
|
|
|
@ -9,6 +9,8 @@ This is the code which interacts with Brick
|
||||||
|
|
||||||
module Kino.UI (runApp) where
|
module Kino.UI (runApp) where
|
||||||
|
|
||||||
|
import Data.Char
|
||||||
|
|
||||||
import Brick hiding (Direction(..))
|
import Brick hiding (Direction(..))
|
||||||
import Brick.Widgets.Edit (handleEditorEvent, editorText, editAttr, getEditContents)
|
import Brick.Widgets.Edit (handleEditorEvent, editorText, editAttr, getEditContents)
|
||||||
import Control.Monad.IO.Class (liftIO)
|
import Control.Monad.IO.Class (liftIO)
|
||||||
|
@ -40,6 +42,8 @@ initialState = AppS
|
||||||
, _appContinue = True
|
, _appContinue = True
|
||||||
, _appEditor = editorText Input (Just 1) mempty
|
, _appEditor = editorText Input (Just 1) mempty
|
||||||
, _appReqOpts = defaultOptions
|
, _appReqOpts = defaultOptions
|
||||||
|
, _appSort = UploadDate
|
||||||
|
, _appSortMode = Descending
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Our brick app specification
|
-- | Our brick app specification
|
||||||
|
@ -69,6 +73,7 @@ draw s = pure $ case s ^. appMode of
|
||||||
Browse -> browseWidget s
|
Browse -> browseWidget s
|
||||||
Search -> searchWidget s
|
Search -> searchWidget s
|
||||||
Message -> messageWidget s
|
Message -> messageWidget s
|
||||||
|
Sort -> sortWidget
|
||||||
|
|
||||||
|
|
||||||
-- | Currently just showFirstCursor
|
-- | Currently just showFirstCursor
|
||||||
|
@ -108,6 +113,11 @@ copyMagnet s i = case (do
|
||||||
liftIO (setClipboardString magnet)
|
liftIO (setClipboardString magnet)
|
||||||
continue (displayMessage s False "Copied magnet link to clipboard!")
|
continue (displayMessage s False "Copied magnet link to clipboard!")
|
||||||
|
|
||||||
|
-- | Continue with a new sort mode
|
||||||
|
setSort :: AppS -> SortOrder -> EventM Ident (Next AppS)
|
||||||
|
setSort st so = continue =<< (liftIO $ setMovies (st & appSort .~ so
|
||||||
|
& appMode .~ Browse))
|
||||||
|
|
||||||
-- | The event handler, takes care of keyboard events.
|
-- | The event handler, takes care of keyboard events.
|
||||||
eventHandler :: AppS -> BrickEvent Ident () -> EventM Ident (Next AppS)
|
eventHandler :: AppS -> BrickEvent Ident () -> EventM Ident (Next AppS)
|
||||||
eventHandler s (VtyEvent e@(EvKey k _)) =
|
eventHandler s (VtyEvent e@(EvKey k _)) =
|
||||||
|
@ -118,14 +128,22 @@ eventHandler s (VtyEvent e@(EvKey k _)) =
|
||||||
else halt s
|
else halt s
|
||||||
|
|
||||||
Sort -> case k of
|
Sort -> case k of
|
||||||
(KChar 't') -> undefined
|
(KChar c) -> let s' = s & appSortMode .~ if isUpper c then Ascending else Descending
|
||||||
(KChar 'y') -> undefined
|
in case toLower c of
|
||||||
(KChar 'r') -> undefined
|
't' -> setSort s' Title
|
||||||
(KChar 's') -> undefined
|
'y' -> setSort s' Year
|
||||||
(KChar 'd') -> undefined
|
'r' -> setSort s' Rating
|
||||||
(KChar 'l') -> undefined
|
's' -> setSort s' Seeds
|
||||||
(KChar 'u') -> undefined
|
'd' -> setSort s' Downloads
|
||||||
_ -> undefined
|
'l' -> setSort s' Likes
|
||||||
|
'u' -> setSort s' UploadDate
|
||||||
|
|
||||||
|
'q' -> continue (s & appMode .~ Browse)
|
||||||
|
|
||||||
|
_ -> continueWithoutRedraw s
|
||||||
|
|
||||||
|
|
||||||
|
_ -> continueWithoutRedraw s
|
||||||
|
|
||||||
Search -> case k of
|
Search -> case k of
|
||||||
(KEnter) -> do
|
(KEnter) -> do
|
||||||
|
@ -133,6 +151,7 @@ eventHandler s (VtyEvent e@(EvKey k _)) =
|
||||||
newS <- liftIO (setMovies (s & appReqOpts %~ (\o -> o & param "query_term" .~ [queryText])
|
newS <- liftIO (setMovies (s & appReqOpts %~ (\o -> o & param "query_term" .~ [queryText])
|
||||||
& appPage .~ 1))
|
& appPage .~ 1))
|
||||||
continue (newS & appMode .~ Browse)
|
continue (newS & appMode .~ Browse)
|
||||||
|
|
||||||
_ -> continue =<< handleEventLensed s appEditor handleEditorEvent e
|
_ -> continue =<< handleEventLensed s appEditor handleEditorEvent e
|
||||||
|
|
||||||
Browse -> case k of
|
Browse -> case k of
|
||||||
|
@ -163,7 +182,9 @@ eventHandler s (VtyEvent e@(EvKey k _)) =
|
||||||
(KChar '9') -> copyMagnet s 9
|
(KChar '9') -> copyMagnet s 9
|
||||||
|
|
||||||
(KChar '/') -> continue (s & appMode .~ Search)
|
(KChar '/') -> continue (s & appMode .~ Search)
|
||||||
(KChar 's') -> continue (s & appMode .~ Search)
|
(KChar 'f') -> continue (s & appMode .~ Search)
|
||||||
|
|
||||||
|
(KChar 's') -> continue (s & appMode .~ Sort)
|
||||||
|
|
||||||
_ -> continueWithoutRedraw s
|
_ -> continueWithoutRedraw s
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,7 @@ Description : This is the code which builds the Brick frontend
|
||||||
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) where
|
module Kino.UI.Widgets (messageWidget, searchWidget, browseWidget, sortWidget) where
|
||||||
|
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
|
|
||||||
|
@ -97,3 +97,19 @@ messageWidget s = center $ border $
|
||||||
action = if s ^. appContinue
|
action = if s ^. appContinue
|
||||||
then "continue"
|
then "continue"
|
||||||
else "exit"
|
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]"))
|
||||||
|
|
Loading…
Reference in New Issue
Block a user