aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Text/Pandoc/App.hs8
1 files changed, 7 insertions, 1 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 59af029b5..40fb34834 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -352,7 +353,12 @@ readURI src = do
Just "UTF-8" -> return $ UTF8.toText bs
Just "ISO-8859-1" -> return $ T.pack $ B8.unpack bs
Just charset -> throwError $ PandocUnsupportedCharsetError charset
- Nothing -> return $ UTF8.toText bs
+ Nothing -> liftIO $ -- try first as UTF-8, then as latin1
+ E.catch (return $! UTF8.toText bs)
+ (\case
+ TSE.DecodeError{} ->
+ return $ T.pack $ B8.unpack bs
+ e -> E.throwIO e)
readFile' :: MonadIO m => FilePath -> m BL.ByteString
readFile' "-" = liftIO BL.getContents