Skip to content

Commit

Permalink
Return errors as string from validate_cbor
Browse files Browse the repository at this point in the history
  So that we don't panic in the function and we keep everything pure. Now we can properly hook into Hedgehog annotation system to provide better failures.
  • Loading branch information
KtorZ committed Sep 28, 2023
1 parent a2de401 commit ece7093
Show file tree
Hide file tree
Showing 8 changed files with 51 additions and 26 deletions.
12 changes: 9 additions & 3 deletions cardano-node/test/Test/Cardano/Node/LedgerEvent.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

Expand All @@ -17,9 +18,8 @@ import Data.ByteString.Short (ShortByteString, toShort)
import Data.Map (Map)
import Data.Maybe (fromJust)
import Data.String (IsString(..))
import Data.Set (Set)
import Data.Text (Text)
import Hedgehog (Property, discover, footnote, (===))
import Hedgehog (Property, discover, footnote)
import qualified Hedgehog
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
Expand Down Expand Up @@ -52,7 +52,13 @@ prop_LedgerEvent_CDDL_conformance =
-- This requires the `cddl-cat` Rust crate to support the '.cbor' control
-- operator which should make for a straightforward and nice contribution.
let bytes = serialize' version (ledgerEvent event)
CDDL.validate specification bytes === Right ()
case CDDL.validate specification bytes of
Right () ->
Hedgehog.success
Left (CDDL.ValidationError { CDDL.cbor = cbor, CDDL.hint = hint }) -> do

Check warning on line 58 in cardano-node/test/Test/Cardano/Node/LedgerEvent.hs

View workflow job for this annotation

GitHub Actions / build

Warning in prop_LedgerEvent_CDDL_conformance in module Test.Cardano.Node.LedgerEvent: Redundant bracket ▫︎ Found: "(CDDL.ValidationError {CDDL.cbor = cbor, CDDL.hint = hint})" ▫︎ Perhaps: "CDDL.ValidationError {CDDL.cbor = cbor, CDDL.hint = hint}"
Hedgehog.footnote hint
Hedgehog.footnote cbor
Hedgehog.failure

--
-- Generators
Expand Down
2 changes: 1 addition & 1 deletion cddl/Cargo.toml
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ edition = "2021"

[lib]
name = "cddl"
crate-type = ["staticlib"]
crate-type = ["cdylib"]

[dependencies]
cddl-cat = "0.6.1"
3 changes: 1 addition & 2 deletions cddl/Makefile
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
all:
cargo build --release
mv target/release/libcddl.a /usr/local/lib/libcddl.a
cbindgen --crate cddl > cbits/libcddl.h
@cat cbits/libcddl.h
8 changes: 4 additions & 4 deletions cddl/cbits/libcddl.h
Original file line number Diff line number Diff line change
Expand Up @@ -6,9 +6,9 @@

extern "C" {

void validate_cbor(const uint8_t *cddl_ptr,
uintptr_t cddl_len,
const uint8_t *cbor_ptr,
uintptr_t cbor_len);
int8_t *validate_cbor(const uint8_t *cddl_ptr,
uintptr_t cddl_len,
const uint8_t *cbor_ptr,
uintptr_t cbor_len);

} // extern "C"
1 change: 1 addition & 0 deletions cddl/cddl.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ library
other-modules: Paths_cddl
autogen-modules: Paths_cddl
build-depends: , base
, base16-bytestring
, bytestring
, text

Expand Down
40 changes: 29 additions & 11 deletions cddl/src/Codec/CBOR/Schema.hs
Original file line number Diff line number Diff line change
@@ -1,35 +1,53 @@
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE NamedFieldPuns #-}

module Codec.CBOR.Schema where

import Prelude

import Control.Exception (SomeException(..), Exception(..), catch)
import Data.Text (Text)
import qualified Data.Text as Text
import Data.ByteString (ByteString)
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString as BS
import Foreign.C.String (CString, withCStringLen)
import qualified Data.ByteString.Char8 as B8
import Foreign.Marshal.Alloc (free)
import Foreign.C.String (CString, peekCString, withCStringLen)
import System.IO.Unsafe (unsafePerformIO)

data ValidationError = ValidationError
{ cbor :: String -- | The erroneous CBOR as a base16-encoded text string
, hint :: String -- | An (hopefully) helpful error message
} deriving (Eq, Show)

validate
:: Text
-- ^ A CDDL specification
-> ByteString
-- ^ Some CBOR value
-> Either String ()
validate cddl cbor = unsafePerformIO $ do
withCStringLen (Text.unpack cddl) $ \(cddl_ptr, cddl_len) ->
BS.useAsCStringLen cbor $ \(cbor_ptr, cbor_len) ->
( Right <$> validate_cbor
cddl_ptr (fromIntegral cddl_len)
cbor_ptr (fromIntegral cbor_len)
) `catch` \(SomeException e) -> return (Left (displayException e))
-> Either ValidationError ()
validate cddl cbor =
case result of
[] ->
Right ()
hint ->
Left $ ValidationError
{ hint
, cbor = B8.unpack (Base16.encode cbor)
}
where
result = unsafePerformIO $ do
withCStringLen (Text.unpack cddl) $ \(cddl_ptr, cddl_len) ->
BS.useAsCStringLen cbor $ \(cbor_ptr, cbor_len) -> do
cstr <- validate_cbor
cddl_ptr (fromIntegral cddl_len)
cbor_ptr (fromIntegral cbor_len)
peekCString cstr <* free cstr

foreign import ccall "cbits/libcddl.h validate_cbor"
validate_cbor
:: CString
-> Word
-> CString
-> Word
-> IO ()
-> IO CString
9 changes: 5 additions & 4 deletions cddl/src/lib.rs
Original file line number Diff line number Diff line change
@@ -1,17 +1,18 @@
use cddl_cat::validate_cbor_bytes;
use std::{slice, str};
use std::{ffi::CString, slice, str};

#[no_mangle]
pub extern "C" fn validate_cbor(
cddl_ptr: *const u8,
cddl_len: usize,
cbor_ptr: *const u8,
cbor_len: usize,
) -> () {
) -> *mut i8 {
let cddl = unsafe { slice::from_raw_parts(cddl_ptr, cddl_len) };
let cbor = unsafe { slice::from_raw_parts(cbor_ptr, cbor_len) };
match validate_cbor_bytes("rule", str::from_utf8(cddl).unwrap(), cbor) {
Ok(_) => (),
Err(e) => panic!("{e:#?}"),
Ok(_) => CString::new("").unwrap(),
Err(e) => CString::new(format!("{e:#?}")).unwrap(),
}
.into_raw()
}
2 changes: 1 addition & 1 deletion cddl/test/Codec/CBOR/SchemaSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Test.Hspec (Spec, SpecWith, context, specify, shouldBe)
spec :: Spec
spec = context "Codec.CBOR.SchemaSpec" $ do
specifyCddl "Primitive / Int"
"rule = int"
"rule = uint"
"182A"

specifyCddl
Expand Down

0 comments on commit ece7093

Please sign in to comment.