aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2013-05-28 12:48:17 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-05-28 12:48:17 -0700
commit0a6e9f048a5aa18e3f3832aafc108deadf590a27 (patch)
tree4c10dd0eaa34d05cc1995294c211a3882681b7e1 /src
parentf8e6f9c215c6df318c608d632ca8283406d16c0d (diff)
downloadpandoc-0a6e9f048a5aa18e3f3832aafc108deadf590a27.tar.gz
Shared.openURL: Properly handle data: URIs.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Shared.hs10
1 files changed, 8 insertions, 2 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index aa33c11f6..c571c4143 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -86,7 +86,7 @@ import System.Exit (exitWith, ExitCode(..))
import Data.Char ( toLower, isLower, isUpper, isAlpha,
isLetter, isDigit, isSpace )
import Data.List ( find, isPrefixOf, intercalate )
-import Network.URI ( escapeURIString, isAbsoluteURI, parseURI )
+import Network.URI ( escapeURIString, isAbsoluteURI, parseURI, unEscapeString )
import System.Directory
import Text.Pandoc.MIME (getMimeType)
import System.FilePath ( (</>), takeExtension, dropExtension )
@@ -100,6 +100,7 @@ import System.IO (stderr)
import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..),
renderOptions)
import qualified Data.ByteString as B
+import qualified Data.ByteString.Char8 as B8
import Network.HTTP (findHeader, rspBody,
RequestMethod(..), HeaderName(..), mkRequest)
import Network.Browser (browse, setAllowRedirects, setOutHandler, request)
@@ -567,7 +568,12 @@ fetchItem sourceDir s =
-- | Read from a URL and return raw data and maybe mime type.
openURL :: String -> IO (B.ByteString, Maybe String)
-openURL u = getBodyAndMimeType `fmap` browse
+openURL u
+ | "data:" `isPrefixOf` u =
+ let mime = takeWhile (/=',') $ drop 5 u
+ contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u
+ in return (contents, Just mime)
+ | otherwise = getBodyAndMimeType `fmap` browse
(do S.liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..."
setOutHandler $ const (return ())
setAllowRedirects True