Skip to content

Commit

Permalink
Add tests for isValidUtf8ByteString and isValidUtf8ByteArray
Browse files Browse the repository at this point in the history
  • Loading branch information
Lysxia committed Jan 25, 2024
1 parent a0cf03a commit 7bf58e1
Show file tree
Hide file tree
Showing 3 changed files with 53 additions and 2 deletions.
4 changes: 3 additions & 1 deletion tests/Tests/Properties.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Tests.Properties.Substrings (testSubstrings)
import Tests.Properties.Read (testRead)
import Tests.Properties.Text (testText)
import Tests.Properties.Transcoding (testTranscoding)
import Tests.Properties.Validate (testValidate)

tests :: TestTree
tests =
Expand All @@ -28,5 +29,6 @@ tests =
testSubstrings,
testBuilder,
testLowLevel,
testRead
testRead,
testValidate
]
47 changes: 47 additions & 0 deletions tests/Tests/Properties/Validate.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,47 @@
{-# LANGUAGE CPP #-}
module Tests.Properties.Validate (testValidate) where

import Data.Array.Byte (ByteArray)
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import Data.ByteString.Short (toShort)
import Data.Either (isRight)
import Data.Text.Encoding (decodeUtf8', encodeUtf8)
import Data.Text.Internal.Validate (isValidUtf8ByteString, isValidUtf8ByteArray)
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.QuickCheck ((===), Gen, Property,
testProperty, arbitrary, forAllShrinkShow, forAllShrink, oneof, shrink)

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (ubuntu-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (windows-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

The import of ‘forAllShrinkShow’

Check warning on line 13 in tests/Tests/Properties/Validate.hs

View workflow job for this annotation

GitHub Actions / build (macOS-latest, latest)

The import of ‘forAllShrinkShow’
import Tests.QuickCheckUtils ()
#if MIN_VERSION_bytestring(0,12,0)
import Data.ByteString.Short (unShortByteString)
#else
import Data.ByteString.Short (ShortByteString(SBS))
import Data.Array.Byte (ByteArray(ByteArray))

unShortByteString :: ShortByteString -> ByteArray
unShortByteString (SBS ba) = ByteArray ba
#endif

testValidate :: TestTree
testValidate = testGroup "validate"
[ testProperty "bytestring" $ forAllShrink genByteString shrink $ \bs ->
isValidUtf8ByteString bs === isRight (decodeUtf8' bs)
-- We have all we need to shrink here but I'm too lazy to do that now.
, testProperty "bytearray" $ forAllByteArray $ \ba off len bs ->
isValidUtf8ByteArray ba off len === isRight (decodeUtf8' bs)
]

genByteString :: Gen ByteString
genByteString = oneof
[ arbitrary
, encodeUtf8 <$> arbitrary
]

-- | We want to test 'isValidUtf8ByteArray' with various offsets, so we insert a random
-- prefix and remember its length.
forAllByteArray :: (ByteArray -> Int -> Int -> ByteString -> Property) -> Property
forAllByteArray prop =
forAllShrink genByteString shrink $ \mainSlice ->
forAllShrink arbitrary shrink $ \prefix ->
let bs2ba = unShortByteString . toShort in
prop (bs2ba (prefix <> mainSlice)) (B.length prefix) (B.length mainSlice) mainSlice
4 changes: 3 additions & 1 deletion text.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -275,6 +275,7 @@ test-suite tests
Tests.Properties.Substrings
Tests.Properties.Text
Tests.Properties.Transcoding
Tests.Properties.Validate
Tests.QuickCheckUtils
Tests.RebindableSyntaxTest
Tests.Regressions
Expand All @@ -295,7 +296,8 @@ test-suite tests
template-haskell,
transformers,
text

if impl(ghc < 9.4)
build-depends: data-array-byte >= 0.1 && < 0.2
-- Plugin infrastructure does not work properly in 8.6.1, and
-- ghc-9.2.1 library depends on parsec, which causes a circular dependency.
if impl(ghc >= 8.2.1 && < 8.6 || >= 8.6.2 && < 9.2 || >= 9.2.2)
Expand Down

0 comments on commit 7bf58e1

Please sign in to comment.