Skip to content

Commit 684f9a8

Browse files
ttuegelrv-jenkins
andauthored
Unparse InternalBytes using 8-bit encoding
* Unparse InternalBytes using 8-bit encoding * Format with stylish-haskell * test: make golden * Add Strict pragmas Co-authored-by: ttuegel <[email protected]> Co-authored-by: rv-jenkins <[email protected]>
1 parent deb9d00 commit 684f9a8

File tree

4 files changed

+19
-4
lines changed

4 files changed

+19
-4
lines changed

kore/src/Kore/Internal/InternalBytes.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@ Copyright : (c) Runtime Verification, 2019
33
License : NCSA
44
-}
55

6+
{-# LANGUAGE Strict #-}
7+
68
module Kore.Internal.InternalBytes
79
( InternalBytes (..)
810
) where
@@ -40,14 +42,14 @@ instance Unparse InternalBytes where
4042
unparse internalBytes@(InternalBytes _ _) =
4143
"\\dv"
4244
<> parameters [internalBytesSort]
43-
<> arguments [StringLiteral (Encoding.toBase16 internalBytesValue)]
45+
<> arguments [StringLiteral (Encoding.decode8Bit internalBytesValue)]
4446
where
4547
InternalBytes { internalBytesSort, internalBytesValue } = internalBytes
4648

4749
unparse2 internalBytes@(InternalBytes _ _) =
4850
"\\dv2"
4951
<> parameters2 [internalBytesSort]
50-
<> arguments2 [StringLiteral (Encoding.toBase16 internalBytesValue)]
52+
<> arguments2 [StringLiteral (Encoding.decode8Bit internalBytesValue)]
5153
where
5254
InternalBytes { internalBytesSort, internalBytesValue } = internalBytes
5355

kore/test/Test/Kore/Builtin/InternalBytes.hs

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
module Test.Kore.Builtin.InternalBytes
24
( test_update
35
, test_get
@@ -14,6 +16,7 @@ module Test.Kore.Builtin.InternalBytes
1416
, test_int2bytes
1517
, test_bytes2int
1618
, test_InternalBytes
19+
, test_unparse
1720
) where
1821

1922
import Prelude.Kore
@@ -43,6 +46,7 @@ import qualified Kore.Builtin.Encoding as E
4346
import qualified Kore.Builtin.InternalBytes as InternalBytes
4447
import Kore.Internal.Pattern
4548
import Kore.Internal.TermLike
49+
import Kore.Unparser
4650
import qualified Pretty
4751

4852
import Test.Kore.Builtin.Builtin
@@ -614,6 +618,15 @@ test_InternalBytes =
614618
assertEqual "" expect actual
615619
]
616620

621+
test_unparse :: [TestTree]
622+
test_unparse =
623+
[ testCase "unparse using 8-bit encoding" $ do
624+
let input = asInternal "\x00"
625+
actual = (show . unparse) input
626+
expect = "/* Fl Fn D Sfa Cl */ \\dv{Bytes{}}(\"\\x00\")"
627+
assertEqual "" expect actual
628+
]
629+
617630
-- * Helpers
618631

619632
asInternal :: ByteString -> TermLike VariableName

test/regression-evm-semantics-39dd1e5/test-branching-invalid.sh.out.golden

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@
9696
Lbl'-LT-'program'-GT-'{}(
9797
/* Fl Fn D Sfa Cl */
9898
\dv{SortBytes{}}(
99-
"6003600401600814600c57fe5b00"
99+
"`\x03`\x04\x01`\x08\x14`\x0cW\xfe[\x00"
100100
)
101101
),
102102
/* Fl Fn D Sfa Cl */

test/regression-evm-semantics-39dd1e5/test-straight-line.sh.out.golden

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@
9696
Lbl'-LT-'program'-GT-'{}(
9797
/* Fl Fn D Sfa Cl */
9898
\dv{SortBytes{}}(
99-
"7f00000000000000000000000000000000000000000000000000000000000000037f000000000000000000000000000000000000000000000000000000000000000401fe"
99+
"\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x03\x7f\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x04\x01\xfe"
100100
)
101101
),
102102
/* Fl Fn D Sfa Cl */

0 commit comments

Comments
 (0)