4r: Use v1 api

main
staticvoid 2022-07-12 18:03:17 +03:00
parent c3bb8705dd
commit a02bf265ae
4 changed files with 18 additions and 9 deletions

View File

@ -14,7 +14,7 @@ module Api.Color (
import Relude import Relude
import Api.Types import Api.V1.Types
import Color.Print import Color.Print
import Color.Utils import Color.Utils
import Polysemy.Commonmark.AST (commonmark) import Polysemy.Commonmark.AST (commonmark)

View File

@ -1,3 +1,5 @@
{-# LANGUAGE Strict #-}
module Color.Utils (textColor) where module Color.Utils (textColor) where
import Relude import Relude

View File

@ -1,16 +1,19 @@
{-# LANGUAGE Strict #-}
module Main (main) where module Main (main) where
import Relude hiding (Proxy) import Relude hiding (Proxy)
import Api qualified as Api import Api.V1 qualified as Api
import Api.Color () import Api.Color ()
import Api.Types (last_activity_date) import Api.V1.Types qualified as Api
import Cli import Cli
import Color.Print import Color.Print
import Network.HTTP.Client import Network.HTTP.Client
import Polysemy (Member, Members, Sem) import Polysemy (Member, Members, Sem)
import Polysemy.Embed (Embed) import Polysemy.Embed (Embed)
import Polysemy.Error (Error, errorToIOFinal) import Polysemy.Error (Error, errorToIOFinal)
import Polysemy.Fail (Fail, failToEmbed)
import Polysemy.Final (Final, embedToFinal, runFinal) import Polysemy.Final (Final, embedToFinal, runFinal)
import Polysemy.Output (Output) import Polysemy.Output (Output)
import Polysemy.Output.IO (putTextLnO, runOutputToStdout) import Polysemy.Output.IO (putTextLnO, runOutputToStdout)
@ -28,15 +31,17 @@ runProgram ::
[ Output Text [ Output Text
, ServantClient , ServantClient
, Error ClientError , Error ClientError
, Fail
, Embed IO , Embed IO
, Final IO , Final IO
] ]
() -> () ->
IO () IO ()
runProgram clientEnv = runProgram clientEnv =
(>>= either (error . fromString . displayException) pure) runFinal
. runFinal
. embedToFinal . embedToFinal
. failToEmbed @IO
. (>>= either (error . fromString . displayException) pure)
. errorToIOFinal . errorToIOFinal
. runServantClientWith clientEnv . runServantClientWith clientEnv
. runOutputToStdout . runOutputToStdout
@ -49,22 +54,22 @@ sgrFullInterpreter ::
sgrFullInterpreter noAnsi = if noAnsi then ignoreSgrFull else runSgrFull sgrFullInterpreter noAnsi = if noAnsi then ignoreSgrFull else runSgrFull
program :: program ::
Members [Error ClientError, ServantClient, Output Text, Sgr, SgrRegion] r => Members [Fail, Error ClientError, ServantClient, Output Text, Sgr, SgrRegion] r =>
Choice -> Choice ->
Sem r () Sem r ()
program GetSections = do program GetSections = do
sections <- Api.getSections [Api.OGetSections sections] <- Api.request [Api.IGetSections Api.GetSections]
withSgr [SetColor Foreground Vivid White] do withSgr [SetColor Foreground Vivid White] do
sequenceA_ $ intersperse (putTextLnO "") (printColor <$> sections) sequenceA_ $ intersperse (putTextLnO "") (printColor <$> sections)
program GetTopics{maxEntries} = do program GetTopics{maxEntries} = do
topics <- Api.getTopics [Api.OGetTopics topics] <- Api.request [Api.IGetTopics Api.GetTopics]
withSgr [SetColor Foreground Vivid White] do withSgr [SetColor Foreground Vivid White] do
sequenceA_ $ sequenceA_ $
intersperse intersperse
(putTextLnO "") (putTextLnO "")
(fmap printColor . maybe id take maxEntries . reverse $ sortBy (comparing (.last_activity_date)) topics) (fmap printColor . maybe id take maxEntries . reverse $ sortBy (comparing (.last_activity_date)) topics)
program GetTopic{topic_id} = do program GetTopic{topic_id} = do
topic <- Api.getTopic topic_id [Api.OGetTopic topic] <- Api.request [Api.IGetTopic Api.GetTopic {topic_id}]
withSgr [SetColor Foreground Vivid White] do withSgr [SetColor Foreground Vivid White] do
printColor topic printColor topic

View File

@ -1,3 +1,5 @@
{-# LANGUAGE Strict #-}
module Polysemy.Output.IO ( module Polysemy.Output.IO (
runOutputToIO runOutputToIO
, runOutputToStdout , runOutputToStdout