Skip to content

Commit

Permalink
api: Cardano Scripts
Browse files Browse the repository at this point in the history
  • Loading branch information
sorki committed Oct 12, 2021
1 parent 608fd3a commit 06c45de
Show file tree
Hide file tree
Showing 10 changed files with 261 additions and 0 deletions.
3 changes: 3 additions & 0 deletions blockfrost-api/CHANGELOG.md
Expand Up @@ -16,6 +16,9 @@
* `reserves` field (current reserves supply)
* `/txs/${hash}/redeemers` endpoint with `TransactionRedeemer` and `ValidationPurpose` types
* Epoch cost model parameters to `ProtocolParams`
* `/scripts` endpoint and `ScriptHash` newtype
* `/scripts/${script_hash}` endpoint with `Script` data type
* `/scripts/${script_hash}/redeemers` endpoint with `ScriptRedeemer` data type

# Version [0.1.0.0](https://github.com/blockfrost/blockfrost-haskell/compare/initial...0.1.0.0) (2021-09-14)

Expand Down
5 changes: 5 additions & 0 deletions blockfrost-api/blockfrost-api.cabal
Expand Up @@ -70,6 +70,7 @@ library
, Blockfrost.API.Cardano.Metadata
, Blockfrost.API.Cardano.Network
, Blockfrost.API.Cardano.Pools
, Blockfrost.API.Cardano.Scripts
, Blockfrost.API.Cardano.Transactions
, Blockfrost.API.IPFS
, Blockfrost.API.NutLink
Expand All @@ -89,6 +90,7 @@ library
, Blockfrost.Types.Cardano.Metadata
, Blockfrost.Types.Cardano.Network
, Blockfrost.Types.Cardano.Pools
, Blockfrost.Types.Cardano.Scripts
, Blockfrost.Types.Cardano.Transactions
, Blockfrost.Types.IPFS
, Blockfrost.Types.NutLink
Expand All @@ -101,6 +103,7 @@ library
, Blockfrost.Types.Shared.CBOR
, Blockfrost.Types.Shared.Opts
, Blockfrost.Types.Shared.POSIXMillis
, Blockfrost.Types.Shared.ScriptHash
, Blockfrost.Types.Shared.Slot
, Blockfrost.Types.Shared.TxHash
, Blockfrost.Types.Shared.Amount
Expand All @@ -127,6 +130,7 @@ library
, safe-money
, quickcheck-instances
, QuickCheck
, vector

test-suite blockfrost-api-tests
type: exitcode-stdio-1.0
Expand All @@ -142,6 +146,7 @@ test-suite blockfrost-api-tests
, Cardano.Metadata
, Cardano.Network
, Cardano.Pools
, Cardano.Scripts
, Cardano.Transactions
, IPFS
, NutLink
Expand Down
5 changes: 5 additions & 0 deletions blockfrost-api/src/Blockfrost/API.hs
Expand Up @@ -111,6 +111,11 @@ data CardanoAPI route =
:- "pools"
:> Tag "Cardano » Pools"
:> ToServantApi PoolsAPI
, _scripts
:: route
:- "scripts"
:> Tag "Cardano » Scripts"
:> ToServantApi ScriptsAPI
, _transactions
:: route
:- "txs"
Expand Down
2 changes: 2 additions & 0 deletions blockfrost-api/src/Blockfrost/API/Cardano.hs
Expand Up @@ -12,6 +12,7 @@ module Blockfrost.API.Cardano
, module Blockfrost.API.Cardano.Metadata
, module Blockfrost.API.Cardano.Network
, module Blockfrost.API.Cardano.Pools
, module Blockfrost.API.Cardano.Scripts
, module Blockfrost.API.Cardano.Transactions
) where

Expand All @@ -24,4 +25,5 @@ import Blockfrost.API.Cardano.Ledger
import Blockfrost.API.Cardano.Metadata
import Blockfrost.API.Cardano.Network
import Blockfrost.API.Cardano.Pools
import Blockfrost.API.Cardano.Scripts
import Blockfrost.API.Cardano.Transactions
41 changes: 41 additions & 0 deletions blockfrost-api/src/Blockfrost/API/Cardano/Scripts.hs
@@ -0,0 +1,41 @@
-- | Cardano Scripts endpoints

