Skip to content

Commit 408f7fb

Browse files
committed
Refactor CBORTerm representation and introduce mkCBORTerm helper function
1 parent 177d9ed commit 408f7fb

File tree

5 files changed

+30
-22
lines changed

5 files changed

+30
-22
lines changed

mempack-scls/mempack-1.0/Data/MemPack/Extra.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,8 @@ module Data.MemPack.Extra (
1717
Entry (..),
1818
ByteStringSized (..),
1919
SomeByteStringSized (..),
20-
CBORTerm (..),
20+
CBORTerm (getRawTerm),
21+
mkCBORTerm,
2122
RawBytes (..),
2223
Unpack',
2324
hPutBuffer,
@@ -212,15 +213,18 @@ instance (KnownNat n) => MemPack (ByteStringSized n) where
212213
pure (ByteStringSized bs)
213214

214215
-- | Helper to store CBOR terms directly as entries.
215-
newtype CBORTerm = CBORTerm CBOR.Term
216+
data CBORTerm = CBORTerm {getRawTerm :: !CBOR.Term, getEncodedBytes :: ByteString}
216217
deriving (Eq, Ord, Show)
217218

219+
mkCBORTerm :: CBOR.Term -> CBORTerm
220+
mkCBORTerm t = CBORTerm t (CBOR.toStrictByteString (CBOR.encodeTerm t))
221+
218222
instance MemPack CBORTerm where
219-
packedByteCount (CBORTerm t) =
220-
BS.length (CBOR.toStrictByteString (CBOR.encodeTerm t))
223+
packedByteCount (CBORTerm _ bs) =
224+
BS.length bs
221225

222-
packM (CBORTerm t) =
223-
packByteStringM (CBOR.toStrictByteString (CBOR.encodeTerm t))
226+
packM (CBORTerm _ bs) =
227+
packByteStringM bs
224228

225229
unpackM = do
226230
start <- gets fromIntegral
@@ -229,7 +233,7 @@ instance MemPack CBORTerm where
229233
Left err -> failUnpack $ TextError $ "CBOR term deserialisation failed: " <> T.pack (show err)
230234
Right (_rest, bytesRead, term) -> do
231235
put (start + fromIntegral bytesRead)
232-
pure (CBORTerm term)
236+
pure (CBORTerm term bytes)
233237

234238
hPutBuffer :: (Buffer u) => Handle -> u -> IO ()
235239
hPutBuffer handle u =

mempack-scls/mempack-2.0/Data/MemPack/Extra.hs

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,8 @@ module Data.MemPack.Extra (
1717
Entry (..),
1818
ByteStringSized (..),
1919
SomeByteStringSized (..),
20-
CBORTerm (..),
20+
CBORTerm (getRawTerm),
21+
mkCBORTerm,
2122
RawBytes (..),
2223
Unpack',
2324
hPutBuffer,
@@ -217,15 +218,18 @@ instance (KnownNat n) => MemPack (ByteStringSized n) where
217218
pure (ByteStringSized bs)
218219

219220
-- | Helper to store CBOR terms directly as entries.
220-
newtype CBORTerm = CBORTerm CBOR.Term
221+
data CBORTerm = CBORTerm {getRawTerm :: !CBOR.Term, getEncodedBytes :: ByteString}
221222
deriving (Eq, Ord, Show)
222223

224+
mkCBORTerm :: CBOR.Term -> CBORTerm
225+
mkCBORTerm t = CBORTerm t (CBOR.toStrictByteString (CBOR.encodeTerm t))
226+
223227
instance MemPack CBORTerm where
224-
packedByteCount (CBORTerm t) =
225-
BS.length (CBOR.toStrictByteString (CBOR.encodeTerm t))
228+
packedByteCount (CBORTerm _ bs) =
229+
BS.length bs
226230

227-
packM (CBORTerm t) =
228-
packByteStringM (CBOR.toStrictByteString (CBOR.encodeTerm t))
231+
packM (CBORTerm _ bs) =
232+
packByteStringM bs
229233

230234
unpackM = do
231235
start <- gets fromIntegral
@@ -234,7 +238,7 @@ instance MemPack CBORTerm where
234238
Left err -> failUnpack $ TextError $ "CBOR term deserialisation failed: " <> T.pack (show err)
235239
Right (_rest, bytesRead, term) -> do
236240
put (start + fromIntegral bytesRead)
237-
pure (CBORTerm term)
241+
pure (CBORTerm term bytes)
238242

239243
hPutBuffer :: (Buffer u) => Handle -> u -> IO ()
240244
hPutBuffer handle u =

scls-format/test/Roundtrip.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,7 @@ mkRoundtripTestsFor groupName serialize =
111111
key <- uniformByteStringM (fromIntegral kSize) globalStdGen
112112
term <- applyAtomicGen (generateCBORTerm' mt (Name (T.pack "record_entry") mempty)) globalStdGen
113113
Right (_, canonicalTerm) <- pure $ deserialiseFromBytes decodeTerm $ toLazyByteString (encodeTerm term)
114-
pure $! SomeCBOREntry (GenericCBOREntry $ ChunkEntry (ByteStringSized @n key) (CBORTerm canonicalTerm))
114+
pure $! SomeCBOREntry (GenericCBOREntry $ ChunkEntry (ByteStringSized @n key) (mkCBORTerm canonicalTerm))
115115
mEntries <-
116116
replicateM 1024 $ do
117117
MetadataEntry

scls-util/src/Cardano/SCLS/Util/Check.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -231,29 +231,29 @@ validateChunk cddlTrees Chunk{..} = do
231231
}
232232

233233
validateAgainst :: forall n. CTreeRoot' Identity MonoRef -> (Int, GenericCBOREntry n) -> Maybe CheckError
234-
validateAgainst t v@(i, GenericCBOREntry (ChunkEntry _ (CBORTerm term))) =
234+
validateAgainst t v@(i, GenericCBOREntry (ChunkEntry _ cTerm)) =
235235
case validateCDDLAgainst t v of
236236
Just e -> Just e
237237
Nothing -> case checkCanonical of
238238
Nothing -> Nothing
239-
Just expected -> Just (CBORIsNotCanonicalError i expected term)
239+
Just expected -> Just (CBORIsNotCanonicalError i expected (getRawTerm cTerm))
240240
where
241241
checkCanonical =
242-
let encodedData = toLazyByteString (getRawEncoding $ toCanonicalCBOR Proxy term)
242+
let encodedData = toLazyByteString (getRawEncoding $ toCanonicalCBOR Proxy $ getRawTerm cTerm)
243243
in case deserialiseFromBytes (decodeTerm) encodedData of
244244
Right (_, decodedAsTerm) ->
245-
if term == decodedAsTerm
245+
if getRawTerm cTerm == decodedAsTerm
246246
then Nothing
247247
else Just decodedAsTerm
248248
_ -> Nothing
249249

250250
validateCDDLAgainst :: CTreeRoot' Identity MonoRef -> (Int, GenericCBOREntry n) -> Maybe CheckError
251-
validateCDDLAgainst cddl@(CTreeRoot cddlTree) (seqNum, GenericCBOREntry (ChunkEntry _key (CBORTerm term))) =
251+
validateCDDLAgainst cddl@(CTreeRoot cddlTree) (seqNum, GenericCBOREntry (ChunkEntry _key cTerm)) =
252252
let name = Name (T.pack "record_entry") mempty
253253
in case Map.lookup name cddlTree of
254254
Nothing -> Nothing
255255
Just rule ->
256-
case runReader (validateTerm term (runIdentity rule)) cddl of
256+
case runReader (validateTerm (getRawTerm cTerm) (runIdentity rule)) cddl of
257257
CBORTermResult _term Valid{} -> Nothing
258258
CBORTermResult bad_term problem -> Just (CDDLValidationError seqNum problem bad_term)
259259

scls-util/src/Cardano/SCLS/Util/Debug.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ generateNamespaceEntries count spec = replicateM_ count do
7676
let size = fromSNat @n SNat
7777
keyIn <- liftIO $ uniformByteStringM (fromIntegral size) globalStdGen
7878
term <- liftIO $ applyAtomicGen (generateCBORTerm' spec (Name (T.pack "record_entry") mempty)) globalStdGen
79-
S.yield $ GenericCBOREntry $ ChunkEntry (ByteStringSized @n keyIn) (CBORTerm term)
79+
S.yield $ GenericCBOREntry $ ChunkEntry (ByteStringSized @n keyIn) (mkCBORTerm term)
8080

8181
printHexEntries :: FilePath -> T.Text -> Int -> IO Result
8282
printHexEntries filePath ns_name@(Namespace.fromText -> ns) entryNo = do

0 commit comments

Comments
 (0)