Skip to content

Commit

Permalink
Define IsString instance as a composition
Browse files Browse the repository at this point in the history
  • Loading branch information
iokasimov committed Jun 6, 2024
1 parent 35bc54e commit 34fd3ef
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 22 deletions.
9 changes: 2 additions & 7 deletions src/ZkFold/Symbolic/Data/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ import Control.DeepSeq (NFDa
import Control.Monad (mapM, replicateM, zipWithM)
import Data.Bits as B
import qualified Data.ByteString as Bytes
import Data.Char (ord)
import Data.List (foldl, reverse, unfoldr)
import Data.List.Split (chunksOf)
import Data.Maybe (Maybe (..))
Expand Down Expand Up @@ -52,13 +51,9 @@ newtype ByteString (n :: Natural) a = ByteString [a]

instance
( FromConstant Natural a
, Concat (ByteString 7 a) (ByteString n a)
, Concat (ByteString 8 a) (ByteString n a)
) => IsString (ByteString n a) where
fromString xs = concat
$ fromConstant @Natural @(ByteString 7 a)
. Haskell.fromIntegral
. Haskell.toInteger
. ord <$> xs
fromString = fromConstant . fromString @Bytes.ByteString

instance
( FromConstant Natural a
Expand Down
17 changes: 2 additions & 15 deletions tests/Tests/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,16 @@ module Tests.ByteString (specByteString) where

import Control.Applicative ((<*>))
import Control.Monad (return)
import qualified Data.ByteString as Bytes
import Data.Function (($), (.))
import Data.Function (($))
import Data.Functor ((<$>))
import Data.List (map, (++))
import Data.String (IsString (..), String)
import GHC.TypeNats (Mod)
import Numeric.Natural (Natural)
import Prelude (show, type (~), (<>))
import qualified Prelude as Haskell
import System.IO (IO)
import Test.Hspec (Spec, describe, hspec)
import Test.QuickCheck (Gen, Property, chooseInteger, elements, forAll, oneof,
withMaxSuccess, (===))
import Test.QuickCheck (Gen, Property, chooseInteger, withMaxSuccess, (===))
import Tests.ArithmeticCircuit (eval', it)

import ZkFold.Base.Algebra.Basic.Class
Expand Down Expand Up @@ -116,14 +113,6 @@ testGrow = it ("extends a bytestring of length " <> show (value @n) <> " to leng
n = Haskell.toInteger $ value @n
m = 2 Haskell.^ n -! 1

testFromString :: forall p .
PrimeField (Zp p) =>
String -> Property
testFromString str =
fromString @(ByteString 56 (Zp p)) str
=== fromConstant @Bytes.ByteString @(ByteString 56 (Zp p))
(fromString @Bytes.ByteString str)

-- | For some reason, Haskell can't infer obvious type relations such as n <= n + 1...
--
specByteString
Expand Down Expand Up @@ -156,8 +145,6 @@ specByteString = hspec $ do
let n = Haskell.fromIntegral $ value @n
m = 2 Haskell.^ n -! 1
describe ("ByteString" ++ show n ++ " specification") $ do
it "fromString === fromString . fromConstant"
. forAll ((:[]) <$> elements ['a'..'z']) $ testFromString @p

it "Zp embeds Integer" $ do
x <- toss m
Expand Down

0 comments on commit 34fd3ef

Please sign in to comment.