diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2015-11-06 02:06:15 +0000 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2015-11-06 02:06:15 +0000 |
commit | 6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15 (patch) | |
tree | ced3ff5d08594fa5f5b591d96dd289331d3ff93b | |
parent | 543d5baeac2d772a6cff3ea4b8cf14d740f48119 (diff) | |
download | dirty-haskell.org-6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15.tar dirty-haskell.org-6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15.tar.gz dirty-haskell.org-6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15.tar.bz2 dirty-haskell.org-6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15.tar.xz dirty-haskell.org-6294d6107ba6462bdf4a9b302b7bdd1ff7a69c15.zip |
Extracting math from all posts
-rw-r--r-- | blog.cabal | 1 | ||||
-rw-r--r-- | src/Site.hs | 66 |
2 files changed, 64 insertions, 3 deletions
@@ -24,5 +24,6 @@ executable site | |||
24 | , hakyll >=4.6 && <5 | 24 | , hakyll >=4.6 && <5 |
25 | , containers >=0.5 && <0.6 | 25 | , containers >=0.5 && <0.6 |
26 | , pandoc >=1.13 && <2 | 26 | , pandoc >=1.13 && <2 |
27 | , pandoc-types >=1.12 && <2 | ||
27 | , data-default >=0.5 && <0.6 | 28 | , data-default >=0.5 && <0.6 |
28 | , filepath >=1.3 && <2 | 29 | , filepath >=1.3 && <2 |
diff --git a/src/Site.hs b/src/Site.hs index 25d11d0..279532f 100644 --- a/src/Site.hs +++ b/src/Site.hs | |||
@@ -3,14 +3,18 @@ | |||
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) | 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) |
10 | import qualified Data.Map as Map | 10 | import qualified Data.Map as Map |
11 | import Data.List (take, reverse) | 11 | import qualified Data.Set as Set |
12 | import Data.List (take, reverse, nub, groupBy, concatMap) | ||
13 | import Data.Function (on) | ||
12 | import Data.Default | 14 | import Data.Default |
13 | import Text.Pandoc.Options (WriterOptions(..), ObfuscationMethod(..)) | 15 | import Text.Pandoc |
16 | import Text.Pandoc.Walk (query) | ||
17 | import Text.Pandoc.Error | ||
14 | import Control.Applicative (Alternative(..), Applicative(..)) | 18 | import Control.Applicative (Alternative(..), Applicative(..)) |
15 | 19 | ||
16 | import System.FilePath (takeBaseName, (</>), (<.>)) | 20 | import System.FilePath (takeBaseName, (</>), (<.>)) |
@@ -31,6 +35,14 @@ main = hakyllWith config $ do | |||
31 | >>= loadAndApplyTemplate "templates/default.html" defaultContext | 35 | >>= loadAndApplyTemplate "templates/default.html" defaultContext |
32 | >>= relativizeUrls | 36 | >>= relativizeUrls |
33 | 37 | ||
38 | math <- getMath "posts/*" mathTranslation' | ||
39 | forM_ math $ \(deps, mathStr) -> | ||
40 | rulesExtraDependencies (map IdentifierDependency deps) $ | ||
41 | create [mathTranslation' mathStr] $ do | ||
42 | route idRoute | ||
43 | compile $ do | ||
44 | makeItem $ mathStr | ||
45 | |||
34 | tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" | 46 | tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" |
35 | 47 | ||
36 | tagsRules tags $ \tag pattern -> do | 48 | tagsRules tags $ \tag pattern -> do |
@@ -122,11 +134,59 @@ tagTranslation = mapMaybe charTrans | |||
122 | | isAlphaNum c = Just $ toLower c | 134 | | isAlphaNum c = Just $ toLower c |
123 | | otherwise = Nothing | 135 | | otherwise = Nothing |
124 | 136 | ||
137 | mathTranslation' :: String -> Identifier | ||
138 | mathTranslation' = fromCapture "math/*.svg" . id -- TODO hash math | ||
139 | |||
125 | addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags | 140 | addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags |
126 | addTag name pattern tags = do | 141 | addTag name pattern tags = do |
127 | ids <- getMatches pattern | 142 | ids <- getMatches pattern |
128 | return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] } | 143 | return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] } |
129 | 144 | ||
145 | getMath :: Pattern -> (String -> Identifier) -> Rules [([Identifier], String)] | ||
146 | getMath pattern makeId = do | ||
147 | ids <- getMatches pattern | ||
148 | mathStrs <- concat `liftM` mapM (\id -> map ((,) [id]) `liftM` getMath' (toFilePath' id)) ids | ||
149 | return $ mergeGroups $ groupBy ((==) `on` snd) $ mathStrs | ||
150 | where | ||
151 | getMath' :: FilePath -> Rules [String] | ||
152 | getMath' path = preprocess (query extractMath `liftM` readPandoc' path) | ||
153 | extractMath :: Inline -> [String] | ||
154 | extractMath (Math _ str) = [str] | ||
155 | extractMath _ = [] | ||
156 | mergeGroups :: [[([Identifier], String)]] -> [([Identifier], String)] | ||
157 | mergeGroups = map mergeGroups' . filter (not . null) | ||
158 | mergeGroups' :: [([Identifier], String)] -> ([Identifier], String) | ||
159 | mergeGroups' xs@((_, str):_) = (concatMap fst xs, str) | ||
160 | |||
161 | readPandoc' :: FilePath -> IO Pandoc | ||
162 | readPandoc' path = readFile path >>= either fail return . result' | ||
163 | where | ||
164 | result' str = case result str of | ||
165 | Left (ParseFailure err) -> Left $ | ||
166 | "parse failed: " ++ err | ||
167 | Left (ParsecError _ err) -> Left $ | ||
168 | "parse failed: " ++ show err | ||
169 | Right item' -> Right item' | ||
170 | result str = reader defaultHakyllReaderOptions (fileType path) str | ||
171 | reader ro t = case t of | ||
172 | DocBook -> readDocBook ro | ||
173 | Html -> readHtml ro | ||
174 | LaTeX -> readLaTeX ro | ||
175 | LiterateHaskell t' -> reader (addExt ro Ext_literate_haskell) t' | ||
176 | Markdown -> readMarkdown ro | ||
177 | MediaWiki -> readMediaWiki ro | ||
178 | OrgMode -> readOrg ro | ||
179 | Rst -> readRST ro | ||
180 | Textile -> readTextile ro | ||
181 | _ -> error $ | ||
182 | "I don't know how to read a file of " ++ | ||
183 | "the type " ++ show t ++ " for: " ++ path | ||
184 | |||
185 | addExt ro e = ro {readerExtensions = Set.insert e $ readerExtensions ro} | ||
186 | |||
187 | toFilePath' :: Identifier -> FilePath | ||
188 | toFilePath' = (providerDirectory config </>) . toFilePath | ||
189 | |||
130 | config :: Configuration | 190 | config :: Configuration |
131 | config = defaultConfiguration { providerDirectory = "provider" | 191 | config = defaultConfiguration { providerDirectory = "provider" |
132 | , deployCommand = "rsync -av --progress -c --delete-delay -m _site/ gkleen@surtr.yggdrasil.li:/var/www/dirty-haskell.org/" | 192 | , deployCommand = "rsync -av --progress -c --delete-delay -m _site/ gkleen@surtr.yggdrasil.li:/var/www/dirty-haskell.org/" |