Added Text.Pandoc.Logging (exported module).
This now contains the Verbosity definition previously in Options, as well as a new LogMessage datatype that will eventually be used instead of raw strings for warnings. This will enable us, among other things, to provide machine-readable warnings if desired. See #3392.
This commit is contained in:
parent
c76eec97d4
commit
5e1249481b
13 changed files with 95 additions and 19 deletions
|
@ -392,6 +392,7 @@ Library
|
|||
Text.Pandoc.XML,
|
||||
Text.Pandoc.SelfContained,
|
||||
Text.Pandoc.Highlighting,
|
||||
Text.Pandoc.Logging,
|
||||
Text.Pandoc.Process,
|
||||
Text.Pandoc.MIME,
|
||||
Text.Pandoc.Class
|
||||
|
|
|
@ -58,6 +58,8 @@ module Text.Pandoc
|
|||
, module Text.Pandoc.Generic
|
||||
-- * Options
|
||||
, module Text.Pandoc.Options
|
||||
-- * Logging
|
||||
, module Text.Pandoc.Logging
|
||||
-- * Typeclass
|
||||
, PandocMonad
|
||||
, runIO
|
||||
|
@ -189,6 +191,7 @@ import Text.Pandoc.Writers.Custom
|
|||
import Text.Pandoc.Writers.TEI
|
||||
import Text.Pandoc.Templates
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.Shared (safeRead, mapLeft, pandocVersion)
|
||||
import Text.Pandoc.Error
|
||||
import Text.Pandoc.Class
|
||||
|
|
|
@ -72,8 +72,8 @@ import qualified Text.Pandoc.Shared as IO ( readDataFile
|
|||
, openURL )
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Text.Pandoc.Compat.Time (UTCTime)
|
||||
import Text.Pandoc.Options (Verbosity(..))
|
||||
import Text.Parsec (ParsecT, SourcePos, getPosition)
|
||||
import Text.Pandoc.Logging
|
||||
import Text.Parsec (ParsecT, SourcePos)
|
||||
import qualified Text.Pandoc.Compat.Time as IO (getCurrentTime)
|
||||
import Text.Pandoc.MIME (MimeType, getMimeType)
|
||||
import Data.Time.Clock.POSIX ( utcTimeToPOSIXSeconds
|
||||
|
|
|
@ -29,7 +29,9 @@ This module provides a standard way to deal with possible errors encounted
|
|||
during parsing.
|
||||
|
||||
-}
|
||||
module Text.Pandoc.Error (PandocError(..), handleError) where
|
||||
module Text.Pandoc.Error (
|
||||
PandocError(..),
|
||||
handleError) where
|
||||
|
||||
import Text.Parsec.Error
|
||||
import Text.Parsec.Pos hiding (Line)
|
||||
|
@ -47,13 +49,6 @@ data PandocError = PandocFileReadError FilePath
|
|||
| PandocParsecError Input ParseError
|
||||
deriving (Show, Typeable, Generic)
|
||||
|
||||
|
||||
-- data PandocError = -- | Generic parse failure
|
||||
-- ParseFailure String
|
||||
-- -- | Error thrown by a Parsec parser
|
||||
-- | ParsecError Input ParseError
|
||||
-- deriving (Show, Typeable, Generic)
|
||||
|
||||
instance Exception PandocError
|
||||
|
||||
-- | Handle PandocError by exiting with an error message.
|
||||
|
|
76
src/Text/Pandoc/Logging.hs
Normal file
76
src/Text/Pandoc/Logging.hs
Normal file
|
@ -0,0 +1,76 @@
|
|||
{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}
|
||||
{-
|
||||
Copyright (C) 2016-17 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
This program is free software; you can redistribute it and/or modify
|
||||
it under the terms of the GNU General Public License as published by
|
||||
the Free Software Foundation; either version 2 of the License, or
|
||||
(at your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful,
|
||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
GNU General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
{- |
|
||||
Module : Text.Pandoc.Logging
|
||||
Copyright : Copyright (C) 2006-2016 John MacFarlane
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
||||
Stability : alpha
|
||||
Portability : portable
|
||||
|
||||
This module provides data types and functions for warnings
|
||||
and info messages.
|
||||
|
||||
-}
|
||||
module Text.Pandoc.Logging (
|
||||
Verbosity(..)
|
||||
, LogMessage(..)
|
||||
, messageVerbosity
|
||||
) where
|
||||
|
||||
import Text.Parsec.Pos
|
||||
import Data.Data (Data)
|
||||
import Data.Generics (Typeable)
|
||||
import GHC.Generics (Generic)
|
||||
|
||||
-- | Verbosity level.
|
||||
data Verbosity = ERROR | WARNING | INFO | DEBUG
|
||||
deriving (Show, Read, Eq, Data, Enum, Ord, Bounded, Typeable, Generic)
|
||||
|
||||
data LogMessage =
|
||||
SkippedInput String SourcePos
|
||||
| NotRendered String
|
||||
| YamlSectionNotAnObject SourcePos
|
||||
| DuplicateLinkReference String SourcePos
|
||||
| DuplicateNoteReference String SourcePos
|
||||
| ParsingUnescaped String SourcePos
|
||||
| DocxCommentWillNotRetainFormatting String
|
||||
| CouldNotFetchResource String String
|
||||
| CouldNotDetermineImageSize String
|
||||
| CouldNotDetermineMimeType String
|
||||
| CouldNotConvertTeXMath String
|
||||
deriving (Show, Eq, Data, Ord, Typeable, Generic)
|
||||
|
||||
messageVerbosity:: LogMessage -> Verbosity
|
||||
messageVerbosity msg =
|
||||
case msg of
|
||||
SkippedInput{} -> INFO
|
||||
NotRendered{} -> INFO
|
||||
YamlSectionNotAnObject{} -> WARNING
|
||||
DuplicateLinkReference{} -> WARNING
|
||||
DuplicateNoteReference{} -> WARNING
|
||||
ParsingUnescaped{} -> INFO
|
||||
DocxCommentWillNotRetainFormatting{} -> INFO
|
||||
CouldNotFetchResource{} -> WARNING
|
||||
CouldNotDetermineImageSize{} -> WARNING
|
||||
CouldNotDetermineMimeType{} -> WARNING
|
||||
CouldNotConvertTeXMath{} -> WARNING
|
||||
|
||||
|
|
@ -37,7 +37,6 @@ module Text.Pandoc.Options ( module Text.Pandoc.Extensions
|
|||
, HTMLSlideVariant (..)
|
||||
, EPUBVersion (..)
|
||||
, WrapOption (..)
|
||||
, Verbosity (..)
|
||||
, TopLevelDivision (..)
|
||||
, WriterOptions (..)
|
||||
, TrackChanges (..)
|
||||
|
@ -138,10 +137,6 @@ data ReferenceLocation = EndOfBlock -- ^ End of block
|
|||
| EndOfDocument -- ^ at end of document
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Verbosity level.
|
||||
data Verbosity = ERROR | WARNING | INFO | DEBUG
|
||||
deriving (Show, Read, Eq, Data, Enum, Ord, Bounded, Typeable, Generic)
|
||||
|
||||
-- | Options for writers
|
||||
data WriterOptions = WriterOptions
|
||||
{ writerTemplate :: Maybe String -- ^ Template to use
|
||||
|
|
|
@ -52,8 +52,8 @@ import Text.Pandoc.MediaBag
|
|||
import Text.Pandoc.Walk (walkM)
|
||||
import Text.Pandoc.Shared (warn, withTempDir, inDirectory, stringify)
|
||||
import Text.Pandoc.Writers.Shared (getField, metaToJSON)
|
||||
import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..),
|
||||
Verbosity(..))
|
||||
import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..))
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.MIME (extensionFromMimeType, getMimeType)
|
||||
import Text.Pandoc.Process (pipeProcess)
|
||||
import Control.Monad.Trans (MonadIO(..))
|
||||
|
|
|
@ -12,7 +12,8 @@ import Text.XML.Light
|
|||
import Text.Pandoc.Definition hiding (Attr)
|
||||
import Text.Pandoc.Readers.HTML (readHtml)
|
||||
import Text.Pandoc.Walk (walk, query)
|
||||
import Text.Pandoc.Options ( ReaderOptions(..), Verbosity(..))
|
||||
import Text.Pandoc.Options ( ReaderOptions(..))
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Extensions (enableExtension, Extension(Ext_raw_html))
|
||||
import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField)
|
||||
import Network.URI (unEscapeString)
|
||||
|
|
|
@ -46,8 +46,9 @@ import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
|
|||
import Text.Pandoc.Shared ( extractSpaces, renderTags', addMetaField
|
||||
, escapeURI, safeRead )
|
||||
import Text.Pandoc.Options (ReaderOptions(readerExtensions), extensionEnabled,
|
||||
Verbosity(..), Extension (Ext_epub_html_exts,
|
||||
Extension (Ext_epub_html_exts,
|
||||
Ext_raw_html, Ext_native_divs, Ext_native_spans))
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Parsing hiding ((<|>))
|
||||
import Text.Pandoc.Walk
|
||||
import qualified Data.Map as M
|
||||
|
|
|
@ -51,6 +51,7 @@ import qualified Text.Pandoc.UTF8 as UTF8
|
|||
import qualified Data.Vector as V
|
||||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Pretty (charWidth)
|
||||
import Text.Pandoc.XML (fromEntities)
|
||||
|
|
|
@ -41,6 +41,7 @@ import qualified Text.Pandoc.Builder as B
|
|||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
|
||||
import Data.Monoid ((<>))
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )
|
||||
import Text.Pandoc.XML ( fromEntities )
|
||||
import Text.Pandoc.Parsing hiding ( nested )
|
||||
|
|
|
@ -35,6 +35,7 @@ module Text.Pandoc.Readers.TWiki ( readTWiki
|
|||
import Text.Pandoc.Definition
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Parsing hiding (enclosed, macro, nested)
|
||||
import Text.Pandoc.Readers.HTML (htmlTag, isCommentTag)
|
||||
import Control.Monad
|
||||
|
|
|
@ -56,6 +56,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Logging (Verbosity(..))
|
||||
import Text.Pandoc.Parsing
|
||||
import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isInlineTag )
|
||||
import Text.Pandoc.Shared (trim)
|
||||
|
|
Loading…
Add table
Reference in a new issue