summaryrefslogtreecommitdiff
path: root/provider
diff options
context:
space:
mode:
Diffstat (limited to 'provider')
-rw-r--r--provider/css/default.css2
-rw-r--r--provider/css/math.css49
-rw-r--r--provider/posts/tex-support.md235
-rw-r--r--provider/templates/default.html1
-rw-r--r--provider/templates/math.tex2
5 files changed, 284 insertions, 5 deletions
diff --git a/provider/css/default.css b/provider/css/default.css
index 8f796e0..2d2a777 100644
--- a/provider/css/default.css
+++ b/provider/css/default.css
@@ -25,5 +25,5 @@ pre {
25} 25}
26 26
27p code { 27p code {
28 font-style:italic; 28 font-style:italic;
29} \ No newline at end of file 29} \ No newline at end of file
diff --git a/provider/css/math.css b/provider/css/math.css
new file mode 100644
index 0000000..4dc0dd7
--- /dev/null
+++ b/provider/css/math.css
@@ -0,0 +1,49 @@
1span.inline-math {
2 display:inline;
3}
4
5span.display-math {
6 display:block;
7 text-align:center;
8 margin-top:0.2em;
9 margin-bottom:0.2em;
10}
11
12div.theorem, div.lemma, div.definition, div.corollary, div.proof {
13 margin-left: 2em;
14 margin-top: 1em;
15 margin-bottom: 1em;
16}
17
18div.theorem > p:first-child:before {
19 content: "Theorem. ";
20 font-weight: bold;
21}
22
23div.lemma > p:first-child:before {
24 content: "Lemma. ";
25 font-weight: bold;
26}
27
28div.definition > p:first-child:before {
29 content: "Definition. ";
30 font-weight: bold;
31}
32
33div.corollary > p:first-child:before {
34 content: "Corollary. ";
35 font-weight: bold;
36}
37
38div.proof > p:first-child:before {
39 content: "Proof. ";
40 font-style: italic;
41}
42
43div.proof > p:last-child:after {
44 content: " ∎";
45}
46
47div.theorem + div.proof {
48 margin-top: -1em;
49} \ No newline at end of file
diff --git a/provider/posts/tex-support.md b/provider/posts/tex-support.md
index 16468ca..0beade1 100644
--- a/provider/posts/tex-support.md
+++ b/provider/posts/tex-support.md
@@ -1,14 +1,243 @@
1--- 1---
2title: Cursory LaTeX-Support 2title: Cursory Math-Support
3published: 2015-11-05 3published: 2015-11-05
4tags: Blog Software 4tags: Blog Software
5--- 5---
6 6
7I added some cursory support for LaTeX as shown below: 7## Demonstration
8
9I added some cursory support for math as shown below:
8 10
9<div class="theorem"> 11<div class="theorem">
12
13Formulae are rendered with $\text{\LaTeX}$ and included as [SVG](https://en.wikipedia.org/wiki/SVG).
14
15<div class="proof">
10$$e^{ix} =\text{cos}(x) + i \text{sin} (x)$$ 16$$e^{ix} =\text{cos}(x) + i \text{sin} (x)$$
11</div> 17</div>
18<div class="lemma">
19
20Inline formulae get correctly aligned to match the baseline of the surrounding text.
21
22<div class="proof">
23$\text{tan}(\phi) = \frac{\text{sin}(\phi)}{\text{cos}(\phi)}$
24</div>
25</div>
26</div>
27
28## Implementation
29
30Theorem environments are written using [pandoc](http://pandoc.org)s support for block environments:
31
32~~~ {.markdown .numberLines}
12<div class="theorem"> 33<div class="theorem">
13$$\text{tan}(\phi) = \frac{\text{sin}(\phi)}{\text{cos}(\phi)}$$ 34
35Formulae are rendered with $\text{\LaTeX}$ and included as [SVG](https://en.wikipedia.org/wiki/SVG).
36
37<div class="proof">
38$$e^{ix} =\text{cos}(x) + i \text{sin} (x)$$
39</div>
40<div class="lemma">
41
42Inline formulae get correctly aligned to match the baseline of the surrounding text.
43
44<div class="proof">
45$\text{tan}(\phi) = \frac{\text{sin}(\phi)}{\text{cos}(\phi)}$
46</div>
47</div>
14</div> 48</div>
49~~~
50
51Combined with a smattering of CSS this works nicely.
52$\text{\LaTeX}$ support is, however, lacking as I opted not to patch pandoc ([math.kleen.org](https://math.kleen.org) did).
53
54### `Math.hs`
55
56The actual compilation happens in a new module I named `Math.hs`. We´ll start there.
57For your reading pleasure I added some comments to the reproduction below.
58
59~~~ {.haskell .numberLines}
60module Math
61 ( compileMath
62 ) where
63
64import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile)
65import System.IO.Temp (withSystemTempDirectory)
66import System.Process (callProcess, readProcessWithExitCode)
67import System.Directory (copyFile, getCurrentDirectory, setCurrentDirectory)
68import System.FilePath (takeFileName, FilePath(..), (</>))
69import System.Exit (ExitCode(..))
70
71import Control.Monad (when)
72import Control.Exception (bracket, throwIO)
73import Data.Maybe (fromMaybe, listToMaybe)
74
75import Control.Monad.Writer.Strict (WriterT(..), execWriterT, tell)
76import Control.Monad.Trans (liftIO)
77
78import Control.DeepSeq (($!!))
79
80import Text.Regex.TDFA ((=~))
81
82-- We built a monoid instance for `ExitCode` so we can easily collect failure using a `MonadWriter`
83instance Monoid ExitCode where
84 mempty = ExitSuccess
85 (ExitFailure a) `mappend` _ = ExitFailure a
86 ExitSuccess `mappend` x@(ExitFailure _) = x
87 ExitSuccess `mappend` ExitSuccess = ExitSuccess
88
89
90compileMath :: String -> IO (String, String)
91compileMath = withSystemTempDirectory "math" . compileMath' -- Create a temporary directory, run `compileMath'`, and make sure the directory get's deleted
92
93compileMath' :: String -> FilePath -> IO (String, String)
94compileMath' input tmpDir = do
95 mapM_ (copyToTmp . ("tex" </>)) [ "preamble.tex"
96 , "preview.dtx"
97 , "preview.ins"
98 ]
99 (exitCode, out, err) <- withCurrentDirectory tmpDir $ execWriterT $ do -- Collect stdout, stderr, and exitCode of all subprocesses (stdout and stderr simply get appended to one another)
100 run "latex" [ "-interaction=batchmode"
101 , "preview.ins"
102 ] ""
103 liftIO $ writeFile (tmpDir </> "image.tex") input
104 run "latex" [ "-interaction=batchmode"
105 , "image.tex"
106 ] ""
107 run "dvisvgm" [ "--exact"
108 , "--no-fonts"
109 , tmpDir </> "image.dvi"
110 ] ""
111 when (exitCode /= ExitSuccess) $ do -- Fail with maximum noise if any of the latex passes fail -- otherwise be silent
112 hPutStrLn stdout out
113 hPutStrLn stderr err
114 throwIO exitCode
115 (\x -> return $!! (x, extractAlignment err)) =<< (readFile $ tmpDir </> "image.svg") -- Note the call to `($!!)` -- since we'll be deleting `tmpDir` we need to make sure the entire generated output resides in memory before we leave this block
116 where
117 copyToTmp fp = copyFile fp (tmpDir </> takeFileName fp)
118 run :: String -> [String] -> String -> WriterT (ExitCode, String, String) IO ()
119 run bin args stdin = tell =<< liftIO (readProcessWithExitCode bin args stdin)
120
121withCurrentDirectory :: FilePath -- ^ Directory to execute in
122 -> IO a -- ^ Action to be executed
123 -> IO a
124-- ^ This is provided in newer versions of temporary
125withCurrentDirectory dir action =
126 bracket getCurrentDirectory setCurrentDirectory $ \ _ -> do
127 setCurrentDirectory dir
128 action
129
130extractAlignment :: String -> String
131extractAlignment = fromMaybe "0pt" . extract . (=~ "depth=([^\\s]+)") -- One of the few places where regular expressions really prove usefull
132 where
133 extract :: (String, String, String, [String]) -> Maybe String
134 extract (_, _, _, xs) = listToMaybe xs
135~~~
136
137### `Site.hs`
138
139The more trick part proved to be integration into the framework as provided by [Hakyll](http://jaspervdj.be/hakyll/).
140
141~~~ {.haskell .numberLines}
142
143
144import qualified Crypto.Hash.SHA256 as SHA256 (hash)
145import qualified Data.ByteString.Char8 as CBS
146import Data.Hex (hex)
147import Data.Char (toLower)
148
149import Math (compileMath)
150import Text.Printf (printf)
151
152main :: IO ()
153main = hakyllWith config $ do
154
155
156 math <- getMath "posts/*" mathTranslation'
157 forM_ math $ \(_, mathStr) -> create [mathTranslation' mathStr] $ do
158 route idRoute
159 compile $ do
160 item <- makeItem mathStr
161 >>= loadAndApplyTemplate "templates/math.tex" defaultContext
162 >>= withItemBody (unsafeCompiler . compileMath) -- unsafeCompiler :: IO a -> Compiler a
163 saveSnapshot "alignment" $ fmap snd item
164 return $ fmap fst item
165
166 match "posts/*" $ do
167 route $ setExtension ".html"
168 compile $ do
169 getResourceBody >>= saveSnapshot "content"
170 pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions mathTransform -- pandocCompilerWithTransformM :: ReaderOptions -> WriterOptions -> (Pandoc -> Compiler Pandoc) -> Item String
171 >>= loadAndApplyTemplate "templates/default.html" defaultContext
172 >>= relativizeUrls
173
174
175
176
177mathTranslation' :: String -> Identifier
178-- ^ This generates the filename for a svg file given the TeX-source
179mathTranslation' = fromCapture "math/*.svg" . map toLower . CBS.unpack . hex . SHA256.hash . CBS.pack
180
181getMath :: Pattern -> (String -> Identifier) -> Rules [([Identifier], String)]
182-- ^ We scrape all posts for math, calls `readPandoc'`
183getMath pattern makeId = do
184 ids <- getMatches pattern
185 mathStrs <- concat `liftM` mapM (\id -> map ((,) [id]) `liftM` getMath' (toFilePath' id)) ids
186 return $ mergeGroups $ groupBy ((==) `on` snd) $ mathStrs
187 where
188 getMath' :: FilePath -> Rules [String]
189 getMath' path = preprocess (query extractMath `liftM` readPandoc' path)
190 extractMath :: Inline -> [String]
191 extractMath (Math _ str) = [str]
192 extractMath _ = []
193 mergeGroups :: [[([Identifier], String)]] -> [([Identifier], String)]
194 mergeGroups = map mergeGroups' . filter (not . null)
195 mergeGroups' :: [([Identifier], String)] -> ([Identifier], String)
196 mergeGroups' xs@((_, str):_) = (concatMap fst xs, str)
197
198readPandoc' :: FilePath -> IO Pandoc
199-- ^ This is copied, almost verbatim, from Hakyll source -- Does what it says on the tin
200readPandoc' path = readFile path >>= either fail return . result'
201 where
202 result' str = case result str of
203 Left (ParseFailure err) -> Left $
204 "parse failed: " ++ err
205 Left (ParsecError _ err) -> Left $
206 "parse failed: " ++ show err
207 Right item' -> Right item'
208 result str = reader defaultHakyllReaderOptions (fileType path) str
209 reader ro t = case t of
210 DocBook -> readDocBook ro
211 Html -> readHtml ro
212 LaTeX -> readLaTeX ro
213 LiterateHaskell t' -> reader (addExt ro Ext_literate_haskell) t'
214 Markdown -> readMarkdown ro
215 MediaWiki -> readMediaWiki ro
216 OrgMode -> readOrg ro
217 Rst -> readRST ro
218 Textile -> readTextile ro
219 _ -> error $
220 "I don't know how to read a file of " ++
221 "the type " ++ show t ++ " for: " ++ path
222
223 addExt ro e = ro {readerExtensions = Set.insert e $ readerExtensions ro}
224
225mathTransform :: Pandoc -> Compiler Pandoc
226-- ^ We replace math by raw html includes of the respective svg files here
227mathTransform = walkM mathTransform'
228 where
229 mathTransform' :: Inline -> Compiler Inline
230 mathTransform' (Math mathType tex) = do
231 alignment <- loadSnapshotBody texId "alignment"
232 let
233 html = printf "<object data=\"/%s\" type=\"image/svg+xml\" style=\"vertical-align:-%s\">%s</object>"
234 (toFilePath texId) (alignment :: String) tex
235 return $ Span ("", [classOf mathType], []) [RawInline (Format "html") html]
236 where
237 texId = mathTranslation' tex
238 classOf DisplayMath = "display-math"
239 classOf InlineMath = "inline-math"
240 mathTransform' x = return x
241
242
243~~~
diff --git a/provider/templates/default.html b/provider/templates/default.html
index 5bc0e9f..ba412e6 100644
--- a/provider/templates/default.html
+++ b/provider/templates/default.html
@@ -10,6 +10,7 @@
10 <script src="http://html5shim.googlecode.com/svn/trunk/html5.js"></script> 10 <script src="http://html5shim.googlecode.com/svn/trunk/html5.js"></script>
11 <![endif]--> 11 <![endif]-->
12 <link rel="stylesheet" href="/css/default.css"> 12 <link rel="stylesheet" href="/css/default.css">
13 <link rel="stylesheet" href="/css/math.css">
13 <link rel="stylesheet" href="/css/syntax.css"> 14 <link rel="stylesheet" href="/css/syntax.css">
14 $if(rss)$<link rel="alternate" type="application/atom+xml" href="$rss$" title="Atom 1.0">$endif$ 15 $if(rss)$<link rel="alternate" type="application/atom+xml" href="$rss$" title="Atom 1.0">$endif$
15</head> 16</head>
diff --git a/provider/templates/math.tex b/provider/templates/math.tex
index 4d5455f..23774bf 100644
--- a/provider/templates/math.tex
+++ b/provider/templates/math.tex
@@ -1,5 +1,5 @@
1\documentclass[14pt,preview,border=1pt,class=extarticle]{standalone} 1\documentclass[14pt,preview,border=1pt,class=extarticle]{standalone}
2\include{preamble.tex} 2\include{preamble}
3\begin{document} 3\begin{document}
4\begin{preview} 4\begin{preview}
5\( 5\(