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
1 change: 1 addition & 0 deletions cardano-db-sync/cardano-db-sync.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -334,6 +334,7 @@ test-suite test
Cardano.DbSync.Era.Shelley.Generic.ScriptDataTest
Cardano.DbSync.Era.Shelley.Generic.ScriptTest
Cardano.DbSync.Gen
Cardano.DbSync.OffChain.Vote.TypesTest
Cardano.DbSync.Util.AddressTest
Cardano.DbSync.Util.Bech32Test
Cardano.DbSync.Util.CborTest
Expand Down
5 changes: 3 additions & 2 deletions cardano-db-sync/src/Cardano/DbSync/OffChain/Vote/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -284,8 +284,9 @@ instance FromJSON Image where
| (_, tb) <- Text.break (== '/') ctb
, Text.isPrefixOf "/" tb
, (_, b) <- Text.break (== ';') tb
, Just imageData <- Text.stripPrefix ";base64," b ->
pure $ Image (TextValue imageData) Nothing
, Just _ <- Text.stripPrefix ";base64," b ->
-- Store the full data URI including prefix
pure $ Image curl Nothing
_ -> fromImageUrl <$> parseJSON v
where
withObjectV v' s p = withObject s p v'
Expand Down
71 changes: 71 additions & 0 deletions cardano-db-sync/test/Cardano/DbSync/OffChain/Vote/TypesTest.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,71 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Cardano.DbSync.OffChain.Vote.TypesTest (tests) where

import Cardano.DbSync.OffChain.Vote.Types
import Cardano.Prelude
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Lazy as LBS
import qualified Data.Text as Text
import Hedgehog
import qualified Hedgehog as H
import Prelude ()

tests :: IO Bool
tests =
checkParallel $
Group
"Cardano.DbSync.OffChain.Vote.Types"
[ ("Image preserves data URI prefix", prop_image_preserves_data_uri_prefix)
, ("Image handles URL with hash", prop_image_handles_url_with_hash)
, ("Image preserves JPEG data URI", prop_image_preserves_jpeg_data_uri)
]

prop_image_preserves_data_uri_prefix :: Property
prop_image_preserves_data_uri_prefix = property $ do
let jsonWithDataUri =
LBS.fromStrict $
encodeUtf8
"{ \"contentUrl\": \"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAUA\" }"

case Aeson.eitherDecode jsonWithDataUri of
Left err -> do
H.footnote $ "Parse failed: " <> err
H.failure
Right (img :: Image) -> do
let imgContent = textValue $ content img
H.assert $ "data:" `Text.isPrefixOf` imgContent
H.assert $ "image/png" `Text.isInfixOf` imgContent
H.assert $ "base64" `Text.isInfixOf` imgContent
imgContent === "data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAUA"

prop_image_handles_url_with_hash :: Property
prop_image_handles_url_with_hash = property $ do
let jsonWithUrl =
LBS.fromStrict $
encodeUtf8
"{ \"contentUrl\": \"https://example.com/image.png\", \"sha256\": \"abc123\" }"

case Aeson.eitherDecode jsonWithUrl of
Left err -> do
H.footnote $ "Parse failed: " <> err
H.failure
Right (img :: Image) -> do
textValue (content img) === "https://example.com/image.png"
(textValue <$> msha256 img) === Just "abc123"

prop_image_preserves_jpeg_data_uri :: Property
prop_image_preserves_jpeg_data_uri = property $ do
let jsonWithJpeg =
LBS.fromStrict $
encodeUtf8
"{ \"contentUrl\": \"data:image/jpeg;base64,/9j/4AAQSkZJRg\" }"

case Aeson.eitherDecode jsonWithJpeg of
Left err -> do
H.footnote $ "Parse failed: " <> err
H.failure
Right (img :: Image) -> do
let imgContent = textValue $ content img
imgContent === "data:image/jpeg;base64,/9j/4AAQSkZJRg"
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.Vote.TypesTest as VoteTypes
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
, VoteTypes.tests
]
4 changes: 3 additions & 1 deletion cardano-db/src/Cardano/Db/Statement/OffChain.hs
Original file line number Diff line number Diff line change
Expand Up @@ -507,7 +507,9 @@ insertBulkOffChainVoteData offChainVoteData = do

insertBulkOffChainVoteDrepDataStmt :: HsqlStmt.Statement [SO.OffChainVoteDrepData] ()
insertBulkOffChainVoteDrepDataStmt =
insertBulk
insertBulkWith
(ReplaceWithColumns ["off_chain_vote_data_id"])
False
extractOffChainVoteDrepData
SO.offChainVoteDrepDataBulkEncoder
NoResultBulk
Expand Down
Loading