{-# LANGUAGE ExistentialQuantification #-} module Goldens where import Control.Monad (Monad (..)) import Data.Either (Either (..)) import Data.Function (($)) import Data.Int (Int) import Data.List qualified as List import Data.Semigroup (Semigroup (..)) import Data.String (IsString (..), String) import Symantic.Classes (ProductFunctor (..), SumFunctor (..)) import System.IO (FilePath) import System.IO.Unsafe (unsafePerformIO) import Test.Tasty import Test.Tasty.Golden import Text.Printf (printf) import Text.Show (Show (..)) import Paths_webc import Webc test :: TestTree test = testGroup "Goldens" [ testGroup "Encoder" $ (\f -> List.zipWith f goldens [1 :: Int ..]) $ \(Golden site inps) siteNum -> let siteDir = printf "Site%03d" siteNum in testGroup siteDir $ (\f -> List.zipWith f inps [1 :: Int ..]) $ \inp inpNum -> let expectedFile = getGoldenDir $ printf "Encoder/%s/Input%02d.expected.txt" siteDir inpNum in goldenVsStringDiff (printf "Input%02d" inpNum) goldenDiff expectedFile $ do return $ fromString $ show $ encode site inp , testGroup "Layouter" $ (\f -> List.zipWith f goldens [1 :: Int ..]) $ \(Golden site _) siteNum -> let siteDir = printf "Site%03d" siteNum in let expectedFile = getGoldenDir $ printf "Layouter/%s/expected.txt" siteDir in goldenVsStringDiff siteDir goldenDiff expectedFile $ do return $ fromString $ show $ layouter site ] 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 repr = forall inp. Show inp => Golden (repr inp) [inp] goldens :: ProductFunctor repr => SumFunctor repr => Slugable repr => [Golden repr] goldens = [ Golden index [()] , Golden ("foo" index) [()] , Golden ( "root" ( "foo" index <+> "bar" index ) ) [ Left () , Right () ] ]