-- For Golden {-# LANGUAGE ExistentialQuantification #-} -- For Golden {-# LANGUAGE RankNTypes #-} module Goldens where import Data.List qualified as List import Relude import Symantic.Classes (ProductFunctor (..), SumFunctor (..)) import System.IO.Unsafe (unsafePerformIO) import Test.Tasty import Test.Tasty.Golden import Text.Printf (printf) import Examples.Ex01 qualified as Ex01 import Paths_webc import Utils import Webc test :: TestTree test = testGroup "Goldens" [ testGroup "Generator" $ (\f -> zipWith f goldens [1 :: Int ..]) $ \(Golden site) siteNum -> let siteDir = printf "Site%03d" siteNum in let expectedFile = getGoldenDir $ printf "Generator/%s/expected.txt" siteDir in goldenVsStringDiff siteDir goldenDiff expectedFile $ do return $ fromString $ List.unlines $ show <$> generate site , testGroup "Encoder" $ (\f -> zipWith f goldens [1 :: Int ..]) $ \(Golden site) siteNum -> let siteDir = printf "Site%03d" siteNum in testGroup siteDir $ (\f -> zipWith f (generate site) [1 :: Int ..]) $ \Gen{..} genNum -> let expectedFile = getGoldenDir $ printf "Encoder/%s/output%02d.expected.txt" siteDir genNum in goldenVsStringDiff (printf "output%02d" genNum) goldenDiff expectedFile $ do return $ fromString $ show $ encode site genValue ] getGoldenDir :: FilePath -> FilePath getGoldenDir p = unsafePerformIO $ getDataFileName $ "tests/Goldens/" <> p goldenDiff :: FilePath -> FilePath -> [String] goldenDiff ref new = ["diff", "-u", "-w", "-B", ref, new] data Golden = forall a. Show a => Golden (forall repr. Testable repr => repr a) goldens :: [Golden] goldens = [ Golden index , Golden ("foo" index) , Golden ("root" ("foo" index <+> "bar" index)) , Golden ( "root" ("a" literalSlug "b" <+> "c" literalSlug "d") <.> ("A" literalSlug "B" <+> "C" literalSlug "D") <. index ) , Golden Ex01.site ]