{-# OPTIONS_HADDOCK hide #-}

module Blockfrost.API.Cardano.Scripts
where

import Servant.API
import Servant.API.Generic

import Blockfrost.Types.Cardano.Scripts
import Blockfrost.Types.Shared
import Blockfrost.Util.Pagination
import Blockfrost.Util.Sorting

data ScriptsAPI route =
ScriptsAPI
{
_listScripts
:: route
:- Summary "Scripts"
:> Description "List of scripts."
:> Pagination
:> Sorting
:> Get '[JSON] [ScriptHash]
, _getScript
:: route
:- Summary "Specific scripts"
:> Description "Information about a specific script."
:> Capture "script_hash" ScriptHash
:> Get '[JSON] Script
, _getScriptRedeemers
:: route
:- Summary "Redeemers of a specific script"
:> Description "List of redeemers of a specific script."
:> Capture "script_hash" ScriptHash
:> Pagination
:> Sorting
:> "redeemers"
:> Get '[JSON] [ScriptRedeemer]
} deriving (Generic)
2 changes: 2 additions & 0 deletions blockfrost-api/src/Blockfrost/Types/Cardano.hs
Expand Up @@ -10,6 +10,7 @@ module Blockfrost.Types.Cardano
, module Blockfrost.Types.Cardano.Metadata
, module Blockfrost.Types.Cardano.Network
, module Blockfrost.Types.Cardano.Pools
, module Blockfrost.Types.Cardano.Scripts
, module Blockfrost.Types.Cardano.Transactions
) where

Expand All @@ -22,4 +23,5 @@ import Blockfrost.Types.Cardano.Genesis
import Blockfrost.Types.Cardano.Metadata
import Blockfrost.Types.Cardano.Network
import Blockfrost.Types.Cardano.Pools
import Blockfrost.Types.Cardano.Scripts
import Blockfrost.Types.Cardano.Transactions
64 changes: 64 additions & 0 deletions blockfrost-api/src/Blockfrost/Types/Cardano/Scripts.hs
@@ -0,0 +1,64 @@
-- | Cardano Scripts responses

module Blockfrost.Types.Cardano.Scripts
( Script (..)
, ScriptType (..)
, ScriptRedeemer (..)
) where

import Deriving.Aeson
import Servant.Docs (ToSample (..), samples, singleSample)

import Blockfrost.Types.Shared
import Blockfrost.Types.Cardano.Transactions (ValidationPurpose(Spend))

-- | Script type
data ScriptType = Plutus | Timelock
deriving stock (Show, Eq, Generic)
deriving (FromJSON, ToJSON)
via CustomJSON '[ConstructorTagModifier '[ToLower]] ScriptType

instance ToSample ScriptType where
toSamples = pure $ samples [ Plutus, Timelock ]

-- | Script info
data Script = Script
{ _scriptScriptHash :: ScriptHash -- ^ Hash of the script
, _scriptType :: ScriptType -- ^ Type of the script language
, _scriptSerialisedSize :: Maybe Integer -- ^ The size of the CBOR serialised script, if a Plutus script
}
deriving stock (Show, Eq, Generic)
deriving (FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_script", CamelToSnake]] Script

instance ToSample Script where
toSamples = pure $ singleSample
Script
{ _scriptScriptHash = "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
, _scriptType = Plutus
, _scriptSerialisedSize = Just 3119
}

-- | Script redeemer
data ScriptRedeemer = ScriptRedeemer
{ _scriptRedeemerTxHash :: TxHash -- ^ Hash of the transaction
, _scriptRedeemerTxIndex :: Integer -- ^ Index of the redeemer within a transaction
, _scriptRedeemerPurpose :: ValidationPurpose -- ^ Validation purpose
, _scriptRedeemerUnitMem :: Quantity -- ^ The budget in Memory to run a script
, _scriptRedeemerUnitSteps :: Quantity -- ^ The budget in Steps to run a script
, _scriptRedeemerFee :: Lovelaces -- ^ The fee consumed to run the script
}
deriving stock (Show, Eq, Generic)
deriving (FromJSON, ToJSON)
via CustomJSON '[FieldLabelModifier '[StripPrefix "_scriptRedeemer", CamelToSnake]] ScriptRedeemer

instance ToSample ScriptRedeemer where
toSamples = pure $ singleSample
ScriptRedeemer
{ _scriptRedeemerTxHash = "1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0"
, _scriptRedeemerTxIndex = 0
, _scriptRedeemerPurpose = Spend
, _scriptRedeemerUnitMem = 1700
, _scriptRedeemerUnitSteps = 476468
, _scriptRedeemerFee = 172033
}
2 changes: 2 additions & 0 deletions blockfrost-api/src/Blockfrost/Types/Shared.hs
Expand Up @@ -15,6 +15,7 @@ module Blockfrost.Types.Shared
, module Blockfrost.Types.Shared.PoolId
, module Blockfrost.Types.Shared.Quantity
, module Blockfrost.Types.Shared.Slot
, module Blockfrost.Types.Shared.ScriptHash
, module Blockfrost.Types.Shared.TxHash
) where

