-- | -- Module : Main -- Copyright : (c) Justus Sagemรผller 2017 -- License : GPL v3 -- -- Maintainer : (@) jsag $ hvl.no -- 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 Text.LaTeX.Base.Math import Text.LaTeX.Packages.AMSFonts 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 CAS.Dumb.Symbols.ASCII hiding (d) import CAS.Dumb.Symbols.Unicode.MathLatin_RomanGreek__BopomofoGaps (Unicode_MathLatin_RomanGreek__BopomofoGaps) import System.FilePath import System.Directory import System.Process import Data.Monoid import Data.Function ((&)) import Control.Monad main :: IO () main = do examples_U <- evalTests tests_U Txt.writeFile "EXAMPLES.md" $ "_This file was generated automatically from [MkSnippets.hs](test/PdfSnippets/MkSnippets.hs). Run `cabal test` to refresh it._\n" <> examples_U examples_A <- evalTests tests_A Txt.writeFile "EXAMPLES_ASCII.md" $ "_This file was generated automatically from [MkSnippets.hs](test/PdfSnippets/MkSnippets.hs). Run `cabal test` to refresh it._\n" <> examples_A tests_A :: TestTree ASCII tests_A = testGroup "Tests" [ testGroup "Simple expressions" [ [mkLaTeXSnip| a + b * c |] "a+b{\\cdot}c" #if __GLASGOW_HASKELL__ > 801 , [mkLaTeXSnip| A * B + C |] "A{\\cdot}B+C" #endif , [mkLaTeXSnip| (a + b) * c |] "\\left(a+b\\right){\\cdot}c" , [mkLaTeXSnip|(a + b) / (x - y) |] "\\frac{a+b}{x-y}" , [mkLaTeXSnip| (a + b)**(x - y) |] "\\left(a+b\\right)^{x-y}" , [mkLaTeXSnip| (p/q)**gamma |] "\\left(\\frac{p}{q}\\right)^{\\gamma{}}" , [mkLaTeXSnip| abs(p/q)**xi |] "\\left|\\frac{p}{q}\\right|^{\\xi{}}" , [mkLaTeXSnip| a**b**c |] "a^{b^{c}}" , [mkLaTeXSnip| (a**b)**c |] "\\left(a^{b}\\right)^{c}" , [mkLaTeXSnip| sin (sin x) |] "\\sin{\\left(\\sin{x}\\right)}" , [mkLaTeXSnip| matrix[[ 0,1] ,[-1,0]] |] "\\begin{pmatrix}0&1\\\\ -1&0\\end{pmatrix}" ] , testGroup "Operators" [ testGroup "Arithmetic" [ [mkLaTeXSnip| a + b |] "a+b" , [mkLaTeXSnip| a - b |] "a-b" , [mkLaTeXSnip| a * b |] "a{\\cdot}b" , [mkLaTeXSnip| a `times` b |] "a\\times{}b" , [mkLaTeXSnip| a +- b |] "a\\pm{}b" , [mkLaTeXSnip| a -+ b |] "a\\mp{}b" , [mkLaTeXSnip| a `oplus` b |] "a\\oplus{}b" , [mkLaTeXSnip| a `otimes` b |] "a\\otimes{}b" ] , testGroup "Sub/superscripts" [ [mkLaTeXSnip| a!:b |] "{a}_{b}" , [mkLaTeXSnip| a!^(b,c) |] "{a}_{b}^{c}" , [mkLaTeXSnip| psi!:"Foo" |] "{\\psi{}}_{\\mathrm{Foo}}" , [mkLaTeXSnip| psi!:(F<>o<>o) |] "{\\psi{}}_{Foo}" ] , testGroup "Logical" [ [mkLaTeXSnip| p `vee` q |] "p\\vee{}q" , [mkLaTeXSnip| p `wedge` q |] "p\\wedge{}q" , [mkLaTeXSnip| cases[(1, "Today"), (2, "Else")] |] "\\begin{cases}1&\\text{Today}\\\\2&\\text{Else}\\end{cases}" ] , testGroup "Relations" [ [mkLaTeXSnip| a =: b |] "a=b" , [mkLaTeXSnip| a >=: c |] "a\\geq{}c" , [mkLaTeXSnip| a <: rho |] "a<\\rho{}" , [mkLaTeXSnip| x =: y =: z |] "x=y=z" , [mkLaTeXSnip| s `subset` t `subseteq` u |] "s\\subset{}t\\subseteq{}u" , [mkLaTeXSnip| h `approx` i `sim` j `simeq` k `cong` l |] "h\\approx{}i\\sim{}j\\simeq{}k\\cong{}l" , [mkLaTeXSnip| p `in_` mathbb Q `subset` mathbb R |] "p\\in{}\\mathbb{Q}\\subset{}\\mathbb{R}" , [mkLaTeXSnip| mathbf u `perp` (vec%$>v) `parallel` (underline%$>w) |] "\\mathbf{u}\\perp{}\\vec{v}\\parallel{}\\underline{w}" ] ] ] tests_U :: TestTree Unicode_MathLatin_RomanGreek__BopomofoGaps tests_U = testGroup "Tests" [ testGroup "Simple expressions" [ [mkLaTeXSnip| ๐‘Ž + ๐‘ * ๐‘ |] "a+b{\\cdot}c" #if __GLASGOW_HASKELL__ > 801 , [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| ๐‘Ž <ุŒ> ๐‘ |] "\\left\\langle{a,b}\\right\\rangle" , [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__ > 801 , [mkLaTeXSnip| ฯˆโ—ž๐นโ€๐‘œโ€๐‘œ |] "\\psi{}_{Foo}" , [mkLaTeXSnip| ๐‘“โ—โ€3ยฐ๐‘ฅ |] "f^{\\left(3\\right)}\\left(x\\right)" #endif ] , testGroup "Function application" [ [mkLaTeXSnip| ๐‘“ยฐ๐‘ฅ |] "f\\left(x\\right)" #if __GLASGOW_HASKELL__ > 801 , [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" , [mkLaTeXSnip| โ„Ž โ‰ˆ ๐‘” โˆผ ๐‘“ โ‰ƒ ๐‘’ โ‰… ๐‘‘ |] "h\\approx{}g\\sim{}f\\simeq{}e\\cong{}d" #if __GLASGOW_HASKELL__ > 801 , [mkLaTeXSnip| ๐‘ โˆˆ โ„š โŠ‚ โ„ |] "p\\in{}\\mathbb{Q}\\subset{}\\mathbb{R}" #endif , [mkLaTeXSnip| ๐ฎ โŸ‚ (vec%$>๐‘ฃ) โˆฅ (underline%$>๐‘ค) |] "\\mathbf{u}\\perp{}\\vec{v}\\parallel{}\\underline{w}" ] ] , 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 "Juxtaposition" [ [mkLaTeXSnip| ๐‘š + ๐‘โ€๐‘žโ€๐‘Ÿ |] "m+pqr" , [mkLaTeXSnip| ๐‘š + ๐‘โ€(2+๐‘ž)โ€๐‘Ÿ |] "m+p\\left(2+q\\right)r" , [mkLaTeXSnip| ๐‘š + (๐‘โฃ๐‘žโฃ๐‘Ÿ) |] "m+\\left(p\\ {}q\\ {}r\\right)" , [mkLaTeXSnip| ๐‘š + (๐‘โฃ2+๐‘žโฃ๐‘Ÿ) |] "m+\\left(p\\ {}2+q\\ {}r\\right)" , [mkLaTeXSnip| ๐‘š + (๐‘<>๐‘ž<>๐‘Ÿ) |] "m+pqr" , [mkLaTeXSnip| ๐‘š + (๐‘<>(2+๐‘ž)<>๐‘Ÿ) |] "m+\\left(p2+qr\\right)" , [mkLaTeXSnip| ๐‘š * ((1+2)<>(3+4)) |] "m{\\cdot}\\left(1+23+4\\right)" ] , testGroup "Set-builders" [ [mkLaTeXSnip| set(3ุŒ4ุŒ5) |] "\\left\\{3,4,5\\right\\}" , [mkLaTeXSnip| setCompr (๐‘ฅโ—2) (๐‘ฅโˆˆโ„•) |] "\\left\\{x^{2}\\middle|x\\in{}\\mathbb{N}\\right\\}" , [mkLaTeXSnip| setCompr (๐‘ฅ/๐‘ฆ) (๐‘ฅโˆˆโ„คุŒ ๐‘ฆโˆˆโ„•ุŒ ๐‘ฆโชข0) |] "\\left\\{\\frac{x}{y}\\middle|x\\in{}\\mathbb{Z},y\\in{}\\mathbb{N},y>0\\right\\}" , [mkLaTeXSnip| setCompr (๐‘ฅุŒ๐‘ฆ) (๐‘ฅโˆˆโ„คุŒ ๐‘ฆโˆˆโ„) |] "\\left\\{\\left(x,y\\right)\\middle|x\\in{}\\mathbb{Z},y\\in{}\\mathbb{R}\\right\\}" ] , testGroup "Misc" [ [mkLaTeXSnip| 3*๐‘ง - 1 |] "3{\\cdot}z-1" , [mkLaTeXSnip| ๐‘Ž-๐‘+๐‘ |] "a-b+c" , [mkLaTeXSnip| (๐‘ฅ/2)|โ—žโ—(๐‘ฅโฉต0,1) |] "\\left.\\frac{x}{2}\\right|_{x=0}^{1}" , TestCase (3 - 1 &~~! [ ใ„’-ใ„— โฉต -(ใ„—-ใ„’) ]) "3 - 1 &~~! [ ใ„’-ใ„— โฉต -(ใ„—-ใ„’) ]" "3-1= -\\left(1-3\\right)" , [mkLaTeXSnip| ๐‘Ž โˆ— ๐‘ |] "a\\ast{}b" , [mkLaTeXSnip| ๐‘Ž โ‹† ๐‘ |] "a\\star{}b" ] ] testGroup :: String -> [TestTree ฯƒ] -> TestTree ฯƒ testGroup = TestGroup evalTests :: (SymbolClass ฯƒ, SCConstraint ฯƒ LaTeX) => 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[codesnippetify $ mkGithubtablesaveCode(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) codesnippetify s | '`'`elem`(Txt.unpack s) = "``"<>s<>"`` " | otherwise = "`"<>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