Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 3 additions & 2 deletions cardano-db-sync/app/http-get-json-metadata.hs
Original file line number Diff line number Diff line change
Expand Up @@ -143,11 +143,12 @@ runGetVote :: Text.Text -> Maybe VoteMetaHash -> DB.AnchorType -> IO ()
runGetVote file mExpectedHash vtype = do
respBs <- BS.readFile (Text.unpack file)
let respLBs = fromStrict respBs
(ocvd, val, hsh, mWarning) <- runOrThrowIO $ runExceptT $ parseAndValidateVoteData respBs respLBs mExpectedHash vtype Nothing
print ocvd
(mocvd, val, hsh, mWarning, isValidJson) <- runOrThrowIO $ runExceptT $ parseAndValidateVoteData respBs respLBs mExpectedHash vtype Nothing
print mocvd
print val
print $ bsBase16Encode hsh
print mWarning
putStrLn $ "Is valid JSON: " ++ show isValidJson

-- ------------------------------------------------------------------------------------------------

Expand Down
2 changes: 2 additions & 0 deletions cardano-db-sync/cardano-db-sync.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ category: Cryptocurrency
build-type: Custom
extra-source-files: CHANGELOG.md
schema/*.sql
test/testfiles/*.jsonld

custom-setup
setup-depends:
Expand Down Expand Up @@ -334,6 +335,7 @@ test-suite test
Cardano.DbSync.Era.Shelley.Generic.ScriptDataTest
Cardano.DbSync.Era.Shelley.Generic.ScriptTest
Cardano.DbSync.Gen
Cardano.DbSync.OffChain.VoteTest
Cardano.DbSync.Util.AddressTest
Cardano.DbSync.Util.Bech32Test
Cardano.DbSync.Util.CborTest
Expand Down
69 changes: 48 additions & 21 deletions cardano-db-sync/src/Cardano/DbSync/OffChain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -349,27 +349,54 @@ fetchOffChainVoteData gateways time oVoteWorkQ =
convert eres =
case eres of
Right sVoteData ->
let
offChainData = sovaOffChainVoteData sVoteData
minimalBody = Vote.getMinimalBody offChainData
vdt =
DB.OffChainVoteData
{ DB.offChainVoteDataLanguage = Vote.getLanguage offChainData
, DB.offChainVoteDataComment = Vote.textValue <$> Vote.comment minimalBody
, DB.offChainVoteDataBytes = sovaBytes sVoteData
, DB.offChainVoteDataHash = sovaHash sVoteData
, DB.offChainVoteDataJson = sovaJson sVoteData
, DB.offChainVoteDataVotingAnchorId = oVoteWqReferenceId oVoteWorkQ
, DB.offChainVoteDataWarning = sovaWarning sVoteData
, DB.offChainVoteDataIsValid = Nothing
}
gaF ocvdId = mkGovAction ocvdId offChainData
drepF ocvdId = mkDrep ocvdId offChainData
authorsF ocvdId = map (mkAuthor ocvdId) $ Vote.getAuthors offChainData
referencesF ocvdId = map (mkReference ocvdId) $ mListToList $ Vote.references minimalBody
externalUpdatesF ocvdId = map (mkexternalUpdates ocvdId) $ mListToList $ Vote.externalUpdates minimalBody
in
OffChainVoteResultMetadata vdt (OffChainVoteAccessors gaF drepF authorsF referencesF externalUpdatesF)
case (sovaIsValidJson sVoteData, sovaOffChainVoteData sVoteData) of
-- Scenario 1: Valid JSON + Valid CIP schema
(True, Just offChainData) ->
let
minimalBody = Vote.getMinimalBody offChainData
vdt =
DB.OffChainVoteData
{ DB.offChainVoteDataLanguage = Vote.getLanguage offChainData
, DB.offChainVoteDataComment = Vote.textValue <$> Vote.comment minimalBody
, DB.offChainVoteDataBytes = sovaBytes sVoteData
, DB.offChainVoteDataHash = sovaHash sVoteData
, DB.offChainVoteDataJson = sovaJson sVoteData
, DB.offChainVoteDataVotingAnchorId = oVoteWqReferenceId oVoteWorkQ
, DB.offChainVoteDataWarning = sovaWarning sVoteData
, DB.offChainVoteDataIsValid = Just True
}
gaF ocvdId = mkGovAction ocvdId offChainData
drepF ocvdId = mkDrep ocvdId offChainData
authorsF ocvdId = map (mkAuthor ocvdId) $ Vote.getAuthors offChainData
referencesF ocvdId = map (mkReference ocvdId) $ mListToList $ Vote.references minimalBody
externalUpdatesF ocvdId = map (mkexternalUpdates ocvdId) $ mListToList $ Vote.externalUpdates minimalBody
in
OffChainVoteResultMetadata vdt (OffChainVoteAccessors gaF drepF authorsF referencesF externalUpdatesF)
-- Scenario 2 & 3: Valid JSON but invalid CIP schema OR Invalid JSON
(_, _) ->
let
vdt =
DB.OffChainVoteData
{ DB.offChainVoteDataLanguage = ""
, DB.offChainVoteDataComment = Nothing
, DB.offChainVoteDataBytes = sovaBytes sVoteData
, DB.offChainVoteDataHash = sovaHash sVoteData
, DB.offChainVoteDataJson = sovaJson sVoteData
, DB.offChainVoteDataVotingAnchorId = oVoteWqReferenceId oVoteWorkQ
, DB.offChainVoteDataWarning = sovaWarning sVoteData
, -- Just False if valid JSON but invalid schema, NULL if unparseable JSON
DB.offChainVoteDataIsValid =
if sovaIsValidJson sVoteData
then Just False
else Nothing
}
gaF _ = Nothing
drepF _ = Nothing
authorsF _ = []
referencesF _ = []
externalUpdatesF _ = []
in
OffChainVoteResultMetadata vdt (OffChainVoteAccessors gaF drepF authorsF referencesF externalUpdatesF)
Left err ->
OffChainVoteResultError $
DB.OffChainVoteFetchError
Expand Down
32 changes: 21 additions & 11 deletions cardano-db-sync/src/Cardano/DbSync/OffChain/Http.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,36 +108,46 @@ httpGetOffChainVoteDataSingle vurl metaHash anchorType = do
let req = httpGetBytes manager request 3000000 3000000 url
httpRes <- handleExceptT (convertHttpException url) req
(respBS, respLBS, mContentType) <- hoistEither httpRes
(ocvd, decodedValue, metadataHash, mWarning) <- parseAndValidateVoteData respBS respLBS metaHash anchorType (Just $ OffChainVoteUrl vurl)
(mocvd, decodedValue, metadataHash, mWarning, isValidJson) <- parseAndValidateVoteData respBS respLBS metaHash anchorType (Just $ OffChainVoteUrl vurl)
pure $
SimplifiedOffChainVoteData
{ sovaHash = metadataHash
, sovaBytes = respBS
, sovaJson = Text.decodeUtf8 $ LBS.toStrict (Aeson.encode decodedValue)
, sovaContentType = mContentType
, sovaOffChainVoteData = ocvd
, sovaOffChainVoteData = mocvd
, sovaWarning = mWarning
, sovaIsValidJson = isValidJson
}
where
url = OffChainVoteUrl vurl

parseAndValidateVoteData :: ByteString -> LBS.ByteString -> Maybe VoteMetaHash -> DB.AnchorType -> Maybe OffChainUrlType -> ExceptT OffChainFetchError IO (Vote.OffChainVoteData, Aeson.Value, ByteString, Maybe Text)
parseAndValidateVoteData :: ByteString -> LBS.ByteString -> Maybe VoteMetaHash -> DB.AnchorType -> Maybe OffChainUrlType -> ExceptT OffChainFetchError IO (Maybe Vote.OffChainVoteData, Aeson.Value, ByteString, Maybe Text, Bool)
parseAndValidateVoteData bs lbs metaHash anchorType murl = do
let metadataHash = Crypto.digest (Proxy :: Proxy Crypto.Blake2b_256) bs
-- First check if hash matches - this is critical and must fail if mismatch
(hsh, mWarning) <- case unVoteMetaHash <$> metaHash of
Just expectedMetaHashBs
| metadataHash /= expectedMetaHashBs ->
left $ OCFErrHashMismatch murl (renderByteArray expectedMetaHashBs) (renderByteArray metadataHash)
_ -> pure (metadataHash, Nothing)
decodedValue <-
-- Hash matches, now try to decode as generic JSON
-- If this fails, we still want to store the data with is_valid = NULL and an error message
(decodedValue, isValidJson) <-
case Aeson.eitherDecode' @Aeson.Value lbs of
Left err -> left $ OCFErrJsonDecodeFail murl (Text.pack err)
Right res -> pure res
ocvd <-
case Vote.eitherDecodeOffChainVoteData lbs anchorType of
Left err -> left $ OCFErrJsonDecodeFail murl (Text.pack err)
Right res -> pure res
pure (ocvd, decodedValue, hsh, mWarning)
Left err ->
-- Not valid JSON - create an error message object
pure (Aeson.object [("error", Aeson.String "Content is not valid JSON. See bytes column for raw data."), ("parse_error", Aeson.String $ Text.pack err)], False)
Right res -> pure (res, True)
-- Try to decode into strongly-typed vote data structure (only if JSON was valid)
-- If this fails (e.g., doNotList is string instead of bool), we still store with is_valid = false
let ocvd =
if isValidJson
then case Vote.eitherDecodeOffChainVoteData lbs anchorType of
Left _err -> Nothing -- Don't fail, just return Nothing (will set is_valid = false)
Right res -> Just res
else Nothing -- Not valid JSON, so can't parse as CIP
pure (ocvd, decodedValue, hsh, mWarning, isValidJson)

httpGetBytes ::
Http.Manager ->
Expand Down
3 changes: 2 additions & 1 deletion cardano-db-sync/src/Cardano/DbSync/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -193,8 +193,9 @@ data SimplifiedOffChainVoteData = SimplifiedOffChainVoteData
, sovaBytes :: !ByteString
, sovaJson :: !Text
, sovaContentType :: !(Maybe ByteString)
, sovaOffChainVoteData :: !Vote.OffChainVoteData
, sovaOffChainVoteData :: !(Maybe Vote.OffChainVoteData)
, sovaWarning :: !(Maybe Text)
, sovaIsValidJson :: !Bool
}

data Retry = Retry
Expand Down
146 changes: 146 additions & 0 deletions cardano-db-sync/test/Cardano/DbSync/OffChain/VoteTest.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,146 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Cardano.DbSync.OffChain.VoteTest (tests) where

import qualified Cardano.Db as DB
import Cardano.DbSync.Error (runOrThrowIO)
import Cardano.DbSync.OffChain.Http (parseAndValidateVoteData)
import Cardano.Prelude hiding ((%))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Key as AesonKey
import qualified Data.Aeson.KeyMap as KeyMap
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Text as Text
import Hedgehog

tests :: IO Bool
tests =
checkParallel $
Group
"Cardano.DbSync.OffChain.Vote"
[ ("parseAndValidateVoteData handles valid CIP-119 format", prop_parseValidCIPFormat)
, ("parseAndValidateVoteData handles invalid CIP format (type error)", prop_parseInvalidCIPFormat)
, ("parseAndValidateVoteData handles valid JSON but invalid structure", prop_parseValidJsonInvalidStructure)
, ("parseAndValidateVoteData handles unparseable JSON", prop_parseUnparseableJson)
]

-- | Test that we can parse valid CIP-119 format correctly
-- Scenario: Valid JSON + Valid CIP schema -> is_valid = true
prop_parseValidCIPFormat :: Property
prop_parseValidCIPFormat = withTests 1 $ property $ do
-- Read the test file with valid CIP-119 format
fileContent <- liftIO $ BS.readFile "test/testfiles/valid-vote-minimal.jsonld"
let lbsContent = LBS.fromStrict fileContent

-- Run the parser
result <- liftIO $ runOrThrowIO $ runExceptT $ parseAndValidateVoteData fileContent lbsContent Nothing DB.DrepAnchor Nothing

let (mocvd, val, _hash, _warning, isValidJson) = result

-- Should succeed in parsing generic JSON
annotate "Successfully parsed as generic JSON"
assert isValidJson

-- Should successfully parse into strongly-typed OffChainVoteData
case mocvd of
Just _ocvd -> do
annotate "Successfully parsed into OffChainVoteData"
success
Nothing -> do
annotate "Failed to parse into OffChainVoteData"
failure

-- Should have valid Aeson.Value
case Aeson.toJSON val of
Aeson.Object _obj -> do
annotate "Has valid JSON object"
success
_ -> do
annotate "Expected JSON object"
failure

-- | Test that we can parse JSON with incorrect field types (e.g., doNotList as string instead of bool)
-- This is based on the issue https://github.com/IntersectMBO/cardano-db-sync/issues/1995
-- Scenario: Valid JSON but invalid CIP schema -> is_valid = false
prop_parseInvalidCIPFormat :: Property
prop_parseInvalidCIPFormat = withTests 1 $ property $ do
-- Read the test file with invalid doNotList field (string instead of bool)
fileContent <- liftIO $ BS.readFile "test/testfiles/invalid-vote-type-error.jsonld"
let lbsContent = LBS.fromStrict fileContent

-- Run the parser
result <- liftIO $ runOrThrowIO $ runExceptT $ parseAndValidateVoteData fileContent lbsContent Nothing DB.DrepAnchor Nothing

let (mocvd, val, _hash, _warning, isValidJson) = result

-- Should succeed in parsing generic JSON
annotate "Successfully parsed as generic JSON"
assert isValidJson

-- Should fail to parse into strongly-typed OffChainVoteData
assert $ isNothing mocvd

-- But should have valid Aeson.Value
case Aeson.toJSON val of
Aeson.Object _obj -> do
annotate "Has valid JSON object"
success
_ -> do
annotate "Expected JSON object"
failure

-- | Test with completely valid JSON but not matching the CIP schema
-- Scenario: Valid JSON but invalid CIP schema -> is_valid = false
prop_parseValidJsonInvalidStructure :: Property
prop_parseValidJsonInvalidStructure = withTests 1 $ property $ do
-- Read the test file with valid JSON but wrong structure
fileContent <- liftIO $ BS.readFile "test/testfiles/invalid-vote-wrong-structure.jsonld"
let lbsContent = LBS.fromStrict fileContent

-- This should succeed because it's valid JSON, just not matching the schema
result <- liftIO $ runOrThrowIO $ runExceptT $ parseAndValidateVoteData fileContent lbsContent Nothing DB.DrepAnchor Nothing

let (mocvd, _val, _hash, _warning, isValidJson) = result

annotate "Successfully parsed generic JSON"
assert isValidJson
-- Should not parse into OffChainVoteData
assert $ isNothing mocvd

-- | Test with completely unparseable content (not valid JSON at all)
-- Scenario: Invalid JSON but hash matches -> is_valid = NULL
prop_parseUnparseableJson :: Property
prop_parseUnparseableJson = withTests 1 $ property $ do
-- Read the test file with malformed JSON
fileContent <- liftIO $ BS.readFile "test/testfiles/invalid-vote-malformed-json.jsonld"
let lbsContent = LBS.fromStrict fileContent

-- This should not fail, but instead return an error message in the JSON field
result <- liftIO $ runOrThrowIO $ runExceptT $ parseAndValidateVoteData fileContent lbsContent Nothing DB.DrepAnchor Nothing

let (mocvd, val, _hash, _warning, isValidJson) = result

annotate "Content is not valid JSON"
-- Should flag as invalid JSON
assert $ not isValidJson

-- Should not parse into OffChainVoteData
assert $ isNothing mocvd

-- Should have an error message in the JSON value
case val of
Aeson.Object obj -> do
annotate "Has error message object"
-- Check that error field exists
case KeyMap.lookup (AesonKey.fromString "error") obj of
Just (Aeson.String msg) -> do
annotate $ "Error message: " <> show msg
assert $ Text.isInfixOf "not valid JSON" msg
_ -> do
annotate "Expected error field with string value"
failure
_ -> do
annotate "Expected JSON object with error message"
failure
2 changes: 2 additions & 0 deletions cardano-db-sync/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import qualified Cardano.DbSync.ApiTest as Api
import qualified Cardano.DbSync.Config.TypesTest as Types
import qualified Cardano.DbSync.Era.Shelley.Generic.ScriptDataTest as ScriptData
import qualified Cardano.DbSync.Era.Shelley.Generic.ScriptTest as Script
import qualified Cardano.DbSync.OffChain.VoteTest as VoteTest
import qualified Cardano.DbSync.Util.AddressTest as Address
import qualified Cardano.DbSync.Util.Bech32Test as Bech32
import qualified Cardano.DbSync.Util.CborTest as Cbor
Expand All @@ -23,4 +24,5 @@ main =
, DbSync.tests
, Types.tests
, Api.tests
, VoteTest.tests
]
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
{
"givenName": "Test DRep",
"objectives": "Missing closing quote and brace
"motivations": "This JSON is malformed
Loading
Loading