Skip to content

Commit

Permalink
scripts: Add ICU test
Browse files Browse the repository at this point in the history
Allow ICU tests to fail if Unicode version mismatch
  • Loading branch information
wismill committed Jun 15, 2024
1 parent 432aad1 commit dc4ccb7
Show file tree
Hide file tree
Showing 5 changed files with 281 additions and 147 deletions.
9 changes: 4 additions & 5 deletions unicode-data-names/test/ICU/NamesSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,6 @@ spec = do
#endif
where
ourUnicodeVersion = versionBranch U.unicodeVersion
theirUnicodeVersion = versionBranch ICU.unicodeVersion
showCodePoint c = ("U+" ++) . fmap U.toUpper . showHex (U.ord c)

-- There is no feature to display warnings other than `trace`, so
Expand Down Expand Up @@ -85,8 +84,7 @@ spec = do
| n == nRef = acc
-- Unicode version mismatch: char is not mapped in one of the libs:
-- add warning.
| age' > ourUnicodeVersion || age' > theirUnicodeVersion
= acc{warnings=c : warnings acc}
| ageMismatch c = acc{warnings=c : warnings acc}
-- Error
| otherwise =
let !msg = mconcat
Expand All @@ -97,8 +95,6 @@ spec = do
where
!n = f c
!nRef = fRef c
age = ICU.charAge c
age' = take 3 (versionBranch age)
mkWarning c = it (showCodePoint c "") . pendingWith $ mconcat
[ "Incompatible ICU Unicode version: expected "
, showVersion U.unicodeVersion
Expand All @@ -107,5 +103,8 @@ spec = do
, " (ICU character age is: "
, showVersion (ICU.charAge c)
, ")" ]
ageMismatch c =
let age = take 3 (versionBranch (ICU.charAge c))
in age > ourUnicodeVersion || age == [0, 0, 0]

data Acc = Acc { warnings :: ![Char], firstError :: !(Maybe String) }
108 changes: 108 additions & 0 deletions unicode-data-scripts/test/ICU/ScriptsSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,108 @@
{-# LANGUAGE BlockArguments #-}

module ICU.ScriptsSpec
( spec
) where

import Data.Char (toUpper, ord)
import Data.Foldable (traverse_)
import qualified Data.List as L
import qualified Data.List.NonEmpty as NE
import Data.Maybe (isJust)
import Data.Version (versionBranch, showVersion)
import Debug.Trace (traceM)
import Numeric (showHex)
import Test.Hspec ( Spec, it, expectationFailure, shouldSatisfy )

import qualified ICU.Char as ICU
import qualified ICU.Scripts as ICU
import qualified Unicode.Char.General.Scripts as S

spec :: Spec
spec = do
let icuScripts = (\s -> (ICU.scriptShortName s, s)) <$> [minBound..maxBound]
it "scriptShortName"
let check = isJust . (`lookup` icuScripts) . S.scriptShortName
in traverse_ (`shouldSatisfy` check) [minBound..maxBound]
it "script"
let check c
| s == sRef = pure ()
| versionMismatch = traceM . mconcat $
[ "[WARNING] Cannot test "
, showCodePoint c
, ": incompatible ICU version ("
, showVersion ICU.unicodeVersion
, " /= "
, showVersion S.unicodeVersion
, "). Expected "
, show sRef
, ", but got: "
, show s ]
| otherwise = expectationFailure $ mconcat
[ show c, ": expected “", sRef, "”, got “", s, "" ]
where
!s = S.scriptShortName (S.script c)
!sRef = ICU.scriptShortName (ICU.script c)
in traverse_ check [minBound..maxBound]
it "scriptDefinition"
let {
check s =
case lookup (S.scriptShortName s) icuScripts of
Nothing -> error ("Cannot convert script: " ++ show s)
Just s'
| def == defRef -> pure ()
| ourUnicodeVersion /= theirUnicodeVersion -> traceM . mconcat $
[ "[WARNING] Cannot test "
, show s
, ": incompatible ICU version ("
, showVersion ICU.unicodeVersion
, " /= "
, showVersion S.unicodeVersion
, ")."
, if null missing
then ""
else " Missing: " ++ show missing
, "."
, if null unexpected
then ""
else " Unexpected: " ++ show unexpected
]
| otherwise -> expectationFailure $ mconcat
[ show s
, ": expected “", show def
, "”, got “", show defRef, "" ]
where
!defRef = filter ((== s') . ICU.script) [minBound..maxBound]
!def = S.scriptDefinition s
(missing, unexpected) = case s of
-- No diff for “Unknown” script, lists are too big
S.Unknown -> mempty
_ -> (defRef L.\\ def, def L.\\ defRef)
} in traverse_ check [minBound..maxBound]
it "scriptExtensions"
let check c
| es == esRef = pure ()
| versionMismatch = traceM . mconcat $
[ "[WARNING] Cannot test "
, showCodePoint c
, ": incompatible ICU version ("
, showVersion ICU.unicodeVersion
, " /= "
, showVersion S.unicodeVersion
, "). Expected "
, show esRef
, ", but got: "
, show es ]
| otherwise = expectationFailure $ mconcat
[ show c
, ": expected “", show esRef
, "”, got “", show es, "" ]
where
!es = NE.sort (S.scriptShortName <$> S.scriptExtensions c)
!esRef = NE.sort (ICU.scriptShortName <$> ICU.scriptExtensions c)
in traverse_ check [minBound..maxBound]
where
ourUnicodeVersion = versionBranch S.unicodeVersion
theirUnicodeVersion = take 3 (versionBranch ICU.unicodeVersion)
showCodePoint c = ("U+" ++) . fmap toUpper $ showHex (ord c) ""
versionMismatch = ourUnicodeVersion /= theirUnicodeVersion
11 changes: 10 additions & 1 deletion unicode-data-scripts/test/Main.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,19 @@
{-# LANGUAGE CPP #-}

module Main where

import Test.Hspec
import qualified Unicode.Char.General.ScriptsSpec as Scripts
#ifdef HAS_ICU
import qualified ICU.ScriptsSpec as ICU
#endif

main :: IO ()
main = hspec spec

spec :: Spec
spec = describe "Unicode.Char.General.Scripts" Scripts.spec
spec = do
describe "Unicode.Char.General.Scripts" Scripts.spec
#ifdef HAS_ICU
describe "ICU.Scripts" ICU.spec
#endif
Loading

0 comments on commit dc4ccb7

Please sign in to comment.