From 9b6f1fc495b7b6e4c6d13ef84f600cb3f681d538 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Thu, 5 Dec 2013 11:28:22 -0800
Subject: [PATCH] Allow https: to work in pandoc command line arguments.

(Use openURL from Shared instead of simpleHTTP.)
---
 pandoc.hs | 13 ++++++++-----
 1 file changed, 8 insertions(+), 5 deletions(-)

diff --git a/pandoc.hs b/pandoc.hs
index 8c196c01d..cada3347d 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -35,7 +35,8 @@ import Text.Pandoc.Builder (setMeta)
 import Text.Pandoc.PDF (makePDF)
 import Text.Pandoc.Readers.LaTeX (handleIncludes)
 import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile,
-                            safeRead, headerShift, normalize, err, warn )
+                            safeRead, headerShift, normalize, err, warn,
+                            openURL )
 import Text.Pandoc.XML ( toEntities )
 import Text.Pandoc.SelfContained ( makeSelfContained )
 import Text.Pandoc.Process (pipeProcess)
@@ -55,7 +56,6 @@ import Control.Exception.Extensible ( throwIO )
 import qualified Text.Pandoc.UTF8 as UTF8
 import Control.Monad (when, unless, liftM)
 import Data.Foldable (foldrM)
-import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..))
 import Network.URI (parseURI, isURI, URI(..))
 import qualified Data.ByteString.Lazy as B
 import qualified Data.ByteString as BS
@@ -1120,10 +1120,13 @@ main = do
       readSource "-" = UTF8.getContents
       readSource src = case parseURI src of
                             Just u | uriScheme u `elem` ["http:","https:"] ->
-                                       readURI u
+                                       readURI src
                             _       -> UTF8.readFile src
-      readURI uri = simpleHTTP (mkRequest GET uri) >>= getResponseBody >>=
-                      return . UTF8.toStringLazy  -- treat all as UTF8
+      readURI src = do
+        res <- openURL src
+        case res of
+             Left e        -> throwIO e
+             Right (bs,_)  -> return $ UTF8.toString bs
 
   let convertTabs = tabFilter (if preserveTabs then 0 else tabStop)