[haskell] Add a SpaceTradersT and handle server reset api message
This commit is contained in:
parent
7bd1c116c2
commit
e084d260ff
6 changed files with 110 additions and 31 deletions
23
haskell/src/SpaceTraders.hs
Normal file
23
haskell/src/SpaceTraders.hs
Normal file
|
@ -0,0 +1,23 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module SpaceTraders
|
||||
( SpaceTradersT
|
||||
, runSpaceTradersT
|
||||
, Config(..)
|
||||
, ask
|
||||
, liftIO
|
||||
) where
|
||||
|
||||
import Control.Monad.IO.Class
|
||||
import Control.Monad.Trans.Reader
|
||||
import qualified Database.SQLite.Simple as S
|
||||
import qualified Data.Text as T
|
||||
|
||||
type SpaceTradersT a = ReaderT Config IO a
|
||||
|
||||
runSpaceTradersT :: SpaceTradersT a -> Config -> IO a
|
||||
runSpaceTradersT = runReaderT
|
||||
|
||||
data Config = Config { conn :: S.Connection
|
||||
, token :: T.Text
|
||||
}
|
|
@ -13,14 +13,17 @@ import GHC.Generics
|
|||
import qualified Data.Text as T
|
||||
import Network.HTTP.Simple
|
||||
|
||||
import qualified SpaceTraders as ST
|
||||
import SpaceTraders.APIClient.Client
|
||||
import SpaceTraders.Model.Agent(Agent)
|
||||
import SpaceTraders.Model.Ship(Ship)
|
||||
import SpaceTraders.Model.Contract
|
||||
|
||||
myAgent :: T.Text -> IO (APIResponse Agent)
|
||||
myAgent t = send $ setRequestPath "/v2/my/agent"
|
||||
$ tokenReq t
|
||||
myAgent :: ST.SpaceTradersT (APIResponse Agent)
|
||||
myAgent = do
|
||||
c <- ST.ask
|
||||
ST.liftIO $ send $ setRequestPath "/v2/my/agent"
|
||||
$ tokenReq (ST.token c)
|
||||
|
||||
data RegisterRequest = RegisterRequest { faction :: T.Text
|
||||
, symbol :: T.Text
|
||||
|
|
|
@ -1,17 +1,22 @@
|
|||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module SpaceTraders.APIClient.Errors
|
||||
( APIError(..)
|
||||
, RateLimit(..)
|
||||
, ResetHappened(..)
|
||||
) where
|
||||
|
||||
import Control.Exception
|
||||
import Data.Aeson
|
||||
import Data.Time
|
||||
import qualified Data.Text as T
|
||||
import GHC.Generics
|
||||
|
||||
data APIError = APIError Int T.Text Value
|
||||
| APIRateLimit RateLimit
|
||||
| APIResetHappened ResetHappened
|
||||
deriving Show
|
||||
instance Exception APIError
|
||||
instance FromJSON APIError where
|
||||
|
@ -20,6 +25,7 @@ instance FromJSON APIError where
|
|||
code <- e .: "code"
|
||||
d <- e .: "data"
|
||||
case code of
|
||||
401 -> APIResetHappened <$> parseJSON d
|
||||
429 -> APIRateLimit <$> parseJSON d
|
||||
_ -> APIError <$> pure code
|
||||
<*> e .: "message"
|
||||
|
@ -40,3 +46,7 @@ instance FromJSON RateLimit where
|
|||
<*> o .: "remaining"
|
||||
<*> o .: "reset"
|
||||
<*> o .: "retryAfter"
|
||||
|
||||
data ResetHappened = ResetHappened { actual :: T.Text
|
||||
, expected :: T.Text
|
||||
} deriving (FromJSON, Generic, Show, ToJSON)
|
||||
|
|
58
haskell/src/SpaceTraders/Automation/Init.hs
Normal file
58
haskell/src/SpaceTraders/Automation/Init.hs
Normal file
|
@ -0,0 +1,58 @@
|
|||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module SpaceTraders.Automation.Init
|
||||
( deinitST
|
||||
, initST
|
||||
) where
|
||||
|
||||
import Control.Exception
|
||||
import qualified Database.SQLite.Simple as S
|
||||
import qualified Data.Text as T
|
||||
import System.Directory
|
||||
|
||||
import SpaceTraders
|
||||
import qualified SpaceTraders.APIClient.Agent as STAA
|
||||
import SpaceTraders.APIClient.Errors
|
||||
import SpaceTraders.Database
|
||||
import SpaceTraders.Database.Agents
|
||||
import SpaceTraders.Database.Contracts
|
||||
import SpaceTraders.Database.Ships
|
||||
import SpaceTraders.Database.Tokens
|
||||
|
||||
deinitST :: Config -> IO ()
|
||||
deinitST config = do
|
||||
close $ conn config
|
||||
|
||||
initST :: IO Config
|
||||
initST = do
|
||||
c <- open
|
||||
t <- getToken c `catch` handleNoToken c
|
||||
ma <- runSpaceTradersT STAA.myAgent (Config c t)
|
||||
case ma of
|
||||
Left (APIResetHappened _) -> wipe c
|
||||
Left e -> throwIO e
|
||||
_ -> return $ Config c t
|
||||
where
|
||||
handleNoToken :: S.Connection -> SomeException -> IO T.Text
|
||||
handleNoToken c _ = register c
|
||||
|
||||
register :: S.Connection -> IO (T.Text)
|
||||
register c = do
|
||||
r <- STAA.register "ADYXAX" "COSMIC"
|
||||
case r of
|
||||
Right r' -> do
|
||||
setAgent c $ STAA.agent r'
|
||||
addContract c $ STAA.contract r'
|
||||
addShip c $ STAA.ship r'
|
||||
let t = STAA.token r'
|
||||
setToken c $ t
|
||||
return t
|
||||
Left e' -> throwIO e'
|
||||
|
||||
wipe :: S.Connection -> IO Config
|
||||
wipe c = do
|
||||
close c
|
||||
removeFile "spacetraders.db"
|
||||
conn' <- open
|
||||
t <- register conn'
|
||||
return $ Config conn' t
|
Loading…
Add table
Add a link
Reference in a new issue