Skip to content

Commit

Permalink
Add Jormungandr client
Browse files Browse the repository at this point in the history
  • Loading branch information
Anviking committed May 28, 2019
1 parent 1282540 commit b3eeb5a
Show file tree
Hide file tree
Showing 5 changed files with 302 additions and 9 deletions.
17 changes: 16 additions & 1 deletion lib/jormungandr/cardano-wallet-jormungandr.cabal
Expand Up @@ -38,13 +38,23 @@ library
, cardano-wallet-core
, servant
, memory
, exceptions
-- , http-media
, http-client
, http-types
, transformers
-- , cryptonite
-- , cardano-crypto
, servant-client
, servant-client-core
, text
, text-class
hs-source-dirs:
src
exposed-modules:
Cardano.Wallet.Jormungandr.Api
Cardano.Wallet.Jormungandr.Binary
Cardano.Wallet.Jormungandr.Network
Cardano.Wallet.Jormungandr.Compatibility
Cardano.Wallet.Jormungandr.Environment
Cardano.Wallet.Jormungandr.Transaction
Expand Down Expand Up @@ -99,8 +109,13 @@ test-suite integration
build-depends:
async
, base
, bytestring
, cardano-wallet-jormungandr
, cardano-wallet-core
, cardano-wallet-launcher
, text-class
, text
, transformers
, hspec
type:
exitcode-stdio-1.0
Expand All @@ -110,4 +125,4 @@ test-suite integration
Main.hs
other-modules:
Cardano.LauncherSpec

Cardano.Wallet.Jormungandr.NetworkSpec
15 changes: 7 additions & 8 deletions lib/jormungandr/src/Cardano/Wallet/Jormungandr/Api.hs
Expand Up @@ -16,17 +16,16 @@ module Cardano.Wallet.Jormungandr.Api
, GetTipId
, GetBlockDecendantIds
, PostSignedTx
, BlockId
, BlockId (..)
, api
, SignedTx
) where

import Prelude

import Cardano.Wallet.Jormungandr.Binary
( FromBinary (..), runGet )
import Cardano.Wallet.Primitive.Types
( Block, Hash (..) )
( Block, Hash (..), Tx, TxWitness )
import Data.Binary.Get
( getByteString )
import Data.ByteArray.Encoding
Expand All @@ -41,6 +40,7 @@ import Servant.API
, Accept (..)
, Capture
, Get
, MimeRender (..)
, MimeUnrender (..)
, NoContent
, Post
Expand Down Expand Up @@ -97,14 +97,11 @@ type PostSignedTx
= "api"
:> "v0"
:> "transaction"
:> ReqBody '[JormungandrBinary] SignedTx
:> ReqBody '[JormungandrBinary] (Tx, [TxWitness])
:> Post '[NoContent] NoContent

-- TODO: Replace SignedTx with something real
data SignedTx

newtype BlockId = BlockId (Hash "block")
deriving Show
deriving (Show, Eq)

instance ToHttpApiData BlockId where
toUrlPiece (BlockId (Hash bytes)) = decodeUtf8 $ convertToBase Base16 bytes
Expand All @@ -130,6 +127,8 @@ instance Accept JormungandrBinary where
instance FromBinary a => MimeUnrender JormungandrBinary a where
mimeUnrender _ bs = Right $ runGet get bs

instance MimeRender JormungandrBinary (Tx, [TxWitness]) where
mimeRender _ _bs = undefined

data Hex

Expand Down
164 changes: 164 additions & 0 deletions lib/jormungandr/src/Cardano/Wallet/Jormungandr/Network.hs
@@ -0,0 +1,164 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
--
--
--
-- This module allows the wallet to retrieve blocks from a local @Jormungandr@
-- node. This is done by providing a @NetworkLayer@ with some logic building on
-- top of underlying @Jormungandr@ HTTP client.

module Cardano.Wallet.Jormungandr.Network
( Jormungandr (..)
, mkNetworkLayer
, newNetworkLayer
, mkJormungandr

-- * Re-export
, BaseUrl (..)
, newManager
, defaultManagerSettings
, Scheme (..)
) where

import Prelude

