diff options
-rw-r--r-- | .travis.yml | 8 | ||||
m--------- | data/templates | 14 | ||||
-rw-r--r-- | deb/stack.yaml | 3 | ||||
-rw-r--r-- | osx/stack.yaml | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 25 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ZimWiki.hs | 16 | ||||
-rw-r--r-- | stack.yaml | 4 | ||||
-rw-r--r-- | windows/stack.yaml | 6 |
11 files changed, 53 insertions, 55 deletions
diff --git a/.travis.yml b/.travis.yml index 4c89760fb..62c9acc89 100644 --- a/.travis.yml +++ b/.travis.yml @@ -50,10 +50,6 @@ 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-5" - compiler: ": #stack 7.10.3" - addons: {apt: {packages: [ghc-7.10.3], sources: [hvr-ghc]}} - - env: BUILD=stack ARGS="--resolver lts-6" compiler: ": #stack 7.10.3" addons: {apt: {packages: [ghc-7.10.3], sources: [hvr-ghc]}} @@ -63,10 +59,6 @@ matrix: compiler: ": #stack nightly" addons: {apt: {packages: [libgmp-dev]}} - - env: BUILD=stack ARGS="--resolver lts-5" - compiler: ": #stack 7.10.3 osx" - os: osx - - env: BUILD=stack ARGS="--resolver lts-6" compiler: ": #stack 7.10.3 osx" os: osx diff --git a/data/templates b/data/templates -Subproject ba3a8f742371f9e9f04100d0e61638cf65fd6ce +Subproject 019d6a2bd84ad75dcf9d629561c87794a2f3965 diff --git a/deb/stack.yaml b/deb/stack.yaml index 85e142e09..8b1e64ec0 100644 --- a/deb/stack.yaml +++ b/deb/stack.yaml @@ -15,6 +15,5 @@ packages: - '..' extra-deps: - data-default-0.6.0 -- data-default-instances-base-0.1.0 - pandoc-citeproc-0.10 -resolver: lts-6.1 +resolver: lts-6.5 diff --git a/osx/stack.yaml b/osx/stack.yaml index 0988dacd3..ac438d1a2 100644 --- a/osx/stack.yaml +++ b/osx/stack.yaml @@ -18,8 +18,5 @@ packages: - '..' extra-deps: - 'pandoc-citeproc-0.10' -- 'hsb2hs-0.3.1' - 'data-default-0.6.0' -- 'data-default-instances-base-0.1.0' -- 'preprocessor-tools-1.0.1' -resolver: lts-6.1 +resolver: lts-6.5 diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 258fdfcf4..8100a6823 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -556,7 +556,7 @@ inlineCommands = M.fromList $ tok >>= \lab -> pure (link url "" lab)) , ("includegraphics", do options <- option [] keyvals - src <- unescapeURL <$> braced + src <- unescapeURL . removeDoubleQuotes <$> braced mkImage options src) , ("enquote", enquote) , ("cite", citation "cite" NormalCitation False) @@ -1396,3 +1396,10 @@ endInclude = do co <- braced setPosition $ newPos fn (fromMaybe 1 $ safeRead ln) (fromMaybe 1 $ safeRead co) return mempty + +removeDoubleQuotes :: String -> String +removeDoubleQuotes ('"':xs) = + case reverse xs of + '"':ys -> reverse ys + _ -> '"':xs +removeDoubleQuotes xs = xs diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs index 8c9ee0539..ad71cf08d 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs @@ -383,49 +383,49 @@ raiseAEmpty = arr (fromRight (const mempty) >>> Left) -- | Execute the second arrow if the first succeeds -(>>?) :: (ArrowChoice a, Monoid failure) +(>>?) :: (ArrowChoice a) => FallibleArrow a x failure success -> FallibleArrow a success failure success' -> FallibleArrow a x failure success' a >>? b = a >>> Left ^||| b -- | Execute the lifted second arrow if the first succeeds -(>>?^) :: (ArrowChoice a, Monoid failure) +(>>?^) :: (ArrowChoice a) => FallibleArrow a x failure success -> (success -> success') -> FallibleArrow a x failure success' a >>?^ f = a >>^ Left ^|||^ Right . f -- | Execute the lifted second arrow if the first succeeds -(>>?^?) :: (ArrowChoice a, Monoid failure) +(>>?^?) :: (ArrowChoice a) => FallibleArrow a x failure success -> (success -> Either failure success') -> FallibleArrow a x failure success' a >>?^? b = a >>> Left ^|||^ b -- | Execute the second arrow if the lifted first arrow succeeds -(^>>?) :: (ArrowChoice a, Monoid failure) +(^>>?) :: (ArrowChoice a) => (x -> Either failure success) -> FallibleArrow a success failure success' -> FallibleArrow a x failure success' a ^>>? b = a ^>> Left ^||| b -- | Execute the lifted second arrow if the lifted first arrow succeeds -(^>>?^) :: (ArrowChoice a, Monoid failure) +(^>>?^) :: (ArrowChoice a) => (x -> Either failure success) -> (success -> success') -> FallibleArrow a x failure success' a ^>>?^ f = arr $ a >>> right f -- | Execute the lifted second arrow if the lifted first arrow succeeds -(^>>?^?) :: (ArrowChoice a, Monoid failure) +(^>>?^?) :: (ArrowChoice a) => (x -> Either failure success) -> (success -> Either failure success') -> FallibleArrow a x failure success' a ^>>?^? f = a ^>> Left ^|||^ f -- | Execute the second, non-fallible arrow if the first arrow succeeds -(>>?!) :: (ArrowChoice a, Monoid failure) +(>>?!) :: (ArrowChoice a) => FallibleArrow a x failure success -> a success success' -> FallibleArrow a x failure success' diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index af81c49cd..9c6c4b33f 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -150,9 +150,13 @@ import Text.Pandoc.Data (dataFiles) import Paths_pandoc (getDataFileName) #endif #ifdef HTTP_CLIENT -import Network.HTTP.Client (httpLbs, parseUrl, - responseBody, responseHeaders, +import Network.HTTP.Client (httpLbs, responseBody, responseHeaders, Request(port,host)) +#if MIN_VERSION_http_client(0,4,30) +import Network.HTTP.Client (parseRequest) +#else +import Network.HTTP.Client (parseUrl) +#endif #if MIN_VERSION_http_client(0,4,18) import Network.HTTP.Client (newManager) #else @@ -946,13 +950,18 @@ openURL u in return $ Right (decodeLenient contents, Just mime) #ifdef HTTP_CLIENT | otherwise = withSocketsDo $ E.try $ do - req <- parseUrl u +#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" - let req' = case proxy of - Left _ -> req - Right pr -> case parseUrl pr of - Just r -> addProxy (host r) (port r) req - Nothing -> req + req <- parseReq u + req' <- case proxy of + Left _ -> return req + 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 diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 888c866a6..5829bcd33 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -345,7 +345,7 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts) not (null $ query hasCodeBlock elts ++ query hasCode elts) let frameoptions = ["allowdisplaybreaks", "allowframebreaks", "b", "c", "t", "environment", - "label", "plain", "shrink"] + "label", "plain", "shrink", "standout"] let optionslist = ["fragile" | fragile] ++ [k | k <- classes, k `elem` frameoptions] ++ [k ++ "=" ++ v | (k,v) <- kvs, k `elem` frameoptions] @@ -973,7 +973,7 @@ inlineToLaTeX (Image attr _ (source, _)) = do source' = if isURI source then source else unEscapeString source - source'' <- stringToLaTeX URLString (escapeURI source') + source'' <- stringToLaTeX URLString source' inHeading <- gets stInHeading return $ (if inHeading then "\\protect\\includegraphics" else "\\includegraphics") <> diff --git a/src/Text/Pandoc/Writers/ZimWiki.hs b/src/Text/Pandoc/Writers/ZimWiki.hs index 38a03cd83..05563970a 100644 --- a/src/Text/Pandoc/Writers/ZimWiki.hs +++ b/src/Text/Pandoc/Writers/ZimWiki.hs @@ -114,11 +114,11 @@ blockToZimWiki opts (Para inlines) = do blockToZimWiki opts (RawBlock f str) | f == Format "zimwiki" = return str | f == Format "html" = do cont <- indentFromHTML opts str; return cont - | otherwise = return "" -- $ "** unknown raw block "++ show f ++ "=" ++ str ++ " **" + | otherwise = return "" blockToZimWiki _ HorizontalRule = return "\n----\n" -blockToZimWiki opts (Header level _ inlines) = do +blockToZimWiki opts (Header level _ inlines) = do contents <- inlineListToZimWiki opts $ removeFormatting inlines -- emphasis, links etc. not allowed in headers let eqs = replicate ( 7 - level ) '=' return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n" @@ -204,23 +204,23 @@ indentFromHTML _ str = do let val = drop 10 $ reverse $ drop 1 $ reverse str --let val = take ((length valls) - 2) valls modify $ \s -> s { stItemNum = read val } - return "" -- $ indent ++ val ++ "." -- zim does its own numbering + return "" else if isInfixOf "<ol>" str then do let olcount=countSubStrs "<ol>" str modify $ \s -> s { stIndent = stIndent s ++ replicate olcount '\t', stItemNum = 1 } - return "" -- $ "OL-ON[" ++ newfix ++"]" + return "" else if isInfixOf "</ol>" str then do let olcount=countSubStrs "/<ol>" str modify $ \s -> s{ stIndent = drop olcount (stIndent s) } - return "" -- $ "OL-OFF[" ++ newfix ++"]" - else - return $ "" -- ** unknown inner HTML "++ str ++"**" + return "" + else + return "" countSubStrs :: String -> String -> Int countSubStrs sub str = length $ breakOnAll (pack sub) (pack str) cleanupCode :: String -> String -cleanupCode = substitute "<nowiki>" "" . substitute "</nowiki>" "" +cleanupCode = substitute "<nowiki>" "" . substitute "</nowiki>" "" vcat :: [String] -> String vcat = intercalate "\n" diff --git a/stack.yaml b/stack.yaml index 37b361d44..62bf29b1e 100644 --- a/stack.yaml +++ b/stack.yaml @@ -9,6 +9,4 @@ packages: - '.' extra-deps: - data-default-0.6.0 -- data-default-instances-base-0.1.0 -- texmath-0.8.6.4 -resolver: lts-6.1 +resolver: lts-6.5 diff --git a/windows/stack.yaml b/windows/stack.yaml index 15f203366..011dfb4c9 100644 --- a/windows/stack.yaml +++ b/windows/stack.yaml @@ -14,10 +14,6 @@ flags: packages: - '..' extra-deps: -- 'hsb2hs-0.3.1' - 'data-default-0.6.0' -- 'data-default-instances-base-0.1.0' -- 'preprocessor-tools-1.0.1' - 'pandoc-citeproc-0.10' -- 'texmath-0.8.6.4' -resolver: lts-6.1 +resolver: lts-6.5 |