diff options
70 files changed, 277 insertions, 389 deletions
diff --git a/.travis.yml b/.travis.yml index b9f3163a5..454d43e66 100644 --- a/.travis.yml +++ b/.travis.yml @@ -47,17 +47,17 @@ matrix: # The Stack builds. We can pass in arbitrary Stack arguments via the ARGS # variable, such as using --stack-yaml to point to a different file. - - env: BUILD=stack ARGS="--resolver lts-6 --stack-yaml stack.lts6.yaml" - compiler: ": #stack 7.10.3" - addons: {apt: {packages: [ghc-7.10.3], sources: [hvr-ghc]}} + - env: BUILD=stack ARGS="--resolver lts-7" + compiler: ": #stack 8.0.1" + addons: {apt: {packages: [ghc-8.0.1], sources: [hvr-ghc]}} # Nightly builds are allowed to fail - env: BUILD=stack ARGS="--resolver nightly" compiler: ": #stack nightly" addons: {apt: {packages: [libgmp-dev]}} - - env: BUILD=stack ARGS="--resolver lts-6 --stack-yaml stack.lts6.yaml" - compiler: ": #stack 7.10.3 osx" + - env: BUILD=stack ARGS="--resolver lts-7" + compiler: ": #stack 8.0.1 osx" os: osx - env: BUILD=stack ARGS="--resolver nightly" @@ -93,12 +93,12 @@ install: - | case "$BUILD" in stack) - stack --no-terminal --install-ghc $ARGS test --only-dependencies + stack --no-terminal --install-ghc $ARGS test --flag 'aeson:fast' --only-dependencies --fast ;; cabal) cabal --version travis_retry cabal update - cabal install --only-dependencies --enable-tests --enable-benchmarks --force-reinstalls --ghc-options=-O0 --reorder-goals --max-backjumps=-1 $CABALARGS + cabal install --only-dependencies -ffast --enable-tests --enable-benchmarks --force-reinstalls --ghc-options=-O0 --reorder-goals --max-backjumps=-1 $CABALARGS ;; esac @@ -106,10 +106,10 @@ script: - | case "$BUILD" in stack) - stack --no-terminal $ARGS test --haddock --no-haddock-deps --ghc-options="-Wall -fno-warn-unused-do-bind -Werror" + stack --no-terminal $ARGS test --flag 'aeson:fast' --haddock --no-haddock-deps --ghc-options="-O0 -Wall -fno-warn-unused-do-bind -Werror" ;; cabal) - cabal configure --enable-tests --enable-benchmarks -v2 --ghc-options="-O0 -Werror" + cabal configure --enable-tests --enable-benchmarks -v2 -ffast --ghc-options="-O0 -Wall -fno-warn-unused-do-bind -Werror" cabal build cabal check cabal test diff --git a/MANUAL.txt b/MANUAL.txt index 4119d6e3e..ed05dc3cf 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1298,8 +1298,10 @@ LaTeX variables are used when [creating a PDF]. : bibliography to use for resolving references `biblio-style` -: bibliography style, when used with `--natbib` and - `--biblatex`. +: bibliography style, when used with `--natbib` and `--biblatex`. + +`biblio-title` +: bibliography title, when used with `--natbib` and `--biblatex`. `biblatexoptions` : list of options for biblatex. @@ -18,18 +18,14 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA import Distribution.Simple import Distribution.Simple.PreProcess -import Distribution.Simple.Setup (ConfigFlags(..)) +import Distribution.Simple.Setup (ConfigFlags(..), CopyFlags(..), fromFlag) import Distribution.PackageDescription (PackageDescription(..), FlagName(..)) import Distribution.Simple.Utils ( rawSystemExitCode, findProgramVersion ) import System.Exit -import Distribution.Verbosity ( Verbosity ) import Distribution.Simple.Utils (info, notice, installOrdinaryFiles) -import Distribution.Simple.Setup import Distribution.Simple.Program (simpleProgram, Program(..)) import Distribution.Simple.LocalBuildInfo -import Data.Version import Control.Monad (when) -import qualified Control.Exception as E main :: IO () main = defaultMainWithHooks $ simpleUserHooks { diff --git a/deb/stack.yaml b/deb/stack.yaml index 4a777d4ef..ade5e6ec8 100644 --- a/deb/stack.yaml +++ b/deb/stack.yaml @@ -14,8 +14,7 @@ flags: packages: - '..' extra-deps: -- pandoc-citeproc-0.10.1.1 - doctemplates-0.1.0.2 -- http-client-0.5.0 -- http-client-tls-0.3.0 -resolver: lts-7.0 +- pandoc-types-1.17.0.4 +- pandoc-citeproc-0.10.1.2 +resolver: lts-7.4 diff --git a/osx/stack.yaml b/osx/stack.yaml index 82c5bea7b..6ee3fc66e 100644 --- a/osx/stack.yaml +++ b/osx/stack.yaml @@ -17,8 +17,7 @@ ghc-options: packages: - '..' extra-deps: -- pandoc-citeproc-0.10.1.1 - doctemplates-0.1.0.2 -- 'http-client-0.5.0' -- 'http-client-tls-0.3.0' -resolver: lts-7.0 +- pandoc-types-1.17.0.4 +- pandoc-citeproc-0.10.1.2 +resolver: lts-7.4 diff --git a/pandoc.cabal b/pandoc.cabal index a91c9d02a..ccc7df47a 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -205,8 +205,8 @@ Extra-Source-Files: tests/lhs-test.html+lhs tests/lhs-test.fragment.html+lhs tests/pipe-tables.txt - tests/dokuwiki_external_images.dokuwiki - tests/dokuwiki_external_images.native + tests/dokuwiki_external_images.dokuwiki + tests/dokuwiki_external_images.native tests/dokuwiki_multiblock_table.dokuwiki tests/dokuwiki_multiblock_table.native tests/fb2/*.markdown @@ -267,7 +267,7 @@ Library xml >= 1.3.12 && < 1.4, random >= 1 && < 1.2, extensible-exceptions >= 0.1 && < 0.2, - pandoc-types >= 1.16 && < 1.17, + pandoc-types >= 1.17 && < 1.18, aeson >= 0.7 && < 1.1, tagsoup >= 0.13.7 && < 0.15, base64-bytestring >= 0.1 && < 1.1, @@ -301,8 +301,8 @@ Library else Build-Depends: network >= 2 && < 2.6 if flag(https) - Build-Depends: http-client >= 0.5 && < 0.6, - http-client-tls >= 0.3 && < 0.4, + Build-Depends: http-client >= 0.4.30 && < 0.6, + http-client-tls >= 0.2.4 && < 0.4, http-types >= 0.8 && < 0.10 cpp-options: -DHTTP_CLIENT if flag(embed_data_files) @@ -422,7 +422,7 @@ Library Executable pandoc Build-Depends: pandoc, - pandoc-types >= 1.16 && < 1.17, + pandoc-types >= 1.17 && < 1.18, base >= 4.2 && <5, directory >= 1.2 && < 1.3, filepath >= 1.1 && < 1.5, @@ -479,7 +479,7 @@ Test-Suite test-pandoc Build-Depends: base >= 4.2 && < 5, syb >= 0.1 && < 0.7, pandoc, - pandoc-types >= 1.16 && < 1.17, + pandoc-types >= 1.17 && < 1.18, bytestring >= 0.9 && < 0.11, text >= 0.11 && < 1.3, directory >= 1 && < 1.3, @@ -491,14 +491,13 @@ Test-Suite test-pandoc test-framework-hunit >= 0.2 && < 0.4, test-framework-quickcheck2 >= 0.2.9 && < 0.4, QuickCheck >= 2.4 && < 2.10, - HUnit >= 1.2 && < 1.4, + HUnit >= 1.2 && < 1.6, containers >= 0.1 && < 0.6, ansi-terminal >= 0.5 && < 0.7, executable-path >= 0.0 && < 0.1, zip-archive >= 0.2.3.4 && < 0.4 Other-Modules: Tests.Old Tests.Helpers - Tests.Arbitrary Tests.Shared Tests.Walk Tests.Readers.LaTeX diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index e45e2247d..daf8e867d 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -718,11 +718,14 @@ lineBlockLine = try $ do continuations <- many (try $ char ' ' >> anyLine) return $ white ++ unwords (line : continuations) +blankLineBlockLine :: Stream [Char] m Char => ParserT [Char] st m Char +blankLineBlockLine = try (char '|' >> blankline) + -- | Parses an RST-style line block and returns a list of strings. lineBlockLines :: Stream [Char] m Char => ParserT [Char] st m [String] lineBlockLines = try $ do - lines' <- many1 lineBlockLine - skipMany1 $ blankline <|> try (char '|' >> blankline) + lines' <- many1 (lineBlockLine <|> ((:[]) <$> blankLineBlockLine)) + skipMany1 $ blankline <|> blankLineBlockLine return lines' -- | Parse a table using 'headerParser', 'rowParser', diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 336b40933..4d8d5ab94 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -592,8 +592,6 @@ checkInMeta p = do when accepts p return mempty - - addMeta :: ToMetaValue a => String -> a -> DB () addMeta field val = modify (setMeta field val) @@ -612,7 +610,7 @@ isBlockElement (Elem e) = qName (elName e) `elem` blocktags "important","caution","note","tip","warning","qandadiv", "question","answer","abstract","itemizedlist","orderedlist", "variablelist","article","book","table","informaltable", - "informalexample", + "informalexample", "linegroup", "screen","programlisting","example","calloutlist"] isBlockElement _ = False @@ -779,6 +777,7 @@ parseBlock (Elem e) = "informaltable" -> parseTable "informalexample" -> divWith ("", ["informalexample"], []) <$> getBlocks e + "linegroup" -> lineBlock <$> lineItems "literallayout" -> codeBlockWithLang "screen" -> codeBlockWithLang "programlisting" -> codeBlockWithLang @@ -900,6 +899,7 @@ parseBlock (Elem e) = let ident = attrValue "id" e modify $ \st -> st{ dbSectionLevel = n - 1 } return $ headerWith (ident,[],[]) n' headerText <> b + lineItems = mapM getInlines $ filterChildren (named "line") e metaBlock = acceptingMetadata (getBlocks e) >> return mempty getInlines :: Element -> DB Inlines diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 2e95c518d..68bc936b1 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -32,7 +32,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document. module Text.Pandoc.Readers.Markdown ( readMarkdown, readMarkdownWithWarnings ) where -import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate ) +import Data.List ( transpose, sortBy, findIndex, intercalate ) import qualified Data.Map as M import Data.Scientific (coefficient, base10Exponent) import Data.Ord ( comparing ) @@ -1106,7 +1106,7 @@ lineBlock = try $ do guardEnabled Ext_line_blocks lines' <- lineBlockLines >>= mapM (parseFromString (trimInlinesF . mconcat <$> many inline)) - return $ B.para <$> (mconcat $ intersperse (return B.linebreak) lines') + return $ B.lineBlock <$> sequence lines' -- -- Tables diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 1aaff62e5..11d39498c 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -418,7 +418,7 @@ getListConstructor ListLevelStyle{..} = LltNumbered -> let listNumberStyle = toListNumberStyle listItemFormat listNumberDelim = toListNumberDelim listItemPrefix listItemSuffix - in orderedListWith (1, listNumberStyle, listNumberDelim) + in orderedListWith (listItemStart, listNumberStyle, listNumberDelim) where toListNumberStyle LinfNone = DefaultStyle toListNumberStyle LinfNumber = Decimal diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs index 96cfed0b3..26ba6df82 100644 --- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs +++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs @@ -76,8 +76,9 @@ import Control.Applicative hiding ( liftA, liftA2, liftA3 ) import qualified Data.Foldable as F import qualified Data.Map as M import qualified Data.Set as S -import Data.List ( unfoldr ) +import Data.Char ( isDigit ) import Data.Default +import Data.List ( unfoldr ) import Data.Maybe import qualified Text.XML.Light as XML @@ -390,6 +391,7 @@ data ListLevelStyle = ListLevelStyle { listLevelType :: ListLevelType , listItemPrefix :: Maybe String , listItemSuffix :: Maybe String , listItemFormat :: ListItemNumberFormat + , listItemStart :: Int } deriving ( Eq, Ord ) @@ -578,25 +580,31 @@ readListLevelStyles namespace elementName levelType = readListLevelStyle :: ListLevelType -> StyleReader _x (Int, ListLevelStyle) readListLevelStyle levelType = readAttr NsText "level" >>?! keepingTheValue - ( liftA4 toListLevelStyle - ( returnV levelType ) - ( findAttr' NsStyle "num-prefix" ) - ( findAttr' NsStyle "num-suffix" ) - ( getAttr NsStyle "num-format" ) + ( liftA5 toListLevelStyle + ( returnV levelType ) + ( findAttr' NsStyle "num-prefix" ) + ( findAttr' NsStyle "num-suffix" ) + ( getAttr NsStyle "num-format" ) + ( findAttr' NsText "start-value" ) ) where - toListLevelStyle _ p s LinfNone = ListLevelStyle LltBullet p s LinfNone - toListLevelStyle _ p s f@(LinfString _) = ListLevelStyle LltBullet p s f - toListLevelStyle t p s f = ListLevelStyle t p s f + toListLevelStyle _ p s LinfNone b = ListLevelStyle LltBullet p s LinfNone (startValue b) + toListLevelStyle _ p s f@(LinfString _) b = ListLevelStyle LltBullet p s f (startValue b) + toListLevelStyle t p s f b = ListLevelStyle t p s f (startValue b) + startValue (Just "") = 1 + startValue (Just v) = if all isDigit v + then read v + else 1 + startValue Nothing = 1 -- chooseMostSpecificListLevelStyle :: S.Set ListLevelStyle -> Maybe ListLevelStyle chooseMostSpecificListLevelStyle ls | ls == mempty = Nothing | otherwise = Just ( F.foldr1 select ls ) where - select ( ListLevelStyle t1 p1 s1 f1 ) - ( ListLevelStyle t2 p2 s2 f2 ) - = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2) + select ( ListLevelStyle t1 p1 s1 f1 b1 ) + ( ListLevelStyle t2 p2 s2 f2 _ ) + = ListLevelStyle (select' t1 t2) (p1 <|> p2) (s1 <|> s2) (selectLinf f1 f2) b1 select' LltNumbered _ = LltNumbered select' _ LltNumbered = LltNumbered select' _ _ = LltBullet diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index 82c3a6cbe..61978f79f 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -50,7 +50,7 @@ import Text.Pandoc.Shared ( compactify', compactify'DL ) import Control.Monad ( foldM, guard, mzero, void ) import Data.Char ( isSpace, toLower, toUpper) -import Data.List ( foldl', intersperse, isPrefixOf ) +import Data.List ( foldl', isPrefixOf ) import Data.Maybe ( fromMaybe, isNothing ) import Data.Monoid ((<>)) @@ -288,9 +288,9 @@ blockAttributes = try $ do let kvAttrs = foldl' (appendValues "ATTR_HTML") Nothing kv let name = lookup "NAME" kv let label = lookup "LABEL" kv - caption' <- maybe (return Nothing) - (fmap Just . parseFromString inlines) - caption + caption' <- case caption of + Nothing -> return Nothing + Just s -> Just <$> parseFromString inlines (s ++ "\n") kvAttrs' <- parseFromString keyValues . (++ "\n") $ fromMaybe mempty kvAttrs return $ BlockAttributes { blockAttrName = name @@ -427,7 +427,7 @@ verseBlock :: String -> OrgParser (F Blocks) verseBlock blockType = try $ do ignHeaders content <- rawBlockContent blockType - fmap B.para . mconcat . intersperse (pure B.linebreak) + fmap B.lineBlock . sequence <$> mapM parseVerseLine (lines content) where -- replace initial spaces with nonbreaking spaces to preserve diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index f181d523a..1b06c6f23 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -39,7 +39,7 @@ import Text.Pandoc.Shared import Text.Pandoc.Parsing import Text.Pandoc.Options import Control.Monad ( when, liftM, guard, mzero ) -import Data.List ( findIndex, intersperse, intercalate, +import Data.List ( findIndex, intercalate, transpose, sort, deleteFirstsBy, isSuffixOf , nub, union) import Data.Maybe (fromMaybe) import qualified Data.Map as M @@ -228,7 +228,7 @@ lineBlock :: RSTParser Blocks lineBlock = try $ do lines' <- lineBlockLines lines'' <- mapM parseInlineFromString lines' - return $ B.para (mconcat $ intersperse B.linebreak lines'') + return $ B.lineBlock lines'' -- -- paragraph block @@ -949,7 +949,8 @@ table = gridTable False <|> simpleTable False <|> -- inline :: RSTParser Inlines -inline = choice [ whitespace +inline = choice [ note -- can start with whitespace, so try before ws + , whitespace , link , str , endline @@ -958,7 +959,6 @@ inline = choice [ whitespace , code , subst , interpretedRole - , note , smart , hyphens , escapedChar @@ -1174,6 +1174,7 @@ subst = try $ do note :: RSTParser Inlines note = try $ do + optional whitespace ref <- noteMarker char '_' state <- getState diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 0760b49f8..4c10a5572 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -64,6 +64,7 @@ module Text.Pandoc.Shared ( compactify, compactify', compactify'DL, + linesToPara, Element (..), hierarchicalize, uniqueIdent, @@ -155,7 +156,8 @@ import Paths_pandoc (getDataFileName) #ifdef HTTP_CLIENT import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, Request(port,host)) -import Network.HTTP.Client (parseRequest, newManager) +import Network.HTTP.Client (parseRequest) +import Network.HTTP.Client (newManager) import Network.HTTP.Client.Internal (addProxy) import Network.HTTP.Client.TLS (tlsManagerSettings) import System.Environment (getEnv) @@ -633,6 +635,15 @@ compactify'DL items = | otherwise -> items _ -> items +-- | Combine a list of lines by adding hard linebreaks. +combineLines :: [[Inline]] -> [Inline] +combineLines = intercalate [LineBreak] + +-- | Convert a list of lines into a paragraph with hard line breaks. This is +-- useful e.g. for rudimentary support of LineBlock elements in writers. +linesToPara :: [[Inline]] -> Block +linesToPara = Para . combineLines + isPara :: Block -> Bool isPara (Para _) = True isPara _ = False @@ -950,11 +961,7 @@ openURL u in return $ Right (decodeLenient contents, Just mime) #ifdef HTTP_CLIENT | otherwise = withSocketsDo $ E.try $ do -#if MIN_VERSION_http_client(0,4,30) let parseReq = parseRequest -#else - let parseReq = parseUrl -#endif (proxy :: Either E.SomeException String) <- E.try $ getEnv "http_proxy" req <- parseReq u req' <- case proxy of @@ -962,11 +969,7 @@ openURL u Right pr -> (parseReq pr >>= \r -> return $ addProxy (host r) (port r) req) `mplus` return req -#if MIN_VERSION_http_client(0,4,18) resp <- newManager tlsManagerSettings >>= httpLbs req' -#else - resp <- withManager tlsManagerSettings $ httpLbs req' -#endif return (BS.concat $ toChunks $ responseBody resp, UTF8.toString `fmap` lookup hContentType (responseHeaders resp)) #else @@ -1048,6 +1051,7 @@ filteredFilesFromArchive zf f = blockToInlines :: Block -> [Inline] blockToInlines (Plain ils) = ils blockToInlines (Para ils) = ils +blockToInlines (LineBlock lns) = combineLines lns blockToInlines (CodeBlock attr str) = [Code attr str] blockToInlines (RawBlock fmt str) = [RawInline fmt str] blockToInlines (BlockQuote blks) = blocksToInlines blks diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 0dfbd705e..c7097c368 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -137,6 +137,13 @@ blockToAsciiDoc opts (Para inlines) = do then text "\\" else empty return $ esc <> contents <> blankline +blockToAsciiDoc opts (LineBlock lns) = do + let docify line = if null line + then return blankline + else inlineListToAsciiDoc opts line + let joinWithLinefeeds = nowrap . mconcat . intersperse cr + contents <- joinWithLinefeeds <$> mapM docify lns + return $ "[verse]" $$ text "--" $$ contents $$ text "--" $$ blankline blockToAsciiDoc _ (RawBlock f s) | f == "asciidoc" = return $ text s | otherwise = return empty @@ -459,4 +466,3 @@ inlineToAsciiDoc opts (Span (ident,_,_) ils) = do let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]") contents <- inlineListToAsciiDoc opts ils return $ identifier <> contents - diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 262f491a8..c6509fe92 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -33,7 +33,7 @@ module Text.Pandoc.Writers.CommonMark (writeCommonMark) where import Text.Pandoc.Writers.HTML (writeHtmlString) import Text.Pandoc.Definition -import Text.Pandoc.Shared (isTightList) +import Text.Pandoc.Shared (isTightList, linesToPara) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Writers.Shared import Text.Pandoc.Options @@ -94,6 +94,7 @@ blocksToNodes = foldr blockToNodes [] blockToNodes :: Block -> [Node] -> [Node] blockToNodes (Plain xs) = (node PARAGRAPH (inlinesToNodes xs) :) blockToNodes (Para xs) = (node PARAGRAPH (inlinesToNodes xs) :) +blockToNodes (LineBlock lns) = blockToNodes $ linesToPara lns blockToNodes (CodeBlock (_,classes,_) xs) = (node (CODE_BLOCK (T.pack (unwords classes)) (T.pack xs)) [] :) blockToNodes (RawBlock fmt xs) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 8d54d62bd..398d4170f 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -163,6 +163,9 @@ blockToConTeXt (Para [Image attr txt (src,'f':'i':'g':':':_)]) = do blockToConTeXt (Para lst) = do contents <- inlineListToConTeXt lst return $ contents <> blankline +blockToConTeXt (LineBlock lns) = do + doclines <- nowrap . vcat <$> mapM inlineListToConTeXt lns + return $ "\\startlines" $$ doclines $$ "\\stoplines" <> blankline blockToConTeXt (BlockQuote lst) = do contents <- blockListToConTeXt lst return $ "\\startblockquote" $$ nest 0 contents $$ "\\stopblockquote" <> blankline @@ -467,4 +470,3 @@ fromBcp47 x = fromIso $ head x fromIso "vi" = "vn" fromIso "zh" = "cn" fromIso l = l - diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index d69eaaa64..631241724 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -227,6 +227,8 @@ blockToCustom lua (Para [Image attr txt (src,tit)]) = blockToCustom lua (Para inlines) = callfunc lua "Para" inlines +blockToCustom lua (LineBlock linesList) = callfunc lua "LineBlock" linesList + blockToCustom lua (RawBlock format str) = callfunc lua "RawBlock" format str diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 8bb0810e4..e19b4666b 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -198,6 +198,8 @@ blockToDocbook opts (Para [Image attr txt (src,'f':'i':'g':':':_)]) = blockToDocbook opts (Para lst) | hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst | otherwise = inTagsIndented "para" $ inlinesToDocbook opts lst +blockToDocbook opts (LineBlock lns) = + blockToDocbook opts $ linesToPara lns blockToDocbook opts (BlockQuote blocks) = inTagsIndented "blockquote" $ blocksToDocbook opts blocks blockToDocbook _ (CodeBlock (_,classes,_) str) = @@ -385,4 +387,3 @@ idAndRole (id',cls,_) = ident ++ role role = if null cls then [] else [("role", unwords cls)] - diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a006773d6..dfa011784 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -275,7 +275,7 @@ writeDocx opts doc@(Pandoc meta _) = do } - ((contents, footnotes), st) <- runStateT + ((contents, footnotes), st) <- runStateT (runReaderT (writeOpenXML opts{writerWrapText = WrapNone} doc') env) @@ -446,7 +446,7 @@ writeDocx opts doc@(Pandoc meta _) = do let newstyles = map newParaPropToOpenXml newDynamicParaProps ++ map newTextPropToOpenXml newDynamicTextProps ++ - (styleToOpenXml styleMaps $ writerHighlightStyle opts) + (styleToOpenXml styleMaps $ writerHighlightStyle opts) let styledoc' = styledoc{ elContent = modifyContent (elContent styledoc) } where modifyContent @@ -859,6 +859,7 @@ blockToOpenXML' opts (Para lst) = do modify $ \s -> s { stFirstPara = False } contents <- inlinesToOpenXML opts lst return [mknode "w:p" [] (paraProps' ++ contents)] +blockToOpenXML' opts (LineBlock lns) = blockToOpenXML opts $ linesToPara lns blockToOpenXML' _ (RawBlock format str) | format == Format "openxml" = return [ x | Elem x <- parseXML str ] | otherwise = return [] @@ -1032,7 +1033,7 @@ setFirstPara = modify $ \s -> s { stFirstPara = True } -- | Convert an inline element to OpenXML. inlineToOpenXML :: WriterOptions -> Inline -> WS [Element] -inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il +inlineToOpenXML opts il = withDirection $ inlineToOpenXML' opts il inlineToOpenXML' :: WriterOptions -> Inline -> WS [Element] inlineToOpenXML' _ (Str str) = formattedString str @@ -1286,7 +1287,7 @@ withDirection x = do textProps <- asks envTextProperties -- We want to clean all bidirection (bidi) and right-to-left (rtl) -- properties from the props first. This is because we don't want - -- them to stack up. + -- them to stack up. let paraProps' = filter (\e -> (qName . elName) e /= "bidi") paraProps textProps' = filter (\e -> (qName . elName) e /= "rtl") textProps if isRTL @@ -1298,5 +1299,3 @@ withDirection x = do else flip local x $ \env -> env { envParaProperties = paraProps' , envTextProperties = textProps' } - - diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 56e2b9027..402b74bc3 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -45,8 +45,8 @@ import Text.Pandoc.Options ( WriterOptions( , writerStandalone , writerTemplate , writerWrapText), WrapOption(..) ) -import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated - , trimr, normalize, substitute ) +import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting + , camelCaseToHyphenated, trimr, normalize, substitute ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) @@ -147,6 +147,9 @@ blockToDokuWiki opts (Para inlines) = do then "<HTML><p></HTML>" ++ contents ++ "<HTML></p></HTML>" else contents ++ if null indent then "\n" else "" +blockToDokuWiki opts (LineBlock lns) = + blockToDokuWiki opts $ linesToPara lns + blockToDokuWiki _ (RawBlock f str) | f == Format "dokuwiki" = return str -- See https://www.dokuwiki.org/wiki:syntax diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 80296e111..6f47dbcd2 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -46,7 +46,8 @@ import qualified Text.XML.Light.Cursor as XC import Text.Pandoc.Definition import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def) -import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize) +import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize, + linesToPara) -- | Data to be written at the end of the document: -- (foot)notes, URLs, references, images. @@ -323,6 +324,7 @@ blockToXml (RawBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . lines $ s blockToXml (Div _ bs) = cMapM blockToXml bs blockToXml (BlockQuote bs) = liftM (list . el "cite") $ cMapM blockToXml bs +blockToXml (LineBlock lns) = blockToXml $ linesToPara lns blockToXml (OrderedList a bss) = do state <- get let pmrk = parentListMarker state diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index db8c301ef..2d0df4dbe 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -463,6 +463,13 @@ blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do blockToHtml opts (Para lst) = do contents <- inlineListToHtml opts lst return $ H.p contents +blockToHtml opts (LineBlock lns) = + if writerWrapText opts == WrapNone + then blockToHtml opts $ linesToPara lns + else do + let lf = preEscapedString "\n" + htmlLines <- mconcat . intersperse lf <$> mapM (inlineListToHtml opts) lns + return $ H.div ! A.style "white-space: pre-line;" $ htmlLines blockToHtml opts (Div attr@(ident, classes, kvs) bs) = do let speakerNotes = "notes" `elem` classes -- we don't want incremental output inside speaker notes, see #1394 @@ -807,7 +814,7 @@ inlineToHtml opts inline = let brtag = if writerHtml5 opts then H5.br else H.br return $ case t of InlineMath -> m - DisplayMath -> brtag >> m >> brtag + DisplayMath -> brtag >> m >> brtag (RawInline f str) | f == Format "html" -> return $ preEscapedString str | otherwise -> return mempty diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 2e5f2dd08..caf549916 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -108,6 +108,8 @@ blockToHaddock opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = blockToHaddock opts (Para inlines) = -- TODO: if it contains linebreaks, we need to use a @...@ block (<> blankline) `fmap` blockToHaddock opts (Plain inlines) +blockToHaddock opts (LineBlock lns) = + blockToHaddock opts $ linesToPara lns blockToHaddock _ (RawBlock f str) | f == "haddock" = do return $ text str <> text "\n" diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 57a61178e..8f6123e20 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -2,7 +2,7 @@ {- | Module : Text.Pandoc.Writers.ICML - Copyright : Copyright (C) 2013 github.com/mb21 + Copyright : Copyright (C) 2013-2016 github.com/mb21 License : GNU GPL, version 2 or above Stability : alpha @@ -18,7 +18,7 @@ import Text.Pandoc.Definition import Text.Pandoc.XML import Text.Pandoc.Readers.TeXMath (texMathToInlines) import Text.Pandoc.Writers.Shared -import Text.Pandoc.Shared (splitBy, fetchItem, warn) +import Text.Pandoc.Shared (linesToPara, splitBy, fetchItem, warn) import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Pretty @@ -297,6 +297,8 @@ blockToICML opts style (Para img@[Image _ txt (_,'f':'i':'g':':':_)]) = do caption <- parStyle opts (imgCaptionName:style) txt return $ intersperseBrs [figure, caption] blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst +blockToICML opts style (LineBlock lns) = + blockToICML opts style $ linesToPara lns blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) $ [Str str] blockToICML _ _ (RawBlock f str) | f == Format "icml" = return $ text str diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index a88ff303f..517460f5d 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -437,6 +437,8 @@ blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do else inlineListToLaTeX [Str ".",Space,Str ".",Space,Str "."] blockToLaTeX (Para lst) = inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst +blockToLaTeX (LineBlock lns) = do + blockToLaTeX $ linesToPara lns blockToLaTeX (BlockQuote lst) = do beamer <- writerBeamer `fmap` gets stOptions case lst of diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index caf26d515..159e89308 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -171,6 +171,8 @@ blockToMan opts (Para inlines) = do contents <- liftM vcat $ mapM (inlineListToMan opts) $ splitSentences inlines return $ text ".PP" $$ contents +blockToMan opts (LineBlock lns) = + blockToMan opts $ linesToPara lns blockToMan _ (RawBlock f str) | f == Format "man" = return $ text str | otherwise = return empty @@ -367,4 +369,3 @@ inlineToMan _ (Note contents) = do notes <- liftM stNotes get let ref = show $ (length notes) return $ char '[' <> text ref <> char ']' - diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3ad31d54a..471b28d39 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-} +{-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables, MultiWayIf #-} {- Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu> @@ -79,7 +79,7 @@ instance Default WriterEnv , envRefShortcutable = True , envBlockLevel = 0 } - + data WriterState = WriterState { stNotes :: Notes , stRefs :: Refs , stIds :: Set.Set String @@ -204,15 +204,10 @@ pandocToMarkdown opts (Pandoc meta blocks) = do _ -> blocks else blocks body <- blockListToMarkdown opts blocks' - st <- get - notes' <- notesToMarkdown opts (reverse $ stNotes st) - st' <- get -- note that the notes may contain refs - refs' <- refsToMarkdown opts (reverse $ stRefs st') + notesAndRefs' <- notesAndRefs opts let render' :: Doc -> String render' = render colwidth - let main = render' $ body <> - (if isEmpty notes' then empty else blankline <> notes') <> - (if isEmpty refs' then empty else blankline <> refs') + let main = render' $ body <> notesAndRefs' let context = defField "toc" (render' toc) $ defField "body" main $ (if isNullMeta meta @@ -337,6 +332,23 @@ beginsWithOrderedListMarker str = Left _ -> False Right _ -> True +notesAndRefs :: WriterOptions -> MD Doc +notesAndRefs opts = do + notes' <- reverse <$> gets stNotes >>= notesToMarkdown opts + modify $ \s -> s { stNotes = [] } + refs' <- reverse <$> gets stRefs >>= refsToMarkdown opts + modify $ \s -> s { stRefs = [] } + + let endSpacing = + if | writerReferenceLocation opts == EndOfDocument -> empty + | isEmpty notes' && isEmpty refs' -> empty + | otherwise -> blankline + + return $ + (if isEmpty notes' then empty else blankline <> notes') <> + (if isEmpty refs' then empty else blankline <> refs') <> + endSpacing + -- | Convert Pandoc block element to markdown. blockToMarkdown :: WriterOptions -- ^ Options -> Block -- ^ Block element @@ -346,16 +358,7 @@ blockToMarkdown opts blk = do doc <- blockToMarkdown' opts blk blkLevel <- asks envBlockLevel if writerReferenceLocation opts == EndOfBlock && blkLevel == 1 - then do st <- get - notes' <- notesToMarkdown opts (reverse $ stNotes st) - modify $ \s -> s { stNotes = [] } - st' <- get -- note that the notes may contain refs - refs' <- refsToMarkdown opts (reverse $ stRefs st') - modify $ \s -> s { stRefs = [] } - return $ doc <> - (if isEmpty notes' then empty else blankline <> notes') <> - (if isEmpty refs' then empty else blankline <> refs') <> - (if (isEmpty notes' && isEmpty refs') then empty else blankline) + then notesAndRefs opts >>= (\d -> return $ doc <> d) else return doc blockToMarkdown' :: WriterOptions -- ^ Options @@ -390,6 +393,12 @@ blockToMarkdown' opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown' opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) +blockToMarkdown' opts (LineBlock lns) = + if isEnabled Ext_line_blocks opts + then do + mdLines <- mapM (inlineListToMarkdown opts) lns + return $ (vcat $ map (hang 2 (text "| ")) mdLines) <> blankline + else blockToMarkdown opts $ linesToPara lns blockToMarkdown' opts (RawBlock f str) | f == "markdown" = return $ text str <> text "\n" | f == "html" && isEnabled Ext_raw_html opts = do @@ -412,16 +421,7 @@ blockToMarkdown' opts (Header level attr inlines) = do -- put them here. blkLevel <- asks envBlockLevel refs <- if writerReferenceLocation opts == EndOfSection && blkLevel == 1 - then do st <- get - notes' <- notesToMarkdown opts (reverse $ stNotes st) - modify $ \s -> s { stNotes = [] } - st' <- get -- note that the notes may contain refs - refs' <- refsToMarkdown opts (reverse $ stRefs st') - modify $ \s -> s { stRefs = [] } - return $ - (if isEmpty notes' then empty else blankline <> notes') <> - (if isEmpty refs' then empty else blankline <> refs') <> - (if (isEmpty notes' && isEmpty refs') then empty else blankline) + then notesAndRefs opts else return empty plain <- asks envPlain diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 0da8bc98c..3b2028997 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -120,6 +120,9 @@ blockToMediaWiki (Para inlines) = do then "<p>" ++ contents ++ "</p>" else contents ++ if null lev then "\n" else "" +blockToMediaWiki (LineBlock lns) = + blockToMediaWiki $ linesToPara lns + blockToMediaWiki (RawBlock f str) | f == Format "mediawiki" = return str | f == Format "html" = return str diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index fc96e3e3c..2a9bc5138 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -45,6 +45,8 @@ prettyList ds = -- | Prettyprint Pandoc block element. prettyBlock :: Block -> Doc +prettyBlock (LineBlock lines') = + "LineBlock" $$ prettyList (map (text . show) lines') prettyBlock (BlockQuote blocks) = "BlockQuote" $$ prettyList (map prettyBlock blocks) prettyBlock (OrderedList attribs blockLists) = diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index e0434c630..583aa2e4a 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.XML +import Text.Pandoc.Shared (linesToPara) import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Pretty @@ -291,6 +292,7 @@ blockToOpenDocument o bs | Para b <- bs = if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b + | LineBlock b <- bs = blockToOpenDocument o $ linesToPara b | Div _ xs <- bs = blocksToOpenDocument o xs | Header i _ b <- bs = setFirstPara >> (inHeaderTags i =<< inlinesToOpenDocument o b) diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 96baacbb6..18a820f2e 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -164,6 +164,17 @@ blockToOrg (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do blockToOrg (Para inlines) = do contents <- inlineListToOrg inlines return $ contents <> blankline +blockToOrg (LineBlock lns) = do + let splitStanza [] = [] + splitStanza xs = case break (== mempty) xs of + (l, []) -> l : [] + (l, _:r) -> l : splitStanza r + let joinWithLinefeeds = nowrap . mconcat . intersperse cr + let joinWithBlankLines = mconcat . intersperse blankline + let prettyfyStanza ls = joinWithLinefeeds <$> mapM inlineListToOrg ls + contents <- joinWithBlankLines <$> mapM prettyfyStanza (splitStanza lns) + return $ blankline $$ "#+BEGIN_VERSE" $$ + nest 2 contents $$ "#+END_VERSE" <> blankline blockToOrg (RawBlock "html" str) = return $ blankline $$ "#+BEGIN_HTML" $$ nest 2 (text str) $$ "#+END_HTML" $$ blankline @@ -362,7 +373,7 @@ inlineToOrg (Note contents) = do notes <- get >>= (return . stNotes) modify $ \st -> st { stNotes = contents:notes } let ref = show $ (length notes) + 1 - return $ " [" <> text ref <> "]" + return $ "[" <> text ref <> "]" orgPath :: String -> String orgPath src = diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 98c39bdaf..21f1acd6e 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -201,11 +201,12 @@ blockToRST (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline blockToRST (Para inlines) | LineBreak `elem` inlines = do -- use line block if LineBreaks - lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines - return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline + linesToLineBlock $ splitBy (==LineBreak) inlines | otherwise = do contents <- inlineListToRST inlines return $ contents <> blankline +blockToRST (LineBlock lns) = + linesToLineBlock lns blockToRST (RawBlock f@(Format f') str) | f == "rst" = return $ text str | otherwise = return $ blankline <> ".. raw:: " <> @@ -328,6 +329,12 @@ definitionListItemToRST (label, defs) = do tabstop <- get >>= (return . writerTabStop . stOptions) return $ label' $$ nest tabstop (nestle contents <> cr) +-- | Format a list of lines as line block. +linesToLineBlock :: [[Inline]] -> State WriterState Doc +linesToLineBlock inlineLines = do + lns <- mapM inlineListToRST inlineLines + return $ (vcat $ map (hang 2 (text "| ")) lns) <> blankline + -- | Convert list of Pandoc block elements to RST. blockListToRST' :: Bool -> [Block] -- ^ List of block elements diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 79a28c880..b87ef0fd3 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -233,6 +233,8 @@ blockToRTF indent alignment (Plain lst) = rtfCompact indent 0 alignment $ inlineListToRTF lst blockToRTF indent alignment (Para lst) = rtfPar indent 0 alignment $ inlineListToRTF lst +blockToRTF indent alignment (LineBlock lns) = + blockToRTF indent alignment $ linesToPara lns blockToRTF indent alignment (BlockQuote lst) = concatMap (blockToRTF (indent + indentIncrement) alignment) lst blockToRTF indent _ (CodeBlock _ str) = diff --git a/src/Text/Pandoc/Writers/TEI.hs b/src/Text/Pandoc/Writers/TEI.hs index b9e683ab9..018884202 100644 --- a/src/Text/Pandoc/Writers/TEI.hs +++ b/src/Text/Pandoc/Writers/TEI.hs @@ -108,7 +108,7 @@ plainToPara :: Block -> Block plainToPara (Plain x) = Para x plainToPara x = x --- | Convert a list of pairs of terms and definitions into a TEI +-- | Convert a list of pairs of terms and definitions into a TEI -- list with labels and items. deflistItemsToTEI :: WriterOptions -> [([Inline],[[Block]])] -> Doc deflistItemsToTEI opts items = @@ -167,6 +167,8 @@ blockToTEI opts (Plain lst) = blockToTEI opts $ Para lst -- inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToTEI opts (Para lst) = inTags False "p" [] $ inlinesToTEI opts lst +blockToTEI opts (LineBlock lns) = + blockToTEI opts $ linesToPara lns blockToTEI opts (BlockQuote blocks) = inTagsIndented "quote" $ blocksToTEI opts blocks blockToTEI _ (CodeBlock (_,classes,_) str) = @@ -174,7 +176,7 @@ blockToTEI _ (CodeBlock (_,classes,_) str) = flush (text (escapeStringForXML str) <> cr <> text "</ab>") where lang = if null langs then "" - else escapeStringForXML (head langs) + else escapeStringForXML (head langs) isLang l = map toLower l `elem` map (map toLower) languages langsFrom s = if isLang s then [s] @@ -210,7 +212,7 @@ blockToTEI _ HorizontalRule = selfClosingTag "milestone" [("unit","undefined"), ("type","separator"),("rendition","line")] -- | TEI Tables --- TEI Simple's tables are composed of cells and rows; other +-- TEI Simple's tables are composed of cells and rows; other -- table info in the AST is here lossily discard. blockToTEI opts (Table _ _ _ headers rows) = let @@ -219,8 +221,8 @@ blockToTEI opts (Table _ _ _ headers rows) = -- then return empty -- else tableRowToTEI opts headers in - inTags True "table" [] $ - vcat $ [headers'] <> map (tableRowToTEI opts) rows + inTags True "table" [] $ + vcat $ [headers'] <> map (tableRowToTEI opts) rows tableRowToTEI :: WriterOptions -> [[Block]] @@ -276,7 +278,7 @@ inlineToTEI _ (Math t str) = text (str) DisplayMath -> inTags True "figure" [("type","math")] $ inTags False "formula" [("notation","TeX")] $ text (str) - + inlineToTEI _ (RawInline f x) | f == "tei" = text x | otherwise = empty inlineToTEI _ LineBreak = selfClosingTag "lb" [] @@ -317,4 +319,3 @@ idAndRole (id',cls,_) = ident ++ role role = if null cls then [] else [("role", unwords cls)] - diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 8420704dc..b94229943 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -145,6 +145,9 @@ blockToTexinfo (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do blockToTexinfo (Para lst) = inlineListToTexinfo lst -- this is handled differently from Plain in blockListToTexinfo +blockToTexinfo (LineBlock lns) = + blockToTexinfo $ linesToPara lns + blockToTexinfo (BlockQuote lst) = do contents <- blockListToTexinfo lst return $ text "@quotation" $$ diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 98f9157fb..ec70f3072 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -130,6 +130,9 @@ blockToTextile opts (Para inlines) = do then "<p>" ++ contents ++ "</p>" else contents ++ if null listLevel then "\n" else "" +blockToTextile opts (LineBlock lns) = + blockToTextile opts $ linesToPara lns + blockToTextile _ (RawBlock f str) | f == Format "html" || f == Format "textile" = return str | otherwise = return "" diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 05563970a..8afbfef92 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -33,7 +33,8 @@ http://zim-wiki.org/manual/Help/Wiki_Syntax.html module Text.Pandoc.Writers.ZimWiki ( writeZimWiki ) where import Text.Pandoc.Definition import Text.Pandoc.Options ( WriterOptions(writerTableOfContents, writerStandalone, writerTemplate, writerWrapText), WrapOption(..) ) -import Text.Pandoc.Shared ( escapeURI, removeFormatting, trimr, substitute ) +import Text.Pandoc.Shared ( escapeURI, linesToPara, removeFormatting, trimr + , substitute ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) @@ -111,6 +112,9 @@ blockToZimWiki opts (Para inlines) = do contents <- inlineListToZimWiki opts inlines return $ contents ++ if null indent then "\n" else "" +blockToZimWiki opts (LineBlock lns) = do + blockToZimWiki opts $ linesToPara lns + blockToZimWiki opts (RawBlock f str) | f == Format "zimwiki" = return str | f == Format "html" = do cont <- indentFromHTML opts str; return cont diff --git a/stack.full.yaml b/stack.full.yaml index 4be19b9b6..4881a075d 100644 --- a/stack.full.yaml +++ b/stack.full.yaml @@ -22,6 +22,4 @@ packages: - '../texmath' extra-deps: - doctemplates-0.1.0.2 -- http-client-0.5.0 -- http-client-tls-0.3.0 -resolver: lts-7.0 +resolver: lts-7.4 diff --git a/stack.lts6.yaml b/stack.lts6.yaml deleted file mode 100644 index 7b497479e..000000000 --- a/stack.lts6.yaml +++ /dev/null @@ -1,16 +0,0 @@ -flags: - pandoc: - trypandoc: false - https: true - embed_data_files: false - old-locale: false - network-uri: true -packages: -- '.' -extra-deps: -- data-default-0.6.0 -- http-client-0.5.0 -- http-client-tls-0.3.0 -- doctemplates-0.1.0.2 -- cmark-0.5.3.1 -resolver: lts-6.5 diff --git a/stack.yaml b/stack.yaml index 8514454ff..34a4dc0db 100644 --- a/stack.yaml +++ b/stack.yaml @@ -8,7 +8,6 @@ flags: packages: - '.' extra-deps: -- http-client-0.5.0 -- http-client-tls-0.3.0 - doctemplates-0.1.0.2 -resolver: lts-7.0 +- pandoc-types-1.17.0.4 +resolver: lts-7.4 diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs deleted file mode 100644 index d792e1375..000000000 --- a/tests/Tests/Arbitrary.hs +++ /dev/null @@ -1,194 +0,0 @@ -{-# OPTIONS_GHC -fno-warn-orphans #-} -{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, ScopedTypeVariables #-} --- provides Arbitrary instance for Pandoc types -module Tests.Arbitrary () -where -import Test.QuickCheck.Gen -import Test.QuickCheck.Arbitrary -import Control.Monad (liftM, liftM2) -import Text.Pandoc.Definition -import Text.Pandoc.Shared (normalize, escapeURI) -import Text.Pandoc.Builder - -realString :: Gen String -realString = resize 8 $ listOf $ frequency [ (9, elements [' '..'\127']) - , (1, elements ['\128'..'\9999']) ] - -arbAttr :: Gen Attr -arbAttr = do - id' <- elements ["","loc"] - classes <- elements [[],["haskell"],["c","numberLines"]] - keyvals <- elements [[],[("start","22")],[("a","11"),("b_2","a b c")]] - return (id',classes,keyvals) - -instance Arbitrary Inlines where - arbitrary = liftM (fromList :: [Inline] -> Inlines) arbitrary - -instance Arbitrary Blocks where - arbitrary = liftM (fromList :: [Block] -> Blocks) arbitrary - -instance Arbitrary Inline where - arbitrary = resize 3 $ arbInline 2 - -arbInlines :: Int -> Gen [Inline] -arbInlines n = listOf1 (arbInline n) `suchThat` (not . startsWithSpace) - where startsWithSpace (Space:_) = True - startsWithSpace _ = False - --- restrict to 3 levels of nesting max; otherwise we get --- bogged down in indefinitely large structures -arbInline :: Int -> Gen Inline -arbInline n = frequency $ [ (60, liftM Str realString) - , (60, return Space) - , (10, liftM2 Code arbAttr realString) - , (5, elements [ RawInline (Format "html") "<a id=\"eek\">" - , RawInline (Format "latex") "\\my{command}" ]) - ] ++ [ x | x <- nesters, n > 1] - where nesters = [ (10, liftM Emph $ arbInlines (n-1)) - , (10, liftM Strong $ arbInlines (n-1)) - , (10, liftM Strikeout $ arbInlines (n-1)) - , (10, liftM Superscript $ arbInlines (n-1)) - , (10, liftM Subscript $ arbInlines (n-1)) - , (10, liftM SmallCaps $ arbInlines (n-1)) - , (10, do x1 <- arbitrary - x2 <- arbInlines (n-1) - return $ Quoted x1 x2) - , (10, do x1 <- arbitrary - x2 <- realString - return $ Math x1 x2) - , (10, do x0 <- arbAttr - x1 <- arbInlines (n-1) - x3 <- realString - x2 <- liftM escapeURI realString - return $ Link x0 x1 (x2,x3)) - , (10, do x0 <- arbAttr - x1 <- arbInlines (n-1) - x3 <- realString - x2 <- liftM escapeURI realString - return $ Image x0 x1 (x2,x3)) - , (2, liftM2 Cite arbitrary (arbInlines 1)) - , (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1)) - ] - -instance Arbitrary Block where - arbitrary = resize 3 $ arbBlock 2 - -arbBlock :: Int -> Gen Block -arbBlock n = frequency $ [ (10, liftM Plain $ arbInlines (n-1)) - , (15, liftM Para $ arbInlines (n-1)) - , (5, liftM2 CodeBlock arbAttr realString) - , (2, elements [ RawBlock (Format "html") - "<div>\n*&*\n</div>" - , RawBlock (Format "latex") - "\\begin[opt]{env}\nhi\n{\\end{env}" - ]) - , (5, do x1 <- choose (1 :: Int, 6) - x2 <- arbInlines (n-1) - return (Header x1 nullAttr x2)) - , (2, return HorizontalRule) - ] ++ [x | x <- nesters, n > 0] - where nesters = [ (5, liftM BlockQuote $ listOf1 $ arbBlock (n-1)) - , (5, do x2 <- arbitrary - x3 <- arbitrary - x1 <- arbitrary `suchThat` (> 0) - x4 <- listOf1 $ listOf1 $ arbBlock (n-1) - return $ OrderedList (x1,x2,x3) x4 ) - , (5, liftM BulletList $ (listOf1 $ listOf1 $ arbBlock (n-1))) - , (5, do items <- listOf1 $ do - x1 <- listOf1 $ listOf1 $ arbBlock (n-1) - x2 <- arbInlines (n-1) - return (x2,x1) - return $ DefinitionList items) - , (2, do rs <- choose (1 :: Int, 4) - cs <- choose (1 :: Int, 4) - x1 <- arbInlines (n-1) - x2 <- vector cs - x3 <- vectorOf cs $ elements [0, 0.25] - x4 <- vectorOf cs $ listOf $ arbBlock (n-1) - x5 <- vectorOf rs $ vectorOf cs - $ listOf $ arbBlock (n-1) - return (Table x1 x2 x3 x4 x5)) - ] - -instance Arbitrary Pandoc where - arbitrary = resize 8 $ liftM normalize - $ liftM2 Pandoc arbitrary arbitrary - -instance Arbitrary CitationMode where - arbitrary - = do x <- choose (0 :: Int, 2) - case x of - 0 -> return AuthorInText - 1 -> return SuppressAuthor - 2 -> return NormalCitation - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - -instance Arbitrary Citation where - arbitrary - = do x1 <- listOf $ elements $ ['a'..'z'] ++ ['0'..'9'] ++ ['_'] - x2 <- arbInlines 1 - x3 <- arbInlines 1 - x4 <- arbitrary - x5 <- arbitrary - x6 <- arbitrary - return (Citation x1 x2 x3 x4 x5 x6) - -instance Arbitrary MathType where - arbitrary - = do x <- choose (0 :: Int, 1) - case x of - 0 -> return DisplayMath - 1 -> return InlineMath - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - -instance Arbitrary QuoteType where - arbitrary - = do x <- choose (0 :: Int, 1) - case x of - 0 -> return SingleQuote - 1 -> return DoubleQuote - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - -instance Arbitrary Meta where - arbitrary - = do (x1 :: Inlines) <- arbitrary - (x2 :: [Inlines]) <- liftM (filter (not . isNull)) arbitrary - (x3 :: Inlines) <- arbitrary - return $ setMeta "title" x1 - $ setMeta "author" x2 - $ setMeta "date" x3 - $ nullMeta - -instance Arbitrary Alignment where - arbitrary - = do x <- choose (0 :: Int, 3) - case x of - 0 -> return AlignLeft - 1 -> return AlignRight - 2 -> return AlignCenter - 3 -> return AlignDefault - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - -instance Arbitrary ListNumberStyle where - arbitrary - = do x <- choose (0 :: Int, 6) - case x of - 0 -> return DefaultStyle - 1 -> return Example - 2 -> return Decimal - 3 -> return LowerRoman - 4 -> return UpperRoman - 5 -> return LowerAlpha - 6 -> return UpperAlpha - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - -instance Arbitrary ListNumberDelim where - arbitrary - = do x <- choose (0 :: Int, 3) - case x of - 0 -> return DefaultDelim - 1 -> return Period - 2 -> return OneParen - 3 -> return TwoParens - _ -> error "FATAL ERROR: Arbitrary instance, logic bug" - diff --git a/tests/Tests/Readers/HTML.hs b/tests/Tests/Readers/HTML.hs index ff27b8aed..1a6983b2b 100644 --- a/tests/Tests/Readers/HTML.hs +++ b/tests/Tests/Readers/HTML.hs @@ -4,7 +4,7 @@ module Tests.Readers.HTML (tests) where import Text.Pandoc.Definition import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Text.Pandoc.Error diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index e21f75aa9..c70ce8052 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -4,7 +4,7 @@ module Tests.Readers.LaTeX (tests) where import Text.Pandoc.Definition import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Text.Pandoc.Error diff --git a/tests/Tests/Readers/Markdown.hs b/tests/Tests/Readers/Markdown.hs index 20602afe1..099d75b62 100644 --- a/tests/Tests/Readers/Markdown.hs +++ b/tests/Tests/Readers/Markdown.hs @@ -4,7 +4,7 @@ module Tests.Readers.Markdown (tests) where import Text.Pandoc.Definition import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import qualified Data.Set as Set -- import Text.Pandoc.Shared ( normalize ) diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index d4fedc797..3eab710dc 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -916,6 +916,12 @@ tests = ] =?> let attr = ("fig:myfig", mempty, mempty) in para (imageWith attr "blub.png" "fig:" "My figure") + + , "Figure with empty caption" =: + unlines [ "#+CAPTION:" + , "[[file:guess.jpg]]" + ] =?> + para (image "guess.jpg" "fig:" "") ] , "Footnote" =: @@ -1490,14 +1496,11 @@ tests = mconcat [ para $ spcSep [ "The", "first", "lines", "of" , "Goethe's", emph "Faust" <> ":"] - , para $ mconcat - [ spcSep [ "Habe", "nun,", "ach!", "Philosophie," ] - , linebreak - , spcSep [ "Juristerei", "und", "Medizin," ] - , linebreak - , spcSep [ "Und", "leider", "auch", "Theologie!" ] - , linebreak - , spcSep [ "Durchaus", "studiert,", "mit", "heißem", "Bemühn." ] + , lineBlock + [ "Habe nun, ach! Philosophie," + , "Juristerei und Medizin," + , "Und leider auch Theologie!" + , "Durchaus studiert, mit heißem Bemühn." ] ] @@ -1508,7 +1511,7 @@ tests = , "bar" , "#+END_VERSE" ] =?> - para ("foo" <> linebreak <> linebreak <> "bar") + lineBlock [ "foo", mempty, "bar" ] , "Verse block with varying indentation" =: unlines [ "#+BEGIN_VERSE" @@ -1516,7 +1519,7 @@ tests = , "my old friend" , "#+END_VERSE" ] =?> - para ("\160\160hello darkness" <> linebreak <> "my old friend") + lineBlock [ "\160\160hello darkness", "my old friend" ] , "Raw block LaTeX" =: unlines [ "#+BEGIN_LaTeX" diff --git a/tests/Tests/Readers/RST.hs b/tests/Tests/Readers/RST.hs index 622f5e48b..06a15ad98 100644 --- a/tests/Tests/Readers/RST.hs +++ b/tests/Tests/Readers/RST.hs @@ -4,7 +4,7 @@ module Tests.Readers.RST (tests) where import Text.Pandoc.Definition import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Text.Pandoc.Error @@ -19,8 +19,7 @@ infix 4 =: tests :: [Test] tests = [ "line block with blank line" =: - "| a\n|\n| b" =?> para (str "a") <> - para (str "\160b") + "| a\n|\n| b" =?> lineBlock [ "a", mempty, "\160b" ] , testGroup "field list" [ "general" =: unlines [ "para" @@ -135,7 +134,7 @@ tests = [ "line block with blank line" =: codeBlock "block quotes\n\ncan go on for many lines" <> para "but must stop here") , "line block with 3 lines" =: "| a\n| b\n| c" - =?> para ("a" <> linebreak <> "b" <> linebreak <> "c") + =?> lineBlock ["a", "b", "c"] , "quoted literal block using >" =: "::\n\n> quoted\n> block\n\nOrdinary paragraph" =?> codeBlock "> quoted\n> block" <> para "Ordinary paragraph" , "quoted literal block using | (not a line block)" =: "::\n\n| quoted\n| block\n\nOrdinary paragraph" @@ -164,4 +163,13 @@ tests = [ "line block with blank line" =: =?> para (codeWith ("", ["lhs", "haskell", "sourceCode"], []) "text") , "unknown role" =: ":unknown:`text`" =?> para (str "text") ] + , testGroup "footnotes" + [ "remove space before note" =: unlines + [ "foo [1]_" + , "" + , ".. [1]" + , " bar" + ] =?> + (para $ "foo" <> (note $ para "bar")) + ] ] diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs index e0067c698..e291c3ffe 100644 --- a/tests/Tests/Readers/Txt2Tags.hs +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -4,7 +4,7 @@ module Tests.Readers.Txt2Tags (tests) where import Text.Pandoc.Definition import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc import Text.Pandoc.Error diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs index 12652e4b7..55f520433 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Shared.hs @@ -4,7 +4,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Shared import Test.Framework import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Test.Framework.Providers.HUnit import Test.HUnit ( assertBool, (@?=) ) import Text.Pandoc.Builder diff --git a/tests/Tests/Walk.hs b/tests/Tests/Walk.hs index c87cc17d7..876d75e30 100644 --- a/tests/Tests/Walk.hs +++ b/tests/Tests/Walk.hs @@ -6,7 +6,7 @@ import Text.Pandoc.Walk import Test.Framework import Tests.Helpers import Data.Char (toUpper) -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() import Data.Generics tests :: [Test] diff --git a/tests/Tests/Writers/AsciiDoc.hs b/tests/Tests/Writers/AsciiDoc.hs index 0062667cf..8ab216753 100644 --- a/tests/Tests/Writers/AsciiDoc.hs +++ b/tests/Tests/Writers/AsciiDoc.hs @@ -4,7 +4,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() asciidoc :: (ToPandoc a) => a -> String asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc diff --git a/tests/Tests/Writers/ConTeXt.hs b/tests/Tests/Writers/ConTeXt.hs index 5098a5fee..629e58b8f 100644 --- a/tests/Tests/Writers/ConTeXt.hs +++ b/tests/Tests/Writers/ConTeXt.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() context :: (ToPandoc a) => a -> String context = writeConTeXt def . toPandoc diff --git a/tests/Tests/Writers/Docbook.hs b/tests/Tests/Writers/Docbook.hs index 2c0ff6179..d89631af8 100644 --- a/tests/Tests/Writers/Docbook.hs +++ b/tests/Tests/Writers/Docbook.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() docbook :: (ToPandoc a) => a -> String docbook = writeDocbook def{ writerWrapText = WrapNone } . toPandoc diff --git a/tests/Tests/Writers/HTML.hs b/tests/Tests/Writers/HTML.hs index 9b612e446..5bea99f71 100644 --- a/tests/Tests/Writers/HTML.hs +++ b/tests/Tests/Writers/HTML.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() html :: (ToPandoc a) => a -> String html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index 3dacaacd5..b7f604694 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() latex :: (ToPandoc a) => a -> String latex = writeLaTeX def{ writerHighlight = True } . toPandoc diff --git a/tests/Tests/Writers/Markdown.hs b/tests/Tests/Writers/Markdown.hs index cfc5f8410..aab916b38 100644 --- a/tests/Tests/Writers/Markdown.hs +++ b/tests/Tests/Writers/Markdown.hs @@ -6,7 +6,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() markdown :: (ToPandoc a) => a -> String markdown = writeMarkdown def . toPandoc diff --git a/tests/Tests/Writers/Native.hs b/tests/Tests/Writers/Native.hs index 9833bf5ae..a8659587f 100644 --- a/tests/Tests/Writers/Native.hs +++ b/tests/Tests/Writers/Native.hs @@ -4,7 +4,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() p_write_rt :: Pandoc -> Bool p_write_rt d = diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs index f8f1d3d90..42f77e3ec 100644 --- a/tests/Tests/Writers/Plain.hs +++ b/tests/Tests/Writers/Plain.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() infix 4 =: diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs index b9e359dae..e07d3ffee 100644 --- a/tests/Tests/Writers/RST.hs +++ b/tests/Tests/Writers/RST.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() infix 4 =: (=:) :: (ToString a, ToPandoc a) diff --git a/tests/Tests/Writers/TEI.hs b/tests/Tests/Writers/TEI.hs index 56764db9f..3eb8478b7 100644 --- a/tests/Tests/Writers/TEI.hs +++ b/tests/Tests/Writers/TEI.hs @@ -5,7 +5,7 @@ import Test.Framework import Text.Pandoc.Builder import Text.Pandoc import Tests.Helpers -import Tests.Arbitrary() +import Text.Pandoc.Arbitrary() {- "my test" =: X =?> Y diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native index 136996068..9df6a068a 100644 --- a/tests/markdown-reader-more.native +++ b/tests/markdown-reader-more.native @@ -84,8 +84,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S ,BlockQuote [Header 2 ("foobar",["baz"],[("key","val")]) [Str "Header",Space,Str "attributes",Space,Str "inside",Space,Str "block",Space,Str "quote"]] ,Header 2 ("line-blocks",[],[]) [Str "Line",Space,Str "blocks"] -,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"] -,Para [Str "Continuation",Space,Str "line",LineBreak,Str "\160\160and",Space,Str "another"] +,LineBlock + [[Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be"] + ,[Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,"] + ,[Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,"] + ,[Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"] + ,[] + ,[Str "Continuation",Space,Str "line"] + ,[Str "\160\160and",Space,Str "another"]] ,Header 2 ("grid-tables",[],[]) [Str "Grid",Space,Str "Tables"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.2638888888888889,0.16666666666666666,0.18055555555555555] [[Plain [Str "col",Space,Str "1"]] diff --git a/tests/odt/native/orderedListMixed.native b/tests/odt/native/orderedListMixed.native index a50f5e2ad..c2c8586af 100644 --- a/tests/odt/native/orderedListMixed.native +++ b/tests/odt/native/orderedListMixed.native @@ -1 +1 @@ -Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,Decimal,Period) [[Plain [Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,Decimal,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,LowerAlpha,OneParen) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]]]
\ No newline at end of file +Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,Decimal,Period) [[Plain [Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,Decimal,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,LowerAlpha,OneParen) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]],Para [],OrderedList (4,Decimal,Period) [[Plain [Str "Start",Space,Str "new",Space,Str "list,",Space,Str "but",Space,Str "a",Space,Str "different",Space,Str "starting",Space,Str "point."]] ,[Plain [Str "Because",Space,Str "we",Space,Str "can."]]]]
\ No newline at end of file diff --git a/tests/odt/native/orderedListRoman.native b/tests/odt/native/orderedListRoman.native index f186e0735..73bbbf1c9 100644 --- a/tests/odt/native/orderedListRoman.native +++ b/tests/odt/native/orderedListRoman.native @@ -1 +1 @@ -Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,UpperRoman,Period) [[Plain[Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,UpperRoman,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,UpperRoman,Period) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]]]
\ No newline at end of file +Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,UpperRoman,Period) [[Plain[Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,UpperRoman,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,UpperRoman,Period) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]],Para [],OrderedList (4,UpperRoman,Period) [[Plain [Str "Start",Space,Str "new",Space,Str "list,",Space,Str "but",Space,Str "a",Space,Str "different",Space,Str "starting",Space,Str "point."]] ,[Plain [Str "Because",Space,Str "we",Space,Str "can."]]]]
\ No newline at end of file diff --git a/tests/odt/native/orderedListSimple.native b/tests/odt/native/orderedListSimple.native index 90a51856a..0b1f85231 100644 --- a/tests/odt/native/orderedListSimple.native +++ b/tests/odt/native/orderedListSimple.native @@ -1 +1 @@ -Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,Decimal,Period) [[Plain [Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,Decimal,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,Decimal,Period) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]]]
\ No newline at end of file +Pandoc (Meta {unMeta = fromList []}) [OrderedList (1,Decimal,Period) [[Plain [Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "A",Space,Str "second"]],[Para [Str "A",Space,Str "third"],OrderedList (1,Decimal,Period) [[Para [Str "New",Space,Str "level!"],OrderedList (1,Decimal,Period) [[Plain [Str "And",Space,Str "another!"]],[Plain [Str "It's",Space,Str "great",Space,Str "up",Space,Str "here!"]]]],[Plain [Str "Oh",Space,Str "noes"]],[Plain [Str "We",Space,Str "fell!"]]]],[Plain [Str "Maybe",Space,Str "someone"]],[Plain [Str "Pushed",Space,Str "us?"]]],Para [],OrderedList (4,Decimal,Period) [[Plain [Str "Start",Space,Str "new",Space,Str "list,",Space,Str "but",Space,Str "a",Space,Str "different",Space,Str "starting",Space,Str "point."]] ,[Plain [Str "Because",Space,Str "we",Space,Str "can."]]]]
\ No newline at end of file diff --git a/tests/odt/odt/orderedListMixed.odt b/tests/odt/odt/orderedListMixed.odt Binary files differindex 1aa50ff06..2b593d635 100644 --- a/tests/odt/odt/orderedListMixed.odt +++ b/tests/odt/odt/orderedListMixed.odt diff --git a/tests/odt/odt/orderedListRoman.odt b/tests/odt/odt/orderedListRoman.odt Binary files differindex 7266e89bc..0acfe92ce 100644 --- a/tests/odt/odt/orderedListRoman.odt +++ b/tests/odt/odt/orderedListRoman.odt diff --git a/tests/odt/odt/orderedListSimple.odt b/tests/odt/odt/orderedListSimple.odt Binary files differindex 4fe543794..7af312fcc 100644 --- a/tests/odt/odt/orderedListSimple.odt +++ b/tests/odt/odt/orderedListSimple.odt diff --git a/tests/rst-reader.native b/tests/rst-reader.native index d44fa5efb..4a3df7f24 100644 --- a/tests/rst-reader.native +++ b/tests/rst-reader.native @@ -230,8 +230,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Another",Space,Str "paragraph"] ,Para [Str "A",Space,Str "third",Space,Str "paragraph"] ,Header 1 ("line-blocks",[],[]) [Str "Line",Space,Str "blocks"] -,Para [Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be",LineBreak,Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,",LineBreak,Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"] -,Para [Str "Continuation",Space,Str "line",LineBreak,Str "\160\160and",Space,Str "another"] +,LineBlock + [[Str "But",Space,Str "can",Space,Str "a",Space,Str "bee",Space,Str "be",Space,Str "said",Space,Str "to",Space,Str "be"] + ,[Str "\160\160\160\160or",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "an",Space,Str "entire",Space,Str "bee,"] + ,[Str "\160\160\160\160\160\160\160\160when",Space,Str "half",Space,Str "the",Space,Str "bee",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "bee,"] + ,[Str "\160\160\160\160\160\160\160\160\160\160\160\160due",Space,Str "to",Space,Str "some",Space,Str "ancient",Space,Str "injury?"] + ,[] + ,[Str "Continuation",Space,Str "line"] + ,[Str "\160\160and",Space,Str "another"]] ,Header 1 ("simple-tables",[],[]) [Str "Simple",Space,Str "Tables"] ,Table [] [AlignDefault,AlignDefault,AlignDefault] [0.0,0.0,0.0] [[Plain [Str "col",Space,Str "1"]] diff --git a/tests/writer.org b/tests/writer.org index 6a86a4e3f..f8011e644 100644 --- a/tests/writer.org +++ b/tests/writer.org @@ -819,15 +819,15 @@ Here is a movie [[file:movie.jpg]] icon. :CUSTOM_ID: footnotes :END: -Here is a footnote reference, [1] and another. [2] This should /not/ be a +Here is a footnote reference,[1] and another.[2] This should /not/ be a footnote reference, because it contains a space.[\^my note] Here is an inline -note. [3] +note.[3] #+BEGIN_QUOTE - Notes can go in quotes. [4] + Notes can go in quotes.[4] #+END_QUOTE -1. And in list items. [5] +1. And in list items.[5] This paragraph should not be part of the note, as it is not indented. diff --git a/windows/stack.yaml b/windows/stack.yaml index 7f57323cf..ade5e6ec8 100644 --- a/windows/stack.yaml +++ b/windows/stack.yaml @@ -14,8 +14,7 @@ flags: packages: - '..' extra-deps: -- 'http-client-0.5.0' -- 'http-client-tls-0.3.0' -- pandoc-citeproc-0.10.1.1 - doctemplates-0.1.0.2 -resolver: lts-7.0 +- pandoc-types-1.17.0.4 +- pandoc-citeproc-0.10.1.2 +resolver: lts-7.4 |