import Cardano.Wallet.Jormungandr.Api
( BlockId, GetBlock, GetTipId, api )
import Cardano.Wallet.Network
( ErrNetworkTip (..)
, ErrNetworkUnreachable (..)
, ErrPostTx (..)
, NetworkLayer (..)
)
import Cardano.Wallet.Primitive.Types
( Block, Tx (..), TxWitness (..) )
import Control.Arrow
( left )
import Control.Exception
( Exception )
import Control.Monad.Catch
( throwM )
import Control.Monad.Trans.Except
( ExceptT (..) )
import Data.Proxy
( Proxy (..) )
import Network.HTTP.Client
( Manager, defaultManagerSettings, newManager )
import Network.HTTP.Types.Status
( status404 )
import Servant.API
( (:<|>) (..) )
import Servant.Client
( BaseUrl (..), ClientM, Scheme (..), client, mkClientEnv, runClientM )
import Servant.Client.Core
( ServantError (..), responseStatusCode )
import Servant.Links
( Link, safeLink )

-- | Constructs a network layer with the given @Jormungandr@ client.
mkNetworkLayer :: Monad m => Jormungandr m -> NetworkLayer m
mkNetworkLayer _httpBridge = NetworkLayer
{ nextBlocks = undefined
, networkTip = undefined
, postTx = undefined
}

-- | Creates a jormungandr 'NetworkLayer' using the given connection
-- settings.
newNetworkLayer
:: Int -> IO (NetworkLayer IO)
newNetworkLayer port = mkNetworkLayer <$> newHttpBridge port
where
newHttpBridge = undefined

{-------------------------------------------------------------------------------
Jormungandr Client
-------------------------------------------------------------------------------}

-- | Endpoints of the jormungandr REST API.
data Jormungandr m = HttpBridge
{ getBlock
:: BlockId -> ExceptT ErrNetworkUnreachable m Block
, getTipId
:: ExceptT ErrNetworkTip m BlockId
, getDecendantIds
:: BlockId -> Int -> ExceptT ErrGetDecendants m [BlockId]
, postSignedTx
:: (Tx, [TxWitness])-> ExceptT ErrPostTx m ()
}

-- | Error while trying to get decendants
data ErrGetDecendants
= ErrGetDecendantsNetworkUnreachable ErrNetworkUnreachable
| ErrGetDecendantsParentNotFound
deriving (Show, Eq)

instance Exception ErrGetDecendants

-- | Construct a Jormungandr-client
--
-- >>> mgr <- newManager defaultManagerSettings
-- >>> j = mkJormungandr mgr (BaseUrl Http "localhost" 8080 "")
-- >>> runExceptT $ getTipId j
-- Right (BlockId (Hash {getHash = "26c640a3de09b74398c14ca0a137ec78"}))
mkJormungandr
:: Manager -> BaseUrl -> Jormungandr IO
mkJormungandr mgr baseUrl = HttpBridge
{ getBlock = \hash -> ExceptT $ do
let ctx = safeLink api (Proxy @GetBlock) hash
run (cGetBlock hash) >>= defaultHandler ctx

, getTipId = ExceptT $ do
run cGetTipId >>= \case
Left (FailureResponse e) | responseStatusCode e == status404 ->
return $ Left ErrNetworkTipNotFound
x -> do
let ctx = safeLink api (Proxy @GetTipId)
left ErrNetworkTipNetworkUnreachable <$> defaultHandler ctx x

, getDecendantIds = undefined
, postSignedTx = undefined
}
where
run :: ClientM a -> IO (Either ServantError a)
run query = runClientM query (mkClientEnv mgr baseUrl)

defaultHandler
:: Link
-> Either ServantError a
-> IO (Either ErrNetworkUnreachable a)
defaultHandler ctx = \case
Right c -> return $ Right c

-- The node has not started yet or has exited.
-- This could be recovered from by either waiting for the node
-- initialise, or restarting the node.
Left (ConnectionError e) ->
return $ Left $ ErrNetworkUnreachable e

-- Other errors (status code, decode failure, invalid content type
-- headers). These are considered to be programming errors, so crash.
Left e -> do
throwM (ErrUnexpectedNetworkFailure ctx e)

cGetBlock
:<|> cGetTipId
:<|> _cGetBlockDecendantIds
:<|> _cPostSignedTx
= client api

