diff options
-rw-r--r-- | INSTALL.md | 3 | ||||
-rw-r--r-- | MANUAL.txt | 12 | ||||
-rw-r--r-- | Setup.hs | 28 | ||||
-rw-r--r-- | linux/Dockerfile | 1 | ||||
-rwxr-xr-x | macos/make_macos_package.sh | 3 | ||||
-rw-r--r-- | pandoc.cabal | 3 | ||||
-rw-r--r-- | pandoc.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/App.hs | 94 | ||||
-rw-r--r-- | src/Text/Pandoc/Data.hs (renamed from src/Text/Pandoc/Data.hsb) | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Error.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Templates.hs | 2 |
12 files changed, 90 insertions, 101 deletions
diff --git a/INSTALL.md b/INSTALL.md index ed34a95c9..902e98a9f 100644 --- a/INSTALL.md +++ b/INSTALL.md @@ -226,9 +226,6 @@ assume that the pandoc source directory is your working directory. - `embed_data_files`: embed all data files into the binary (default no). This is helpful if you want to create a relocatable binary. - Note: if this option is selected, you need to install the - `hsb2hs` preprocessor: `cabal install hsb2hs` (version 0.3.1 or - higher is required). - `https`: enable support for downloading resources over https (using the `http-client` and `http-client-tls` libraries). diff --git a/MANUAL.txt b/MANUAL.txt index 1534beec2..529bbd6ff 100644 --- a/MANUAL.txt +++ b/MANUAL.txt @@ -1904,11 +1904,11 @@ this syntax: Here `mycode` is an identifier, `haskell` and `numberLines` are classes, and `startFrom` is an attribute with value `100`. Some output formats can use this information to do syntax highlighting. Currently, the only output formats -that uses this information are HTML and LaTeX. If highlighting is supported -for your output format and language, then the code block above will appear -highlighted, with numbered lines. (To see which languages are supported, type -`pandoc --list-highlight-languages`.) Otherwise, the code block above will -appear as follows: +that uses this information are HTML, LaTeX, Docx, and Ms. If highlighting +is supported for your output format and language, then the code block above +will appear highlighted, with numbered lines. (To see which languages are +supported, type `pandoc --list-highlight-languages`.) Otherwise, the code +block above will appear as follows: <pre id="mycode" class="haskell numberLines" startFrom="100"> <code> @@ -4045,7 +4045,7 @@ Syntax highlighting Pandoc will automatically highlight syntax in [fenced code blocks] that are marked with a language name. The Haskell library [highlighting-kate] is -used for highlighting, which works in HTML, Docx, and LaTeX/PDF output. +used for highlighting, which works in HTML, Docx, Ms, and LaTeX/PDF output. To see a list of language names that pandoc will recognize, type `pandoc --list-highlight-languages`. @@ -20,41 +20,17 @@ import Distribution.Simple import Distribution.Simple.PreProcess import Distribution.Simple.Setup (ConfigFlags(..), CopyFlags(..), fromFlag) import Distribution.PackageDescription (PackageDescription(..), FlagName(..)) -import Distribution.Simple.Utils ( rawSystemExitCode, findProgramVersion ) import System.Exit -import Distribution.Simple.Utils (info, notice, installOrdinaryFiles) +import Distribution.Simple.Utils (notice, installOrdinaryFiles) import Distribution.Simple.Program (simpleProgram, Program(..)) import Distribution.Simple.LocalBuildInfo import Control.Monad (when) main :: IO () main = defaultMainWithHooks $ simpleUserHooks { - -- enable hsb2hs preprocessor for .hsb files - hookedPreProcessors = [ppBlobSuffixHandler] - , hookedPrograms = [(simpleProgram "hsb2hs"){ - programFindVersion = \verbosity fp -> - findProgramVersion "--version" id verbosity fp }] - , postCopy = installManPage + postCopy = installManPage } -ppBlobSuffixHandler :: PPSuffixHandler -ppBlobSuffixHandler = ("hsb", \_ lbi -> - PreProcessor { - platformIndependent = True, - runPreProcessor = mkSimplePreProcessor $ \infile outfile verbosity -> - do let embedData = case lookup (FlagName "embed_data_files") - (configConfigurationsFlags (configFlags lbi)) of - Just True -> True - _ -> False - when embedData $ - do info verbosity $ "Preprocessing " ++ infile ++ " to " ++ outfile - ec <- rawSystemExitCode verbosity "hsb2hs" - [infile, infile, outfile] - case ec of - ExitSuccess -> return () - ExitFailure _ -> error "hsb2hs is needed to build this program" - }) - installManPage :: Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO () installManPage _ flags pkg lbi = do diff --git a/linux/Dockerfile b/linux/Dockerfile index 630abc17e..b725bbaa5 100644 --- a/linux/Dockerfile +++ b/linux/Dockerfile @@ -14,7 +14,6 @@ RUN mkdir -p /usr/src/ WORKDIR /usr/src/ RUN git clone https://github.com/jgm/pandoc WORKDIR /usr/src/pandoc -RUN stack install --local-bin-path /usr/bin hsb2hs RUN stack install --stack-yaml stack.pkg.yaml --only-dependencies \ --flag 'pandoc:embed_data_files' \ --test --ghc-options '-O2 -optc-Os -optl-static -fPIC' \ diff --git a/macos/make_macos_package.sh b/macos/make_macos_package.sh index 911219f14..c5d073cdc 100755 --- a/macos/make_macos_package.sh +++ b/macos/make_macos_package.sh @@ -14,8 +14,6 @@ PACKAGEMAKER=/Applications/PackageMaker.app/Contents/MacOS/PackageMaker DEVELOPER_ID_APPLICATION=${DEVELOPER_ID_APPLICATION:-Developer ID Application: John Macfarlane} DEVELOPER_ID_INSTALLER=${DEVELOPER_ID_INSTALLER:-Developer ID Installer: John Macfarlane} -# We need this for hsb2hs: -PATH=$LOCALBIN:$PATH export MACMACOS_DEPLOYMENT_TARGET=10.7 # echo Removing old files... @@ -23,7 +21,6 @@ rm -rf $DIST mkdir -p $DIST mkdir -p $RESOURCES stack setup -which hsb2hs || stack install hsb2hs which cpphs || stack install cpphs echo Building pandoc... diff --git a/pandoc.cabal b/pandoc.cabal index 06754ae26..246b36841 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -297,7 +297,6 @@ Library texmath >= 0.9.4 && < 0.10, xml >= 1.3.12 && < 1.4, random >= 1 && < 1.2, - extensible-exceptions >= 0.1 && < 0.2, pandoc-types >= 1.17 && < 1.18, aeson >= 0.7 && < 1.2, aeson-pretty >= 0.8 && < 0.9, @@ -342,7 +341,7 @@ Library cpp-options: -DHTTP_CLIENT if flag(embed_data_files) cpp-options: -DEMBED_DATA_FILES - Build-Tools: hsb2hs >= 0.3.1 + build-depends: file-embed >= 0.0 && < 0.1 other-modules: Text.Pandoc.Data if os(darwin) Build-Tools: cpphs >= 1.19 @@ -34,6 +34,9 @@ writers. -} module Main where import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions) +import Text.Pandoc.Error (handleError, PandocError) +import qualified Control.Exception as E main :: IO () -main = parseOptions options defaultOpts >>= convertWithOpts +main = E.catch (parseOptions options defaultOpts >>= convertWithOpts) + (\(e :: PandocError) -> handleError (Left e)) diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs index 8f0410f12..b7ac4fd75 100644 --- a/src/Text/Pandoc/App.hs +++ b/src/Text/Pandoc/App.hs @@ -39,7 +39,6 @@ module Text.Pandoc.App ( ) where import Control.Applicative ((<|>)) import qualified Control.Exception as E -import Control.Exception.Extensible (throwIO) import Control.Monad import Control.Monad.Trans import Data.Aeson (eitherDecode', encode) @@ -68,6 +67,7 @@ import System.FilePath import System.IO (stderr, stdout) import System.IO.Error (isDoesNotExistError) import Text.Pandoc +import Text.Pandoc.Error (PandocError(..)) import Text.Pandoc.Builder (setMeta) import Text.Pandoc.Class (PandocIO, getLog, withMediaBag) import Text.Pandoc.Highlighting (highlightingStyles) @@ -76,7 +76,7 @@ import Text.Pandoc.MediaBag (MediaBag, extractMediaBag, mediaDirectory) import Text.Pandoc.PDF (makePDF) import Text.Pandoc.Process (pipeProcess) import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI) -import Text.Pandoc.Shared (err, headerShift, openURL, readDataFile, +import Text.Pandoc.Shared (headerShift, openURL, readDataFile, readDataFileUTF8, safeRead, tabFilter) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Walk (walk) @@ -98,7 +98,8 @@ parseOptions options' defaults = do let unknownOptionErrors = foldr handleUnrecognizedOption [] unrecognizedOpts unless (null errors && null unknownOptionErrors) $ - err 2 $ concat errors ++ unlines unknownOptionErrors ++ + E.throwIO $ PandocAppError 2 $ + concat errors ++ unlines unknownOptionErrors ++ ("Try " ++ prg ++ " --help for more information.") -- thread option data structure through all supplied option actions @@ -175,7 +176,7 @@ convertWithOpts opts = do (\o d -> liftIO $ writeCustom writerName o d) :: Writer PandocIO) else case getWriter writerName of - Left e -> err 9 $ + Left e -> E.throwIO $ PandocAppError 9 $ if format == "pdf" then e ++ "\nTo create a pdf with pandoc, use " ++ @@ -189,7 +190,7 @@ convertWithOpts opts = do -- the sake of the text2tags reader. reader <- case getReader readerName of Right r -> return (r :: Reader PandocIO) - Left e -> err 7 e' + Left e -> E.throwIO $ PandocAppError 7 e' where e' = case readerName of "pdf" -> e ++ "\nPandoc can convert to PDF, but not from PDF." @@ -204,7 +205,7 @@ convertWithOpts opts = do Nothing -> do deftemp <- getDefaultTemplate datadir format case deftemp of - Left e -> throwIO e + Left e -> E.throwIO e Right t -> return (Just t) Just tp -> do -- strip off extensions @@ -217,8 +218,8 @@ convertWithOpts opts = do (readDataFileUTF8 datadir ("templates" </> tp')) (\e' -> let _ = (e' :: E.SomeException) - in throwIO e') - else throwIO e) + in E.throwIO e') + else E.throwIO e) let addStringAsVariable varname s vars = return $ (varname, s) : vars @@ -304,7 +305,7 @@ convertWithOpts opts = do let addSyntaxMap existingmap f = do res <- parseSyntaxDefinition f case res of - Left errstr -> err 67 errstr + Left errstr -> E.throwIO $ PandocAppError 67 errstr Right syn -> return $ addSyntaxDefinition syn existingmap syntaxMap <- foldM addSyntaxMap defaultSyntaxMap @@ -312,7 +313,8 @@ convertWithOpts opts = do case missingIncludes (M.elems syntaxMap) of [] -> return () - xs -> err 73 $ "Missing syntax definitions:\n" ++ + xs -> E.throwIO $ PandocAppError 73 $ + "Missing syntax definitions:\n" ++ unlines (map (\(syn,dep) -> (T.unpack syn ++ " requires " ++ T.unpack dep ++ " through IncludeRules.")) xs) @@ -358,7 +360,8 @@ convertWithOpts opts = do istty <- queryTerminal stdOutput #endif when (istty && not (isTextFormat format) && outputFile == "-") $ - err 5 $ "Cannot write " ++ format ++ " output to stdout.\n" ++ + E.throwIO $ PandocAppError 5 $ + "Cannot write " ++ format ++ " output to stdout.\n" ++ "Specify an output file using the -o option." @@ -386,7 +389,8 @@ convertWithOpts opts = do Just logfile -> B.writeFile logfile (encodeLogMessages reports) let isWarning msg = messageVerbosity msg == WARNING when (optFailIfWarnings opts && any isWarning reports) $ - err 3 "Failing because there were warnings." + E.throwIO $ + PandocAppError 3 "Failing because there were warnings." return res let sourceToDoc :: [FilePath] -> PandocIO (Pandoc, MediaBag) @@ -429,8 +433,8 @@ convertWithOpts opts = do -- make sure writer is latex, beamer, context, html5 or ms unless (laTeXOutput || conTeXtOutput || html5Output || msOutput) $ - err 47 $ "cannot produce pdf output with " ++ format ++ - " writer" + liftIO $ E.throwIO $ PandocAppError 47 $ + "cannot produce pdf output with " ++ format ++ " writer" let pdfprog = case () of _ | conTeXtOutput -> "context" @@ -441,7 +445,8 @@ convertWithOpts opts = do -- check for pdf creating program mbPdfProg <- liftIO $ findExecutable pdfprog when (isNothing mbPdfProg) $ - err 41 $ pdfprog ++ " not found. " ++ + liftIO $ E.throwIO $ PandocAppError 41 $ + pdfprog ++ " not found. " ++ pdfprog ++ " is needed for pdf output." res <- makePDF pdfprog f writerOptions verbosity media doc' @@ -450,7 +455,7 @@ convertWithOpts opts = do Left err' -> liftIO $ do B.hPutStr stderr err' B.hPut stderr $ B.pack [10] - err 43 "Error producing PDF" + E.throwIO $ PandocAppError 43 "Error producing PDF" | otherwise -> do let htmlFormat = format `elem` ["html","html4","html5","s5","slidy","slideous","dzslides","revealjs"] @@ -492,19 +497,21 @@ externalFilter f args' d = liftIO $ do unless (exists && isExecutable) $ do mbExe <- findExecutable f' when (isNothing mbExe) $ - err 83 $ "Error running filter " ++ f ++ ":\n" ++ - "Could not find executable '" ++ f' ++ "'." + E.throwIO $ PandocAppError 83 $ + "Error running filter " ++ f ++ ":\n" ++ + "Could not find executable '" ++ f' ++ "'." env <- getEnvironment let env' = Just $ ("PANDOC_VERSION", pandocVersion) : env (exitcode, outbs) <- E.handle filterException $ pipeProcess env' f' args'' $ encode d case exitcode of ExitSuccess -> return $ either error id $ eitherDecode' outbs - ExitFailure ec -> err 83 $ "Error running filter " ++ f ++ "\n" ++ - "Filter returned error status " ++ show ec + ExitFailure ec -> E.throwIO $ PandocAppError 83 $ + "Error running filter " ++ f ++ "\n" ++ + "Filter returned error status " ++ show ec where filterException :: E.SomeException -> IO a - filterException e = err 83 $ "Error running filter " ++ f ++ "\n" ++ - show e + filterException e = E.throwIO $ PandocAppError 83 $ + "Error running filter " ++ f ++ "\n" ++ show e -- | Data structure for command line options. data Opt = Opt @@ -806,12 +813,14 @@ lookupHighlightStyle (Just s) | takeExtension s == ".theme" = -- attempt to load KDE theme do contents <- B.readFile s case parseTheme contents of - Left _ -> err 69 $ "Could not read highlighting theme " ++ s + Left _ -> E.throwIO $ PandocAppError 69 $ + "Could not read highlighting theme " ++ s Right sty -> return (Just sty) | otherwise = case lookup (map toLower s) highlightingStyles of Just sty -> return (Just sty) - Nothing -> err 68 $ "Unknown highlight-style " ++ s + Nothing -> E.throwIO $ PandocAppError 68 $ + "Unknown highlight-style " ++ s -- | A list of functions, each transforming the options data structure -- in response to a command-line option. @@ -847,8 +856,8 @@ options = case safeRead arg of Just t | t > 0 && t < 6 -> return opt{ optBaseHeaderLevel = t } - _ -> err 19 - "base-header-level must be 1-5") + _ -> E.throwIO $ PandocAppError 19 + "base-header-level must be 1-5") "NUMBER") "" -- "Headers base level" @@ -881,8 +890,8 @@ options = (\arg opt -> case safeRead arg of Just t | t > 0 -> return opt { optTabStop = t } - _ -> err 31 - "tab-stop must be a number greater than 0") + _ -> E.throwIO $ PandocAppError 31 + "tab-stop must be a number greater than 0") "NUMBER") "" -- "Tab stop (default 4)" @@ -893,7 +902,7 @@ options = "accept" -> return AcceptChanges "reject" -> return RejectChanges "all" -> return AllChanges - _ -> err 6 + _ -> E.throwIO $ PandocAppError 6 ("Unknown option for track-changes: " ++ arg) return opt { optTrackChanges = action }) "accept|reject|all") @@ -964,7 +973,7 @@ options = (\arg opt -> case safeRead arg of Just t | t > 0 -> return opt { optDpi = t } - _ -> err 31 + _ -> E.throwIO $ PandocAppError 31 "dpi must be a number greater than 0") "NUMBER") "" -- "Dpi (default 96)" @@ -974,7 +983,8 @@ options = (\arg opt -> case safeRead ("Wrap" ++ uppercaseFirstLetter arg) of Just o -> return opt { optWrapText = o } - Nothing -> err 77 "--wrap must be auto, none, or preserve") + Nothing -> E.throwIO $ PandocAppError 77 + "--wrap must be auto, none, or preserve") "auto|none|preserve") "" -- "Option for wrapping text in output" @@ -983,7 +993,7 @@ options = (\arg opt -> case safeRead arg of Just t | t > 0 -> return opt { optColumns = t } - _ -> err 33 + _ -> E.throwIO $ PandocAppError 33 "columns must be a number greater than 0") "NUMBER") "" -- "Length of line in characters" @@ -999,7 +1009,7 @@ options = case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optTOCDepth = t } - _ -> err 57 + _ -> E.throwIO $ PandocAppError 57 "TOC level must be a number between 1 and 6") "NUMBER") "" -- "Number of levels to include in TOC" @@ -1075,7 +1085,7 @@ options = "block" -> return EndOfBlock "section" -> return EndOfSection "document" -> return EndOfDocument - _ -> err 6 + _ -> E.throwIO $ PandocAppError 6 ("Unknown option for reference-location: " ++ arg) return opt { optReferenceLocation = action }) "block|section|document") @@ -1092,8 +1102,9 @@ options = let tldName = "TopLevel" ++ uppercaseFirstLetter arg case safeRead tldName of Just tlDiv -> return opt { optTopLevelDivision = tlDiv } - _ -> err 76 ("Top-level division must be " ++ - "section, chapter, part, or default")) + _ -> E.throwIO $ PandocAppError 76 + ("Top-level division must be " ++ + "section, chapter, part, or default")) "section|chapter|part") "" -- "Use top-level division type in LaTeX, ConTeXt, DocBook" @@ -1108,7 +1119,8 @@ options = case safeRead ('[':arg ++ "]") of Just ns -> return opt { optNumberOffset = ns, optNumberSections = True } - _ -> err 57 "could not parse number-offset") + _ -> E.throwIO $ PandocAppError 57 + "could not parse number-offset") "NUMBERS") "" -- "Starting number for sections, subsections, etc." @@ -1128,7 +1140,7 @@ options = case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optSlideLevel = Just t } - _ -> err 39 + _ -> E.throwIO $ PandocAppError 39 "slide level must be a number between 1 and 6") "NUMBER") "" -- "Force header level for slides" @@ -1151,7 +1163,7 @@ options = "references" -> return ReferenceObfuscation "javascript" -> return JavascriptObfuscation "none" -> return NoObfuscation - _ -> err 6 + _ -> E.throwIO $ PandocAppError 6 ("Unknown obfuscation method: " ++ arg) return opt { optEmailObfuscation = method }) "none|javascript|references") @@ -1213,7 +1225,7 @@ options = case safeRead arg of Just t | t >= 1 && t <= 6 -> return opt { optEpubChapterLevel = t } - _ -> err 59 + _ -> E.throwIO $ PandocAppError 59 "chapter level must be a number between 1 and 6") "NUMBER") "" -- "Header level at which to split chapters in EPUB" @@ -1224,7 +1236,7 @@ options = let b = takeBaseName arg if b `elem` ["pdflatex", "lualatex", "xelatex"] then return opt { optLaTeXEngine = arg } - else err 45 "latex-engine must be pdflatex, lualatex, or xelatex.") + else E.throwIO $ PandocAppError 45 "latex-engine must be pdflatex, lualatex, or xelatex.") "PROGRAM") "" -- "Name of latex program to use in generating PDF" diff --git a/src/Text/Pandoc/Data.hsb b/src/Text/Pandoc/Data.hs index 02c109816..b8e189440 100644 --- a/src/Text/Pandoc/Data.hsb +++ b/src/Text/Pandoc/Data.hs @@ -1,6 +1,8 @@ -{-# LANGUAGE OverloadedStrings #-} --- to be processed using hsb2hs +{-# LANGUAGE TemplateHaskell #-} + module Text.Pandoc.Data (dataFiles) where + +import Data.FileEmbed import qualified Data.ByteString as B import System.FilePath (splitDirectories) import qualified System.FilePath.Posix as Posix @@ -12,5 +14,8 @@ dataFiles = map (\(fp, contents) -> (Posix.joinPath (splitDirectories fp), contents)) dataFiles' dataFiles' :: [(FilePath, B.ByteString)] -dataFiles' = ("MANUAL.txt", %blob "MANUAL.txt") : %blobs "data" - +dataFiles' = ("MANUAL.txt", $(embedFile "MANUAL.txt")) : + -- handle the hidden file separately, since embedDir doesn't + -- include it: + ("docx/_rels/.rels", $(embedFile "data/docx/_rels/.rels")) : + $(embedDir "data") diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 4b38348ac..252c469b1 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -37,9 +37,11 @@ module Text.Pandoc.Error ( import Control.Exception (Exception) import Data.Generics (Typeable) import GHC.Generics (Generic) -import Text.Pandoc.Shared (err) import Text.Parsec.Error import Text.Parsec.Pos hiding (Line) +import qualified Text.Pandoc.UTF8 as UTF8 +import System.Exit (exitWith, ExitCode(..)) +import System.IO (stderr) type Input = String @@ -49,6 +51,7 @@ data PandocError = PandocIOError String IOError | PandocParseError String | PandocParsecError Input ParseError | PandocMakePDFError String + | PandocAppError Int String deriving (Show, Typeable, Generic) instance Exception PandocError @@ -74,4 +77,10 @@ handleError (Left e) = else "" in err 65 $ "\nError at " ++ show err' ++ errorInFile PandocMakePDFError s -> err 65 s + PandocAppError ec s -> err ec s +err :: Int -> String -> IO a +err exitCode msg = do + UTF8.hPutStrLn stderr msg + exitWith $ ExitFailure exitCode + return undefined diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 3b9ae7501..dfdbaf428 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -82,7 +82,6 @@ module Text.Pandoc.Shared ( collapseFilePath, filteredFilesFromArchive, -- * Error handling - err, mapLeft, -- * for squashing blocks blocksToInlines, @@ -99,7 +98,6 @@ import Text.Pandoc.Walk import Text.Pandoc.Builder (Inlines, Blocks, ToMetaValue(..)) import qualified Text.Pandoc.Builder as B import qualified Text.Pandoc.UTF8 as UTF8 -import System.Exit (exitWith, ExitCode(..)) import Data.Char ( toLower, isLower, isUpper, isAlpha, isLetter, isDigit, isSpace ) import Data.List ( find, stripPrefix, intercalate ) @@ -112,16 +110,15 @@ import System.Directory import System.FilePath (splitDirectories, isPathSeparator) import qualified System.FilePath.Posix as Posix import Text.Pandoc.MIME (MimeType) +import Text.Pandoc.Error (PandocError(..)) import System.FilePath ( (</>) ) import Data.Generics (Typeable, Data) import qualified Control.Monad.State as S -import Control.Monad.Trans (MonadIO (..)) import qualified Control.Exception as E import Control.Monad (msum, unless, MonadPlus(..)) import Text.Pandoc.Pretty (charWidth) import Text.Pandoc.Compat.Time import Data.Time.Clock.POSIX -import System.IO (stderr) import System.IO.Error import System.IO.Temp import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..), @@ -677,7 +674,8 @@ readDefaultDataFile "reference.odt" = readDefaultDataFile fname = #ifdef EMBED_DATA_FILES case lookup (makeCanonical fname) dataFiles of - Nothing -> err 97 $ "Could not find data file " ++ fname + Nothing -> E.throwIO $ PandocAppError 97 $ + "Could not find data file " ++ fname Just contents -> return contents where makeCanonical = Posix.joinPath . transformPathParts . splitDirectories transformPathParts = reverse . foldl go [] @@ -693,7 +691,7 @@ checkExistence fn = do exists <- doesFileExist fn if exists then return fn - else err 97 ("Could not find data file " ++ fn) + else E.throwIO $ PandocAppError 97 ("Could not find data file " ++ fn) #endif -- | Read file from specified user data directory or, if not found there, from @@ -759,12 +757,6 @@ openURL u -- Error reporting -- -err :: MonadIO m => Int -> String -> m a -err exitCode msg = liftIO $ do - UTF8.hPutStrLn stderr msg - exitWith $ ExitFailure exitCode - return undefined - mapLeft :: (a -> b) -> Either a c -> Either b c mapLeft f (Left x) = Left (f x) mapLeft _ (Right x) = Right x diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 4ae2e80d7..26aeb9a73 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -41,7 +41,7 @@ module Text.Pandoc.Templates ( renderTemplate , Template , getDefaultTemplate ) where -import qualified Control.Exception.Extensible as E (IOException, try) +import qualified Control.Exception as E (IOException, try) import Data.Aeson (ToJSON (..)) import qualified Data.Text as T import System.FilePath ((<.>), (</>)) |