Skip to content

Commit

Permalink
Merge pull request #27 from geniusyield/11-wrong-strategy-value-stran…
Browse files Browse the repository at this point in the history
…ge-error

11 wrong strategy value strange error
  • Loading branch information
Micrograx authored Oct 27, 2023
2 parents a421364 + f531b27 commit 75aeeb7
Show file tree
Hide file tree
Showing 4 changed files with 34 additions and 18 deletions.
9 changes: 6 additions & 3 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -444,9 +444,12 @@ oneBuyToManySell :: Natural -> OrderBook -> [MatchResult]
oneBuyToManySell _ _ = []
```

Even more! We can go to the [Main](./geniusyield-orderbot/test/Main.hs) testing module,
and add the new constructor `OneBuyToManySell` to ["Strategies tests" list](./geniusyield-orderbot/test/Main.hs#L25C9-L25C29)
and it will be enough to start testing our strategy by running the tests.
Even more! We can add the new constructor `OneBuyToManySell` to the `allStrategies` list and it will be enough to start testing our strategy by running the tests.

```haskell
allStrategies :: [BotStrategy]
allStrategies = [OneSellToManyBuy]
```

Finishing the implementation of `oneBuyToManySell` is left as an exercise.

Expand Down
30 changes: 20 additions & 10 deletions geniusyield-orderbot/src/OrderBotConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ module OrderBotConfig where
import Control.Exception ( throwIO )
import Control.Monad ( (<=<) )
import Control.Monad.Reader ( runReaderT )
import Control.Monad.Error.Class ( throwError )
import Data.Aeson ( eitherDecodeFileStrict
, (.:), (.:?)
, withArray, withObject
Expand All @@ -26,7 +27,9 @@ import qualified Data.Vector as V
import Data.List ( nub )
import GHC.Generics ( Generic )
import GHC.Natural ( naturalToInteger )
import System.Envy ( FromEnv (fromEnv), envMaybe, env, decodeEnv )
import System.Envy ( FromEnv (fromEnv), Var, Parser, envMaybe, env
, decodeEnv
)
import System.Random.MWC (fromSeed, initialize, createSystemSeed)

import Ply (readTypedScript, TypedScript, ScriptRole (..))
Expand All @@ -44,7 +47,7 @@ import Cardano.Api ( AsType (AsSigningKey, AsPaymentKey)
, deserialiseFromTextEnvelope
)

import Strategies ( BotStrategy(..), mkIndependentStrategy )
import Strategies ( BotStrategy(..), allStrategies, mkIndependentStrategy )
import GeniusYield.DEX.Api.Types

-- | Order bot vanilla config.
Expand Down Expand Up @@ -97,30 +100,37 @@ instance FromEnv OrderBotConfig where
OrderBotConfig
<$> (Right . parseCBORSKey <$> env "BOTC_SKEY")
<*> (fmap fromString <$> envMaybe "BOTC_COLLATERAL")
<*> env "BOTC_EXECUTION_STRAT"
<*> envWithMsg ("Invalid Strategy. Must be one of: " ++ show allStrategies) "BOTC_EXECUTION_STRAT"
<*> (parseArray <$> env "BOTC_ASSET_FILTER")
<*> env "BOTC_RESCAN_DELAY"
<*> envIntWithMsg "BOTC_RESCAN_DELAY"
<*> env "BOTC_FP_NFT_POLICY"
<*> env "BOTC_FP_ORDER_VALIDATOR"
<*> env "BOTC_MAX_ORDERS_MATCHES"
<*> env "BOTC_MAX_TXS_PER_ITERATION"
<*> env "BOTC_RANDOMIZE_MATCHES_FOUND"
<*> envIntWithMsg "BOTC_MAX_ORDERS_MATCHES"
<*> envIntWithMsg "BOTC_MAX_TXS_PER_ITERATION"
<*> envWithMsg "Must be either 'True' or 'False'" "BOTC_RANDOMIZE_MATCHES_FOUND"
<*> (parsePORDict <$> env "BOTC_POREFS")
where
parseCBORSKey :: String -> GYPaymentSigningKey
parseCBORSKey s =
either error paymentSigningKeyFromApi $
either (error . ("Error parsing 'BOTC_SKEY': " ++)) paymentSigningKeyFromApi $
eitherDecodeStrict (fromString s) >>=
first show . deserialiseFromTextEnvelope (AsSigningKey AsPaymentKey)

parsePORDict :: String -> PORConfig
parsePORDict = either error id . eitherDecodeStrict . fromString
parsePORDict = either (error . ("Error parsing 'BOTC_POREFS': " ++)) id
. eitherDecodeStrict . fromString

parseArray :: String -> [OrderAssetPair]
parseArray s = either error id $
parseArray s = either (error . ("Error parsing 'BOTC_ASSET_FILTER': " ++) ) id $
eitherDecodeStrict (fromString s) >>=
Aeson.parseEither parseScanTokenPairs

envIntWithMsg :: Var a => String -> Parser a
envIntWithMsg = envWithMsg "Not a number"

envWithMsg :: Var a => String -> String -> Parser a
envWithMsg msg name = maybe (throwError $ unwords ["Error parsing enviroment variable", name ++ ":", msg]) return =<< envMaybe name

instance FromJSON OrderBotConfig where
parseJSON (Object obj) = OrderBotConfig
<$> (Left <$> obj .: "signingKeyFP")
Expand Down
7 changes: 7 additions & 0 deletions geniusyield-orderbot/src/Strategies.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ Stability : develop
-}
module Strategies
( BotStrategy(..)
, allStrategies
, mkIndependentStrategy
) where

Expand Down Expand Up @@ -50,6 +51,12 @@ instance Var BotStrategy where
_ -> Nothing
toVar = show

{- | A list containing all implemented strategies. This list is used for the
tests and for the error message during env variable parsing.
-}
allStrategies :: [BotStrategy]
allStrategies = [OneSellToManyBuy]

{- | Given a bot strategy and a max amount of orders per transaction, creates
an independent strategy.
-}
Expand Down
6 changes: 1 addition & 5 deletions geniusyield-orderbot/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,11 +18,7 @@ main = defaultMain $ testGroup "QC"
, testProperty "sellsAreInOrder" propSellsAreInOrder
, testProperty "buysAreInOrder" propBuysAreInOrder
]
, testGroup "Strategies tests" $ map qcTestsForStrategy
-- Every strategy property is ran over each element of this list. So adding
-- a new BotStrategy constructor to the list is enough to include the new
-- strategy into the complete tests suit.
[ OneSellToManyBuy ]
, testGroup "Strategies tests" $ map qcTestsForStrategy allStrategies
]

qcTestsForStrategy :: BotStrategy -> TestTree
Expand Down

0 comments on commit 75aeeb7

Please sign in to comment.