data ErrUnexpectedNetworkFailure
= ErrUnexpectedNetworkFailure Link ServantError
deriving (Show)

instance Exception ErrUnexpectedNetworkFailure
@@ -0,0 +1,113 @@
{-# LANGUAGE LambdaCase #-}
module Cardano.Wallet.Jormungandr.NetworkSpec
( spec
) where

import Prelude

import Cardano.Launcher
( Command (..), StdStream (..), launch )
import Cardano.Wallet.Jormungandr.Api
( BlockId (..) )
import Cardano.Wallet.Jormungandr.Network
( BaseUrl (..)
, Scheme (Http)
, defaultManagerSettings
, getBlock
, getTipId
, mkJormungandr
, newManager
, postSignedTx
)
import Cardano.Wallet.Network
( ErrNetworkTip (..), ErrNetworkUnreachable (..), ErrPostTx (..) )
import Cardano.Wallet.Primitive.Types
( Block (..), Hash (..), Tx (..) )
import Control.Concurrent
( threadDelay )
import Control.Concurrent.Async
( async, cancel )
import Control.Monad.Trans.Except
( runExceptT )
import Test.Hspec
( Spec
, afterAll
, beforeAll
, describe
, it
, shouldBe
, shouldReturn
, shouldSatisfy
, xit
)

import qualified Data.ByteString as BS

spec :: Spec
spec = do
describe "Happy paths"
$ beforeAll startNode $ afterAll closeNode $ do
it "get tip (should be genesis)" $ \(_, client) -> do
(BlockId (Hash tipHash)) <- run $ getTipId client
tipHash `shouldBe` genesisHash
(BS.length tipHash) `shouldBe` 32

it "get block (genesis)" $ \(_, client) -> do
b <- run $ getBlock client (BlockId $ Hash genesisHash)
length (transactions b) `shouldBe` 1

describe "Error paths" $ beforeAll newClient $ do
it "gets a 'ErrNetworkUnreachable' if jormungandr isn't up (1)"
$ \bridge -> do
let msg x = "Expected a ErrNetworkUnreachable' failure but got "
<> show x
let action = do
res <- runExceptT $ getTipId bridge
res `shouldSatisfy` \case
Left (ErrNetworkTipNetworkUnreachable _) -> True
_ -> error (msg res)
action `shouldReturn` ()

xit "gets a 'ErrNetworkUnreachable' if jormungandr isn't up (2)"
$ \bridge -> do
let msg x = "Expected a ErrNetworkUnreachable' failure but got "
<> show x
let action = do
res <- runExceptT $ postSignedTx bridge (txEmpty, [])
res `shouldSatisfy` \case
Left (ErrPostTxNetworkUnreachable (ErrNetworkUnreachable _)) ->
True
_ ->
error (msg res)
action `shouldReturn` ()

where
txEmpty = Tx [] []

genesisHash = "&\198@\163\222\t\183C\152\193L\160\161\&7\236x\245\229\EOT\175\177\167\131\190\b\b/\174\212\177:\179"

run x = (either (error . show) id) <$> runExceptT x

closeNode (handle, _) = do
cancel handle
threadDelay 1000000


newClient = do
manager <- newManager defaultManagerSettings
return $ mkJormungandr manager (BaseUrl Http "localhost" 8081 "")


startNode = do
handle <- async $ launch $ return $ Command
"jormungandr"
[ "--genesis-block", dir ++ "/block-0.bin"
, "--config", dir ++ "/node.config"
, "--secret", dir ++ "/secret.yaml"
] (return ())
Inherit
client <- newClient
threadDelay 1000000
return (handle, client)

dir = "test/data/jormungandr"
2 changes: 2 additions & 0 deletions lib/jormungandr/test/integration/Main.hs
Expand Up @@ -9,6 +9,7 @@ import Test.Hspec
( describe, hspec )

import qualified Cardano.LauncherSpec as Launcher
import qualified Cardano.Wallet.Jormungandr.NetworkSpec as Network

main :: IO ()
main = do
Expand All @@ -20,3 +21,4 @@ main = do

hspec $ do
describe "Cardano.LauncherSpec" Launcher.spec
describe "Cardano.Wallet.Network.JormunganrSpec" Network.spec

0 comments on commit b3eeb5a

Please sign in to comment.