aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Logging.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Logging.hs')
-rw-r--r--src/Text/Pandoc/Logging.hs43
1 files changed, 33 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Logging.hs b/src/Text/Pandoc/Logging.hs
index 825fdaadb..193b8b61c 100644
--- a/src/Text/Pandoc/Logging.hs
+++ b/src/Text/Pandoc/Logging.hs
@@ -4,7 +4,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Logging
- Copyright : Copyright (C) 2006-2020 John MacFarlane
+ Copyright : Copyright (C) 2006-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -36,6 +36,7 @@ import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Pandoc.Definition
import Text.Parsec.Pos
+import Text.Pandoc.Shared (tshow)
-- | Verbosity level.
data Verbosity = ERROR | WARNING | INFO
@@ -84,6 +85,7 @@ data LogMessage =
| CouldNotParseCSS Text
| Fetching Text
| Extracting Text
+ | LoadedResource FilePath FilePath
| NoTitleElement Text
| NoLangSpecified
| InvalidLang Text
@@ -100,6 +102,8 @@ data LogMessage =
| FilterCompleted FilePath Integer
| CiteprocWarning Text
| ATXHeadingInLHS Int Text
+ | EnvironmentVariableUndefined Text
+ | DuplicateAttribute Text Text
deriving (Show, Eq, Data, Ord, Typeable, Generic)
instance ToJSON LogMessage where
@@ -192,6 +196,9 @@ instance ToJSON LogMessage where
["path" .= fp]
Extracting fp ->
["path" .= fp]
+ LoadedResource orig found ->
+ ["for" .= orig
+ ,"from" .= found]
NoTitleElement fallback ->
["fallback" .= fallback]
NoLangSpecified -> []
@@ -229,13 +236,20 @@ instance ToJSON LogMessage where
ATXHeadingInLHS lvl contents ->
["level" .= lvl
,"contents" .= contents]
+ EnvironmentVariableUndefined var ->
+ ["variable" .= var ]
+ DuplicateAttribute attr val ->
+ ["attribute" .= attr
+ ,"value" .= val]
showPos :: SourcePos -> Text
showPos pos = Text.pack $ sn ++ "line " ++
show (sourceLine pos) ++ " column " ++ show (sourceColumn pos)
- where sn = if sourceName pos == "source" || sourceName pos == ""
- then ""
- else sourceName pos ++ " "
+ where
+ sn' = sourceName pos
+ sn = if sn' == "source" || sn' == "" || sn' == "-"
+ then ""
+ else sn' ++ " "
encodeLogMessages :: [LogMessage] -> BL.ByteString
encodeLogMessages ms =
@@ -268,7 +282,7 @@ showLogMessage msg =
ParsingUnescaped s pos ->
"Parsing unescaped '" <> s <> "' at " <> showPos pos
CouldNotLoadIncludeFile fp pos ->
- "Could not load include file '" <> fp <> "' at " <> showPos pos
+ "Could not load include file " <> fp <> " at " <> showPos pos
MacroAlreadyDefined name pos ->
"Macro '" <> name <> "' already defined, ignoring at " <> showPos pos
InlineNotRendered il ->
@@ -280,18 +294,18 @@ showLogMessage msg =
IgnoredIOError s ->
"IO Error (ignored): " <> s
CouldNotFetchResource fp s ->
- "Could not fetch resource '" <> fp <> "'" <>
+ "Could not fetch resource " <> fp <>
if Text.null s then "" else ": " <> s
CouldNotDetermineImageSize fp s ->
- "Could not determine image size for '" <> fp <> "'" <>
+ "Could not determine image size for " <> fp <>
if Text.null s then "" else ": " <> s
CouldNotConvertImage fp s ->
- "Could not convert image '" <> fp <> "'" <>
+ "Could not convert image " <> fp <>
if Text.null s then "" else ": " <> s
CouldNotDetermineMimeType fp ->
- "Could not determine mime type for '" <> fp <> "'"
+ "Could not determine mime type for " <> fp
CouldNotConvertTeXMath s m ->
- "Could not convert TeX math '" <> s <> "', rendering as TeX" <>
+ "Could not convert TeX math " <> s <> ", rendering as TeX" <>
if Text.null m then "" else ":\n" <> m
CouldNotParseCSS m ->
"Could not parse CSS" <> if Text.null m then "" else ":\n" <> m
@@ -299,6 +313,8 @@ showLogMessage msg =
"Fetching " <> fp <> "..."
Extracting fp ->
"Extracting " <> fp <> "..."
+ LoadedResource orig found ->
+ "Loaded " <> Text.pack orig <> " from " <> Text.pack found
NoTitleElement fallback ->
"This document format requires a nonempty <title> element.\n" <>
"Defaulting to '" <> fallback <> "' as the title.\n" <>
@@ -345,6 +361,10 @@ showLogMessage msg =
if lvl < 3
then " Consider using --markdown-headings=setext."
else ""
+ EnvironmentVariableUndefined var ->
+ "Undefined environment variable " <> var <> " in defaults file."
+ DuplicateAttribute attr val ->
+ "Ignoring duplicate attribute " <> attr <> "=" <> tshow val <> "."
messageVerbosity :: LogMessage -> Verbosity
messageVerbosity msg =
@@ -375,6 +395,7 @@ messageVerbosity msg =
CouldNotParseCSS{} -> WARNING
Fetching{} -> INFO
Extracting{} -> INFO
+ LoadedResource{} -> INFO
NoTitleElement{} -> WARNING
NoLangSpecified -> INFO
InvalidLang{} -> WARNING
@@ -391,3 +412,5 @@ messageVerbosity msg =
FilterCompleted{} -> INFO
CiteprocWarning{} -> WARNING
ATXHeadingInLHS{} -> WARNING
+ EnvironmentVariableUndefined{}-> WARNING
+ DuplicateAttribute{} -> WARNING