+ Added a 'substitute' function to Shared.hs. This is a generic

list function that can be used to substitute one substring
  for another in a string, like 'gsub' except without regular
  expressions.
+ Use 'substitute' instead of 'gsub' in the LaTeX writer.  This
  avoids what appears to be a bug in Text.Regex, whereby "\\^"
  matches "\350".  There seems to be a slight speed improvement
  as well.  (Note:  If this works, it would be good to replace
  other uses of gsub that don't employ regexs with 'substitute'.) 


git-svn-id: https://pandoc.googlecode.com/svn/trunk@500 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2007-01-22 21:28:46 +00:00
parent a7839a18a7
commit 8f0750574a
2 changed files with 18 additions and 8 deletions

View file

@ -31,6 +31,7 @@ module Text.Pandoc.Shared (
-- * List processing
splitBy,
splitByIndices,
substitute,
-- * Text processing
gsub,
joinWithSep,
@ -79,8 +80,8 @@ import Text.Pandoc.Entities ( decodeEntities, encodeEntities, characterEntity )
import Text.Regex ( matchRegexAll, mkRegex, subRegex, Regex )
import Text.PrettyPrint.HughesPJ as PP ( text, char, (<>), ($$), nest, Doc,
isEmpty )
import Char ( toLower )
import List ( find, groupBy )
import Data.Char ( toLower )
import Data.List ( find, groupBy, isPrefixOf )
-- | Parse a string with a given parser and state.
readWith :: GenParser Char ParserState a -- ^ parser
@ -288,6 +289,15 @@ removeTrailingSpace = reverse . removeLeadingSpace . reverse
stripFirstAndLast str =
drop 1 $ take ((length str) - 1) str
-- | Replace each occurrence of one sublist in a list with another.
substitute :: (Eq a) => [a] -> [a] -> [a] -> [a]
substitute _ _ [] = []
substitute [] _ lst = lst
substitute target replacement lst =
if isPrefixOf target lst
then replacement ++ (substitute target replacement $ drop (length target) lst)
else (head lst):(substitute target replacement $ tail lst)
-- | Split list into groups separated by sep.
splitBy :: (Eq a) => a -> [a] -> [[a]]
splitBy _ [] = []

View file

@ -78,12 +78,12 @@ latexHeader notes options (Meta title authors date) =
escapeBrackets = backslashEscape "{}"
escapeSpecial = backslashEscape "$%&~_#"
escapeBackslash = gsub "\\\\" "\\\\textbackslash{}"
fixBackslash = gsub "\\\\textbackslash\\\\\\{\\\\\\}" "\\\\textbackslash{}"
escapeHat = gsub "\\^" "\\\\^{}"
escapeBar = gsub "\\|" "\\\\textbar{}"
escapeLt = gsub "<" "\\\\textless{}"
escapeGt = gsub ">" "\\\\textgreater{}"
escapeBackslash = substitute "\\" "\\textbackslash{}"
fixBackslash = substitute "\\textbackslash\\{\\}" "\\textbackslash{}"
escapeHat = substitute "^" "\\^{}"
escapeBar = substitute "|" "\\textbar{}"
escapeLt = substitute "<" "\\textless{}"
escapeGt = substitute ">" "\\textgreater{}"
-- | Escape string for LaTeX
stringToLaTeX :: String -> String