Skip to content

Commit 80fff93

Browse files
committed
Introduce NetworkVersions module and parse networks.json
Signed-off-by: Sasha Bogicevic <[email protected]>
1 parent da4ee11 commit 80fff93

File tree

2 files changed

+58
-0
lines changed

2 files changed

+58
-0
lines changed

hydra-node/hydra-node.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -86,6 +86,7 @@ library
8686
Hydra.Network.Authenticate
8787
Hydra.Network.Etcd
8888
Hydra.Network.Message
89+
Hydra.NetworkVersions
8990
Hydra.Node
9091
Hydra.Node.DepositPeriod
9192
Hydra.Node.EmbedTH
Lines changed: 57 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,57 @@
1+
{-# LANGUAGE DerivingStrategies #-}
2+
{-# LANGUAGE TemplateHaskell #-}
3+
4+
module Hydra.NetworkVersions where
5+
6+
import Hydra.Prelude hiding (encodeUtf8)
7+
8+
import Control.Lens ((^@..))
9+
import Data.Aeson (Value (..))
10+
import Data.Aeson.Key qualified as Key
11+
import Data.Aeson.KeyMap qualified as KeyMap
12+
import Data.Aeson.Lens (members, _Object)
13+
import Data.FileEmbed (embedFile)
14+
import Data.List qualified as List
15+
import Data.Text (splitOn)
16+
import Data.Text.Encoding (encodeUtf8)
17+
import Hydra.Cardano.Api (NetworkId (..), NetworkMagic (..), TxId, deserialiseFromRawBytesHex)
18+
19+
networkVersionsFile :: ByteString
20+
networkVersionsFile = $(embedFile "./../networks.json")
21+
22+
data ParseError
23+
= ExpectedStringForTxId
24+
| FailedToParseTextToTxId Text
25+
| UnknownNetwork Text
26+
deriving stock (Eq, Show)
27+
28+
instance Exception ParseError
29+
30+
parseNetworkVersions :: ByteString -> IO [(NetworkId, [TxId])]
31+
parseNetworkVersions bs = do
32+
let info = bs ^@.. members . _Object
33+
fmap catMaybes <$> forM info $ \(n, t) -> do
34+
let textKey = Key.toText n
35+
case textKey of
36+
"mainnet" -> do
37+
txids <- getLastTxId t
38+
pure $ Just (Mainnet, txids)
39+
"preview" -> do
40+
txids <- getLastTxId t
41+
pure $ Just (Testnet $ NetworkMagic 2, txids)
42+
"preprod" -> do
43+
txids <- getLastTxId t
44+
pure $ Just (Testnet $ NetworkMagic 1, txids)
45+
_ -> pure Nothing
46+
where
47+
getLastTxId t = do
48+
lastTxIds <-
49+
case List.last $ KeyMap.elems t of
50+
String s -> pure s
51+
_ -> throwIO ExpectedStringForTxId
52+
mapM parseToTxId (splitOn "," lastTxIds)
53+
54+
parseToTxId textTxId = do
55+
case deserialiseFromRawBytesHex $ encodeUtf8 textTxId of
56+
Left _ -> throwIO $ FailedToParseTextToTxId textTxId
57+
Right txid -> pure txid

0 commit comments

Comments
 (0)