@@ 0,0 1,230 @@
+module Data.Text.ParagraphLayout.Internal.BiDiReorderSpec where
+
+import Data.Foldable (toList)
+import Data.List.NonEmpty (NonEmpty, fromList)
+import Data.Word (Word8)
+
+import Test.Hspec
+import Data.Text.ParagraphLayout.Internal.BiDiReorder
+
+ne :: [a] -> NonEmpty a
+ne = fromList
+
+data ExampleItem = ExampleItem Word8 String
+ deriving (Eq, Show)
+
+instance WithLevel ExampleItem where
+ level (ExampleItem lvl _) = lvl
+
+toString :: ExampleItem -> String
+toString (ExampleItem _ str) = str
+
+toStrings :: Foldable t => t ExampleItem -> [String]
+toStrings = map toString . toList
+
+singleItemLevel :: Level -> NonEmpty ExampleItem
+singleItemLevel lvl = ne
+ [ ExampleItem lvl "item"
+ ]
+
+flatLevel :: Level -> NonEmpty ExampleItem
+flatLevel lvl = ne
+ [ ExampleItem lvl "start"
+ , ExampleItem lvl "mid"
+ , ExampleItem lvl "end"
+ ]
+
+-- | Example 1 from <https://www.unicode.org/reports/tr9/#L2>,
+-- split into words and individual punctuation marks.
+example1Words :: NonEmpty ExampleItem
+example1Words = ne
+ [ ExampleItem 0 "car"
+ , ExampleItem 0 "means"
+ , ExampleItem 1 "CAR"
+ , ExampleItem 0 "."
+ ]
+
+-- | Example 2 from <https://www.unicode.org/reports/tr9/#L2>,
+-- split into words and individual punctuation marks.
+example2Words :: NonEmpty ExampleItem
+example2Words = ne
+ [ ExampleItem 2 "car"
+ , ExampleItem 1 "MEANS"
+ , ExampleItem 1 "CAR"
+ , ExampleItem 1 "."
+ ]
+
+-- | Example 3 from <https://www.unicode.org/reports/tr9/#L2>,
+-- split into words and individual punctuation marks.
+example3Words :: NonEmpty ExampleItem
+example3Words = ne
+ [ ExampleItem 0 "he"
+ , ExampleItem 0 "said"
+ , ExampleItem 0 "“"
+ , ExampleItem 2 "car"
+ , ExampleItem 1 "MEANS"
+ , ExampleItem 1 "CAR"
+ , ExampleItem 0 "."
+ , ExampleItem 0 "”"
+ , ExampleItem 0 "“"
+ , ExampleItem 1 "IT"
+ , ExampleItem 1 "DOES"
+ , ExampleItem 0 ","
+ , ExampleItem 0 "”"
+ , ExampleItem 0 "she"
+ , ExampleItem 0 "agreed"
+ , ExampleItem 0 "."
+ ]
+
+-- | Example 4 from <https://www.unicode.org/reports/tr9/#L2>,
+-- split into words and individual punctuation marks.
+example4Words :: NonEmpty ExampleItem
+example4Words = ne
+ [ ExampleItem 1 "DID"
+ , ExampleItem 1 "YOU"
+ , ExampleItem 1 "SAY"
+ , ExampleItem 1 "’"
+ , ExampleItem 2 "he"
+ , ExampleItem 2 "said"
+ , ExampleItem 2 "“"
+ , ExampleItem 4 "car"
+ , ExampleItem 3 "MEANS"
+ , ExampleItem 3 "CAR"
+ , ExampleItem 2 "”"
+ , ExampleItem 1 "‘"
+ , ExampleItem 1 "?"
+ ]
+
+-- | Example 4 from <https://www.unicode.org/reports/tr9/#L2>,
+-- split into individual characters.
+example4Characters :: NonEmpty ExampleItem
+example4Characters = ne
+ [ ExampleItem 1 "D"
+ , ExampleItem 1 "I"
+ , ExampleItem 1 "D"
+ , ExampleItem 1 " "
+ , ExampleItem 1 "Y"
+ , ExampleItem 1 "O"
+ , ExampleItem 1 "U"
+ , ExampleItem 1 " "
+ , ExampleItem 1 "S"
+ , ExampleItem 1 "A"
+ , ExampleItem 1 "Y"
+ , ExampleItem 1 " "
+ , ExampleItem 1 "’"
+ , ExampleItem 1 ">"
+ , ExampleItem 2 "h"
+ , ExampleItem 2 "e"
+ , ExampleItem 2 " "
+ , ExampleItem 2 "s"
+ , ExampleItem 2 "a"
+ , ExampleItem 2 "i"
+ , ExampleItem 2 "d"
+ , ExampleItem 2 " "
+ , ExampleItem 2 "“"
+ , ExampleItem 2 "<"
+ , ExampleItem 4 "c"
+ , ExampleItem 4 "a"
+ , ExampleItem 4 "r"
+ , ExampleItem 3 " "
+ , ExampleItem 3 "M"
+ , ExampleItem 3 "E"
+ , ExampleItem 3 "A"
+ , ExampleItem 3 "N"
+ , ExampleItem 3 "S"
+ , ExampleItem 3 " "
+ , ExampleItem 3 "C"
+ , ExampleItem 3 "A"
+ , ExampleItem 3 "R"
+ , ExampleItem 2 "="
+ , ExampleItem 2 "”"
+ , ExampleItem 1 "="
+ , ExampleItem 1 "‘"
+ , ExampleItem 1 "?"
+ ]
+
+spec :: Spec
+spec = do
+
+ describe "reorder" $ do
+
+ it "passes through single item at level 0" $ do
+ toStrings (reorder $ singleItemLevel 0) `shouldBe` ["item"]
+
+ it "passes through single item at level 1" $ do
+ toStrings (reorder $ singleItemLevel 1) `shouldBe` ["item"]
+
+ it "passes through single item at level 2" $ do
+ toStrings (reorder $ singleItemLevel 2) `shouldBe` ["item"]
+
+ it "passes through single item at level 3" $ do
+ toStrings (reorder $ singleItemLevel 3) `shouldBe` ["item"]
+
+ it "does not reverse at level 0" $ do
+ toStrings (reorder $ flatLevel 0) `shouldBe` ["start", "mid", "end"]
+
+ it "reverses at level 1" $ do
+ toStrings (reorder $ flatLevel 1) `shouldBe` ["end", "mid", "start"]
+
+ it "does not reverse at level 2" $ do
+ toStrings (reorder $ flatLevel 2) `shouldBe` ["start", "mid", "end"]
+
+ it "reverses at level 3" $ do
+ toStrings (reorder $ flatLevel 3) `shouldBe` ["end", "mid", "start"]
+
+ it "reorders UAX #9 example 1 as words" $
+ toStrings (reorder example1Words) `shouldBe`
+ [ "car"
+ , "means"
+ , "CAR"
+ , "."
+ ]
+
+ it "reorders UAX #9 example 2 as words" $
+ toStrings (reorder example2Words) `shouldBe`
+ [ "."
+ , "CAR"
+ , "MEANS"
+ , "car"
+ ]
+
+ it "reorders UAX #9 example 3 as words" $
+ toStrings (reorder example3Words) `shouldBe`
+ [ "he"
+ , "said"
+ , "“"
+ , "CAR"
+ , "MEANS"
+ , "car"
+ , "."
+ , "”"
+ , "“"
+ , "DOES"
+ , "IT"
+ , ","
+ , "”"
+ , "she"
+ , "agreed"
+ , "."
+ ]
+
+ it "reorders UAX #9 example 4 as words" $
+ toStrings (reorder example4Words) `shouldBe`
+ [ "?"
+ , "‘"
+ , "he"
+ , "said"
+ , "“"
+ , "CAR"
+ , "MEANS"
+ , "car"
+ , "”"
+ , "’"
+ , "SAY"
+ , "YOU"
+ , "DID"
+ ]
+
+ it "reorders UAX #9 example 4 as characters" $
+ concat (toStrings (reorder example4Characters)) `shouldBe`
+ "?‘=he said “<RAC SNAEM car=”>’ YAS UOY DID"