Move utility error functions to Text.Pandoc.Shared

This commit is contained in:
Matthew Pickering 2015-02-18 21:05:47 +00:00
parent 48f442f477
commit ad39bc7009
5 changed files with 14 additions and 12 deletions

View file

@ -164,7 +164,7 @@ import Text.Pandoc.Writers.Haddock
import Text.Pandoc.Writers.Custom
import Text.Pandoc.Templates
import Text.Pandoc.Options
import Text.Pandoc.Shared (safeRead, warn)
import Text.Pandoc.Shared (safeRead, warn, mapLeft)
import Text.Pandoc.MediaBag (MediaBag)
import Text.Pandoc.Error
import Data.Aeson

View file

@ -28,7 +28,7 @@ This module provides a standard way to deal with possible errors encounted
during parsing.
-}
module Text.Pandoc.Error (PandocError(..), handleError,hush, mapLeft) where
module Text.Pandoc.Error (PandocError(..), handleError) where
import Text.Parsec.Error
import Text.Parsec.Pos hiding (Line)
@ -46,13 +46,6 @@ data PandocError = -- | Generic parse failure
instance Error PandocError where
strMsg = ParseFailure
mapLeft :: (a -> b) -> Either a c -> Either b c
mapLeft f (Left x) = Left (f x)
mapLeft _ (Right x) = Right x
hush :: Either a b -> Maybe b
hush (Left _) = Nothing
hush (Right x) = Just x
-- | An unsafe method to handle `PandocError`s.
handleError :: Either PandocError a -> a

View file

@ -39,10 +39,9 @@ import Control.Monad
import Data.Bits
import Data.Binary
import Data.Binary.Get
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.Shared (safeRead, hush)
import qualified Data.Map as M
import Text.Pandoc.Compat.Except
import Text.Pandoc.Error
import Control.Monad.Trans
import Data.Maybe (fromMaybe)

View file

@ -44,7 +44,7 @@ import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
import Text.Pandoc.Shared ( extractSpaces, renderTags'
, escapeURI, safeRead )
, escapeURI, safeRead, mapLeft )
import Text.Pandoc.Options (ReaderOptions(readerParseRaw, readerTrace)
, Extension (Ext_epub_html_exts,
Ext_native_divs, Ext_native_spans))

View file

@ -85,6 +85,8 @@ module Text.Pandoc.Shared (
-- * Error handling
err,
warn,
mapLeft,
hush,
-- * Safe read
safeRead,
-- * Temp directory
@ -855,6 +857,14 @@ warn msg = do
name <- getProgName
UTF8.hPutStrLn stderr $ name ++ ": " ++ msg
mapLeft :: (a -> b) -> Either a c -> Either b c
mapLeft f (Left x) = Left (f x)
mapLeft _ (Right x) = Right x
hush :: Either a b -> Maybe b
hush (Left _) = Nothing
hush (Right x) = Just x
-- | Remove intermediate "." and ".." directories from a path.
--
-- > collapseFilePath "./foo" == "foo"