-- | -- Module : Main -- Copyright : (c) Justus SagemΓΌller 2017 -- License : GPL v3 -- -- Maintainer : (@) sagemueller $ geo.uni-koeln.de -- Stability : experimental -- Portability : portable -- {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE CPP #-} module Main where import LaTeXComparer import Math.LaTeX.Prelude import Math.LaTeX.StringLiterals import Text.LaTeX (LaTeX, raw, Text) import qualified Text.LaTeX as LaTeX import qualified Data.Text as Txt import qualified Data.Text.IO as Txt import Data.Char import CAS.Dumb import System.FilePath import System.Directory import System.Process import Data.Monoid import Data.Function ((&)) import Control.Monad main :: IO () main = do examples <- evalTests tests Txt.writeFile "EXAMPLES.md" $ "_This file was generated automatically from [MkSnippets.hs](test/PdfSnippets/MkSnippets.hs). Run `cabal test` to refresh it._\n" <> examples tests :: TestTree tests = testGroup "Tests" [ testGroup "Simple expressions" [ [mkLaTeXSnip| π‘Ž + 𝑏 * 𝑐 |] "a+b{\\cdot}c" #if __GLASGOW_HASKELL__ > 802 , [mkLaTeXSnip| 𝐴 * 𝐡 + 𝐢 |] "A{\\cdot}B+C" #endif , [mkLaTeXSnip| (π‘Ž + 𝑏) * 𝑐 |] "\\left(a+b\\right){\\cdot}c" , [mkLaTeXSnip|(π‘Ž + 𝑏) / (π‘₯ - 𝑦) |] "\\frac{a+b}{x-y}" , [mkLaTeXSnip| (π‘Ž + 𝑏)**(π‘₯ - 𝑦) |] "\\left(a+b\\right)^{x-y}" , [mkLaTeXSnip| (𝑝/π‘ž)**Ξ³ |] "\\left(\\frac{p}{q}\\right)^{\\gamma{}}" , [mkLaTeXSnip| abs(𝑝/π‘ž)**ΞΎ |] "\\left|\\frac{p}{q}\\right|^{\\xi{}}" , [mkLaTeXSnip| π‘Ž**𝑏**𝑐 |] "a^{b^{c}}" , [mkLaTeXSnip| (π‘Ž**𝑏)**𝑐 |] "\\left(a^{b}\\right)^{c}" , [mkLaTeXSnip| sin (sin π‘₯) |] "\\sin{\\left(\\sin{x}\\right)}" , [mkLaTeXSnip| (𝑖⩡0,3)βˆ‘ 𝑖 |] "\\sum_{i=0}^{3} i" , [mkLaTeXSnip| matrix[[ 0,1] ,[-1,0]] |] "\\begin{pmatrix}0&1\\\\-1&0\\end{pmatrix}" ] , testGroup "Number literals" [ [mkLaTeXSnip| 25697325 |] "25697325" , [mkLaTeXSnip| 4.718 |] "4.718" , [mkLaTeXSnip| 1e-3 |] "1{\\cdot}10^{-3}" , [mkLaTeXSnip| 257.35e9 |] "2.5735{\\cdot}10^{11}" , [mkLaTeXSnip| -5.1e-8 |] "-5.1{\\cdot}10^{-8}" , [mkLaTeXSnip| 7/13 |] "\\frac{7}{13}" , [mkLaTeXSnip| -(1/2) |] "-\\frac{1}{2}" ] , testGroup "Operators" [ testGroup "Arithmetic" [ [mkLaTeXSnip| π‘Ž + 𝑏 |] "a+b" , [mkLaTeXSnip| π‘Ž - 𝑏 |] "a-b" , [mkLaTeXSnip| π‘Ž * 𝑏 |] "a{\\cdot}b" , [mkLaTeXSnip| π‘Ž Γ— 𝑏 |] "a\\times{}b" , [mkLaTeXSnip| π‘Ž Β± 𝑏 |] "a\\pm{}b" , [mkLaTeXSnip| π‘Ž βˆ“ 𝑏 |] "a\\mp{}b" , [mkLaTeXSnip| π‘Ž βŠ• 𝑏 |] "a\\oplus{}b" , [mkLaTeXSnip| π‘Ž βŠ— 𝑏 |] "a\\otimes{}b" ] , testGroup "Sub/superscripts" [ [mkLaTeXSnip| π‘Žβ—žπ‘ |] "a_{b}" , [mkLaTeXSnip| π‘Žβ—žβ—(𝑏,𝑐) |] "a_{b}^{c}" , [mkLaTeXSnip| Οˆβ—ž"Foo" |] "\\psi{}_{\\mathrm{Foo}}" #if __GLASGOW_HASKELL__ > 802 , [mkLaTeXSnip| Οˆβ—žπΉβ€π‘œβ€π‘œ |] "\\psi{}_{Foo}" #endif ] , testGroup "Function application" [ [mkLaTeXSnip| 𝑓°π‘₯ |] "f\\left(x\\right)" #if __GLASGOW_HASKELL__ > 802 , [mkLaTeXSnip| 𝑓°(π‘₯ΨŒπ‘¦) |] "f\\left(x,y\\right)" #endif ] , testGroup "Logical" [ [mkLaTeXSnip| 𝑝 ∨ π‘ž |] "p\\vee{}q" , [mkLaTeXSnip| 𝑝 ∧ π‘ž |] "p\\wedge{}q" , [mkLaTeXSnip| 𝑝==>π‘ž |] "p\\Longrightarrow q" , [mkLaTeXSnip| 𝑝<==π‘ž |] "p\\Longleftarrow q" , [mkLaTeXSnip| 𝑝<=>π‘ž |] "p\\Longleftrightarrow q" , [mkLaTeXSnip| 𝑝==>π‘ž==>π‘Ÿ |] "p\\Longrightarrow q\\Longrightarrow r" , [mkLaTeXSnip| cases[(1, "Today"), (2, "Else")] |] "\\begin{cases}1&\\text{Today}\\\\2&\\text{Else}\\end{cases}" ] , testGroup "Relations" [ [mkLaTeXSnip| π‘Ž β©΅ 𝑏 |] "a=b" , [mkLaTeXSnip| π‘Ž β‰₯ 𝑐 |] "a\\geq{}c" , [mkLaTeXSnip| π‘Ž βͺ‘ ρ |] "a<\\rho{}" , [mkLaTeXSnip| π‘₯ β©΅ 𝑦 β©΅ 𝑧 |] "x=y=z" , [mkLaTeXSnip| 𝑠 βŠ‚ 𝑑 βŠ† 𝑒 |] "s\\subset{}t\\subseteq{}u" #if __GLASGOW_HASKELL__ > 802 , [mkLaTeXSnip| 𝑝 ∈ β„š βŠ‚ ℝ |] "p\\in{}\\mathbb{Q}\\subset{}\\mathbb{R}" #endif ] ] , testGroup "Calculus" [ testGroup "Integration" [ [mkLaTeXSnip| (-1,1)∫d π‘₯ (π‘₯**2) |] "\\int\\limits_{-1}^{1}\\mathrm{d}x\\ x^{2}" , [mkLaTeXSnip| Ο‰β—žβˆ«d π‘₯ (exp $ -(π‘₯**2)) |] "\\int_{\\omega{}}\\!\\!\\!\\mathrm{d}x\\ \\exp{\\left(-x^{2}\\right)}" , [mkLaTeXSnip| (0,1)∫d π‘₯ ((0,1)∫d 𝑦 (π‘₯*𝑦)) |] "\\int\\limits_{0}^{1}\\mathrm{d}x\\ \\int\\limits_{0}^{1}\\mathrm{d}y\\ \\left(x{\\cdot}y\\right)" ] ] , testGroup "Algebraic manipulation" [ [mkLaTeXSnip| π‘Ž + 𝑏 + 𝑐 &~~! [𝑏 β©΅ 𝑦] |] "a+b+c=a+y+c" , [mkLaTeXSnip| π‘Ž + 𝑏 + 𝑐 &~~! [𝑏+𝑐 β©΅ 𝑐+𝑏, π‘Ž+𝑐 β©΅ ΞΎ] |] "a+b+c=\\xi{}+b" , [mkLaTeXSnip| π‘Ž - 𝑏 &~~! [𝑏 β©΅ 𝑦] &~~! [π‘Ž β©΅ 𝑧] |] "a-b=a-y=z-y" , [mkLaTeXSnip| π‘₯ + 𝑦 & continueExpr (β©΅) (&~: 𝑦 :=: π‘₯*(1+π‘₯)) & continueExpr (β©΅) (&~: π‘₯ :=: 2◝𝑝) |] "x+y=x+x{\\cdot}\\left(1+x\\right)=2^{p}+2^{p}{\\cdot}\\left(1+2^{p}\\right)" ] ] testGroup :: String -> [TestTree] -> TestTree testGroup = TestGroup evalTests :: TestTree -> IO Text evalTests = go False 1 where go hasHeader _ (TestCase e ec s) | s==s' = do let snipName = "test/PdfSnippets"encode (Txt.unpack s) doesFileExist (snipName<.>".png") >>= flip (when . not)`id` do Txt.writeFile ("expression.tex") $ Txt.unlines [ "\\documentclass[border=2pt]{standalone}" , "\\usepackage[utf8x]{inputenc}" , "\\usepackage{amsmath}" , "\\usepackage{amssymb}" , "\\pagestyle{empty}" , "\\begin{document}" , "$"<>s<>"$" , "\\end{document}" ] readProcess "pdflatex" ["expression.tex"] "" callProcess "convert" [ "-density","300" , "-background","grey", "-alpha","remove" , "expression.pdf", snipName<.>"png" ] return . (if hasHeader then id else (("| Haskell | LaTeX | pdf |" <>"\n| ---: | --- | :--- |\n")<>)) $ "| "<>mconcat["`"<>Txt.pack (dropWhile (==' ') ecl)<>"` " | ecl<-lines ec] <>"| `"<>mkGithubtablesaveCode s <>"` | ![pdflatex-rendered version of `"<>mkGithubtablesaveCode s <>"`]("<>Txt.pack(snipName<.>"png")<>") |\n" | otherwise = error $ "Got "<>show s'<>"; expected " <> show s<>", when rendering "<>ec where s' = LaTeX.render (toMathLaTeX e) go _ i (TestGroup g (sβ‚€:s)) = (Txt.pack (replicate i '#' <> " " <> g <> "\n") <>) . Txt.concat <$> ((:) <$> go False (i+1) sβ‚€ <*> mapM (go True $ i+1) s) encode :: String -> String encode = concatMap enc where enc c | isAlphaNum c = [c] enc '+' = "βΌ¦" enc '-' = "βΌ€" enc '\\' = "α“­" enc '{' = "⢈" enc '}' = "βΆ‰" enc '(' = "α‘•" enc ')' = "ᑐ" enc '^' = "ᐞ" enc '_' = "β£€" enc '|' = "ᛁ" enc '!' = "⒘" enc '&' = "ΰ²€" enc '=' = "〧" enc '<' = "ᐸ" enc '>' = "ᐳ" enc ',' = "،" enc '.' = "៰" enc ' ' = "ᐧ" enc c = error $ "Unencodable character '"++[c]++"'" mkGithubtablesaveCode :: Text -> Text mkGithubtablesaveCode = Txt.concatMap esc where esc '|' = "\\|" esc c = Txt.singleton c