parent
59d6f02a9a
commit
b27783e2ec
9 changed files with 49 additions and 28 deletions
|
@ -14,4 +14,6 @@ flags:
|
||||||
packages:
|
packages:
|
||||||
- '..'
|
- '..'
|
||||||
- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
|
- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
|
||||||
|
- location: 'https://hackage.haskell.org/package/cmark-0.5.0/cmark-0.5.0.tar.gz'
|
||||||
|
extra-dep: true
|
||||||
resolver: lts-3.18
|
resolver: lts-3.18
|
||||||
|
|
|
@ -17,4 +17,6 @@ ghc-options:
|
||||||
packages:
|
packages:
|
||||||
- '..'
|
- '..'
|
||||||
- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
|
- 'https://hackage.haskell.org/package/pandoc-citeproc-0.8.1.3/pandoc-citeproc-0.8.1.3.tar.gz'
|
||||||
resolver: lts-3.16
|
- location: 'https://hackage.haskell.org/package/cmark-0.5.0/cmark-0.5.0.tar.gz'
|
||||||
|
extra-dep: true
|
||||||
|
resolver: lts-3.18
|
||||||
|
|
|
@ -279,7 +279,7 @@ Library
|
||||||
deepseq-generics >= 0.1 && < 0.2,
|
deepseq-generics >= 0.1 && < 0.2,
|
||||||
JuicyPixels >= 3.1.6.1 && < 3.3,
|
JuicyPixels >= 3.1.6.1 && < 3.3,
|
||||||
filemanip >= 0.3 && < 0.4,
|
filemanip >= 0.3 && < 0.4,
|
||||||
cmark >= 0.4.0.1 && < 0.5,
|
cmark >= 0.5 && < 0.6,
|
||||||
ghc-prim >= 0.2
|
ghc-prim >= 0.2
|
||||||
if flag(old-locale)
|
if flag(old-locale)
|
||||||
Build-Depends: old-locale >= 1 && < 1.1,
|
Build-Depends: old-locale >= 1 && < 1.1,
|
||||||
|
|
|
@ -58,15 +58,19 @@ addBlocks = foldr addBlock []
|
||||||
addBlock :: Node -> [Block] -> [Block]
|
addBlock :: Node -> [Block] -> [Block]
|
||||||
addBlock (Node _ PARAGRAPH nodes) =
|
addBlock (Node _ PARAGRAPH nodes) =
|
||||||
(Para (addInlines nodes) :)
|
(Para (addInlines nodes) :)
|
||||||
addBlock (Node _ HRULE _) =
|
addBlock (Node _ THEMATIC_BREAK _) =
|
||||||
(HorizontalRule :)
|
(HorizontalRule :)
|
||||||
addBlock (Node _ BLOCK_QUOTE nodes) =
|
addBlock (Node _ BLOCK_QUOTE nodes) =
|
||||||
(BlockQuote (addBlocks nodes) :)
|
(BlockQuote (addBlocks nodes) :)
|
||||||
addBlock (Node _ (HTML t) _) =
|
addBlock (Node _ (HTML_BLOCK t) _) =
|
||||||
(RawBlock (Format "html") (unpack t) :)
|
(RawBlock (Format "html") (unpack t) :)
|
||||||
|
-- Note: the cmark parser will never generate CUSTOM_BLOCK,
|
||||||
|
-- so we don't need to handle it:
|
||||||
|
addBlock (Node _ (CUSTOM_BLOCK _onEnter _onExit) _nodes) =
|
||||||
|
id
|
||||||
addBlock (Node _ (CODE_BLOCK info t) _) =
|
addBlock (Node _ (CODE_BLOCK info t) _) =
|
||||||
(CodeBlock ("", take 1 (words (unpack info)), []) (unpack t) :)
|
(CodeBlock ("", take 1 (words (unpack info)), []) (unpack t) :)
|
||||||
addBlock (Node _ (HEADER lev) nodes) =
|
addBlock (Node _ (HEADING lev) nodes) =
|
||||||
(Header lev ("",[],[]) (addInlines nodes) :)
|
(Header lev ("",[],[]) (addInlines nodes) :)
|
||||||
addBlock (Node _ (LIST listAttrs) nodes) =
|
addBlock (Node _ (LIST listAttrs) nodes) =
|
||||||
(constructor (map (setTightness . addBlocks . children) nodes) :)
|
(constructor (map (setTightness . addBlocks . children) nodes) :)
|
||||||
|
@ -104,8 +108,12 @@ addInline (Node _ (TEXT t) _) = (map toinl clumps ++)
|
||||||
toinl xs = Str xs
|
toinl xs = Str xs
|
||||||
addInline (Node _ LINEBREAK _) = (LineBreak :)
|
addInline (Node _ LINEBREAK _) = (LineBreak :)
|
||||||
addInline (Node _ SOFTBREAK _) = (SoftBreak :)
|
addInline (Node _ SOFTBREAK _) = (SoftBreak :)
|
||||||
addInline (Node _ (INLINE_HTML t) _) =
|
addInline (Node _ (HTML_INLINE t) _) =
|
||||||
(RawInline (Format "html") (unpack t) :)
|
(RawInline (Format "html") (unpack t) :)
|
||||||
|
-- Note: the cmark parser will never generate CUSTOM_BLOCK,
|
||||||
|
-- so we don't need to handle it:
|
||||||
|
addInline (Node _ (CUSTOM_INLINE _onEnter _onExit) _nodes) =
|
||||||
|
id
|
||||||
addInline (Node _ (CODE t) _) =
|
addInline (Node _ (CODE t) _) =
|
||||||
(Code ("",[],[]) (unpack t) :)
|
(Code ("",[],[]) (unpack t) :)
|
||||||
addInline (Node _ EMPH nodes) =
|
addInline (Node _ EMPH nodes) =
|
||||||
|
|
|
@ -909,9 +909,11 @@ fetchItem sourceURL s =
|
||||||
case parseURI s' of -- requires absolute URI
|
case parseURI s' of -- requires absolute URI
|
||||||
-- We don't want to treat C:/ as a scheme:
|
-- We don't want to treat C:/ as a scheme:
|
||||||
Just u' | length (uriScheme u') > 2 -> openURL (show u')
|
Just u' | length (uriScheme u') > 2 -> openURL (show u')
|
||||||
_ -> E.try readLocalFile -- get from local file system
|
Just u' | uriScheme u' == "file:" ->
|
||||||
where readLocalFile = do
|
E.try $ readLocalFile $ dropWhile (=='/') (uriPath u')
|
||||||
cont <- BS.readFile fp
|
_ -> E.try $ readLocalFile fp -- get from local file system
|
||||||
|
where readLocalFile f = do
|
||||||
|
cont <- BS.readFile f
|
||||||
return (cont, mime)
|
return (cont, mime)
|
||||||
dropFragmentAndQuery = takeWhile (\c -> c /= '?' && c /= '#')
|
dropFragmentAndQuery = takeWhile (\c -> c /= '?' && c /= '#')
|
||||||
fp = unEscapeString $ dropFragmentAndQuery s
|
fp = unEscapeString $ dropFragmentAndQuery s
|
||||||
|
@ -919,8 +921,9 @@ fetchItem sourceURL s =
|
||||||
".gz" -> getMimeType $ dropExtension fp
|
".gz" -> getMimeType $ dropExtension fp
|
||||||
".svgz" -> getMimeType $ dropExtension fp ++ ".svg"
|
".svgz" -> getMimeType $ dropExtension fp ++ ".svg"
|
||||||
x -> getMimeType x
|
x -> getMimeType x
|
||||||
ensureEscaped x@(_:':':'\\':_) = x -- likely windows path
|
ensureEscaped = escapeURIString isAllowedInURI . map convertSlash
|
||||||
ensureEscaped x = escapeURIString isAllowedInURI x
|
convertSlash '\\' = '/'
|
||||||
|
convertSlash x = x
|
||||||
|
|
||||||
-- | Like 'fetchItem', but also looks for items in a 'MediaBag'.
|
-- | Like 'fetchItem', but also looks for items in a 'MediaBag'.
|
||||||
fetchItem' :: MediaBag -> Maybe String -> String
|
fetchItem' :: MediaBag -> Maybe String -> String
|
||||||
|
|
|
@ -97,8 +97,8 @@ blockToNodes (Para xs) = (node PARAGRAPH (inlinesToNodes xs) :)
|
||||||
blockToNodes (CodeBlock (_,classes,_) xs) =
|
blockToNodes (CodeBlock (_,classes,_) xs) =
|
||||||
(node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] :)
|
(node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] :)
|
||||||
blockToNodes (RawBlock fmt xs)
|
blockToNodes (RawBlock fmt xs)
|
||||||
| fmt == Format "html" = (node (HTML (T.pack xs)) [] :)
|
| fmt == Format "html" = (node (HTML_BLOCK (T.pack xs)) [] :)
|
||||||
| otherwise = id
|
| otherwise = (node (CUSTOM_BLOCK (T.pack xs) (T.empty)) [] :)
|
||||||
blockToNodes (BlockQuote bs) =
|
blockToNodes (BlockQuote bs) =
|
||||||
(node BLOCK_QUOTE (blocksToNodes bs) :)
|
(node BLOCK_QUOTE (blocksToNodes bs) :)
|
||||||
blockToNodes (BulletList items) =
|
blockToNodes (BulletList items) =
|
||||||
|
@ -116,8 +116,8 @@ blockToNodes (OrderedList (start, _sty, delim) items) =
|
||||||
_ -> PERIOD_DELIM,
|
_ -> PERIOD_DELIM,
|
||||||
listTight = isTightList items,
|
listTight = isTightList items,
|
||||||
listStart = start }) (map (node ITEM . blocksToNodes) items) :)
|
listStart = start }) (map (node ITEM . blocksToNodes) items) :)
|
||||||
blockToNodes HorizontalRule = (node HRULE [] :)
|
blockToNodes HorizontalRule = (node THEMATIC_BREAK [] :)
|
||||||
blockToNodes (Header lev _ ils) = (node (HEADER lev) (inlinesToNodes ils) :)
|
blockToNodes (Header lev _ ils) = (node (HEADING lev) (inlinesToNodes ils) :)
|
||||||
blockToNodes (Div _ bs) = (blocksToNodes bs ++)
|
blockToNodes (Div _ bs) = (blocksToNodes bs ++)
|
||||||
blockToNodes (DefinitionList items) = blockToNodes (BulletList items')
|
blockToNodes (DefinitionList items) = blockToNodes (BulletList items')
|
||||||
where items' = map dlToBullet items
|
where items' = map dlToBullet items
|
||||||
|
@ -128,7 +128,7 @@ blockToNodes (DefinitionList items) = blockToNodes (BulletList items')
|
||||||
dlToBullet (term, xs) =
|
dlToBullet (term, xs) =
|
||||||
Para term : concat xs
|
Para term : concat xs
|
||||||
blockToNodes t@(Table _ _ _ _ _) =
|
blockToNodes t@(Table _ _ _ _ _) =
|
||||||
(node (HTML (T.pack $! writeHtmlString def $! Pandoc nullMeta [t])) [] :)
|
(node (HTML_BLOCK (T.pack $! writeHtmlString def $! Pandoc nullMeta [t])) [] :)
|
||||||
blockToNodes Null = id
|
blockToNodes Null = id
|
||||||
|
|
||||||
inlinesToNodes :: [Inline] -> [Node]
|
inlinesToNodes :: [Inline] -> [Node]
|
||||||
|
@ -142,25 +142,25 @@ inlineToNodes SoftBreak = (node SOFTBREAK [] :)
|
||||||
inlineToNodes (Emph xs) = (node EMPH (inlinesToNodes xs) :)
|
inlineToNodes (Emph xs) = (node EMPH (inlinesToNodes xs) :)
|
||||||
inlineToNodes (Strong xs) = (node STRONG (inlinesToNodes xs) :)
|
inlineToNodes (Strong xs) = (node STRONG (inlinesToNodes xs) :)
|
||||||
inlineToNodes (Strikeout xs) =
|
inlineToNodes (Strikeout xs) =
|
||||||
((node (INLINE_HTML (T.pack "<s>")) [] : inlinesToNodes xs ++
|
((node (HTML_INLINE (T.pack "<s>")) [] : inlinesToNodes xs ++
|
||||||
[node (INLINE_HTML (T.pack "</s>")) []]) ++ )
|
[node (HTML_INLINE (T.pack "</s>")) []]) ++ )
|
||||||
inlineToNodes (Superscript xs) =
|
inlineToNodes (Superscript xs) =
|
||||||
((node (INLINE_HTML (T.pack "<sup>")) [] : inlinesToNodes xs ++
|
((node (HTML_INLINE (T.pack "<sup>")) [] : inlinesToNodes xs ++
|
||||||
[node (INLINE_HTML (T.pack "</sup>")) []]) ++ )
|
[node (HTML_INLINE (T.pack "</sup>")) []]) ++ )
|
||||||
inlineToNodes (Subscript xs) =
|
inlineToNodes (Subscript xs) =
|
||||||
((node (INLINE_HTML (T.pack "<sub>")) [] : inlinesToNodes xs ++
|
((node (HTML_INLINE (T.pack "<sub>")) [] : inlinesToNodes xs ++
|
||||||
[node (INLINE_HTML (T.pack "</sub>")) []]) ++ )
|
[node (HTML_INLINE (T.pack "</sub>")) []]) ++ )
|
||||||
inlineToNodes (SmallCaps xs) =
|
inlineToNodes (SmallCaps xs) =
|
||||||
((node (INLINE_HTML (T.pack "<span style=\"font-variant:small-caps;\">")) []
|
((node (HTML_INLINE (T.pack "<span style=\"font-variant:small-caps;\">")) []
|
||||||
: inlinesToNodes xs ++
|
: inlinesToNodes xs ++
|
||||||
[node (INLINE_HTML (T.pack "</span>")) []]) ++ )
|
[node (HTML_INLINE (T.pack "</span>")) []]) ++ )
|
||||||
inlineToNodes (Link _ ils (url,tit)) =
|
inlineToNodes (Link _ ils (url,tit)) =
|
||||||
(node (LINK (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
|
(node (LINK (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
|
||||||
inlineToNodes (Image _ ils (url,tit)) =
|
inlineToNodes (Image _ ils (url,tit)) =
|
||||||
(node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
|
(node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
|
||||||
inlineToNodes (RawInline fmt xs)
|
inlineToNodes (RawInline fmt xs)
|
||||||
| fmt == Format "html" = (node (INLINE_HTML (T.pack xs)) [] :)
|
| fmt == Format "html" = (node (HTML_INLINE (T.pack xs)) [] :)
|
||||||
| otherwise = id
|
| otherwise = (node (CUSTOM_INLINE (T.pack xs) (T.empty)) [] :)
|
||||||
inlineToNodes (Quoted qt ils) =
|
inlineToNodes (Quoted qt ils) =
|
||||||
((node (TEXT start) [] : inlinesToNodes ils ++ [node (TEXT end) []]) ++)
|
((node (TEXT start) [] : inlinesToNodes ils ++ [node (TEXT end) []]) ++)
|
||||||
where (start, end) = case qt of
|
where (start, end) = case qt of
|
||||||
|
@ -170,9 +170,9 @@ inlineToNodes (Code _ str) = (node (CODE (T.pack str)) [] :)
|
||||||
inlineToNodes (Math mt str) =
|
inlineToNodes (Math mt str) =
|
||||||
case mt of
|
case mt of
|
||||||
InlineMath ->
|
InlineMath ->
|
||||||
(node (INLINE_HTML (T.pack ("\\(" ++ str ++ "\\)"))) [] :)
|
(node (HTML_INLINE (T.pack ("\\(" ++ str ++ "\\)"))) [] :)
|
||||||
DisplayMath ->
|
DisplayMath ->
|
||||||
(node (INLINE_HTML (T.pack ("\\[" ++ str ++ "\\]"))) [] :)
|
(node (HTML_INLINE (T.pack ("\\[" ++ str ++ "\\]"))) [] :)
|
||||||
inlineToNodes (Span _ ils) = (inlinesToNodes ils ++)
|
inlineToNodes (Span _ ils) = (inlinesToNodes ils ++)
|
||||||
inlineToNodes (Cite _ ils) = (inlinesToNodes ils ++)
|
inlineToNodes (Cite _ ils) = (inlinesToNodes ils ++)
|
||||||
inlineToNodes (Note _) = id -- should not occur
|
inlineToNodes (Note _) = id -- should not occur
|
||||||
|
|
|
@ -12,5 +12,7 @@ packages:
|
||||||
- '../pandoc-citeproc'
|
- '../pandoc-citeproc'
|
||||||
- '../pandoc-types'
|
- '../pandoc-types'
|
||||||
- '../texmath'
|
- '../texmath'
|
||||||
|
- location: 'https://hackage.haskell.org/package/cmark-0.5.0/cmark-0.5.0.tar.gz'
|
||||||
|
extra-dep: true
|
||||||
extra-deps: []
|
extra-deps: []
|
||||||
resolver: lts-3.18
|
resolver: lts-3.18
|
||||||
|
|
|
@ -11,5 +11,7 @@ packages:
|
||||||
git: 'https://github.com/jgm/pandoc-types'
|
git: 'https://github.com/jgm/pandoc-types'
|
||||||
commit: 7b471a3d129efd8155f6cdcb2f2b58b5605df0fc
|
commit: 7b471a3d129efd8155f6cdcb2f2b58b5605df0fc
|
||||||
extra-dep: true
|
extra-dep: true
|
||||||
|
- location: 'https://hackage.haskell.org/package/cmark-0.5.0/cmark-0.5.0.tar.gz'
|
||||||
|
extra-dep: true
|
||||||
extra-deps: []
|
extra-deps: []
|
||||||
resolver: lts-3.18
|
resolver: lts-3.18
|
||||||
|
|
|
@ -18,6 +18,8 @@ packages:
|
||||||
git: 'https://github.com/jgm/pandoc-types'
|
git: 'https://github.com/jgm/pandoc-types'
|
||||||
commit: 7b471a3d129efd8155f6cdcb2f2b58b5605df0fc
|
commit: 7b471a3d129efd8155f6cdcb2f2b58b5605df0fc
|
||||||
extra-dep: true
|
extra-dep: true
|
||||||
|
- location: 'https://hackage.haskell.org/package/cmark-0.5.0/cmark-0.5.0.tar.gz'
|
||||||
|
extra-dep: true
|
||||||
extra-deps:
|
extra-deps:
|
||||||
- 'hsb2hs-0.3.1'
|
- 'hsb2hs-0.3.1'
|
||||||
resolver: lts-3.18
|
resolver: lts-3.18
|
||||||
|
|
Loading…
Add table
Reference in a new issue