Expand All @@ -32,4 +33,5 @@ import Blockfrost.Types.Shared.PolicyId
import Blockfrost.Types.Shared.PoolId
import Blockfrost.Types.Shared.Quantity
import Blockfrost.Types.Shared.Slot
import Blockfrost.Types.Shared.ScriptHash
import Blockfrost.Types.Shared.TxHash
47 changes: 47 additions & 0 deletions blockfrost-api/src/Blockfrost/Types/Shared/ScriptHash.hs
@@ -0,0 +1,47 @@
-- | Script Hash newtype

module Blockfrost.Types.Shared.ScriptHash
( ScriptHash (..)
) where

import Data.Aeson (FromJSON (..), ToJSON (..), Value(..), (.=), (.:))
import Data.String (IsString (..))
import Data.Text (Text)
import qualified Data.Text
import qualified Data.Vector
import GHC.Generics
import Servant.API (Capture, FromHttpApiData (..), ToHttpApiData (..))
import Servant.Docs (DocCapture (..), ToCapture (..), ToSample (..), samples)

-- | Id (hash) of the transaction
newtype ScriptHash = ScriptHash { unScriptHash :: Text }
deriving stock (Show, Eq, Generic)
deriving newtype (FromHttpApiData, ToHttpApiData)

instance IsString ScriptHash where
fromString = ScriptHash . Data.Text.pack

instance ToJSON ScriptHash where
toJSON = toJSON . unScriptHash
toEncoding = toEncoding . unScriptHash
instance FromJSON ScriptHash where
parseJSON = fmap ScriptHash <$> parseJSON

-- Custom instance for list used by script list endpoint
instance {-# OVERLAPS #-} ToJSON [ScriptHash] where
toJSON = Array . Data.Vector.fromList . map (\sh -> Object ("script_hash" .= (toJSON . unScriptHash $ sh)))
instance {-# OVERLAPS #-} FromJSON [ScriptHash] where
parseJSON (Array a) = mapM parseJSON' (Data.Vector.toList a)
where
parseJSON' (Object b) = b .: "script_hash"
parseJSON' _ = fail "Unexpected type for ScriptHash"
parseJSON _ = fail "Expected array for [ScriptHash]"

instance ToSample ScriptHash where
toSamples _ = samples $ map ScriptHash
[ "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
, "e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e"
]

instance ToCapture (Capture "script_hash" ScriptHash) where
toCapture _ = DocCapture "script_hash" "Hash of the script."
90 changes: 90 additions & 0 deletions blockfrost-api/test/Cardano/Scripts.hs
@@ -0,0 +1,90 @@
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}

module Cardano.Scripts
where

import Data.Aeson (decode, eitherDecode, encode)
import Data.Text (Text)
import qualified Money
import Test.Hspec
import Test.Tasty.Hspec
import Text.RawString.QQ

import Blockfrost.Types

spec_scripts :: Spec
spec_scripts = do
it "parses script list sample" $ do
eitherDecode scriptListSample
`shouldBe`
Right scriptListExpected

it "parses script info sample" $ do
eitherDecode scriptSample
`shouldBe`
Right scriptSampleExpected

it "parses script redeemer sample" $ do
eitherDecode scriptRedeemerSample
`shouldBe`
Right scriptRedeemerExpected

scriptListSample = [r|
[
{
"script_hash": "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
},
{
"script_hash": "e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e"
},
{
"script_hash": "a6e63c0ff05c96943d1cc30bf53112ffff0f34b45986021ca058ec54"
}
]
|]

scriptListExpected :: [ScriptHash]
scriptListExpected =
[ "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
, "e1457a0c47dfb7a2f6b8fbb059bdceab163c05d34f195b87b9f2b30e"
, "a6e63c0ff05c96943d1cc30bf53112ffff0f34b45986021ca058ec54"
]

scriptSample = [r|
{
"script_hash": "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656",
"type": "plutus",
"serialised_size": 3119
}
|]

scriptSampleExpected =
Script
{ _scriptScriptHash = "67f33146617a5e61936081db3b2117cbf59bd2123748f58ac9678656"
, _scriptType = Plutus
, _scriptSerialisedSize = Just 3119
}

scriptRedeemerSample = [r|
{
"tx_hash": "1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0",
"tx_index": 0,
"purpose": "spend",
"unit_mem": "1700",
"unit_steps": "476468",
"fee": "172033"
}
|]

scriptRedeemerExpected =
ScriptRedeemer
{ _scriptRedeemerTxHash = "1a0570af966fb355a7160e4f82d5a80b8681b7955f5d44bec0dce628516157f0"
, _scriptRedeemerTxIndex = 0
, _scriptRedeemerPurpose = Spend
, _scriptRedeemerUnitMem = 1700
, _scriptRedeemerUnitSteps = 476468
, _scriptRedeemerFee = 172033
}

0 comments on commit 06c45de

Please sign in to comment.