Skip to content

Commit

Permalink
Add Cardano.Wallet.Jormungandr.Network.Api
Browse files Browse the repository at this point in the history
- Servant type in the .Api module, with Plain and Binary content types.
- I added a FromBinary class in the binary module to play nicely with the Binary content-type
  • Loading branch information
Anviking committed May 24, 2019
1 parent 8977931 commit c78975a
Show file tree
Hide file tree
Showing 3 changed files with 173 additions and 1 deletion.
3 changes: 3 additions & 0 deletions lib/jormungandr/cardano-wallet-jormungandr.cabal
Expand Up @@ -36,13 +36,16 @@ library
, binary
, bytestring
, cardano-wallet-core
, servant
, memory
, text
, text-class
hs-source-dirs:
src
exposed-modules:
Cardano.Environment.Jormungandr
Cardano.Wallet.Binary.Jormungandr
Cardano.Wallet.Network.Jormungandr.Api
Cardano.Wallet.Compatibility.Jormungandr
Cardano.Wallet.Transaction.Jormungandr

Expand Down
39 changes: 38 additions & 1 deletion lib/jormungandr/src/Cardano/Wallet/Binary/Jormungandr.hs
Expand Up @@ -25,8 +25,13 @@ module Cardano.Wallet.Binary.Jormungandr
, LinearFee (..)
, Milli (..)

-- * Classes
, FromBinary (..)


-- * Re-export
, runGet
, Get

) where

Expand Down Expand Up @@ -67,13 +72,15 @@ import Data.Quantity
import Data.Word
( Word16, Word32, Word64, Word8 )

import qualified Cardano.Wallet.Primitive.Types as W

data BlockHeader = BlockHeader
{ version :: Word16
, contentSize :: Word32
, slot :: SlotId
, chainLength :: Word32
, contentHash :: Hash "content"
, parentHeaderHash :: Hash "parentHeader"
, parentHeaderHash :: Hash "BlockHeader"
} deriving (Show, Eq)

data Block = Block BlockHeader [Message]
Expand Down Expand Up @@ -364,3 +371,33 @@ whileM cond next = go
as <- go
return (a : as)
else return []


{-------------------------------------------------------------------------------
Classes
-------------------------------------------------------------------------------}

class FromBinary a where
get :: Get a

instance FromBinary Block where
get = getBlock

instance FromBinary W.Block where
get = convertBlock <$> getBlock
where
convertBlock :: Block -> W.Block
convertBlock (Block h msgs) =
W.Block (convertHeader h) (convertMessages msgs)

convertHeader :: BlockHeader -> W.BlockHeader
convertHeader h = W.BlockHeader (slot h) (parentHeaderHash h)

convertMessages :: [Message] -> [Tx]
convertMessages msgs = msgs >>= \case
Initial _ -> []
Transaction tx -> return tx
UnimplementedMessage _ -> []

instance FromBinary a => FromBinary [a] where
get = whileM (not <$> isEmpty) get
132 changes: 132 additions & 0 deletions lib/jormungandr/src/Cardano/Wallet/Network/Jormungandr/Api.hs
@@ -0,0 +1,132 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}

-- |
-- Copyright: © 2018-2019 IOHK
-- License: MIT
--
-- An specification for the Jörmungandr REST API.
module Cardano.Wallet.Network.Jormungandr.Api
( Api
, GetBlock
, GetTipId
, GetBlockDecendantIds
, PostSignedTx
, BlockId
, api
, SignedTx
) where

import Prelude

import Cardano.Wallet.Binary.Jormungandr
( FromBinary (..), runGet )
import Cardano.Wallet.Primitive.Types
( Block, Hash (..) )
import Data.Binary.Get
( getByteString )
import Data.ByteArray.Encoding
( Base (Base16), convertFromBase, convertToBase )
import Data.Proxy
( Proxy (..) )
import Data.Text.Encoding
( decodeUtf8 )
import Servant.API
( (:<|>)
, (:>)
, Accept (..)
, Capture
, Get
, MimeUnrender (..)
, NoContent
, Post
, QueryParam
, ReqBody
, ToHttpApiData (..)
)

import qualified Data.ByteString.Lazy as BL
import qualified Servant.API.ContentTypes as Servant


api :: Proxy Api
api = Proxy

type Api =
GetBlock :<|> GetTipId :<|> GetBlockDecendantIds :<|> PostSignedTx


-- | Retrieve a block by its id.
type GetBlock
= "api"
:> "v0"
:> "block"
:> Capture "blockHeaderHash" BlockId
:> Get '[JormungandrBinary] Block

-- | Retrieve a list of 'n' block decendant ids, sorted from closest to
-- farthest.
--
-- There might also exist fewer than 'n' decendants.
type GetBlockDecendantIds
= "api"
:> "v0"
:> "block"
:> Capture "blockId" BlockId
:> QueryParam "count" Int
:> Get '[JormungandrBinary] [BlockId]

-- | Retrieve the header of the latest known block.
type GetTipId
= "api"
:> "v0"
:> "tip"
:> Get '[Hex] BlockId

type PostSignedTx
= "api"
:> "v0"
:> "transaction"
:> ReqBody '[JormungandrBinary] SignedTx
:> Post '[NoContent] NoContent

-- TODO: Replace SignedTx with something real
data SignedTx

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

instance ToHttpApiData BlockId where
toUrlPiece (BlockId (Hash bytes)) = decodeUtf8 $ convertToBase Base16 bytes

instance FromBinary BlockId where
get = BlockId . Hash <$> getByteString 32

instance MimeUnrender Hex BlockId where
mimeUnrender _ bs =
BlockId . Hash <$> convertFromBase Base16 (BL.toStrict bs)


{-------------------------------------------------------------------------------
Content Types
-------------------------------------------------------------------------------}

-- | Represents the binary format of Jörmungandr.
data JormungandrBinary

instance Accept JormungandrBinary where
contentType _ = contentType $ Proxy @Servant.OctetStream

instance FromBinary a => MimeUnrender JormungandrBinary a where
mimeUnrender _ bs = Right $ runGet get bs


data Hex

-- | Represents data rendered to hexadecimal text.
instance Accept Hex where
contentType _ = contentType $ Proxy @Servant.PlainText

0 comments on commit c78975a

Please sign in to comment.