File: Main.hs

package info (click to toggle)
haskell-typst 0.5.0.1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 16,564 kB
  • sloc: haskell: 8,314; xml: 32; makefile: 6
file content (75 lines) | stat: -rw-r--r-- 2,454 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}

module Main (main) where

import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Text.IO as TIO
import System.FilePath (replaceExtension)
import Test.Tasty (TestTree, Timeout (..), defaultMain, localOption, testGroup)
import Test.Tasty.Golden (findByExtension, goldenVsStringDiff)
import Text.Show.Pretty (ppShow)
import Typst.Evaluate (evaluateTypst)
import Typst.Parse (parseTypst)
import Typst.Types (Val (VContent), repr, Operations(..))
import Data.Time (getCurrentTime)
import System.Directory (doesFileExist)
import System.Environment (lookupEnv)

main :: IO ()
main = defaultMain =<< goldenTests

operations :: Operations IO
operations = Operations
  { loadBytes = BS.readFile
  , currentUTCTime = getCurrentTime
  , lookupEnvVar = lookupEnv
  , checkExistence = doesFileExist
  }

goldenTests :: IO TestTree
goldenTests = do
  inputs <- findByExtension [".typ"] "test/typ"
  pure $
    localOption (Timeout 1000000 "1s") $
      testGroup "golden tests" (map runTest inputs)

runTest :: FilePath -> TestTree
runTest input =
  goldenVsStringDiff
    input
    (\ref new -> ["diff", "-u", ref, new])
    ("test/out" <> drop 8 (replaceExtension input ".out"))
    (writeTest input)

writeTest :: FilePath -> IO BL.ByteString
writeTest input = do
  let fromText = BL.fromStrict . TE.encodeUtf8 . (<> "\n")
  let testCommand =
        "#let test = (x,y) => { if x == y [✅] else [❌(#repr(x) /= #repr(y))] }\n"
  contents <- TIO.readFile input
  if "// Error"
    `T.isInfixOf` contents
    || "cycle1.typ"
    `T.isInfixOf` contents
    || "cycle2.typ"
    `T.isInfixOf` contents
    then pure $ fromText "--- skipped ---\n"
    else do
      let parseResult = parseTypst input (testCommand <> contents)
      case parseResult of
        Left e -> pure $ fromText $ T.pack $ show e
        Right parsed -> do
          evalResult <- evaluateTypst operations input parsed
          let parseOutput = "--- parse tree ---\n" <> T.pack (ppShow parsed) <> "\n"
          case evalResult of
            Left e ->
              pure $
                fromText $
                  parseOutput <> T.pack (show e)
            Right c -> do
              let evalOutput = "--- evaluated ---\n" <> repr (VContent [c])
              pure $ fromText $ parseOutput <> evalOutput