summaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
authordr@jones.dk <dr@jones.dk>2010-03-22 12:40:10 +0100
committerdr@jones.dk <dr@jones.dk>2010-03-22 12:40:10 +0100
commit96d4f941026a8eca3ba211facdc8ce66b2ab38bb (patch)
treeaae68ec157e85fe9590d1dd5216fc6b7916e08d3 /src/Text/Pandoc/Shared.hs
parent789d0772d8b5d9c066fb8624bd51576cbde5e30b (diff)
Imported Upstream version 1.5.0.1
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs52
1 files changed, 37 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index c99fa3e9e..f093ddbee 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, DeriveDataTypeable #-}
+{-# LANGUAGE DeriveDataTypeable #-}
{-
Copyright (C) 2006-8 John MacFarlane <jgm@berkeley.edu>
@@ -97,6 +97,7 @@ module Text.Pandoc.Shared (
compactify,
Element (..),
hierarchicalize,
+ uniqueIdent,
isHeaderBlock,
-- * Writer options
HTMLMathMethod (..),
@@ -104,7 +105,8 @@ module Text.Pandoc.Shared (
WriterOptions (..),
defaultWriterOptions,
-- * File handling
- inDirectory
+ inDirectory,
+ readDataFile
) where
import Text.Pandoc.Definition
@@ -117,12 +119,18 @@ import Data.Char ( toLower, toUpper, ord, isLower, isUpper, isAlpha,
import Data.List ( find, isPrefixOf, intercalate )
import Network.URI ( parseURI, URI (..), isAllowedInURI )
import System.Directory
-import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
+import System.FilePath ( (</>) )
+-- Note: ghc >= 6.12 (base >=4.2) supports unicode through iconv
+-- So we use System.IO.UTF8 only if we have an earlier version
+#if MIN_VERSION_base(4,2,0)
+#else
+import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents )
import System.IO.UTF8
+#endif
import Data.Generics
import qualified Control.Monad.State as S
import Control.Monad (join)
-
+import Paths_pandoc (getDataFileName)
--
-- List processing
--
@@ -665,8 +673,8 @@ data ParserState = ParserState
stateTabStop :: Int, -- ^ Tab stop
stateStandalone :: Bool, -- ^ Parse bibliographic info?
stateTitle :: [Inline], -- ^ Title of document
- stateAuthors :: [String], -- ^ Authors of document
- stateDate :: String, -- ^ Date of document
+ stateAuthors :: [[Inline]], -- ^ Authors of document
+ stateDate :: [Inline], -- ^ Date of document
stateStrict :: Bool, -- ^ Use strict markdown syntax?
stateSmart :: Bool, -- ^ Use smart typography?
stateLiterateHaskell :: Bool, -- ^ Treat input as literate haskell
@@ -895,7 +903,7 @@ inlineListToIdentifier' [] = ""
inlineListToIdentifier' (x:xs) =
xAsText ++ inlineListToIdentifier' xs
where xAsText = case x of
- Str s -> filter (\c -> c `elem` "_-.~" || not (isPunctuation c)) $
+ Str s -> filter (\c -> c `elem` "_-." || not (isPunctuation c)) $
intercalate "-" $ words $ map toLower s
Emph lst -> inlineListToIdentifier' lst
Strikeout lst -> inlineListToIdentifier' lst
@@ -945,6 +953,8 @@ headerLtEq :: Int -> Block -> Bool
headerLtEq level (Header l _) = l <= level
headerLtEq _ _ = False
+-- | Generate a unique identifier from a list of inlines.
+-- Second argument is a list of already used identifiers.
uniqueIdent :: [Inline] -> [String] -> String
uniqueIdent title' usedIdents =
let baseIdent = inlineListToIdentifier title'
@@ -969,6 +979,7 @@ data HTMLMathMethod = PlainMath
| JsMath (Maybe String) -- url of jsMath load script
| GladTeX
| MimeTeX String -- url of mimetex.cgi
+ | MathML (Maybe String) -- url of MathMLinHTML.js
deriving (Show, Read, Eq)
-- | Methods for obfuscating email addresses in HTML.
@@ -980,17 +991,18 @@ data ObfuscationMethod = NoObfuscation
-- | Options for writers
data WriterOptions = WriterOptions
{ writerStandalone :: Bool -- ^ Include header and footer
- , writerHeader :: String -- ^ Header for the document
- , writerTitlePrefix :: String -- ^ Prefix for HTML titles
+ , writerTemplate :: String -- ^ Template to use in standalone mode
+ , writerVariables :: [(String, String)] -- ^ Variables to set in template
+ , writerIncludeBefore :: String -- ^ Text to include before the body
+ , writerIncludeAfter :: String -- ^ Text to include after the body
, writerTabStop :: Int -- ^ Tabstop for conversion btw spaces and tabs
, writerTableOfContents :: Bool -- ^ Include table of contents
, writerS5 :: Bool -- ^ We're writing S5
+ , writerXeTeX :: Bool -- ^ Create latex suitable for use by xetex
, writerHTMLMathMethod :: HTMLMathMethod -- ^ How to print math in HTML
, writerIgnoreNotes :: Bool -- ^ Ignore footnotes (used in making toc)
, writerIncremental :: Bool -- ^ Incremental S5 lists
, writerNumberSections :: Bool -- ^ Number sections in LaTeX
- , writerIncludeBefore :: String -- ^ String to include before the body
- , writerIncludeAfter :: String -- ^ String to include after the body
, writerStrictMarkdown :: Bool -- ^ Use strict markdown syntax
, writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
, writerWrapText :: Bool -- ^ Wrap text to line length
@@ -1003,17 +1015,18 @@ data WriterOptions = WriterOptions
defaultWriterOptions :: WriterOptions
defaultWriterOptions =
WriterOptions { writerStandalone = False
- , writerHeader = ""
- , writerTitlePrefix = ""
+ , writerTemplate = ""
+ , writerVariables = []
+ , writerIncludeBefore = ""
+ , writerIncludeAfter = ""
, writerTabStop = 4
, writerTableOfContents = False
, writerS5 = False
+ , writerXeTeX = False
, writerHTMLMathMethod = PlainMath
, writerIgnoreNotes = False
, writerIncremental = False
, writerNumberSections = False
- , writerIncludeBefore = ""
- , writerIncludeAfter = ""
, writerStrictMarkdown = False
, writerReferenceLinks = False
, writerWrapText = True
@@ -1034,3 +1047,12 @@ inDirectory path action = do
result <- action
setCurrentDirectory oldDir
return result
+
+-- | Read file from specified user data directory or, if not found there, from
+-- Cabal data directory.
+readDataFile :: Maybe FilePath -> FilePath -> IO String
+readDataFile userDir fname =
+ case userDir of
+ Nothing -> getDataFileName fname >>= readFile
+ Just u -> catch (readFile $ u </> fname)
+ (\_ -> getDataFileName fname >>= readFile)