Have to do some work to get the mediabag out.

This commit is contained in:
Jesse Rosenthal 2016-11-30 13:55:52 -05:00 committed by John MacFarlane
parent 3f7b3f5fd0
commit 5a02a81b43
2 changed files with 22 additions and 14 deletions

View file

@ -436,7 +436,8 @@ Executable pandoc
aeson >= 0.7.0.5 && < 1.2,
yaml >= 0.8.8.2 && < 0.9,
containers >= 0.1 && < 0.6,
HTTP >= 4000.0.5 && < 4000.4
HTTP >= 4000.0.5 && < 4000.4,
mtl >= 2.2 && < 2.3
if flag(network-uri)
Build-Depends: network-uri >= 2.6 && < 2.7, network >= 2.6
else

View file

@ -77,7 +77,9 @@ import Text.Printf (printf)
import System.Posix.Terminal (queryTerminal)
import System.Posix.IO (stdOutput)
#endif
import Text.Pandoc.Class (runIOorExplode, PandocIO)
import Control.Monad.Trans
import Text.Pandoc.Class (runIOorExplode, PandocMonad, PandocIO)
import qualified Text.Pandoc.Class as P
type Transform = Pandoc -> Pandoc
@ -1285,11 +1287,9 @@ convertWithOpts opts args = do
else e
Right w -> return w
reader <- if "t2t" == readerName'
then (mkStringReader .
readTxt2Tags) <$>
getT2TMeta sources outputFile
else case getReader readerName' of
-- TODO: we have to get the input and the output into the state for
-- the sake of the text2tags reader.
reader <- case getReader readerName' of
Right r -> return r
Left e -> err 7 e'
where e' = case readerName' of
@ -1374,19 +1374,26 @@ convertWithOpts opts args = do
err 5 $ "Cannot write " ++ format ++ " output to stdout.\n" ++
"Specify an output file using the -o option."
let readSources [] = mapM readSource ["-"]
readSources srcs = mapM readSource srcs
readSource "-" = UTF8.getContents
let readSource :: MonadIO m => FilePath -> m String
readSource "-" = liftIO UTF8.getContents
readSource src = case parseURI src of
Just u | uriScheme u `elem` ["http:","https:"] ->
readURI src
| uriScheme u == "file:" ->
UTF8.readFile (uriPath u)
_ -> UTF8.readFile src
liftIO $ UTF8.readFile (uriPath u)
_ -> liftIO $ UTF8.readFile src
readSources :: MonadIO m => [FilePath] -> m [String]
readSources [] = mapM readSource ["-"]
readSources srcs = mapM readSource srcs
readURI :: MonadIO m => FilePath -> m String
readURI src = do
res <- openURL src
res <- liftIO $ openURL src
case res of
Left e -> throwIO e
Left e -> liftIO $ throwIO e
Right (bs,_) -> return $ UTF8.toString bs
let readFiles [] = error "Cannot read archive from stdin"