diff options
author | Yan Pashkovsky <Yanpas@users.noreply.github.com> | 2018-05-09 19:48:34 +0300 |
---|---|---|
committer | GitHub <noreply@github.com> | 2018-05-09 19:48:34 +0300 |
commit | a337685fe0ab9c63b9456f27787bbe4f0d785a94 (patch) | |
tree | e9fc4dfc0802f8acd97f06a8cc8d7c89b5a988ab /src/Text/Pandoc/Writers/JATS.hs | |
parent | 8e9973b9f761262b6871206f741ac3f2a25aa6bb (diff) | |
parent | 5f33d2e0cd9f19566904c93be04f586de811dd75 (diff) | |
download | pandoc-a337685fe0ab9c63b9456f27787bbe4f0d785a94.tar.gz |
Merge branch 'master' into groff_reader
Diffstat (limited to 'src/Text/Pandoc/Writers/JATS.hs')
-rw-r--r-- | src/Text/Pandoc/Writers/JATS.hs | 14 |
1 files changed, 8 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/JATS.hs b/src/Text/Pandoc/Writers/JATS.hs index 639961acd..fb3236bd9 100644 --- a/src/Text/Pandoc/Writers/JATS.hs +++ b/src/Text/Pandoc/Writers/JATS.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {- @@ -28,9 +29,10 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of 'Pandoc' documents to JATS XML. Reference: -https://jats.nlm.nih.gov/publishing/tag-library/1.1d3/element/mml-math.html +https://jats.nlm.nih.gov/publishing/tag-library -} module Text.Pandoc.Writers.JATS ( writeJATS ) where +import Prelude import Control.Monad.Reader import Data.Char (toLower) import Data.Generics (everywhere, mkT) @@ -139,7 +141,7 @@ deflistItemToJATS opts term defs = do term' <- inlinesToJATS opts term def' <- blocksToJATS opts $ concatMap (map plainToPara) defs return $ inTagsIndented "def-item" $ - inTagsIndented "term" term' $$ + inTagsSimple "term" term' $$ inTagsIndented "def" def' -- | Convert a list of lists of blocks to a list of JATS list items. @@ -156,7 +158,7 @@ listItemToJATS :: PandocMonad m listItemToJATS opts mbmarker item = do contents <- blocksToJATS opts item return $ inTagsIndented "list-item" $ - maybe empty (\lbl -> inTagsIndented "label" (text lbl)) mbmarker + maybe empty (\lbl -> inTagsSimple "label" (text lbl)) mbmarker $$ contents imageMimeType :: String -> [(String, String)] -> (String, String) @@ -250,7 +252,7 @@ blockToJATS _ (Para [Image (ident,_,kvs) _ (src, tit)]) = do "xlink:type"]] return $ selfClosingTag "graphic" attr blockToJATS opts (Para lst) = - inTagsIndented "p" <$> inlinesToJATS opts lst + inTagsSimple "p" <$> inlinesToJATS opts lst blockToJATS opts (LineBlock lns) = blockToJATS opts $ linesToPara lns blockToJATS opts (BlockQuote blocks) = @@ -326,10 +328,10 @@ tableItemToJATS :: PandocMonad m -> [Block] -> JATS m Doc tableItemToJATS opts isHeader [Plain item] = - inTags True (if isHeader then "th" else "td") [] <$> + inTags False (if isHeader then "th" else "td") [] <$> inlinesToJATS opts item tableItemToJATS opts isHeader item = - (inTags True (if isHeader then "th" else "td") [] . vcat) <$> + (inTags False (if isHeader then "th" else "td") [] . vcat) <$> mapM (blockToJATS opts) item -- | Convert a list of inline elements to JATS. |