aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Main.hs70
-rw-r--r--Text/Pandoc/Writers/HTML.hs17
-rw-r--r--Text/Pandoc/Writers/RTF.hs24
-rw-r--r--pandoc.cabal2
4 files changed, 59 insertions, 54 deletions
diff --git a/Main.hs b/Main.hs
index a48a82577..e25b0b1ad 100644
--- a/Main.hs
+++ b/Main.hs
@@ -32,9 +32,9 @@ module Main where
import Text.Pandoc
import Text.Pandoc.UTF8
import Text.Pandoc.Shared ( joinWithSep, HTMLMathMethod (..) )
-import Text.Regex ( mkRegex, matchRegex )
import System.Environment ( getArgs, getProgName, getEnvironment )
import System.Exit ( exitWith, ExitCode (..) )
+import System.FilePath ( takeExtension )
import System.Console.GetOpt
import System.IO
import Data.Maybe ( fromMaybe )
@@ -338,48 +338,44 @@ usageMessage programName options = usageInfo
options
-- Determine default reader based on source file extensions
-defaultReaderName :: [String] -> String
+defaultReaderName :: [FilePath] -> String
defaultReaderName [] = "markdown"
defaultReaderName (x:xs) =
- let x' = map toLower x in
- case (matchRegex (mkRegex ".*\\.(.*)") x') of
- Nothing -> defaultReaderName xs -- no extension
- Just ["xhtml"] -> "html"
- Just ["html"] -> "html"
- Just ["htm"] -> "html"
- Just ["tex"] -> "latex"
- Just ["latex"] -> "latex"
- Just ["ltx"] -> "latex"
- Just ["rst"] -> "rst"
- Just ["native"] -> "native"
- Just _ -> "markdown"
+ case takeExtension (map toLower x) of
+ ".xhtml" -> "html"
+ ".html" -> "html"
+ ".htm" -> "html"
+ ".tex" -> "latex"
+ ".latex" -> "latex"
+ ".ltx" -> "latex"
+ ".rst" -> "rst"
+ ".native" -> "native"
+ _ -> defaultReaderName xs
-- Determine default writer based on output file extension
-defaultWriterName :: String -> String
+defaultWriterName :: FilePath -> String
defaultWriterName "-" = "html" -- no output file
defaultWriterName x =
- let x' = map toLower x in
- case (matchRegex (mkRegex ".*\\.(.*)") x') of
- Nothing -> "markdown" -- no extension
- Just [""] -> "markdown" -- empty extension
- Just ["tex"] -> "latex"
- Just ["latex"] -> "latex"
- Just ["ltx"] -> "latex"
- Just ["context"] -> "context"
- Just ["ctx"] -> "context"
- Just ["rtf"] -> "rtf"
- Just ["rst"] -> "rst"
- Just ["s5"] -> "s5"
- Just ["native"] -> "native"
- Just ["txt"] -> "markdown"
- Just ["text"] -> "markdown"
- Just ["md"] -> "markdown"
- Just ["markdown"] -> "markdown"
- Just ["db"] -> "docbook"
- Just ["xml"] -> "docbook"
- Just ["sgml"] -> "docbook"
- Just [[x]] | x `elem` ['1'..'9'] -> "man"
- Just _ -> "html"
+ case takeExtension (map toLower x) of
+ "" -> "markdown" -- empty extension
+ "tex" -> "latex"
+ "latex" -> "latex"
+ "ltx" -> "latex"
+ "context" -> "context"
+ "ctx" -> "context"
+ "rtf" -> "rtf"
+ "rst" -> "rst"
+ "s5" -> "s5"
+ "native" -> "native"
+ "txt" -> "markdown"
+ "text" -> "markdown"
+ "md" -> "markdown"
+ "markdown" -> "markdown"
+ "db" -> "docbook"
+ "xml" -> "docbook"
+ "sgml" -> "docbook"
+ [x] | x `elem` ['1'..'9'] -> "man"
+ _ -> "html"
main = do
diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs
index acb9f32bb..7837493a1 100644
--- a/Text/Pandoc/Writers/HTML.hs
+++ b/Text/Pandoc/Writers/HTML.hs
@@ -33,7 +33,6 @@ import Text.Pandoc.ASCIIMathML
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
-import Text.Regex ( mkRegex, matchRegex )
import Numeric ( showHex )
import Data.Char ( ord, toLower, isAlpha )
import Data.List ( isPrefixOf, intersperse, find )
@@ -162,13 +161,21 @@ footnoteSection opts notes =
then noHtml
else thediv ! [theclass "footnotes"] $ hr +++ (olist << notes)
+
+-- | Parse a mailto link; return Just (name, domain) or Nothing.
+parseMailto :: String -> Maybe (String, String)
+parseMailto ('m':'a':'i':'l':'t':'o':':':address) =
+ let (name, rest) = span (/='@') address
+ domain = drop 1 rest
+ in Just (name, domain)
+parseMailto _ = Nothing
+
-- | Obfuscate a "mailto:" link using Javascript.
obfuscateLink :: WriterOptions -> String -> String -> Html
obfuscateLink opts text src =
- let emailRegex = mkRegex "^mailto:([^@]*)@(.*)$"
- src' = map toLower src
- in case (matchRegex emailRegex src') of
- (Just [name, domain]) ->
+ let src' = map toLower src
+ in case parseMailto src' of
+ (Just (name, domain)) ->
let domain' = substitute "." " dot " domain
at' = obfuscateChar '@'
(linkText, altText) =
diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs
index 00cc8c6cd..c95c24b2f 100644
--- a/Text/Pandoc/Writers/RTF.hs
+++ b/Text/Pandoc/Writers/RTF.hs
@@ -31,9 +31,8 @@ module Text.Pandoc.Writers.RTF ( writeRTF ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
-import Text.Regex ( matchRegexAll, mkRegex )
import Data.List ( isSuffixOf )
-import Data.Char ( ord )
+import Data.Char ( ord, isDigit )
-- | Convert Pandoc to a string in rich text format.
writeRTF :: WriterOptions -> Pandoc -> String
@@ -230,15 +229,18 @@ listItemToRTF alignment indent marker [] =
rtfCompact (indent + listIncrement) (0 - listIncrement) alignment
(marker ++ "\\tx" ++ (show listIncrement) ++ "\\tab ")
listItemToRTF alignment indent marker list =
- let (first:rest) = map (blockToRTF (indent + listIncrement) alignment) list in
- -- insert the list marker into the (processed) first block
- let modFirst = case matchRegexAll (mkRegex "\\\\fi-?[0-9]+") first of
- Just (before, matched, after, _) ->
- before ++ "\\fi" ++ show (0 - listIncrement) ++
- " " ++ marker ++ "\\tx" ++
- show listIncrement ++ "\\tab" ++ after
- Nothing -> first in
- modFirst ++ concat rest
+ let (first:rest) = map (blockToRTF (indent + listIncrement) alignment) list
+ listMarker = "\\fi" ++ show (0 - listIncrement) ++ " " ++ marker ++ "\\tx" ++
+ show listIncrement ++ "\\tab"
+ insertListMarker ('\\':'f':'i':'-':d:xs) | isDigit d =
+ listMarker ++ dropWhile isDigit xs
+ insertListMarker ('\\':'f':'i':d:xs) | isDigit d =
+ listMarker ++ dropWhile isDigit xs
+ insertListMarker (x:xs) =
+ x : insertListMarker xs
+ insertListmarker [] = []
+ -- insert the list marker into the (processed) first block
+ in insertListMarker first ++ concat rest
-- | Convert definition list item (label, list of blocks) to RTF.
definitionListItemToRTF :: Alignment -- ^ alignment
diff --git a/pandoc.cabal b/pandoc.cabal
index bdd6c7d8e..a5c76ee51 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -41,7 +41,7 @@ Library
Build-Depends: base >= 3, pretty, containers
else
Build-Depends: base < 3
- Build-Depends: parsec, xhtml, mtl, regex-compat, network, highlighting-kate
+ Build-Depends: parsec, xhtml, mtl, network, filepath, highlighting-kate
Hs-Source-Dirs: .
Exposed-Modules: Text.Pandoc,
Text.Pandoc.Blocks,