]> Git — Sourcephile - haskell/symantic-parser.git/blob - test/Golden.hs
stick to ParsleyHaskell's optimizations, except on pattern-matching at the Haskell...
[haskell/symantic-parser.git] / test / Golden.hs
1 {-# LANGUAGE NoMonomorphismRestriction #-}
2 {-# LANGUAGE Rank2Types #-}
3 {-# LANGUAGE TemplateHaskell #-}
4 {-# LANGUAGE UnboxedTuples #-}
5 module Golden where
6
7 import Control.Monad (Monad(..))
8 import Data.Char (Char)
9 import Data.Either (Either(..))
10 import Data.Function (($))
11 import Data.Semigroup (Semigroup(..))
12 import Data.String (String, IsString(..))
13 import Data.Text (Text)
14 import Data.Text.IO (readFile)
15 import System.IO (IO, FilePath)
16 import Test.Tasty
17 import Test.Tasty.Golden
18 import Text.Show (Show(..))
19 import qualified Data.ByteString.Lazy as BSL
20 import qualified Data.IORef as IORef
21 import qualified Data.Text.Lazy as TL
22 import qualified Data.Text.Lazy.Encoding as TL
23 import qualified Language.Haskell.TH.Syntax as TH
24
25 import qualified Symantic.Parser as P
26 import qualified Symantic.Parser.Haskell as H
27 import qualified Parser
28 --import Golden.Utils
29
30 goldensIO :: IO TestTree
31 goldensIO = return $ testGroup "Golden"
32 [ goldensGrammar
33 -- Commented-out for the release
34 -- because resetTHNameCounter is not enough:
35 -- TH names still change between runs
36 -- with and without --accept
37 , goldensMachine
38 , goldensParser
39 ]
40
41 goldensGrammar :: TestTree
42 goldensGrammar = testGroup "Grammar"
43 [ testGroup "ViewGrammar" $ tests $ \name repr ->
44 let file = "test/Golden/Grammar/"<>name<>".dump" in
45 goldenVsStringDiff file diffGolden file $ do
46 resetTHNameCounter
47 return $ fromString $ show $
48 P.viewGrammar $ P.observeSharing repr
49 , testGroup "OptimizeGrammar" $ tests $ \name repr ->
50 let file = "test/Golden/Grammar/"<>name<>".opt.dump" in
51 goldenVsStringDiff file diffGolden file $ do
52 resetTHNameCounter
53 return $ fromString $ show $
54 P.viewGrammar $ P.optimizeGrammar $ P.observeSharing repr
55 ]
56 where
57 tests :: P.Grammar repr =>
58 P.Satisfiable repr Char =>
59 (forall a. String -> repr a -> TestTree) -> [TestTree]
60 tests test =
61 [ test "unit" $ P.unit
62 , test "unit-unit" $ P.unit P.*> P.unit
63 , test "app" $ P.pure H.id P.<*> P.unit
64 , test "string" $ P.string "abcd"
65 , test "tokens" $ P.tokens "abcd"
66 , test "many-a" $ P.many (P.char 'a')
67 , test "boom" $ Parser.boom
68 , test "brainfuck" $ Parser.brainfuck
69 , test "many-char-eof" $ P.many (P.char 'r') P.<* P.eof
70 , test "eof" $ P.eof
71 , test "nandlang" $ Parser.nandlang
72 ]
73
74 goldensMachine :: TestTree
75 goldensMachine = testGroup "Machine"
76 [ testGroup "DumpInstr" $ tests $ \name repr ->
77 let file = "test/Golden/Machine/"<>name<>".dump" in
78 goldenVsStringDiff file diffGolden file $ do
79 resetTHNameCounter
80 return $ fromString $ show $
81 P.viewInstr $ {-P.machine @() $ -}repr
82 ]
83 where
84 tests ::
85 P.Executable repr =>
86 P.Readable repr Char =>
87 (forall vs es ret. String -> repr Text vs es ret -> TestTree) -> [TestTree]
88 tests test =
89 [ test "unit" $ P.machine $ P.unit
90 , test "unit-unit" $ P.machine $ P.unit P.*> P.unit
91 , test "string" $ P.machine $ P.string "abcd"
92 , test "a-or-b" $ P.machine $ P.char 'a' P.<|> P.char 'b'
93 , test "app" $ P.machine $ P.pure H.id P.<*> P.unit
94 , test "many-a" $ P.machine $ P.many (P.char 'a')
95 , test "some-string" $ P.machine $ P.some (P.string "abcd")
96 , test "boom" $ P.machine $ Parser.boom
97 , test "brainfuck" $ P.machine $ Parser.brainfuck
98 , test "many-char-eof" $ P.machine $ P.many (P.char 'r') P.<* P.eof
99 , test "eof" $ P.machine $ P.eof
100 , test "many-char-fail" $ P.machine $ P.many (P.char 'a') P.<* P.char 'b'
101 , test "nandlang" $ P.machine $ Parser.nandlang
102 ]
103
104 goldensParser :: TestTree
105 goldensParser = testGroup "Parser"
106 [ testGroup "runParser" $ tests $ \name p ->
107 let file = "test/Golden/Parser/"<>name in
108 goldenVsStringDiff (file<>".txt") diffGolden (file<>".dump") $ do
109 input :: Text <- readFile (file<>".txt")
110 return $ fromString $
111 case p input of
112 Left err -> show err
113 Right a -> show a
114 ]
115 where
116 tests :: (forall a. Show a => String -> (Text -> Either (P.ParsingError Text) a) -> TestTree) -> [TestTree]
117 tests test =
118 [ test "char" $$(P.runParser $ P.char 'a')
119 , test "string" $$(P.runParser $ P.string "abc")
120 , test "string-fail-horizon" $$(P.runParser $ P.string "abc")
121 , test "many-char" $$(P.runParser $ P.many (P.char 'a'))
122 , test "some-string" $$(P.runParser $ P.some (P.string "abcd"))
123 , test "some-string-fail" $$(P.runParser $ P.some (P.string "abcd"))
124 , test "some-string-eof-fail" $$(P.runParser $ P.some (P.string "abcd") P.<* P.eof)
125 , test "alt-right-notry" $$(P.runParser $ P.traverse P.char "aa" P.<|> P.traverse P.char "ab")
126 , test "alt-right-try" $$(P.runParser $ P.string "aa" P.<|> P.string "ab")
127 , test "alt-left" $$(P.runParser $ P.string "aa" P.<|> P.string "ab")
128 , test "many-char-eof" $$(P.runParser $ P.many (P.char 'r') P.<* P.eof)
129 , test "eof" $$(P.runParser $ P.eof)
130 , test "eof-fail" $$(P.runParser $ P.eof)
131 , test "alt-char-fail" $$(P.runParser $ P.char 'a' P.<|> P.char 'b')
132 , test "many-char-fail" $$(P.runParser $ P.many (P.char 'a') P.<* P.char 'b')
133 , test "many-oneOf" $$(P.runParser $ P.many (P.oneOf ['a', 'b', 'c', 'd']) P.<* P.eof)
134 ]
135
136 -- | Resetting 'TH.counter' makes 'makeLetName' deterministic,
137 -- except when flags change, like profiling
138 -- or even --accept unfortunately,
139 -- in those case the 'goldensMachine' tests may fail
140 -- due to a different numbering of the 'def' and 'ref' combinators.
141 resetTHNameCounter :: IO ()
142 resetTHNameCounter = IORef.writeIORef TH.counter 0
143
144 -- * Golden testing utilities
145
146 diffGolden :: FilePath -> FilePath -> [String]
147 diffGolden ref new = ["diff", "-u", ref, new]
148
149 unLeft :: Either String BSL.ByteString -> IO BSL.ByteString
150 unLeft = \case
151 Left err -> return $ TL.encodeUtf8 $ TL.pack err
152 Right a -> return a