diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Biblio.hs | 192 | ||||
-rw-r--r-- | src/Text/Pandoc/Definition.hs | 151 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/HTML.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 129 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 27 | ||||
-rw-r--r-- | src/pandoc.hs | 77 |
7 files changed, 320 insertions, 261 deletions
diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs index 436eadd68..0241b2d6d 100644 --- a/src/Text/Pandoc/Biblio.hs +++ b/src/Text/Pandoc/Biblio.hs @@ -22,45 +22,195 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Copyright : Copyright (C) 2008 Andrea Rossato License : GNU GPL, version 2 or above - Maintainer : Andrea Rossato <andrea.rossato@ing.unitn.it> + Maintainer : Andrea Rossato <andrea.rossato@unitn.it> Stability : alpha Portability : portable -} module Text.Pandoc.Biblio ( processBiblio ) where -import Control.Monad ( when ) import Data.List -import Text.CSL +import Data.Unique +import Data.Char ( isDigit ) +import qualified Data.Map as M +import Text.CSL hiding ( Cite(..), Citation(..) ) +import qualified Text.CSL as CSL ( Cite(..) ) import Text.Pandoc.Definition +import Text.Pandoc.Shared (stringify) +import Text.ParserCombinators.Parsec +import Control.Monad -- | Process a 'Pandoc' document by adding citations formatted -- according to a CSL style, using 'citeproc' from citeproc-hs. -processBiblio :: String -> [Reference] -> Pandoc -> IO Pandoc -processBiblio cf r p +processBiblio :: FilePath -> [Reference] -> Pandoc -> IO Pandoc +processBiblio cslfile r p = if null r then return p else do - when (null cf) $ error "Missing the needed citation style file" - csl <- readCSLFile cf - let groups = queryWith getCite p - result = citeproc csl r groups - cits_map = zip groups (citations result) - biblioList = map (read . renderPandoc' csl) (bibliography result) - Pandoc m b = processWith (processCite csl cits_map) p - return $ Pandoc m $ b ++ biblioList + csl <- readCSLFile cslfile + p' <- processWithM setHash p + let (nts,grps) = if styleClass csl == "note" + then let cits = queryWith getCite p' + ncits = map (queryWith getCite) $ queryWith getNote p' + needNt = cits \\ concat ncits + in (,) needNt $ getNoteCitations needNt p' + else (,) [] $ queryWith getCitation p' + result = citeproc procOpts csl r (setNearNote csl $ + map (map toCslCite) grps) + cits_map = M.fromList $ zip grps (citations result) + biblioList = map (renderPandoc' csl) (bibliography result) + Pandoc m b = processWith (procInlines $ processCite csl cits_map) p' + return . generateNotes nts . Pandoc m $ b ++ biblioList -- | Substitute 'Cite' elements with formatted citations. -processCite :: Style -> [([Target],[FormattedOutput])] -> Inline -> Inline -processCite s cs il - | Cite t _ <- il = Cite t (process t) - | otherwise = il +processCite :: Style -> M.Map [Citation] [FormattedOutput] -> [Inline] -> [Inline] +processCite _ _ [] = [] +processCite s cs (i:is) + | Cite t _ <- i = process t ++ processCite s cs is + | otherwise = i : processCite s cs is where - process t = case elemIndex t (map fst cs) of - Just i -> read . renderPandoc s $ snd (cs !! i) + addNt t x = if null x then [] else [Cite t $ renderPandoc s x] + process t = case M.lookup t cs of + Just x -> if isTextualCitation t && x /= [] + then renderPandoc s [head x] ++ + if tail x /= [] + then Space : addNt t (tail x) + else [] + else [Cite t $ renderPandoc s x] Nothing -> [Str ("Error processing " ++ show t)] +isTextualCitation :: [Citation] -> Bool +isTextualCitation (c:_) = citationMode c == AuthorInText +isTextualCitation _ = False + -- | Retrieve all citations from a 'Pandoc' docuument. To be used with -- 'queryWith'. -getCite :: Inline -> [[(String,String)]] -getCite i | Cite t _ <- i = [t] +getCitation :: Inline -> [[Citation]] +getCitation i | Cite t _ <- i = [t] + | otherwise = [] + +getNote :: Inline -> [Inline] +getNote i | Note _ <- i = [i] + | otherwise = [] + +getCite :: Inline -> [Inline] +getCite i | Cite _ _ <- i = [i] | otherwise = [] + +getNoteCitations :: [Inline] -> Pandoc -> [[Citation]] +getNoteCitations needNote + = let mvCite i = if i `elem` needNote then Note [Para [i]] else i + setNote = processWith mvCite + getCits = concat . flip (zipWith $ setCiteNoteNum) [1..] . + map (queryWith getCite) . queryWith getNote . setNote + in queryWith getCitation . getCits + +setHash :: Citation -> IO Citation +setHash (Citation i p s cm nn _) + = hashUnique `fmap` newUnique >>= return . Citation i p s cm nn + +generateNotes :: [Inline] -> Pandoc -> Pandoc +generateNotes needNote = processWith (mvCiteInNote needNote) + +procInlines :: ([Inline] -> [Inline]) -> Block -> Block +procInlines f b + | Plain inls <- b = Plain $ f inls + | Para inls <- b = Para $ f inls + | Header i inls <- b = Header i $ f inls + | otherwise = b + +mvCiteInNote :: [Inline] -> Block -> Block +mvCiteInNote is = procInlines mvCite + where + mvCite :: [Inline] -> [Inline] + mvCite inls + | x:i:xs <- inls, startWithPunct xs + , x == Space, i `elem_` is = switch i xs ++ mvCite (tailFirstInlineStr xs) + | x:i:xs <- inls + , x == Space, i `elem_` is = mvInNote i : mvCite xs + | i:xs <- inls, i `elem_` is + , startWithPunct xs = switch i xs ++ mvCite (tailFirstInlineStr xs) + | i:xs <- inls, Note _ <- i = checkNt i : mvCite xs + | i:xs <- inls = i : mvCite xs + | otherwise = [] + elem_ x xs = case x of Cite cs _ -> (Cite cs []) `elem` xs; _ -> False + switch i xs = Str (headInline xs) : mvInNote i : [] + mvInNote i + | Cite t o <- i = Note [Para [Cite t $ sanitize o]] + | otherwise = Note [Para [i ]] + sanitize i + | endWithPunct i = toCapital i + | otherwise = toCapital (i ++ [Str "."]) + + checkPt i + | Cite c o : xs <- i + , endWithPunct o, startWithPunct xs + , endWithPunct o = Cite c (initInline o) : checkPt xs + | x:xs <- i = x : checkPt xs + | otherwise = [] + checkNt = processWith $ procInlines checkPt + +setCiteNoteNum :: [Inline] -> Int -> [Inline] +setCiteNoteNum ((Cite cs o):xs) n = Cite (setCitationNoteNum n cs) o : setCiteNoteNum xs n +setCiteNoteNum _ _ = [] + +setCitationNoteNum :: Int -> [Citation] -> [Citation] +setCitationNoteNum i = map $ \c -> c { citationNoteNum = i} + +toCslCite :: Citation -> CSL.Cite +toCslCite c + = let (l, s) = locatorWords $ citationSuffix c + (la,lo) = parseLocator l + citMode = case citationMode c of + AuthorInText -> (True, False) + SuppressAuthor -> (False,True ) + NormalCitation -> (False,False) + in emptyCite { CSL.citeId = citationId c + , CSL.citePrefix = PandocText $ citationPrefix c + , CSL.citeSuffix = PandocText $ s + , CSL.citeLabel = la + , CSL.citeLocator = lo + , CSL.citeNoteNumber = show $ citationNoteNum c + , CSL.authorInText = fst citMode + , CSL.suppressAuthor = snd citMode + , CSL.citeHash = citationHash c + } + +locatorWords :: [Inline] -> (String, [Inline]) +locatorWords inp = + case parse pLocatorWords "suffix" inp of + Right r -> r + Left _ -> ("",inp) + +pLocatorWords :: GenParser Inline st (String, [Inline]) +pLocatorWords = do + l <- pLocator + s <- getInput -- rest is suffix + if length l > 0 && last l == ',' + then return (init l, Str "," : s) + else return (l, s) + +pMatch :: (Inline -> Bool) -> GenParser Inline st Inline +pMatch condition = try $ do + t <- anyToken + guard $ condition t + return t + +pSpace :: GenParser Inline st Inline +pSpace = pMatch (== Space) + +pLocator :: GenParser Inline st String +pLocator = try $ do + optional $ pMatch (== Str ",") + optional pSpace + f <- many1 (notFollowedBy pSpace >> anyToken) + gs <- many1 pWordWithDigits + return $ stringify f ++ (' ' : unwords gs) + +pWordWithDigits :: GenParser Inline st String +pWordWithDigits = try $ do + pSpace + r <- many1 (notFollowedBy pSpace >> anyToken) + let s = stringify r + guard $ any isDigit s + return s + diff --git a/src/Text/Pandoc/Definition.hs b/src/Text/Pandoc/Definition.hs deleted file mode 100644 index fffca3b2e..000000000 --- a/src/Text/Pandoc/Definition.hs +++ /dev/null @@ -1,151 +0,0 @@ -{-# OPTIONS_GHC -fglasgow-exts #-} -- for deriving Typeable -{- -Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu> - -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.Definition - Copyright : Copyright (C) 2006-2010 John MacFarlane - License : GNU GPL, version 2 or above - - Maintainer : John MacFarlane <jgm@berkeley.edu> - Stability : alpha - Portability : portable - -Definition of 'Pandoc' data structure for format-neutral representation -of documents. --} -module Text.Pandoc.Definition where - -import Data.Generics - -data Pandoc = Pandoc Meta [Block] deriving (Eq, Ord, Read, Show, Typeable, Data) - --- | Bibliographic information for the document: title, authors, date. -data Meta = Meta { docTitle :: [Inline] - , docAuthors :: [[Inline]] - , docDate :: [Inline] } - deriving (Eq, Ord, Show, Read, Typeable, Data) - --- | Alignment of a table column. -data Alignment = AlignLeft - | AlignRight - | AlignCenter - | AlignDefault deriving (Eq, Ord, Show, Read, Typeable, Data) - --- | List attributes. -type ListAttributes = (Int, ListNumberStyle, ListNumberDelim) - --- | Style of list numbers. -data ListNumberStyle = DefaultStyle - | Example - | Decimal - | LowerRoman - | UpperRoman - | LowerAlpha - | UpperAlpha deriving (Eq, Ord, Show, Read, Typeable, Data) - --- | Delimiter of list numbers. -data ListNumberDelim = DefaultDelim - | Period - | OneParen - | TwoParens deriving (Eq, Ord, Show, Read, Typeable, Data) - --- | Attributes: identifier, classes, key-value pairs -type Attr = (String, [String], [(String, String)]) - --- | Block element. -data Block - = Plain [Inline] -- ^ Plain text, not a paragraph - | Para [Inline] -- ^ Paragraph - | CodeBlock Attr String -- ^ Code block (literal) with attributes - | RawHtml String -- ^ Raw HTML block (literal) - | BlockQuote [Block] -- ^ Block quote (list of blocks) - | OrderedList ListAttributes [[Block]] -- ^ Ordered list (attributes - -- and a list of items, each a list of blocks) - | BulletList [[Block]] -- ^ Bullet list (list of items, each - -- a list of blocks) - | DefinitionList [([Inline],[[Block]])] -- ^ Definition list - -- Each list item is a pair consisting of a - -- term (a list of inlines) and one or more - -- definitions (each a list of blocks) - | Header Int [Inline] -- ^ Header - level (integer) and text (inlines) - | HorizontalRule -- ^ Horizontal rule - | Table [Inline] [Alignment] [Double] [[Block]] [[[Block]]] -- ^ Table, - -- with caption, column alignments, - -- relative column widths (0 = default), - -- column headers (each a list of blocks), and - -- rows (each a list of lists of blocks) - | Null -- ^ Nothing - deriving (Eq, Ord, Read, Show, Typeable, Data) - --- | Type of quotation marks to use in Quoted inline. -data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Ord, Read, Typeable, Data) - --- | Link target (URL, title). -type Target = (String, String) - --- | Type of math element (display or inline). -data MathType = DisplayMath | InlineMath deriving (Show, Eq, Ord, Read, Typeable, Data) - --- | Inline elements. -data Inline - = Str String -- ^ Text (string) - | Emph [Inline] -- ^ Emphasized text (list of inlines) - | Strong [Inline] -- ^ Strongly emphasized text (list of inlines) - | Strikeout [Inline] -- ^ Strikeout text (list of inlines) - | Superscript [Inline] -- ^ Superscripted text (list of inlines) - | Subscript [Inline] -- ^ Subscripted text (list of inlines) - | SmallCaps [Inline] -- ^ Small caps text (list of inlines) - | Quoted QuoteType [Inline] -- ^ Quoted text (list of inlines) - | Cite [Target] [Inline] -- ^ Citation (list of inlines) - | Code String -- ^ Inline code (literal) - | Space -- ^ Inter-word space - | EmDash -- ^ Em dash - | EnDash -- ^ En dash - | Apostrophe -- ^ Apostrophe - | Ellipses -- ^ Ellipses - | LineBreak -- ^ Hard line break - | Math MathType String -- ^ TeX math (literal) - | TeX String -- ^ LaTeX code (literal) - | HtmlInline String -- ^ HTML code (literal) - | Link [Inline] Target -- ^ Hyperlink: text (list of inlines), target - | Image [Inline] Target -- ^ Image: alt text (list of inlines), target - -- and target - | Note [Block] -- ^ Footnote or endnote - deriving (Show, Eq, Ord, Read, Typeable, Data) - --- | Applies a transformation on @a@s to matching elements in a @b@. -processWith :: (Data a, Data b) => (a -> a) -> b -> b -processWith f = everywhere (mkT f) - --- | Like 'processWith', but with monadic transformations. -processWithM :: (Monad m, Data a, Data b) => (a -> m a) -> b -> m b -processWithM f = everywhereM (mkM f) - --- | Runs a query on matching @a@ elements in a @c@. -queryWith :: (Data a, Data c) => (a -> [b]) -> c -> [b] -queryWith f = everything (++) ([] `mkQ` f) - -{-# DEPRECATED processPandoc "Use processWith instead" #-} -processPandoc :: Data a => (a -> a) -> Pandoc -> Pandoc -processPandoc = processWith - -{-# DEPRECATED queryPandoc "Use queryWith instead" #-} -queryPandoc :: Data a => (a -> [b]) -> Pandoc -> [b] -queryPandoc = queryWith - diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index dce99fd75..47e97c7cc 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -586,9 +586,7 @@ data ParserState = ParserState stateQuoteContext :: QuoteContext, -- ^ Inside quoted environment? stateSanitizeHTML :: Bool, -- ^ Sanitize HTML? stateKeys :: KeyTable, -- ^ List of reference keys -#ifdef _CITEPROC stateCitations :: [String], -- ^ List of available citations -#endif stateNotes :: NoteTable, -- ^ List of notes stateTabStop :: Int, -- ^ Tab stop stateStandalone :: Bool, -- ^ Parse bibliographic info? @@ -616,9 +614,7 @@ defaultParserState = stateQuoteContext = NoQuote, stateSanitizeHTML = False, stateKeys = M.empty, -#ifdef _CITEPROC stateCitations = [], -#endif stateNotes = [], stateTabStop = 4, stateStandalone = False, diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 5ccbc4fb1..462267d89 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -35,6 +35,7 @@ module Text.Pandoc.Readers.HTML ( anyHtmlInlineTag, anyHtmlTag, anyHtmlEndTag, + htmlTag, htmlEndTag, extractTagType, htmlBlockElement, diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 9fe5c9f06..b664476b4 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -34,7 +34,7 @@ module Text.Pandoc.Readers.Markdown ( import Data.List ( transpose, isSuffixOf, sortBy, findIndex, intercalate ) import qualified Data.Map as M import Data.Ord ( comparing ) -import Data.Char ( isAlphaNum ) +import Data.Char ( isAlphaNum, isPunctuation ) import Data.Maybe import Text.Pandoc.Definition import Text.Pandoc.Shared @@ -376,6 +376,7 @@ attributes = try $ do attribute :: GenParser Char st ([Char], [[Char]], [([Char], [Char])]) attribute = identifierAttr <|> classAttr <|> keyValAttr + identifier :: GenParser Char st [Char] identifier = do first <- letter @@ -915,9 +916,7 @@ inlineParsers = [ str , note , inlineNote , link -#ifdef _CITEPROC - , inlineCitation -#endif + , cite , image , math , strikeout @@ -1308,38 +1307,94 @@ rawHtmlInline' = do else choice [htmlComment, anyHtmlInlineTag] return $ HtmlInline result -#ifdef _CITEPROC -inlineCitation :: GenParser Char ParserState Inline -inlineCitation = try $ do +-- Citations + +cite :: GenParser Char ParserState Inline +cite = do failIfStrict - cit <- citeMarker - let citations = readWith parseCitation defaultParserState cit - mr <- mapM chkCit citations - if catMaybes mr /= [] - then return $ Cite citations [] - else fail "no citation found" - -chkCit :: Target -> GenParser Char ParserState (Maybe Target) -chkCit t = do + citations <- textualCite <|> normalCite + return $ Cite citations [] + +spnl :: GenParser Char st () +spnl = try $ do + skipSpaces + optional newline + skipSpaces + notFollowedBy (char '\n') + +textualCite :: GenParser Char ParserState [Citation] +textualCite = try $ do + (_, key) <- citeKey + let first = Citation{ citationId = key + , citationPrefix = [] + , citationSuffix = [] + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + rest <- option [] $ try $ spnl >> normalCite + if null rest + then option [first] $ bareloc first + else return $ first : rest + +bareloc :: Citation -> GenParser Char ParserState [Citation] +bareloc c = try $ do + spnl + char '[' + suff <- suffix + rest <- option [] $ try $ char ';' >> citeList + spnl + char ']' + return $ c{ citationSuffix = suff } : rest + +normalCite :: GenParser Char ParserState [Citation] +normalCite = try $ do + char '[' + spnl + citations <- citeList + spnl + char ']' + return citations + +citeKey :: GenParser Char ParserState (Bool, String) +citeKey = try $ do + suppress_author <- option False (char '-' >> return True) + char '@' + first <- letter + rest <- many $ (noneOf ",;]@ \t\n") + let key = first:rest st <- getState - case lookupKeySrc (stateKeys st) (Key [Str $ fst t]) of - Just _ -> fail "This is a link" - Nothing -> if elem (fst t) $ stateCitations st - then return $ Just t - else return $ Nothing - -citeMarker :: GenParser Char ParserState String -citeMarker = char '[' >> manyTill ( noneOf "\n" <|> (newline >>~ notFollowedBy blankline) ) (char ']') - -parseCitation :: GenParser Char ParserState [(String,String)] -parseCitation = try $ sepBy (parseLabel) (oneOf ";") - -parseLabel :: GenParser Char ParserState (String,String) -parseLabel = try $ do - res <- sepBy (skipSpaces >> optional newline >> skipSpaces >> many1 (noneOf "@;")) (oneOf "@") - case res of - [lab,loc] -> return (lab, loc) - [lab] -> return (lab, "" ) - _ -> return ("" , "" ) - -#endif + guard $ key `elem` stateCitations st + return (suppress_author, key) + +suffix :: GenParser Char ParserState [Inline] +suffix = try $ do + spnl + res <- many $ notFollowedBy (oneOf ";]") >> inline + return $ case res of + [] -> [] + (Str (y:_) : _) | isPunctuation y + -> res + _ -> Str "," : Space : res + +prefix :: GenParser Char ParserState [Inline] +prefix = liftM normalizeSpaces $ + manyTill inline (char ']' <|> liftM (const ']') (lookAhead citeKey)) + +citeList :: GenParser Char ParserState [Citation] +citeList = sepBy1 citation (try $ char ';' >> spnl) + +citation :: GenParser Char ParserState Citation +citation = try $ do + pref <- prefix + (suppress_author, key) <- citeKey + suff <- suffix + return $ Citation{ citationId = key + , citationPrefix = pref + , citationSuffix = suff + , citationMode = if suppress_author + then SuppressAuthor + else NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 0fdaf42f3..f2f38519b 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -57,6 +57,7 @@ module Text.Pandoc.Shared ( -- * Pandoc block and inline list processing orderedListMarkers, normalizeSpaces, + stringify, compactify, Element (..), hierarchicalize, @@ -71,6 +72,7 @@ module Text.Pandoc.Shared ( defaultWriterOptions, -- * File handling inDirectory, + findDataFile, readDataFile ) where @@ -339,6 +341,15 @@ normalizeSpaces list = else lst in removeLeading $ removeTrailing $ removeDoubles list +-- | Convert list of inlines to a string with formatting removed. +stringify :: [Inline] -> String +stringify = queryWith go + where go :: Inline -> [Char] + go Space = " " + go (Str x) = x + go (Code x) = x + go _ = "" + -- | Change final list item from @Para@ to @Plain@ if the list contains -- no other @Para@ blocks. compactify :: [[Block]] -- ^ List of list items (each a list of blocks) @@ -538,11 +549,17 @@ inDirectory path action = do setCurrentDirectory oldDir return result +-- | Get file path for data file, either from specified user data directory, +-- or, if not found there, from Cabal data directory. +findDataFile :: Maybe FilePath -> FilePath -> IO FilePath +findDataFile Nothing f = getDataFileName f +findDataFile (Just u) f = do + ex <- doesFileExist (u </> f) + if ex + then return (u </> f) + else getDataFileName f + -- | 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 >>= UTF8.readFile - Just u -> catch (UTF8.readFile $ u </> fname) - (\_ -> getDataFileName fname >>= UTF8.readFile) +readDataFile userDir fname = findDataFile userDir fname >>= UTF8.readFile diff --git a/src/pandoc.hs b/src/pandoc.hs index 4f5a1c32a..f73391b6b 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -32,7 +32,7 @@ module Main where import Text.Pandoc import Text.Pandoc.S5 (s5HeaderIncludes) import Text.Pandoc.Shared ( tabFilter, ObfuscationMethod (..), readDataFile, - headerShift ) + headerShift, findDataFile ) #ifdef _HIGHLIGHTING import Text.Pandoc.Highlighting ( languages ) #endif @@ -42,13 +42,11 @@ import System.FilePath import System.Console.GetOpt import Data.Char ( toLower, isDigit ) import Data.List ( intercalate, isSuffixOf ) -import System.Directory ( getAppUserDataDirectory ) +import System.Directory ( getAppUserDataDirectory, doesFileExist ) import System.IO ( stdout, stderr ) import qualified Text.Pandoc.UTF8 as UTF8 -#ifdef _CITEPROC import Text.CSL import Text.Pandoc.Biblio -#endif import Control.Monad (when, unless, liftM) import Network.HTTP (simpleHTTP, mkRequest, getResponseBody, RequestMethod(..)) import Network.URI (parseURI, isURI, URI(..)) @@ -64,9 +62,7 @@ copyrightMessage = "\nCopyright (C) 2006-2010 John MacFarlane\n" ++ compileInfo :: String compileInfo = -#ifdef _CITEPROC "\nCompiled with citeproc support." ++ -#endif #ifdef _HIGHLIGHTING "\nCompiled with syntax highlighting support for:\n" ++ wrapWords 78 languages ++ @@ -163,11 +159,8 @@ data Opt = Opt , optIdentifierPrefix :: String , optIndentedCodeClasses :: [String] -- ^ Default classes for indented code blocks , optDataDir :: Maybe FilePath -#ifdef _CITEPROC - , optBiblioFile :: String - , optBiblioFormat :: String - , optCslFile :: String -#endif + , optBibliography :: [Reference] + , optCslFile :: FilePath } -- | Defaults for command-line options. @@ -205,11 +198,8 @@ defaultOpts = Opt , optIdentifierPrefix = "" , optIndentedCodeClasses = [] , optDataDir = Nothing -#ifdef _CITEPROC - , optBiblioFile = [] - , optBiblioFormat = [] - , optCslFile = [] -#endif + , optBibliography = [] + , optCslFile = "" } -- | A list of functions, each transforming the options data structure @@ -520,23 +510,23 @@ options = exitWith ExitSuccess) "FORMAT") "" -- "Print default template for FORMAT" -#ifdef _CITEPROC - , Option "" ["biblio"] + , Option "" ["bibliography"] (ReqArg - (\arg opt -> return opt { optBiblioFile = arg} ) + (\arg opt -> do + refs <- catch (readBiblioFile arg) $ \e -> do + UTF8.hPutStrLn stderr $ + "Error reading bibliography `" ++ arg ++ "'" + UTF8.hPutStrLn stderr $ show e + exitWith (ExitFailure 23) + return opt { optBibliography = + optBibliography opt ++ refs } ) "FILENAME") "" - , Option "" ["biblio-format"] - (ReqArg - (\arg opt -> return opt { optBiblioFormat = arg} ) - "STRING") - "" , Option "" ["csl"] (ReqArg - (\arg opt -> return opt { optCslFile = arg} ) + (\arg opt -> return opt { optCslFile = arg }) "FILENAME") "" -#endif , Option "" ["data-dir"] (ReqArg (\arg opt -> return opt { optDataDir = Just arg }) @@ -684,11 +674,8 @@ main = do , optIdentifierPrefix = idPrefix , optIndentedCodeClasses = codeBlockClasses , optDataDir = mbDataDir -#ifdef _CITEPROC - , optBiblioFile = biblioFile - , optBiblioFormat = biblioFormat - , optCslFile = cslFile -#endif + , optBibliography = refs + , optCslFile = cslfile } = opts when dumpArgs $ @@ -747,10 +734,6 @@ main = do let standalone' = standalone || isNonTextOutput writerName' -#ifdef _CITEPROC - refs <- if null biblioFile then return [] else readBiblioFile biblioFile biblioFormat -#endif - variables' <- case (writerName', standalone', offline) of ("s5", True, True) -> do inc <- s5HeaderIncludes datadir @@ -789,9 +772,7 @@ main = do stateLiterateHaskell = "+lhs" `isSuffixOf` readerName' || lhsExtension sources, stateStandalone = standalone', -#ifdef _CITEPROC - stateCitations = map citeKey refs, -#endif + stateCitations = map refId refs, stateSmart = smart || writerName' `elem` ["latex", "context", "latex+lhs", "man"], stateColumns = columns, @@ -849,11 +830,21 @@ main = do let doc' = foldr ($) doc transforms doc'' <- do -#ifdef _CITEPROC - processBiblio cslFile refs doc' -#else - return doc' -#endif + if null refs + then return doc' + else do + csldir <- getAppUserDataDirectory "csl" + cslfile' <- if null cslfile + then findDataFile datadir "default.csl" + else do + ex <- doesFileExist cslfile + if ex + then return cslfile + else findDataFile datadir $ + replaceDirectory + (replaceExtension cslfile "csl") + csldir + processBiblio cslfile' refs doc' writerOutput <- writer writerOptions doc'' |