plutus-pioneer-program/code/week06/app/swap-client.hs

124 lines
4.3 KiB
Haskell
Raw Normal View History

2021-05-10 22:41:10 +02:00
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
2021-05-10 21:47:35 +02:00
module Main
( main
) where
2021-05-10 22:41:10 +02:00
import Control.Concurrent
2021-05-10 23:10:43 +02:00
import Control.Exception
2021-05-10 22:41:10 +02:00
import Control.Monad.IO.Class (MonadIO (..))
import Data.Aeson (Result (..), fromJSON)
import Data.Monoid (Last (..))
import Data.Proxy (Proxy (..))
import Data.Text (pack)
import Data.UUID
import Ledger.Value (flattenValue)
import Network.HTTP.Req
import Plutus.PAB.Events.ContractInstanceState (PartiallyDecodedResponse (..))
import Plutus.PAB.Webserver.Types
import System.Environment (getArgs)
2021-05-10 23:10:43 +02:00
import System.IO
import Text.Read (readMaybe)
2021-05-10 22:41:10 +02:00
import Week06.Oracle.PAB (OracleContracts)
2021-05-10 21:47:35 +02:00
main :: IO ()
2021-05-10 22:41:10 +02:00
main = do
2021-05-10 23:10:43 +02:00
[i :: Int] <- map read <$> getArgs
uuid <- read <$> readFile ('W' : show i ++ ".cid")
hSetBuffering stdout NoBuffering
2021-05-10 22:41:10 +02:00
putStrLn $ "swap contract instance id for Wallet " ++ show i ++ ": " ++ show uuid
2021-05-10 23:10:43 +02:00
go uuid
where
go :: UUID -> IO a
go uuid = do
cmd <- readCommand
case cmd of
Offer amt -> offer uuid amt
Retrieve -> retrieve uuid
Use -> use uuid
Funds -> getFunds uuid
go uuid
readCommand :: IO Command
readCommand = do
2021-05-12 18:18:29 +02:00
putStr "enter command (Offer amt, Retrieve, Use or Funds): "
2021-05-10 23:10:43 +02:00
s <- getLine
maybe readCommand return $ readMaybe s
data Command = Offer Integer | Retrieve | Use | Funds
deriving (Show, Read, Eq, Ord)
2021-05-10 22:41:10 +02:00
getFunds :: UUID -> IO ()
2021-05-10 23:10:43 +02:00
getFunds uuid = handle h $ runReq defaultHttpConfig $ do
2021-05-10 22:41:10 +02:00
v <- req
POST
(http "127.0.0.1" /: "api" /: "new" /: "contract" /: "instance" /: pack (show uuid) /: "endpoint" /: "funds")
(ReqBodyJson ())
(Proxy :: Proxy (JsonResponse ()))
(port 8080)
if responseStatusCode v /= 200
then liftIO $ putStrLn "error getting funds"
else do
w <- req
GET
(http "127.0.0.1" /: "api" /: "new" /: "contract" /: "instance" /: pack (show uuid) /: "status")
NoReqBody
(Proxy :: Proxy (JsonResponse (ContractInstanceClientState OracleContracts)))
(port 8080)
liftIO $ putStrLn $ case fromJSON $ observableState $ cicCurrentState $ responseBody w of
2021-05-10 23:10:43 +02:00
Success (Last (Just f)) -> "funds: " ++ show (flattenValue f)
2021-05-10 22:41:10 +02:00
_ -> "error decoding state"
2021-05-10 23:10:43 +02:00
where
h :: HttpException -> IO ()
h _ = threadDelay 1_000_000 >> getFunds uuid
2021-05-10 22:41:10 +02:00
2021-05-10 23:10:43 +02:00
offer :: UUID -> Integer -> IO ()
offer uuid amt = handle h $ runReq defaultHttpConfig $ do
v <- req
POST
(http "127.0.0.1" /: "api" /: "new" /: "contract" /: "instance" /: pack (show uuid) /: "endpoint" /: "offer")
(ReqBodyJson amt)
(Proxy :: Proxy (JsonResponse ()))
(port 8080)
2021-05-10 22:41:10 +02:00
liftIO $ putStrLn $ if responseStatusCode v == 200
2021-05-10 23:10:43 +02:00
then "offered swap of " ++ show amt ++ " lovelace"
else "error offering swap"
where
h :: HttpException -> IO ()
h _ = threadDelay 1_000_000 >> offer uuid amt
2021-05-10 22:41:10 +02:00
2021-05-10 23:10:43 +02:00
retrieve :: UUID -> IO ()
retrieve uuid = handle h $ runReq defaultHttpConfig $ do
2021-05-10 22:41:10 +02:00
v <- req
POST
2021-05-10 23:10:43 +02:00
(http "127.0.0.1" /: "api" /: "new" /: "contract" /: "instance" /: pack (show uuid) /: "endpoint" /: "retrieve")
(ReqBodyJson ())
2021-05-10 22:41:10 +02:00
(Proxy :: Proxy (JsonResponse ()))
(port 8080)
liftIO $ putStrLn $ if responseStatusCode v == 200
2021-05-10 23:10:43 +02:00
then "retrieved swaps"
else "error retrieving swaps"
where
h :: HttpException -> IO ()
h _ = threadDelay 1_000_000 >> retrieve uuid
2021-05-10 22:41:10 +02:00
2021-05-10 23:10:43 +02:00
use :: UUID -> IO ()
use uuid = handle h $ runReq defaultHttpConfig $ do
2021-05-10 22:41:10 +02:00
v <- req
2021-05-10 23:10:43 +02:00
POST
(http "127.0.0.1" /: "api" /: "new" /: "contract" /: "instance" /: pack (show uuid) /: "endpoint" /: "use")
(ReqBodyJson ())
(Proxy :: Proxy (JsonResponse ()))
(port 8080)
liftIO $ putStrLn $ if responseStatusCode v == 200
then "used swap"
else "error using swap"
where
h :: HttpException -> IO ()
h _ = threadDelay 1_000_000 >> use uuid