2013-08-10 18:13:38 -07:00
|
|
|
{-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses #-}
|
2007-11-03 23:27:58 +00:00
|
|
|
{-
|
2013-05-10 22:53:35 -07:00
|
|
|
Copyright (C) 2006-2013 John MacFarlane <jgm@berkeley.edu>
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
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.Shared
|
2013-05-10 22:53:35 -07:00
|
|
|
Copyright : Copyright (C) 2006-2013 John MacFarlane
|
2012-07-26 22:32:53 -07:00
|
|
|
License : GNU GPL, version 2 or above
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
Stability : alpha
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
Utility functions and definitions used by the various Pandoc modules.
|
|
|
|
-}
|
2010-03-23 15:05:33 -07:00
|
|
|
module Text.Pandoc.Shared (
|
2007-11-03 23:27:58 +00:00
|
|
|
-- * List processing
|
|
|
|
splitBy,
|
|
|
|
splitByIndices,
|
2012-01-27 00:37:46 -08:00
|
|
|
splitStringByIndices,
|
2007-11-03 23:27:58 +00:00
|
|
|
substitute,
|
|
|
|
-- * Text processing
|
|
|
|
backslashEscapes,
|
|
|
|
escapeStringUsing,
|
|
|
|
stripTrailingNewlines,
|
2012-09-29 17:09:34 -04:00
|
|
|
trim,
|
|
|
|
triml,
|
|
|
|
trimr,
|
2007-11-03 23:27:58 +00:00
|
|
|
stripFirstAndLast,
|
|
|
|
camelCaseToHyphenated,
|
|
|
|
toRomanNumeral,
|
2010-03-23 15:05:33 -07:00
|
|
|
escapeURI,
|
2010-07-06 23:17:06 -07:00
|
|
|
tabFilter,
|
2012-01-28 15:54:05 -08:00
|
|
|
-- * Date/time
|
|
|
|
normalizeDate,
|
2007-11-03 23:27:58 +00:00
|
|
|
-- * Pandoc block and inline list processing
|
|
|
|
orderedListMarkers,
|
|
|
|
normalizeSpaces,
|
2010-12-14 20:04:37 -08:00
|
|
|
normalize,
|
2010-11-27 07:08:06 -08:00
|
|
|
stringify,
|
2007-11-03 23:27:58 +00:00
|
|
|
compactify,
|
2012-09-27 17:22:17 -07:00
|
|
|
compactify',
|
2007-11-03 23:27:58 +00:00
|
|
|
Element (..),
|
|
|
|
hierarchicalize,
|
2010-03-16 06:45:52 +00:00
|
|
|
uniqueIdent,
|
2007-11-03 23:27:58 +00:00
|
|
|
isHeaderBlock,
|
2010-07-11 20:03:55 -07:00
|
|
|
headerShift,
|
2013-01-07 20:12:05 -08:00
|
|
|
isTightList,
|
2013-05-10 22:53:35 -07:00
|
|
|
addMetaField,
|
|
|
|
makeMeta,
|
2012-08-15 09:42:16 -07:00
|
|
|
-- * TagSoup HTML handling
|
|
|
|
renderTags',
|
2008-07-31 23:16:02 +00:00
|
|
|
-- * File handling
|
2009-12-31 01:11:23 +00:00
|
|
|
inDirectory,
|
2011-07-17 19:33:52 -07:00
|
|
|
readDataFile,
|
2012-12-29 17:44:02 -08:00
|
|
|
readDataFileUTF8,
|
2013-01-11 16:19:06 -08:00
|
|
|
fetchItem,
|
|
|
|
openURL,
|
2012-01-29 23:54:00 -08:00
|
|
|
-- * Error handling
|
|
|
|
err,
|
2012-08-09 07:52:39 -07:00
|
|
|
warn,
|
|
|
|
-- * Safe read
|
|
|
|
safeRead
|
2007-11-03 23:27:58 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Text.Pandoc.Definition
|
2013-08-10 18:13:38 -07:00
|
|
|
import Text.Pandoc.Walk
|
2010-12-24 13:39:27 -08:00
|
|
|
import Text.Pandoc.Generic
|
2013-05-10 22:53:35 -07:00
|
|
|
import Text.Pandoc.Builder (Blocks, ToMetaValue(..))
|
2012-09-27 17:22:17 -07:00
|
|
|
import qualified Text.Pandoc.Builder as B
|
2012-01-29 23:54:00 -08:00
|
|
|
import qualified Text.Pandoc.UTF8 as UTF8
|
|
|
|
import System.Environment (getProgName)
|
|
|
|
import System.Exit (exitWith, ExitCode(..))
|
2011-12-02 19:39:30 -08:00
|
|
|
import Data.Char ( toLower, isLower, isUpper, isAlpha,
|
|
|
|
isLetter, isDigit, isSpace )
|
2008-09-08 06:36:28 +00:00
|
|
|
import Data.List ( find, isPrefixOf, intercalate )
|
2013-05-10 22:53:35 -07:00
|
|
|
import qualified Data.Map as M
|
2013-07-04 22:40:23 -07:00
|
|
|
import Network.URI ( escapeURIString, isAbsoluteURI, unEscapeString )
|
2008-07-31 23:16:02 +00:00
|
|
|
import System.Directory
|
2013-01-11 11:30:31 -08:00
|
|
|
import Text.Pandoc.MIME (getMimeType)
|
|
|
|
import System.FilePath ( (</>), takeExtension, dropExtension )
|
2010-12-24 13:39:27 -08:00
|
|
|
import Data.Generics (Typeable, Data)
|
2009-04-25 00:29:58 +00:00
|
|
|
import qualified Control.Monad.State as S
|
2013-07-18 20:58:14 -07:00
|
|
|
import qualified Control.Exception as E
|
2013-07-01 20:47:26 -07:00
|
|
|
import Control.Monad (msum, unless)
|
2012-01-27 00:37:46 -08:00
|
|
|
import Text.Pandoc.Pretty (charWidth)
|
2012-01-28 15:54:05 -08:00
|
|
|
import System.Locale (defaultTimeLocale)
|
|
|
|
import Data.Time
|
2012-09-23 22:53:34 -07:00
|
|
|
import System.IO (stderr)
|
2012-08-15 09:42:16 -07:00
|
|
|
import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..),
|
|
|
|
renderOptions)
|
2013-07-04 22:40:23 -07:00
|
|
|
import qualified Data.ByteString as BS
|
2013-05-28 12:48:17 -07:00
|
|
|
import qualified Data.ByteString.Char8 as B8
|
2013-08-10 18:13:38 -07:00
|
|
|
import Text.Pandoc.Compat.Monoid
|
2013-05-10 22:53:35 -07:00
|
|
|
|
2012-12-29 17:44:02 -08:00
|
|
|
#ifdef EMBED_DATA_FILES
|
2013-01-23 08:14:23 -08:00
|
|
|
import Text.Pandoc.Data (dataFiles)
|
2013-04-20 13:07:50 -07:00
|
|
|
import System.FilePath ( joinPath, splitDirectories )
|
2012-12-29 17:44:02 -08:00
|
|
|
#else
|
|
|
|
import Paths_pandoc (getDataFileName)
|
|
|
|
#endif
|
2013-07-04 22:40:23 -07:00
|
|
|
#ifdef HTTP_CONDUIT
|
2013-07-30 08:38:13 -07:00
|
|
|
import Data.ByteString.Lazy (toChunks)
|
2013-07-04 22:40:23 -07:00
|
|
|
import Network.HTTP.Conduit (httpLbs, parseUrl, withManager,
|
|
|
|
responseBody, responseHeaders)
|
|
|
|
import Network.HTTP.Types.Header ( hContentType)
|
|
|
|
#else
|
|
|
|
import Network.URI (parseURI)
|
|
|
|
import Network.HTTP (findHeader, rspBody,
|
|
|
|
RequestMethod(..), HeaderName(..), mkRequest)
|
|
|
|
import Network.Browser (browse, setAllowRedirects, setOutHandler, request)
|
|
|
|
#endif
|
2010-03-22 19:29:37 -07:00
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
--
|
|
|
|
-- List processing
|
|
|
|
--
|
|
|
|
|
|
|
|
-- | Split list by groups of one or more sep.
|
2010-12-21 08:41:24 -08:00
|
|
|
splitBy :: (a -> Bool) -> [a] -> [[a]]
|
2007-11-03 23:27:58 +00:00
|
|
|
splitBy _ [] = []
|
2010-12-21 08:41:24 -08:00
|
|
|
splitBy isSep lst =
|
|
|
|
let (first, rest) = break isSep lst
|
|
|
|
rest' = dropWhile isSep rest
|
|
|
|
in first:(splitBy isSep rest')
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
splitByIndices :: [Int] -> [a] -> [[a]]
|
|
|
|
splitByIndices [] lst = [lst]
|
2012-01-27 00:37:46 -08:00
|
|
|
splitByIndices (x:xs) lst = first:(splitByIndices (map (\y -> y - x) xs) rest)
|
|
|
|
where (first, rest) = splitAt x lst
|
|
|
|
|
|
|
|
-- | Split string into chunks divided at specified indices.
|
|
|
|
splitStringByIndices :: [Int] -> [Char] -> [[Char]]
|
|
|
|
splitStringByIndices [] lst = [lst]
|
|
|
|
splitStringByIndices (x:xs) lst =
|
|
|
|
let (first, rest) = splitAt' x lst in
|
|
|
|
first : (splitStringByIndices (map (\y -> y - x) xs) rest)
|
|
|
|
|
|
|
|
splitAt' :: Int -> [Char] -> ([Char],[Char])
|
|
|
|
splitAt' _ [] = ([],[])
|
|
|
|
splitAt' n xs | n <= 0 = ([],xs)
|
|
|
|
splitAt' n (x:xs) = (x:ys,zs)
|
|
|
|
where (ys,zs) = splitAt' (n - charWidth x) xs
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Replace each occurrence of one sublist in a list with another.
|
|
|
|
substitute :: (Eq a) => [a] -> [a] -> [a] -> [a]
|
|
|
|
substitute _ _ [] = []
|
2010-07-11 12:22:18 -07:00
|
|
|
substitute [] _ xs = xs
|
|
|
|
substitute target replacement lst@(x:xs) =
|
2007-11-03 23:27:58 +00:00
|
|
|
if target `isPrefixOf` lst
|
2010-07-11 12:22:18 -07:00
|
|
|
then replacement ++ substitute target replacement (drop (length target) lst)
|
|
|
|
else x : substitute target replacement xs
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
--
|
|
|
|
-- Text processing
|
|
|
|
--
|
|
|
|
|
|
|
|
-- | Returns an association list of backslash escapes for the
|
|
|
|
-- designated characters.
|
|
|
|
backslashEscapes :: [Char] -- ^ list of special characters to escape
|
|
|
|
-> [(Char, String)]
|
|
|
|
backslashEscapes = map (\ch -> (ch, ['\\',ch]))
|
|
|
|
|
|
|
|
-- | Escape a string of characters, using an association list of
|
|
|
|
-- characters and strings.
|
|
|
|
escapeStringUsing :: [(Char, String)] -> String -> String
|
|
|
|
escapeStringUsing _ [] = ""
|
2012-07-26 22:32:53 -07:00
|
|
|
escapeStringUsing escapeTable (x:xs) =
|
2007-11-03 23:27:58 +00:00
|
|
|
case (lookup x escapeTable) of
|
|
|
|
Just str -> str ++ rest
|
|
|
|
Nothing -> x:rest
|
|
|
|
where rest = escapeStringUsing escapeTable xs
|
|
|
|
|
|
|
|
-- | Strip trailing newlines from string.
|
|
|
|
stripTrailingNewlines :: String -> String
|
|
|
|
stripTrailingNewlines = reverse . dropWhile (== '\n') . reverse
|
|
|
|
|
|
|
|
-- | Remove leading and trailing space (including newlines) from string.
|
2012-09-29 17:09:34 -04:00
|
|
|
trim :: String -> String
|
|
|
|
trim = triml . trimr
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Remove leading space (including newlines) from string.
|
2012-09-29 17:09:34 -04:00
|
|
|
triml :: String -> String
|
|
|
|
triml = dropWhile (`elem` " \r\n\t")
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Remove trailing space (including newlines) from string.
|
2012-09-29 17:09:34 -04:00
|
|
|
trimr :: String -> String
|
|
|
|
trimr = reverse . triml . reverse
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Strip leading and trailing characters from string
|
|
|
|
stripFirstAndLast :: String -> String
|
|
|
|
stripFirstAndLast str =
|
|
|
|
drop 1 $ take ((length str) - 1) str
|
|
|
|
|
2012-07-26 22:32:53 -07:00
|
|
|
-- | Change CamelCase word to hyphenated lowercase (e.g., camel-case).
|
2007-11-03 23:27:58 +00:00
|
|
|
camelCaseToHyphenated :: String -> String
|
|
|
|
camelCaseToHyphenated [] = ""
|
|
|
|
camelCaseToHyphenated (a:b:rest) | isLower a && isUpper b =
|
|
|
|
a:'-':(toLower b):(camelCaseToHyphenated rest)
|
|
|
|
camelCaseToHyphenated (a:rest) = (toLower a):(camelCaseToHyphenated rest)
|
|
|
|
|
|
|
|
-- | Convert number < 4000 to uppercase roman numeral.
|
|
|
|
toRomanNumeral :: Int -> String
|
|
|
|
toRomanNumeral x =
|
|
|
|
if x >= 4000 || x < 0
|
|
|
|
then "?"
|
|
|
|
else case x of
|
|
|
|
_ | x >= 1000 -> "M" ++ toRomanNumeral (x - 1000)
|
|
|
|
_ | x >= 900 -> "CM" ++ toRomanNumeral (x - 900)
|
|
|
|
_ | x >= 500 -> "D" ++ toRomanNumeral (x - 500)
|
|
|
|
_ | x >= 400 -> "CD" ++ toRomanNumeral (x - 400)
|
|
|
|
_ | x >= 100 -> "C" ++ toRomanNumeral (x - 100)
|
|
|
|
_ | x >= 90 -> "XC" ++ toRomanNumeral (x - 90)
|
|
|
|
_ | x >= 50 -> "L" ++ toRomanNumeral (x - 50)
|
|
|
|
_ | x >= 40 -> "XL" ++ toRomanNumeral (x - 40)
|
|
|
|
_ | x >= 10 -> "X" ++ toRomanNumeral (x - 10)
|
|
|
|
_ | x >= 9 -> "IX" ++ toRomanNumeral (x - 5)
|
|
|
|
_ | x >= 5 -> "V" ++ toRomanNumeral (x - 5)
|
|
|
|
_ | x >= 4 -> "IV" ++ toRomanNumeral (x - 4)
|
|
|
|
_ | x >= 1 -> "I" ++ toRomanNumeral (x - 1)
|
|
|
|
_ -> ""
|
|
|
|
|
2011-12-02 19:39:30 -08:00
|
|
|
-- | Escape whitespace in URI.
|
2010-03-23 15:05:33 -07:00
|
|
|
escapeURI :: String -> String
|
2011-12-02 19:39:30 -08:00
|
|
|
escapeURI = escapeURIString (not . isSpace)
|
2010-03-23 15:34:53 -07:00
|
|
|
|
2010-07-06 23:17:06 -07:00
|
|
|
-- | Convert tabs to spaces and filter out DOS line endings.
|
|
|
|
-- Tabs will be preserved if tab stop is set to 0.
|
|
|
|
tabFilter :: Int -- ^ Tab stop
|
|
|
|
-> String -- ^ Input
|
|
|
|
-> String
|
|
|
|
tabFilter tabStop =
|
|
|
|
let go _ [] = ""
|
|
|
|
go _ ('\n':xs) = '\n' : go tabStop xs
|
|
|
|
go _ ('\r':'\n':xs) = '\n' : go tabStop xs
|
|
|
|
go _ ('\r':xs) = '\n' : go tabStop xs
|
|
|
|
go spsToNextStop ('\t':xs) =
|
|
|
|
if tabStop == 0
|
|
|
|
then '\t' : go tabStop xs
|
|
|
|
else replicate spsToNextStop ' ' ++ go tabStop xs
|
|
|
|
go 1 (x:xs) =
|
|
|
|
x : go tabStop xs
|
|
|
|
go spsToNextStop (x:xs) =
|
|
|
|
x : go (spsToNextStop - 1) xs
|
|
|
|
in go tabStop
|
|
|
|
|
2012-01-28 15:54:05 -08:00
|
|
|
--
|
|
|
|
-- Date/time
|
|
|
|
--
|
|
|
|
|
|
|
|
-- | Parse a date and convert (if possible) to "YYYY-MM-DD" format.
|
|
|
|
normalizeDate :: String -> Maybe String
|
|
|
|
normalizeDate s = fmap (formatTime defaultTimeLocale "%F")
|
|
|
|
(msum $ map (\fs -> parsetimeWith fs s) formats :: Maybe Day)
|
|
|
|
where parsetimeWith = parseTime defaultTimeLocale
|
|
|
|
formats = ["%x","%m/%d/%Y", "%D","%F", "%d %b %Y",
|
|
|
|
"%d %B %Y", "%b. %d, %Y", "%B %d, %Y"]
|
|
|
|
|
2007-11-03 23:27:58 +00:00
|
|
|
--
|
|
|
|
-- Pandoc block and inline list processing
|
|
|
|
--
|
|
|
|
|
|
|
|
-- | Generate infinite lazy list of markers for an ordered list,
|
|
|
|
-- depending on list attributes.
|
|
|
|
orderedListMarkers :: (Int, ListNumberStyle, ListNumberDelim) -> [String]
|
2012-07-26 22:32:53 -07:00
|
|
|
orderedListMarkers (start, numstyle, numdelim) =
|
2007-11-03 23:27:58 +00:00
|
|
|
let singleton c = [c]
|
|
|
|
nums = case numstyle of
|
|
|
|
DefaultStyle -> map show [start..]
|
2010-07-11 22:47:52 -07:00
|
|
|
Example -> map show [start..]
|
2007-11-03 23:27:58 +00:00
|
|
|
Decimal -> map show [start..]
|
2012-07-26 22:32:53 -07:00
|
|
|
UpperAlpha -> drop (start - 1) $ cycle $
|
2007-11-03 23:27:58 +00:00
|
|
|
map singleton ['A'..'Z']
|
|
|
|
LowerAlpha -> drop (start - 1) $ cycle $
|
|
|
|
map singleton ['a'..'z']
|
|
|
|
UpperRoman -> map toRomanNumeral [start..]
|
|
|
|
LowerRoman -> map (map toLower . toRomanNumeral) [start..]
|
|
|
|
inDelim str = case numdelim of
|
|
|
|
DefaultDelim -> str ++ "."
|
|
|
|
Period -> str ++ "."
|
|
|
|
OneParen -> str ++ ")"
|
|
|
|
TwoParens -> "(" ++ str ++ ")"
|
|
|
|
in map inDelim nums
|
|
|
|
|
|
|
|
-- | Normalize a list of inline elements: remove leading and trailing
|
|
|
|
-- @Space@ elements, collapse double @Space@s into singles, and
|
|
|
|
-- remove empty Str elements.
|
|
|
|
normalizeSpaces :: [Inline] -> [Inline]
|
2010-12-07 20:10:21 -08:00
|
|
|
normalizeSpaces = cleanup . dropWhile isSpaceOrEmpty
|
2012-07-24 22:12:18 -07:00
|
|
|
where cleanup [] = []
|
|
|
|
cleanup (Space:rest) = case dropWhile isSpaceOrEmpty rest of
|
|
|
|
[] -> []
|
|
|
|
(x:xs) -> Space : x : cleanup xs
|
2010-12-07 20:10:21 -08:00
|
|
|
cleanup ((Str ""):rest) = cleanup rest
|
2012-07-24 22:12:18 -07:00
|
|
|
cleanup (x:rest) = x : cleanup rest
|
2007-11-03 23:27:58 +00:00
|
|
|
|
2011-02-04 13:22:31 -08:00
|
|
|
isSpaceOrEmpty :: Inline -> Bool
|
|
|
|
isSpaceOrEmpty Space = True
|
|
|
|
isSpaceOrEmpty (Str "") = True
|
|
|
|
isSpaceOrEmpty _ = False
|
|
|
|
|
2010-12-14 20:04:37 -08:00
|
|
|
-- | Normalize @Pandoc@ document, consolidating doubled 'Space's,
|
|
|
|
-- combining adjacent 'Str's and 'Emph's, remove 'Null's and
|
|
|
|
-- empty elements, etc.
|
2011-01-29 10:03:31 -08:00
|
|
|
normalize :: (Eq a, Data a) => a -> a
|
|
|
|
normalize = topDown removeEmptyBlocks .
|
|
|
|
topDown consolidateInlines .
|
2011-02-04 13:22:31 -08:00
|
|
|
bottomUp (removeEmptyInlines . removeTrailingInlineSpaces)
|
2010-12-26 10:24:15 -08:00
|
|
|
|
|
|
|
removeEmptyBlocks :: [Block] -> [Block]
|
|
|
|
removeEmptyBlocks (Null : xs) = removeEmptyBlocks xs
|
|
|
|
removeEmptyBlocks (BulletList [] : xs) = removeEmptyBlocks xs
|
|
|
|
removeEmptyBlocks (OrderedList _ [] : xs) = removeEmptyBlocks xs
|
|
|
|
removeEmptyBlocks (DefinitionList [] : xs) = removeEmptyBlocks xs
|
2011-01-23 10:55:56 -08:00
|
|
|
removeEmptyBlocks (RawBlock _ [] : xs) = removeEmptyBlocks xs
|
2010-12-26 10:24:15 -08:00
|
|
|
removeEmptyBlocks (x:xs) = x : removeEmptyBlocks xs
|
|
|
|
removeEmptyBlocks [] = []
|
|
|
|
|
|
|
|
removeEmptyInlines :: [Inline] -> [Inline]
|
|
|
|
removeEmptyInlines (Emph [] : zs) = removeEmptyInlines zs
|
|
|
|
removeEmptyInlines (Strong [] : zs) = removeEmptyInlines zs
|
|
|
|
removeEmptyInlines (Subscript [] : zs) = removeEmptyInlines zs
|
|
|
|
removeEmptyInlines (Superscript [] : zs) = removeEmptyInlines zs
|
|
|
|
removeEmptyInlines (SmallCaps [] : zs) = removeEmptyInlines zs
|
|
|
|
removeEmptyInlines (Strikeout [] : zs) = removeEmptyInlines zs
|
2011-01-23 10:55:56 -08:00
|
|
|
removeEmptyInlines (RawInline _ [] : zs) = removeEmptyInlines zs
|
2011-01-26 20:44:25 -08:00
|
|
|
removeEmptyInlines (Code _ [] : zs) = removeEmptyInlines zs
|
2011-01-29 10:03:31 -08:00
|
|
|
removeEmptyInlines (Str "" : zs) = removeEmptyInlines zs
|
2010-12-26 10:24:15 -08:00
|
|
|
removeEmptyInlines (x : xs) = x : removeEmptyInlines xs
|
|
|
|
removeEmptyInlines [] = []
|
|
|
|
|
2011-02-04 13:22:31 -08:00
|
|
|
removeTrailingInlineSpaces :: [Inline] -> [Inline]
|
2011-02-04 18:32:54 -08:00
|
|
|
removeTrailingInlineSpaces = reverse . removeLeadingInlineSpaces . reverse
|
|
|
|
|
|
|
|
removeLeadingInlineSpaces :: [Inline] -> [Inline]
|
|
|
|
removeLeadingInlineSpaces = dropWhile isSpaceOrEmpty
|
2011-02-04 13:22:31 -08:00
|
|
|
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines :: [Inline] -> [Inline]
|
|
|
|
consolidateInlines (Str x : ys) =
|
2010-12-14 20:04:37 -08:00
|
|
|
case concat (x : map fromStr strs) of
|
2010-12-26 10:24:15 -08:00
|
|
|
"" -> consolidateInlines rest
|
|
|
|
n -> Str n : consolidateInlines rest
|
2010-12-14 20:04:37 -08:00
|
|
|
where
|
|
|
|
(strs, rest) = span isStr ys
|
|
|
|
isStr (Str _) = True
|
|
|
|
isStr _ = False
|
|
|
|
fromStr (Str z) = z
|
2010-12-26 10:24:15 -08:00
|
|
|
fromStr _ = error "consolidateInlines - fromStr - not a Str"
|
2010-12-26 12:01:33 -08:00
|
|
|
consolidateInlines (Space : ys) = Space : rest
|
2011-12-02 19:39:30 -08:00
|
|
|
where isSp Space = True
|
|
|
|
isSp _ = False
|
|
|
|
rest = consolidateInlines $ dropWhile isSp ys
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (Emph xs : Emph ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
Emph (xs ++ ys) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (Strong xs : Strong ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
Strong (xs ++ ys) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (Subscript xs : Subscript ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
Subscript (xs ++ ys) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (Superscript xs : Superscript ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
Superscript (xs ++ ys) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (SmallCaps xs : SmallCaps ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
SmallCaps (xs ++ ys) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (Strikeout xs : Strikeout ys : zs) = consolidateInlines $
|
2010-12-14 20:04:37 -08:00
|
|
|
Strikeout (xs ++ ys) : zs
|
2011-01-23 10:55:56 -08:00
|
|
|
consolidateInlines (RawInline f x : RawInline f' y : zs) | f == f' =
|
|
|
|
consolidateInlines $ RawInline f (x ++ y) : zs
|
2011-01-26 20:44:25 -08:00
|
|
|
consolidateInlines (Code a1 x : Code a2 y : zs) | a1 == a2 =
|
|
|
|
consolidateInlines $ Code a1 (x ++ y) : zs
|
2010-12-26 10:24:15 -08:00
|
|
|
consolidateInlines (x : xs) = x : consolidateInlines xs
|
|
|
|
consolidateInlines [] = []
|
2010-12-14 20:04:37 -08:00
|
|
|
|
2010-11-27 07:08:06 -08:00
|
|
|
-- | Convert list of inlines to a string with formatting removed.
|
2013-08-16 13:22:27 -07:00
|
|
|
-- Footnotes are skipped (since we don't want their contents in link
|
|
|
|
-- labels).
|
2010-11-27 07:08:06 -08:00
|
|
|
stringify :: [Inline] -> String
|
2013-08-16 13:22:27 -07:00
|
|
|
stringify = query go . walk deNote
|
2010-11-27 07:08:06 -08:00
|
|
|
where go :: Inline -> [Char]
|
|
|
|
go Space = " "
|
|
|
|
go (Str x) = x
|
2011-01-26 20:44:25 -08:00
|
|
|
go (Code _ x) = x
|
2010-12-12 20:09:14 -08:00
|
|
|
go (Math _ x) = x
|
2010-12-19 10:13:36 -08:00
|
|
|
go LineBreak = " "
|
2010-11-27 07:08:06 -08:00
|
|
|
go _ = ""
|
2013-08-16 13:22:27 -07:00
|
|
|
deNote (Note _) = Str ""
|
|
|
|
deNote x = x
|
2010-11-27 07:08:06 -08:00
|
|
|
|
2009-11-01 02:38:18 +00:00
|
|
|
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
|
|
|
-- no other @Para@ blocks.
|
2007-11-03 23:27:58 +00:00
|
|
|
compactify :: [[Block]] -- ^ List of list items (each a list of blocks)
|
|
|
|
-> [[Block]]
|
|
|
|
compactify [] = []
|
|
|
|
compactify items =
|
2009-11-01 02:38:18 +00:00
|
|
|
case (init items, last items) of
|
|
|
|
(_,[]) -> items
|
|
|
|
(others, final) ->
|
|
|
|
case last final of
|
|
|
|
Para a -> case (filter isPara $ concat items) of
|
|
|
|
-- if this is only Para, change to Plain
|
|
|
|
[_] -> others ++ [init final ++ [Plain a]]
|
|
|
|
_ -> items
|
|
|
|
_ -> items
|
|
|
|
|
2012-09-27 17:22:17 -07:00
|
|
|
-- | Change final list item from @Para@ to @Plain@ if the list contains
|
|
|
|
-- no other @Para@ blocks. Like compactify, but operates on @Blocks@ rather
|
|
|
|
-- than @[Block]@.
|
|
|
|
compactify' :: [Blocks] -- ^ List of list items (each a list of blocks)
|
|
|
|
-> [Blocks]
|
|
|
|
compactify' [] = []
|
|
|
|
compactify' items =
|
|
|
|
let (others, final) = (init items, last items)
|
|
|
|
in case reverse (B.toList final) of
|
|
|
|
(Para a:xs) -> case [Para x | Para x <- concatMap B.toList items] of
|
|
|
|
-- if this is only Para, change to Plain
|
|
|
|
[_] -> others ++ [B.fromList (reverse $ Plain a : xs)]
|
|
|
|
_ -> items
|
|
|
|
_ -> items
|
|
|
|
|
2009-11-01 02:38:18 +00:00
|
|
|
isPara :: Block -> Bool
|
|
|
|
isPara (Para _) = True
|
|
|
|
isPara _ = False
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Data structure for defining hierarchical Pandoc documents
|
2012-07-26 22:32:53 -07:00
|
|
|
data Element = Blk Block
|
2013-02-12 20:13:23 -08:00
|
|
|
| Sec Int [Int] Attr [Inline] [Element]
|
|
|
|
-- lvl num attributes label contents
|
2009-04-25 00:29:58 +00:00
|
|
|
deriving (Eq, Read, Show, Typeable, Data)
|
|
|
|
|
2013-08-10 18:13:38 -07:00
|
|
|
instance Walkable Inline Element where
|
|
|
|
walk f (Blk x) = Blk (walk f x)
|
|
|
|
walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
|
|
|
|
walkM f (Blk x) = Blk `fmap` walkM f x
|
|
|
|
walkM f (Sec lev nums attr ils elts) = do
|
|
|
|
ils' <- walkM f ils
|
|
|
|
elts' <- walkM f elts
|
|
|
|
return $ Sec lev nums attr ils' elts'
|
|
|
|
query f (Blk x) = query f x
|
|
|
|
query f (Sec _ _ _ ils elts) = query f ils <> query f elts
|
|
|
|
|
|
|
|
instance Walkable Block Element where
|
|
|
|
walk f (Blk x) = Blk (walk f x)
|
|
|
|
walk f (Sec lev nums attr ils elts) = Sec lev nums attr (walk f ils) (walk f elts)
|
|
|
|
walkM f (Blk x) = Blk `fmap` walkM f x
|
|
|
|
walkM f (Sec lev nums attr ils elts) = do
|
|
|
|
ils' <- walkM f ils
|
|
|
|
elts' <- walkM f elts
|
|
|
|
return $ Sec lev nums attr ils' elts'
|
|
|
|
query f (Blk x) = query f x
|
|
|
|
query f (Sec _ _ _ ils elts) = query f ils <> query f elts
|
|
|
|
|
|
|
|
|
2010-03-28 22:29:31 -07:00
|
|
|
-- | Convert Pandoc inline list to plain text identifier. HTML
|
|
|
|
-- identifiers must start with a letter, and may contain only
|
2010-07-04 23:26:04 -07:00
|
|
|
-- letters, digits, and the characters _-.
|
2009-04-25 00:29:58 +00:00
|
|
|
inlineListToIdentifier :: [Inline] -> String
|
2010-03-28 22:29:31 -07:00
|
|
|
inlineListToIdentifier =
|
2010-12-19 10:13:36 -08:00
|
|
|
dropWhile (not . isAlpha) . intercalate "-" . words .
|
|
|
|
map (nbspToSp . toLower) .
|
|
|
|
filter (\c -> isLetter c || isDigit c || c `elem` "_-. ") .
|
|
|
|
stringify
|
|
|
|
where nbspToSp '\160' = ' '
|
|
|
|
nbspToSp x = x
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements
|
|
|
|
hierarchicalize :: [Block] -> [Element]
|
2012-10-29 22:45:52 -07:00
|
|
|
hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) []
|
2009-04-25 00:29:58 +00:00
|
|
|
|
2012-10-29 22:45:52 -07:00
|
|
|
hierarchicalizeWithIds :: [Block] -> S.State [Int] [Element]
|
2009-04-25 00:29:58 +00:00
|
|
|
hierarchicalizeWithIds [] = return []
|
2013-02-13 08:49:48 -08:00
|
|
|
hierarchicalizeWithIds ((Header level attr@(_,classes,_) title'):xs) = do
|
2012-10-29 22:45:52 -07:00
|
|
|
lastnum <- S.get
|
2009-12-08 02:36:16 +00:00
|
|
|
let lastnum' = take level lastnum
|
2013-02-13 08:49:48 -08:00
|
|
|
let newnum = case length lastnum' of
|
|
|
|
x | "unnumbered" `elem` classes -> []
|
|
|
|
| x >= level -> init lastnum' ++ [last lastnum' + 1]
|
|
|
|
| otherwise -> lastnum ++
|
|
|
|
replicate (level - length lastnum - 1) 0 ++ [1]
|
|
|
|
unless (null newnum) $ S.put newnum
|
2009-04-25 00:29:58 +00:00
|
|
|
let (sectionContents, rest) = break (headerLtEq level) xs
|
|
|
|
sectionContents' <- hierarchicalizeWithIds sectionContents
|
|
|
|
rest' <- hierarchicalizeWithIds rest
|
2013-02-12 20:13:23 -08:00
|
|
|
return $ Sec level newnum attr title' sectionContents' : rest'
|
2009-04-25 00:29:58 +00:00
|
|
|
hierarchicalizeWithIds (x:rest) = do
|
|
|
|
rest' <- hierarchicalizeWithIds rest
|
|
|
|
return $ (Blk x) : rest'
|
|
|
|
|
|
|
|
headerLtEq :: Int -> Block -> Bool
|
2012-10-29 22:45:52 -07:00
|
|
|
headerLtEq level (Header l _ _) = l <= level
|
2009-04-25 00:29:58 +00:00
|
|
|
headerLtEq _ _ = False
|
|
|
|
|
2010-03-16 06:45:52 +00:00
|
|
|
-- | Generate a unique identifier from a list of inlines.
|
|
|
|
-- Second argument is a list of already used identifiers.
|
2009-04-25 00:29:58 +00:00
|
|
|
uniqueIdent :: [Inline] -> [String] -> String
|
|
|
|
uniqueIdent title' usedIdents =
|
2010-03-28 22:29:31 -07:00
|
|
|
let baseIdent = case inlineListToIdentifier title' of
|
|
|
|
"" -> "section"
|
|
|
|
x -> x
|
2009-04-25 00:29:58 +00:00
|
|
|
numIdent n = baseIdent ++ "-" ++ show n
|
|
|
|
in if baseIdent `elem` usedIdents
|
|
|
|
then case find (\x -> numIdent x `notElem` usedIdents) ([1..60000] :: [Int]) of
|
|
|
|
Just x -> numIdent x
|
|
|
|
Nothing -> baseIdent -- if we have more than 60,000, allow repeats
|
|
|
|
else baseIdent
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
-- | True if block is a Header block.
|
|
|
|
isHeaderBlock :: Block -> Bool
|
2012-10-29 22:45:52 -07:00
|
|
|
isHeaderBlock (Header _ _ _) = True
|
2007-11-03 23:27:58 +00:00
|
|
|
isHeaderBlock _ = False
|
|
|
|
|
2010-07-11 20:03:55 -07:00
|
|
|
-- | Shift header levels up or down.
|
|
|
|
headerShift :: Int -> Pandoc -> Pandoc
|
2013-08-10 18:45:00 -07:00
|
|
|
headerShift n = walk shift
|
2010-07-11 20:03:55 -07:00
|
|
|
where shift :: Block -> Block
|
2012-10-29 22:45:52 -07:00
|
|
|
shift (Header level attr inner) = Header (level + n) attr inner
|
|
|
|
shift x = x
|
2010-07-11 20:03:55 -07:00
|
|
|
|
2013-01-07 20:12:05 -08:00
|
|
|
-- | Detect if a list is tight.
|
|
|
|
isTightList :: [[Block]] -> Bool
|
|
|
|
isTightList = and . map firstIsPlain
|
|
|
|
where firstIsPlain (Plain _ : _) = True
|
|
|
|
firstIsPlain _ = False
|
|
|
|
|
2013-05-10 22:53:35 -07:00
|
|
|
-- | Set a field of a 'Meta' object. If the field already has a value,
|
|
|
|
-- convert it into a list with the new value appended to the old value(s).
|
|
|
|
addMetaField :: ToMetaValue a
|
|
|
|
=> String
|
|
|
|
-> a
|
|
|
|
-> Meta
|
|
|
|
-> Meta
|
|
|
|
addMetaField key val (Meta meta) =
|
|
|
|
Meta $ M.insertWith combine key (toMetaValue val) meta
|
|
|
|
where combine newval (MetaList xs) = MetaList (xs ++ [newval])
|
|
|
|
combine newval x = MetaList [x, newval]
|
|
|
|
|
|
|
|
-- | Create 'Meta' from old-style title, authors, date. This is
|
|
|
|
-- provided to ease the transition from the old API.
|
|
|
|
makeMeta :: [Inline] -> [[Inline]] -> [Inline] -> Meta
|
|
|
|
makeMeta title authors date =
|
|
|
|
addMetaField "title" (B.fromList title)
|
|
|
|
$ addMetaField "author" (map B.fromList authors)
|
|
|
|
$ addMetaField "date" (B.fromList date)
|
|
|
|
$ nullMeta
|
|
|
|
|
2012-08-15 09:42:16 -07:00
|
|
|
--
|
|
|
|
-- TagSoup HTML handling
|
|
|
|
--
|
|
|
|
|
|
|
|
-- | Render HTML tags.
|
|
|
|
renderTags' :: [Tag String] -> String
|
|
|
|
renderTags' = renderTagsOptions
|
|
|
|
renderOptions{ optMinimize = \x ->
|
|
|
|
let y = map toLower x
|
|
|
|
in y == "hr" || y == "br" ||
|
|
|
|
y == "img" || y == "meta" ||
|
|
|
|
y == "link"
|
|
|
|
, optRawTag = \x ->
|
|
|
|
let y = map toLower x
|
|
|
|
in y == "script" || y == "style" }
|
|
|
|
|
2008-08-02 17:22:55 +00:00
|
|
|
--
|
|
|
|
-- File handling
|
|
|
|
--
|
|
|
|
|
2008-09-04 02:51:28 +00:00
|
|
|
-- | Perform an IO action in a directory, returning to starting directory.
|
|
|
|
inDirectory :: FilePath -> IO a -> IO a
|
|
|
|
inDirectory path action = do
|
|
|
|
oldDir <- getCurrentDirectory
|
|
|
|
setCurrentDirectory path
|
|
|
|
result <- action
|
|
|
|
setCurrentDirectory oldDir
|
|
|
|
return result
|
2009-12-31 01:11:23 +00:00
|
|
|
|
2013-07-04 22:40:23 -07:00
|
|
|
readDefaultDataFile :: FilePath -> IO BS.ByteString
|
2012-12-29 17:44:02 -08:00
|
|
|
readDefaultDataFile fname =
|
|
|
|
#ifdef EMBED_DATA_FILES
|
2013-04-19 23:02:38 -07:00
|
|
|
case lookup (makeCanonical fname) dataFiles of
|
2013-08-15 17:21:56 -07:00
|
|
|
Nothing -> err 97 $ "Could not find data file " ++ fname
|
2012-12-29 18:45:20 -08:00
|
|
|
Just contents -> return contents
|
2013-04-20 13:07:50 -07:00
|
|
|
where makeCanonical = joinPath . transformPathParts . splitDirectories
|
2013-04-19 23:02:38 -07:00
|
|
|
transformPathParts = reverse . foldl go []
|
|
|
|
go as "." = as
|
|
|
|
go (_:as) ".." = as
|
|
|
|
go as x = x : as
|
2012-12-29 17:44:02 -08:00
|
|
|
#else
|
2013-08-15 17:21:56 -07:00
|
|
|
getDataFileName ("data" </> fname) >>= checkExistence >>= BS.readFile
|
|
|
|
where checkExistence fn = do
|
|
|
|
exists <- doesFileExist fn
|
|
|
|
if exists
|
|
|
|
then return fn
|
|
|
|
else err 97 ("Could not find data file " ++ fname)
|
2012-12-29 17:44:02 -08:00
|
|
|
#endif
|
2010-11-19 22:13:30 -08:00
|
|
|
|
2010-01-14 05:54:38 +00:00
|
|
|
-- | Read file from specified user data directory or, if not found there, from
|
|
|
|
-- Cabal data directory.
|
2013-07-04 22:40:23 -07:00
|
|
|
readDataFile :: Maybe FilePath -> FilePath -> IO BS.ByteString
|
2012-12-29 17:44:02 -08:00
|
|
|
readDataFile Nothing fname = readDefaultDataFile fname
|
|
|
|
readDataFile (Just userDir) fname = do
|
|
|
|
exists <- doesFileExist (userDir </> fname)
|
|
|
|
if exists
|
2013-07-04 22:40:23 -07:00
|
|
|
then BS.readFile (userDir </> fname)
|
2012-12-29 17:44:02 -08:00
|
|
|
else readDefaultDataFile fname
|
|
|
|
|
|
|
|
-- | Same as 'readDataFile' but returns a String instead of a ByteString.
|
|
|
|
readDataFileUTF8 :: Maybe FilePath -> FilePath -> IO String
|
|
|
|
readDataFileUTF8 userDir fname =
|
|
|
|
UTF8.toString `fmap` readDataFile userDir fname
|
2012-01-29 23:54:00 -08:00
|
|
|
|
2013-01-11 16:19:06 -08:00
|
|
|
-- | Fetch an image or other item from the local filesystem or the net.
|
|
|
|
-- Returns raw content and maybe mime type.
|
Options: Changed `writerSourceDir` to `writerSourceURL` (now a Maybe).
Previously we used to store the directory of the first input file,
even if it was local, and used this as a base directory for
finding images in ODT, EPUB, Docx, and PDF.
This has been confusing to many users. It seems better to look for
images relative to the current working directory, even if the first
file argument is in another directory.
writerSourceURL is set to 'Just url' when the first command-line
argument is an absolute URL. (So, relative links will be resolved
in relation to the first page.) Otherwise, 'Nothing'.
The ODT, EPUB, Docx, and PDF writers have been modified accordingly.
Note that this change may break some existing workflows. If you
have been assuming that relative links will be interpreted relative
to the directory of the first file argument, you'll need to
make that the current directory before running pandoc.
Closes #942.
2013-08-11 15:58:09 -07:00
|
|
|
fetchItem :: Maybe String -> String
|
2013-07-18 20:58:14 -07:00
|
|
|
-> IO (Either E.SomeException (BS.ByteString, Maybe String))
|
Options: Changed `writerSourceDir` to `writerSourceURL` (now a Maybe).
Previously we used to store the directory of the first input file,
even if it was local, and used this as a base directory for
finding images in ODT, EPUB, Docx, and PDF.
This has been confusing to many users. It seems better to look for
images relative to the current working directory, even if the first
file argument is in another directory.
writerSourceURL is set to 'Just url' when the first command-line
argument is an absolute URL. (So, relative links will be resolved
in relation to the first page.) Otherwise, 'Nothing'.
The ODT, EPUB, Docx, and PDF writers have been modified accordingly.
Note that this change may break some existing workflows. If you
have been assuming that relative links will be interpreted relative
to the directory of the first file argument, you'll need to
make that the current directory before running pandoc.
Closes #942.
2013-08-11 15:58:09 -07:00
|
|
|
fetchItem sourceURL s
|
|
|
|
| isAbsoluteURI s = openURL s
|
|
|
|
| otherwise = case sourceURL of
|
|
|
|
Just u -> openURL (u ++ "/" ++ s)
|
|
|
|
Nothing -> E.try readLocalFile
|
|
|
|
where readLocalFile = do
|
2013-01-11 16:19:06 -08:00
|
|
|
let mime = case takeExtension s of
|
Options: Changed `writerSourceDir` to `writerSourceURL` (now a Maybe).
Previously we used to store the directory of the first input file,
even if it was local, and used this as a base directory for
finding images in ODT, EPUB, Docx, and PDF.
This has been confusing to many users. It seems better to look for
images relative to the current working directory, even if the first
file argument is in another directory.
writerSourceURL is set to 'Just url' when the first command-line
argument is an absolute URL. (So, relative links will be resolved
in relation to the first page.) Otherwise, 'Nothing'.
The ODT, EPUB, Docx, and PDF writers have been modified accordingly.
Note that this change may break some existing workflows. If you
have been assuming that relative links will be interpreted relative
to the directory of the first file argument, you'll need to
make that the current directory before running pandoc.
Closes #942.
2013-08-11 15:58:09 -07:00
|
|
|
".gz" -> getMimeType $ dropExtension s
|
|
|
|
x -> getMimeType x
|
|
|
|
cont <- BS.readFile s
|
2013-01-11 16:19:06 -08:00
|
|
|
return (cont, mime)
|
2013-01-11 11:30:31 -08:00
|
|
|
|
2013-01-11 16:19:06 -08:00
|
|
|
-- | Read from a URL and return raw data and maybe mime type.
|
2013-07-18 20:58:14 -07:00
|
|
|
openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe String))
|
2013-05-28 12:48:17 -07:00
|
|
|
openURL u
|
|
|
|
| "data:" `isPrefixOf` u =
|
|
|
|
let mime = takeWhile (/=',') $ drop 5 u
|
|
|
|
contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u
|
2013-07-18 20:58:14 -07:00
|
|
|
in return $ Right (contents, Just mime)
|
2013-07-04 22:40:23 -07:00
|
|
|
#ifdef HTTP_CONDUIT
|
2013-07-18 20:58:14 -07:00
|
|
|
| otherwise = E.try $ do
|
2013-07-04 22:40:23 -07:00
|
|
|
req <- parseUrl u
|
|
|
|
resp <- withManager $ httpLbs req
|
|
|
|
return (BS.concat $ toChunks $ responseBody resp,
|
|
|
|
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
|
|
|
|
#else
|
2013-07-18 20:58:14 -07:00
|
|
|
| otherwise = E.try $ getBodyAndMimeType `fmap` browse
|
2013-07-30 08:38:13 -07:00
|
|
|
(do S.liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..."
|
2013-05-04 21:53:06 -07:00
|
|
|
setOutHandler $ const (return ())
|
2013-05-01 10:55:06 -07:00
|
|
|
setAllowRedirects True
|
|
|
|
request (getRequest' u'))
|
2013-03-26 08:31:45 -07:00
|
|
|
where getBodyAndMimeType (_, r) = (rspBody r, findHeader HdrContentType r)
|
|
|
|
getRequest' uriString = case parseURI uriString of
|
|
|
|
Nothing -> error ("Not a valid URL: " ++
|
|
|
|
uriString)
|
|
|
|
Just v -> mkRequest GET v
|
2013-04-28 22:57:17 -07:00
|
|
|
u' = escapeURIString (/= '|') u -- pipes are rejected by Network.URI
|
2013-07-04 22:40:23 -07:00
|
|
|
#endif
|
2013-01-11 11:30:31 -08:00
|
|
|
|
2012-01-29 23:54:00 -08:00
|
|
|
--
|
|
|
|
-- Error reporting
|
|
|
|
--
|
|
|
|
|
|
|
|
err :: Int -> String -> IO a
|
|
|
|
err exitCode msg = do
|
|
|
|
name <- getProgName
|
2012-09-23 22:53:34 -07:00
|
|
|
UTF8.hPutStrLn stderr $ name ++ ": " ++ msg
|
2012-01-29 23:54:00 -08:00
|
|
|
exitWith $ ExitFailure exitCode
|
|
|
|
return undefined
|
|
|
|
|
|
|
|
warn :: String -> IO ()
|
|
|
|
warn msg = do
|
|
|
|
name <- getProgName
|
2012-09-23 22:53:34 -07:00
|
|
|
UTF8.hPutStrLn stderr $ name ++ ": " ++ msg
|
2012-08-09 07:52:39 -07:00
|
|
|
|
|
|
|
--
|
|
|
|
-- Safe read
|
|
|
|
--
|
|
|
|
|
|
|
|
safeRead :: (Monad m, Read a) => String -> m a
|
|
|
|
safeRead s = case reads s of
|
2012-08-09 20:19:06 -07:00
|
|
|
(d,x):_
|
|
|
|
| all isSpace x -> return d
|
|
|
|
_ -> fail $ "Could not read `" ++ s ++ "'"
|
2012-08-15 09:42:16 -07:00
|
|
|
|
|
|
|
|