]> Git — Sourcephile - haskell/literate-web.git/blob - tests/Goldens.hs
501a729341434e8728fa6b31b649668fe456cb61
[haskell/literate-web.git] / tests / Goldens.hs
1 {-# LANGUAGE AllowAmbiguousTypes #-}
2 -- For Golden
3 {-# LANGUAGE ExistentialQuantification #-}
4 {-# LANGUAGE ImportQualifiedPost #-}
5 {-# LANGUAGE PartialTypeSignatures #-}
6 -- For Golden
7 {-# LANGUAGE RankNTypes #-}
8 {-# OPTIONS_GHC -Wno-orphans #-}
9
10 module Goldens where
11
12 import Control.Monad.Classes qualified as MC
13 import Control.Monad.Trans.Reader as MT
14 import Data.ByteString.Lazy qualified as BSL
15 import Data.Functor.Identity (Identity (..))
16 import Data.Text qualified as Text
17 import Relude
18 import Symantic qualified as Sym
19 import System.FilePath qualified as Sys
20 import System.IO.Unsafe (unsafePerformIO)
21 import Test.Tasty
22 import Test.Tasty.Golden
23 import Text.Printf (printf)
24
25 import Examples.Ex01 qualified as Ex01
26 import Examples.Ex02 qualified as Ex02
27 import Examples.Ex03 qualified as Ex03
28 import Examples.Ex04 qualified as Ex04
29 import Examples.Ex05 qualified as Ex05
30 import Literate.Web
31 import Paths_literate_web
32 import Utils
33
34 test :: TestTree
35 test =
36 testGroup
37 "Goldens"
38 [ testGroup
39 "Compiler"
40 [ testGroup
41 (printf "Site%03d" siteNum)
42 [ withResource
43 (goldenCompiler CompilerEnv{..})
44 (\_ -> return ())
45 $ \compilerIO ->
46 testGroup
47 (printf "Model%02d" modelNum)
48 [ goldenVsFileDiff
49 (printf "/%s" destPath)
50 goldenDiff
51 (getGoldenDir (printf "Compiler/Site%03d/Model%02d/Expected/%s" siteNum modelNum destPath))
52 (compilerEnvDest Sys.</> destPath)
53 compilerIO
54 | destPath <- goldenManifest
55 ]
56 | (modelNum, Golden{..}) <- ol goldenModels
57 , let compilerEnvDest = getGoldenDir (printf "Compiler/Site%03d/Model%02d/Got/" siteNum modelNum)
58 , let compilerEnvIndex :: FilePath = "index.html"
59 -- , let compilerEnvSource = getGoldenDir (printf "Compiler/Site%03d/Model%02d/Source/" siteNum modelNum)
60 ]
61 | (siteNum, goldenModels) <- ol goldens
62 ]
63 ]
64
65 getGoldenDir :: FilePath -> FilePath
66 getGoldenDir p = unsafePerformIO $ getDataFileName $ "tests/Goldens/" <> p
67
68 goldenDiff :: FilePath -> FilePath -> [String]
69 goldenDiff ref new = ["diff", "-u", "-w", "-B", ref, new]
70
71 data Golden = Golden
72 { goldenCompiler :: CompilerEnv -> IO ()
73 , goldenManifest :: [Sys.FilePath]
74 }
75 goldens :: [[Golden]]
76 goldens =
77 {- [ Golden @() index [()]
78 , Golden @()
79 ("foo" </> index)
80 [()]
81 , Golden @(Either () ())
82 ("root" </> ("foo" </> index <+> "bar" </> index))
83 [()]
84 , Golden @(Either () (), Either () ())
85 ( "root"
86 </> ("a" </> literalSlug "b" <+> "c" </> literalSlug "d")
87 <.> ("A" </> literalSlug "B" <+> "C" </> literalSlug "D")
88 <. index
89 )
90 [()]
91 -}
92 [
93 [ Golden
94 { goldenCompiler = \env -> compile env Ex01.router Ex01.content
95 , goldenManifest = runIdentity $ manifest Ex01.router Ex01.content
96 }
97 ]
98 ,
99 [ Golden
100 { goldenCompiler = \env -> compile env Ex02.router Ex02.content
101 , goldenManifest = runIdentity $ manifest Ex02.router Ex02.content
102 }
103 ]
104 , [ Golden
105 { goldenCompiler = \env -> MT.runReaderT (compile env Ex03.router Ex03.content) model
106 , goldenManifest = runReader (manifest Ex03.router Ex03.content) model
107 }
108 | model <- [Ex03.model1, Ex03.model2]
109 ]
110 , [ Golden
111 { goldenCompiler = \env -> MT.runReaderT (compile env Ex04.router Ex04.content) model
112 , goldenManifest = runReader (manifest Ex04.router Ex04.content) model
113 }
114 | model <- [Ex04.model1]
115 ]
116 , [ Golden
117 { goldenCompiler = \env -> MT.runReaderT (MT.runReaderT (compile env Ex05.router Ex05.content) model03) model04
118 , goldenManifest = MT.runReader (MT.runReaderT (manifest Ex05.router Ex05.content) model03) model04
119 }
120 | model03 <- [Ex03.model1, Ex03.model2]
121 , model04 <- [Ex04.model1]
122 ]
123 ]