diff options
| -rw-r--r-- | default.nix | 2 | ||||
| -rw-r--r-- | provider/css/math.css | 5 | ||||
| -rw-r--r-- | provider/templates/preamble.tex (renamed from tex/preamble.tex) | 6 | ||||
| -rw-r--r-- | provider/templates/preview.tex (renamed from provider/templates/math.tex) | 4 | ||||
| -rw-r--r-- | provider/tex/preview.dtx (renamed from tex/preview.dtx) | 0 | ||||
| -rw-r--r-- | provider/tex/preview.ins (renamed from tex/preview.ins) | 0 | ||||
| -rw-r--r-- | src/Site.hs | 70 | ||||
| -rw-r--r-- | src/Tex.hs (renamed from src/Math.hs) | 23 |
8 files changed, 61 insertions, 49 deletions
diff --git a/default.nix b/default.nix index 0770eb3..8d04076 100644 --- a/default.nix +++ b/default.nix | |||
| @@ -11,7 +11,7 @@ rec { | |||
| 11 | } | 11 | } |
| 12 | ); | 12 | ); |
| 13 | texEnv = with pkgs; texlive.combine { | 13 | texEnv = with pkgs; texlive.combine { |
| 14 | inherit (texlive) scheme-small standalone dvisvgm amsmath tikz tikz-cd; | 14 | inherit (texlive) scheme-small standalone dvisvgm amsmath tikz-cd; |
| 15 | }; | 15 | }; |
| 16 | dirty-haskell-wrapper = pkgs.stdenv.mkDerivation rec { | 16 | dirty-haskell-wrapper = pkgs.stdenv.mkDerivation rec { |
| 17 | name = "dirty-haskell-wrapper"; | 17 | name = "dirty-haskell-wrapper"; |
diff --git a/provider/css/math.css b/provider/css/math.css index e045853..b2a3644 100644 --- a/provider/css/math.css +++ b/provider/css/math.css | |||
| @@ -18,6 +18,11 @@ div div { | |||
| 18 | margin-left: 2em; | 18 | margin-left: 2em; |
| 19 | } | 19 | } |
| 20 | 20 | ||
| 21 | div.exercise > p:first-child:before { | ||
| 22 | content: "Exercise. "; | ||
| 23 | font-weight: bold; | ||
| 24 | } | ||
| 25 | |||
| 21 | div.theorem > p:first-child:before { | 26 | div.theorem > p:first-child:before { |
| 22 | content: "Theorem. "; | 27 | content: "Theorem. "; |
| 23 | font-weight: bold; | 28 | font-weight: bold; |
diff --git a/tex/preamble.tex b/provider/templates/preamble.tex index 8ff41d1..129eba8 100644 --- a/tex/preamble.tex +++ b/provider/templates/preamble.tex | |||
| @@ -1,7 +1,6 @@ | |||
| 1 | \usepackage[utf8]{inputenc} | 1 | \usepackage[utf8]{inputenc} |
| 2 | 2 | ||
| 3 | \usepackage{amssymb} | 3 | \usepackage{amssymb} |
| 4 | \usepackage{xspace} | ||
| 5 | \usepackage{amsmath} | 4 | \usepackage{amsmath} |
| 6 | \usepackage{mathrsfs} | 5 | \usepackage{mathrsfs} |
| 7 | 6 | ||
| @@ -9,8 +8,11 @@ | |||
| 9 | 8 | ||
| 10 | \usetikzlibrary{cd} | 9 | \usetikzlibrary{cd} |
| 11 | 10 | ||
| 12 | \newcommand*{\ca}[1]{\ensuremath{\mathbf{#1}}\xspace} | 11 | \newcommand*{\ca}[1]{\ensuremath{\mathbf{#1}}} |
| 13 | \newcommand*{\idarr}[1]{\ensuremath{\mathrm{id}_{#1}}} | 12 | \newcommand*{\idarr}[1]{\ensuremath{\mathrm{id}_{#1}}} |
| 14 | 13 | ||
| 15 | \newcommand{\id}{\ensuremath{\mathrm{id}}} | 14 | \newcommand{\id}{\ensuremath{\mathrm{id}}} |
| 16 | \renewcommand{\implies}{\rightarrow} | 15 | \renewcommand{\implies}{\rightarrow} |
| 16 | |||
| 17 | \newcommand{\N}{\ensuremath{\mathbb{N}}} | ||
| 18 | \newcommand{\arr}[3]{\ensuremath{\begin{tikzcd}[ampersand replacement=\&]{#1} \rar{#2} \& {#3}\end{tikzcd}}} | ||
diff --git a/provider/templates/math.tex b/provider/templates/preview.tex index 23774bf..da3c585 100644 --- a/provider/templates/math.tex +++ b/provider/templates/preview.tex | |||
| @@ -1,9 +1,7 @@ | |||
| 1 | \documentclass[14pt,preview,border=1pt,class=extarticle]{standalone} | 1 | \documentclass[14pt,preview,border=1pt,class=extarticle]{standalone} |
| 2 | \include{preamble} | 2 | $partial("templates/preamble.tex")$ |
| 3 | \begin{document} | 3 | \begin{document} |
| 4 | \begin{preview} | 4 | \begin{preview} |
| 5 | \( | ||
| 6 | $body$ | 5 | $body$ |
| 7 | \) | ||
| 8 | \end{preview} | 6 | \end{preview} |
| 9 | \end{document} | 7 | \end{document} |
diff --git a/tex/preview.dtx b/provider/tex/preview.dtx index 0675c27..0675c27 100644 --- a/tex/preview.dtx +++ b/provider/tex/preview.dtx | |||
diff --git a/tex/preview.ins b/provider/tex/preview.ins index 1d4229d..1d4229d 100644 --- a/tex/preview.ins +++ b/provider/tex/preview.ins | |||
diff --git a/src/Site.hs b/src/Site.hs index 5f5fbc0..d3ac76d 100644 --- a/src/Site.hs +++ b/src/Site.hs | |||
| @@ -3,7 +3,7 @@ | |||
| 3 | import Hakyll | 3 | import Hakyll |
| 4 | 4 | ||
| 5 | import Data.Monoid (Monoid(..), mconcat, (<>)) | 5 | import Data.Monoid (Monoid(..), mconcat, (<>)) |
| 6 | import Control.Monad (liftM, forM_) | 6 | import Control.Monad (liftM, forM_, (<=<)) |
| 7 | import Data.Char (toLower, isSpace, isAlphaNum) | 7 | import Data.Char (toLower, isSpace, isAlphaNum) |
| 8 | import Data.Maybe (mapMaybe, fromMaybe) | 8 | import Data.Maybe (mapMaybe, fromMaybe) |
| 9 | import Data.Map (Map) | 9 | import Data.Map (Map) |
| @@ -27,7 +27,7 @@ import qualified Data.ByteString.Char8 as CBS | |||
| 27 | import Data.Hex (hex) | 27 | import Data.Hex (hex) |
| 28 | import Data.Char (toLower) | 28 | import Data.Char (toLower) |
| 29 | 29 | ||
| 30 | import Math (compileMath) | 30 | import Tex (compileTex) |
| 31 | import Text.Printf (printf) | 31 | import Text.Printf (printf) |
| 32 | 32 | ||
| 33 | main :: IO () | 33 | main :: IO () |
| @@ -38,13 +38,13 @@ main = hakyllWith config $ do | |||
| 38 | route idRoute | 38 | route idRoute |
| 39 | compile copyFileCompiler | 39 | compile copyFileCompiler |
| 40 | 40 | ||
| 41 | math <- getMath "posts/**" mathTranslation' | 41 | tex <- getTex "posts/**" texTranslation' |
| 42 | forM_ math $ \(_, mathStr) -> create [mathTranslation' mathStr] $ do | 42 | forM_ tex $ \(_, texStr) -> create [texTranslation' texStr] $ do |
| 43 | route idRoute | 43 | route idRoute |
| 44 | compile $ do | 44 | compile $ do |
| 45 | item <- makeItem mathStr | 45 | item <- makeItem texStr |
| 46 | >>= loadAndApplyTemplate "templates/math.tex" defaultContext | 46 | >>= loadAndApplyTemplate "templates/preview.tex" defaultContext |
| 47 | >>= withItemBody (unsafeCompiler . compileMath) | 47 | >>= withItemBody (unsafeCompiler . compileTex) |
| 48 | saveSnapshot "alignment" $ fmap snd item | 48 | saveSnapshot "alignment" $ fmap snd item |
| 49 | return $ fmap fst item | 49 | return $ fmap fst item |
| 50 | 50 | ||
| @@ -58,7 +58,7 @@ main = hakyllWith config $ do | |||
| 58 | , tagsFieldWith getTags (\tag _ -> Just . H.li $ H.a ! A.href (toValue . toUrl $ "tags" </> tagTranslation tag <.> "html") $ toHtml tag) (mconcat . intersperse "\n") "tagList" tags | 58 | , tagsFieldWith getTags (\tag _ -> Just . H.li $ H.a ! A.href (toValue . toUrl $ "tags" </> tagTranslation tag <.> "html") $ toHtml tag) (mconcat . intersperse "\n") "tagList" tags |
| 59 | ] | 59 | ] |
| 60 | getResourceBody >>= saveSnapshot "content" | 60 | getResourceBody >>= saveSnapshot "content" |
| 61 | pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions mathTransform | 61 | pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions texTransform |
| 62 | >>= loadAndApplyTemplate "templates/default.html" ctx | 62 | >>= loadAndApplyTemplate "templates/default.html" ctx |
| 63 | >>= relativizeUrls | 63 | >>= relativizeUrls |
| 64 | 64 | ||
| @@ -158,20 +158,24 @@ addTag name pattern tags = do | |||
| 158 | ids <- getMatches pattern | 158 | ids <- getMatches pattern |
| 159 | return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] } | 159 | return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] } |
| 160 | 160 | ||
| 161 | mathTranslation' :: String -> Identifier | 161 | texTranslation' :: String -> Identifier |
| 162 | mathTranslation' = fromCapture "math/*.svg" . map toLower . CBS.unpack . hex . SHA256.hash . CBS.pack | 162 | texTranslation' = fromCapture "tex/*.svg" . map toLower . CBS.unpack . hex . SHA256.hash . CBS.pack |
| 163 | 163 | ||
| 164 | getMath :: Pattern -> (String -> Identifier) -> Rules [([Identifier], String)] | 164 | getTex :: Pattern -> (String -> Identifier) -> Rules [([Identifier], String)] |
| 165 | getMath pattern makeId = do | 165 | getTex pattern makeId = do |
| 166 | ids <- getMatches pattern | 166 | ids <- getMatches pattern |
| 167 | mathStrs <- concat `liftM` mapM (\id -> map ((,) [id]) `liftM` getMath' (toFilePath' id)) ids | 167 | texStrs <- concat `liftM` mapM (\id -> map ((,) [id]) `liftM` getTex' (toFilePath' id)) ids |
| 168 | return $ mergeGroups $ groupBy ((==) `on` snd) $ mathStrs | 168 | return $ mergeGroups $ groupBy ((==) `on` snd) $ texStrs |
| 169 | where | 169 | where |
| 170 | getMath' :: FilePath -> Rules [String] | 170 | getTex' :: FilePath -> Rules [String] |
| 171 | getMath' path = preprocess (query extractMath `liftM` readPandoc' path) | 171 | getTex' path = preprocess . fmap concat $ (\x -> [query extractTex, query extractTex'] <*> pure x) `liftM` readPandoc' path |
| 172 | extractMath :: Inline -> [String] | 172 | extractTex :: Inline -> [String] |
| 173 | extractMath (Math _ str) = [str] | 173 | extractTex (Math _ str) = ["\\(" ++ str ++ "\\)"] |
| 174 | extractMath _ = [] | 174 | extractTex (RawInline "latex" str) = [str] |
| 175 | extractTex _ = [] | ||
| 176 | extractTex' :: Block -> [String] | ||
| 177 | extractTex' (RawBlock "latex" str) = [str] | ||
| 178 | extractTex' _ = [] | ||
| 175 | mergeGroups :: [[([Identifier], String)]] -> [([Identifier], String)] | 179 | mergeGroups :: [[([Identifier], String)]] -> [([Identifier], String)] |
| 176 | mergeGroups = map mergeGroups' . filter (not . null) | 180 | mergeGroups = map mergeGroups' . filter (not . null) |
| 177 | mergeGroups' :: [([Identifier], String)] -> ([Identifier], String) | 181 | mergeGroups' :: [([Identifier], String)] -> ([Identifier], String) |
| @@ -203,21 +207,25 @@ readPandoc' path = readFile path >>= either fail return . result' | |||
| 203 | 207 | ||
| 204 | addExt ro e = ro {readerExtensions = Set.insert e $ readerExtensions ro} | 208 | addExt ro e = ro {readerExtensions = Set.insert e $ readerExtensions ro} |
| 205 | 209 | ||
| 206 | mathTransform :: Pandoc -> Compiler Pandoc | 210 | texTransform :: Pandoc -> Compiler Pandoc |
| 207 | mathTransform = walkM mathTransform' | 211 | texTransform = walkM texTransformInline <=< walkM texTransformBlock |
| 208 | where | 212 | where |
| 209 | mathTransform' :: Inline -> Compiler Inline | 213 | texTransformInline :: Inline -> Compiler Inline |
| 210 | mathTransform' (Math mathType tex) = do | 214 | texTransformInline (Math mathType tex) = (\html -> Span ("", [classOf mathType], []) [RawInline "html" html]) <$> texTransform' ("\\(" ++ tex ++ "\\)") |
| 211 | alignment <- loadSnapshotBody texId "alignment" | 215 | texTransformInline (RawInline "latex" tex) = (\html -> Span ("", [], []) [RawInline "html" html]) <$> texTransform' tex |
| 216 | texTransformInline x = return x | ||
| 217 | texTransformBlock :: Block -> Compiler Block | ||
| 218 | texTransformBlock (RawBlock "latex" tex) = (\html -> Div ("", [], []) [RawBlock "html" html]) <$> texTransform' tex | ||
| 219 | texTransformBlock x = return x | ||
| 220 | texTransform' :: String -> Compiler String | ||
| 221 | texTransform' tex = do | ||
| 212 | let | 222 | let |
| 213 | html = printf "<object data=\"/%s\" type=\"image/svg+xml\" style=\"vertical-align:-%s\">%s</object>" | 223 | texId = texTranslation' tex |
| 224 | alignment <- loadSnapshotBody texId "alignment" | ||
| 225 | return $ printf "<object data=\"/%s\" type=\"image/svg+xml\" style=\"vertical-align:-%s\">%s</object>" | ||
| 214 | (toFilePath texId) (alignment :: String) tex | 226 | (toFilePath texId) (alignment :: String) tex |
| 215 | return $ Span ("", [classOf mathType], []) [RawInline (Format "html") html] | 227 | classOf DisplayMath = "display-math" |
| 216 | where | 228 | classOf InlineMath = "inline-math" |
| 217 | texId = mathTranslation' tex | ||
| 218 | classOf DisplayMath = "display-math" | ||
| 219 | classOf InlineMath = "inline-math" | ||
| 220 | mathTransform' x = return x | ||
| 221 | 229 | ||
| 222 | toFilePath' :: Identifier -> FilePath | 230 | toFilePath' :: Identifier -> FilePath |
| 223 | toFilePath' = (providerDirectory config </>) . toFilePath | 231 | toFilePath' = (providerDirectory config </>) . toFilePath |
| @@ -1,5 +1,5 @@ | |||
| 1 | module Math | 1 | module Tex |
| 2 | ( compileMath | 2 | ( compileTex |
| 3 | ) where | 3 | ) where |
| 4 | 4 | ||
| 5 | import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile) | 5 | import System.IO (stdout, stderr, hPutStrLn, writeFile, readFile) |
| @@ -27,22 +27,21 @@ instance Monoid ExitCode where | |||
| 27 | ExitSuccess `mappend` ExitSuccess = ExitSuccess | 27 | ExitSuccess `mappend` ExitSuccess = ExitSuccess |
| 28 | 28 | ||
| 29 | 29 | ||
| 30 | compileMath :: String -> IO (String, String) | 30 | compileTex :: String -> IO (String, String) |
| 31 | compileMath = withSystemTempDirectory "math" . compileMath' | 31 | compileTex = withSystemTempDirectory "tex" . compileTex' |
| 32 | 32 | ||
| 33 | compileMath' :: String -> FilePath -> IO (String, String) | 33 | compileTex' :: String -> FilePath -> IO (String, String) |
| 34 | compileMath' input tmpDir = do | 34 | compileTex' input tmpDir = do |
| 35 | mapM_ (copyToTmp . ("tex" </>)) [ "preamble.tex" | 35 | mapM_ (copyToTmp . ("provider/tex" </>)) [ "preview.dtx" |
| 36 | , "preview.dtx" | 36 | , "preview.ins" |
| 37 | , "preview.ins" | 37 | ] |
| 38 | ] | ||
| 39 | (exitCode, out, err) <- withCurrentDirectory tmpDir $ execWriterT $ do | 38 | (exitCode, out, err) <- withCurrentDirectory tmpDir $ execWriterT $ do |
| 40 | run "latex" [ "-interaction=batchmode" | 39 | run "latex" [ "-interaction=batchmode" |
| 41 | , "preview.ins" | 40 | , "preview.ins" |
| 42 | ] "" | 41 | ] "" |
| 43 | liftIO $ writeFile (tmpDir </> "image.tex") input | 42 | liftIO $ writeFile (tmpDir </> "image.tex") input |
| 44 | run "latex" [ "-interaction=batchmode" | 43 | run "latex" [ {- "-interaction=batchmode" |
| 45 | , "image.tex" | 44 | , -} "image.tex" |
| 46 | ] "" | 45 | ] "" |
| 47 | run "dvisvgm" [ "--exact" | 46 | run "dvisvgm" [ "--exact" |
| 48 | , "--no-fonts" | 47 | , "--no-fonts" |
