diff options
-rw-r--r-- | pandoc.cabal | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Biblio.hs | 134 | ||||
-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/Markdown.hs | 132 | ||||
-rw-r--r-- | src/pandoc.hs | 2 | ||||
-rw-r--r-- | tests/RunTests.hs | 6 | ||||
-rw-r--r-- | tests/biblio.bib | 26 | ||||
-rw-r--r-- | tests/chicago-author-date.csl | 369 | ||||
-rw-r--r-- | tests/ieee.csl | 129 | ||||
-rw-r--r-- | tests/markdown-citations.plain | 37 | ||||
-rw-r--r-- | tests/markdown-citations.txt | 28 | ||||
-rw-r--r-- | tests/mhra.csl | 390 |
13 files changed, 1206 insertions, 215 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index c760df2be..13b343d07 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -1,5 +1,5 @@ Name: pandoc -Version: 1.6.1 +Version: 1.7 Cabal-Version: >= 1.2 Build-Type: Custom License: GPL @@ -158,7 +158,8 @@ Library bytestring >= 0.9, zip-archive >= 0.1.1.4, utf8-string >= 0.3, old-time >= 1, HTTP >= 4000.0.5, texmath >= 0.4, xml >= 1.3.5 && < 1.4, - random, extensible-exceptions + random, extensible-exceptions, + pandoc-types == 1.7.* if impl(ghc >= 6.10) Build-depends: base >= 4 && < 5, syb else @@ -167,7 +168,7 @@ Library Build-depends: highlighting-kate >= 0.2.7.1 cpp-options: -D_HIGHLIGHTING if flag(citeproc) - Build-depends: citeproc-hs >= 0.2 + Build-depends: citeproc-hs >= 0.3 && < 0.4 cpp-options: -D_CITEPROC if impl(ghc >= 6.12) Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind @@ -180,7 +181,6 @@ Library Exposed-Modules: Text.Pandoc, Text.Pandoc.Blocks, - Text.Pandoc.Definition, Text.Pandoc.CharacterReferences, Text.Pandoc.Shared, Text.Pandoc.Parsing, @@ -229,7 +229,8 @@ Executable pandoc bytestring >= 0.9, zip-archive >= 0.1.1.4, utf8-string >= 0.3, old-time >= 1, HTTP >= 4000.0.5, texmath, xml >= 1.3.5 && < 1.4, - random, extensible-exceptions + random, extensible-exceptions, + pandoc-types == 1.7.* if impl(ghc >= 6.10) Build-depends: base >= 4 && < 5, syb else @@ -238,7 +239,7 @@ Executable pandoc Build-depends: highlighting-kate >= 0.2.7.1 cpp-options: -D_HIGHLIGHTING if flag(citeproc) - Build-depends: citeproc-hs >= 0.2 + Build-depends: citeproc-hs >= 0.3 && < 0.4 cpp-options: -D_CITEPROC if impl(ghc >= 6.12) Ghc-Options: -O2 -Wall -fno-warn-unused-do-bind diff --git a/src/Text/Pandoc/Biblio.hs b/src/Text/Pandoc/Biblio.hs index 436eadd68..bca24d815 100644 --- a/src/Text/Pandoc/Biblio.hs +++ b/src/Text/Pandoc/Biblio.hs @@ -22,7 +22,7 @@ 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 -} @@ -31,7 +31,10 @@ module Text.Pandoc.Biblio ( processBiblio ) where import Control.Monad ( when ) import Data.List -import Text.CSL +import Data.Unique +import qualified Data.Map as M +import Text.CSL hiding ( Cite(..), Citation(..) ) +import qualified Text.CSL as CSL ( Cite(..) ) import Text.Pandoc.Definition -- | Process a 'Pandoc' document by adding citations formatted @@ -42,25 +45,124 @@ processBiblio cf r 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 + p' <- processWithM setHash p + let (nts,grps) = if styleClass csl /= "note" + then (,) [] $ queryWith getCitation p' + else let cits = queryWith getCite p' + ncits = map (queryWith getCite) $ queryWith getNote p' + needNt = cits \\ concat ncits + in (,) needNt $ getNoteCitations needNt p' + result = citeproc 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) + process t = case M.lookup t cs of + Just x -> if isTextualCitation t && x /= [] + then renderPandoc s [head x] ++ [Space] ++ + [Cite t $ renderPandoc s $ tail x] + 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 l cm nn _) + = hashUnique `fmap` newUnique >>= return . Citation i p l 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 (Citation i p l cm nn h) + = let (la,lo) = parseLocator l + citMode = case cm of + AuthorInText -> (True, False) + SuppressAuthor -> (False,True ) + NormalCitation -> (False,False) + in emptyCite { CSL.citeId = i + , CSL.citePrefix = p + , CSL.citeLabel = la + , CSL.citeLocator = lo + , CSL.citeNoteNumber = show nn + , CSL.authorInText = fst citMode + , CSL.suppressAuthor = snd citMode + , CSL.citeHash = h + } 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/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index b655ea1a9..eb9646df2 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -373,6 +373,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 @@ -912,9 +913,7 @@ inlineParsers = [ str , note , inlineNote , link -#ifdef _CITEPROC - , inlineCitation -#endif + , cite , image , math , strikeout @@ -1305,38 +1304,99 @@ 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 + textualCite <|> normalCite + +spnl :: GenParser Char st () +spnl = try $ skipSpaces >> optional newline >> skipSpaces >> + notFollowedBy (char '\n') + +textualCite :: GenParser Char ParserState Inline +textualCite = try $ do + key <- citeKey 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 + unless (key `elem` stateCitations st) $ + fail "not a citation" + let first = Citation{ citationId = key + , citationPrefix = "" + , citationLocator = "" + , citationMode = AuthorInText + , citationNoteNum = 0 + , citationHash = 0 + } + option (Cite [first] []) $ try $ do + spnl + char '[' + spnl + bareloc <- option "" locator + rest <- many $ try $ do + char ';' + spnl + citation + spnl + char ']' + let first' = if null bareloc + then first + else first{ citationLocator = bareloc + , citationMode = AuthorInText } + return $ Cite (first' : rest) [] + +normalCite :: GenParser Char ParserState Inline +normalCite = try $ do + cites <- citeList + return $ Cite cites [] + +citeKey :: GenParser Char st String +citeKey = try $ do + char '@' + first <- letter + rest <- many $ noneOf ",;]@ \t\n" + return (first:rest) + +locator :: GenParser Char st String +locator = try $ do + optional $ char ',' + spnl + -- TODO should eventually be list of inlines + many1 $ (char '\\' >> oneOf "];\n") <|> noneOf "];\n" <|> + (char '\n' >> notFollowedBy blankline >> return ' ') + +prefix :: GenParser Char st String +prefix = try $ liftM removeLeadingTrailingSpace $ + many $ (char '\\' >> anyChar) <|> noneOf "@]\n" <|> + (char '-' >> notFollowedBy (char '@') >> return '-') <|> + (char '\n' >> notFollowedBy blankline >> return ' ') + +citeList :: GenParser Char st [Citation] +citeList = try $ do + char '[' + spnl + first <- citation + spnl + rest <- many $ try $ do + char ';' + spnl + citation + spnl + char ']' + return (first:rest) + +citation :: GenParser Char st Citation +citation = try $ do + suppress_auth <- option False (char '-' >> return True) + pref <- prefix + key <- citeKey + loc <- locator + return $ Citation{ citationId = key + , citationPrefix = pref + , citationLocator = loc + , citationMode = if suppress_auth + then SuppressAuthor + else NormalCitation + , citationNoteNum = 0 + , citationHash = 0 + } diff --git a/src/pandoc.hs b/src/pandoc.hs index 4caabdd29..349d86ca2 100644 --- a/src/pandoc.hs +++ b/src/pandoc.hs @@ -789,7 +789,7 @@ main = do lhsExtension sources, stateStandalone = standalone', #ifdef _CITEPROC - stateCitations = map citeKey refs, + stateCitations = map refId refs, #endif stateSmart = smart || writerName' `elem` ["latex", "context", "latex+lhs", "man"], diff --git a/tests/RunTests.hs b/tests/RunTests.hs index 1715400fd..468451562 100644 --- a/tests/RunTests.hs +++ b/tests/RunTests.hs @@ -106,6 +106,7 @@ main = do "latex-reader.latex" "latex-reader.native" r11 <- runTest "native reader" ["-r", "native", "-w", "native", "-s"] "testsuite.native" "testsuite.native" + r14 <- runTest "markdown reader (citations)" ["-r", "markdown", "-w", "plain", "--biblio", "biblio.bib", "--csl", "chicago-author-date.csl"] "markdown-citations.txt" "markdown-citations.plain" r12s <- if runLhsTests then mapM runLhsWriterTest lhsWriterFormats else putStrLn "Skipping lhs writer tests because they presuppose highlighting support" >> return [] @@ -113,12 +114,14 @@ main = do then mapM runLhsReaderTest lhsReaderFormats else putStrLn "Skipping lhs reader tests because they presuppose highlighting support" >> return [] let results = r1s ++ + [ r2, r3, r4, r5 -- S5 , r6, r7, r7a -- markdown reader , r8, r8a -- rst , r9 -- html , r10 -- latex , r11 -- native + , r14 -- citations ] ++ r12s ++ r13s if all id results then do @@ -165,7 +168,8 @@ runTest testname opts inp norm = do let normPath = norm hFlush stdout -- Note: COLUMNS must be set for markdown table reader - ph <- runProcess pandocPath (opts ++ [inpPath] ++ ["--data-dir", ".."]) Nothing (Just [("COLUMNS", "80")]) Nothing (Just hOut) (Just stderr) + ph <- runProcess pandocPath (opts ++ [inpPath] ++ ["--data-dir", ".."]) Nothing + (Just [("LANG","en_US.UTF-8"),("COLUMNS", "80")]) Nothing (Just hOut) (Just stderr) ec <- waitForProcess ph result <- if ec == ExitSuccess then do diff --git a/tests/biblio.bib b/tests/biblio.bib new file mode 100644 index 000000000..755d535a8 --- /dev/null +++ b/tests/biblio.bib @@ -0,0 +1,26 @@ +@Book{item1, +author="John Doe", +title="First Book", +year="2005", +address="Cambridge", +publisher="Cambridge University Press" +} + +@Article{item2, +author="John Doe", +title="Article", +year="2006", +journal="Journal of Generic Studies", +volume="6", +pages="33-34" +} + +@InCollection{item3, +author="John Doe and Jenny Roe", +title="Why Water Is Wet", +booktitle="Third Book", +editor="Sam Smith", +publisher="Oxford University Press", +address="Oxford", +year="2007" +} diff --git a/tests/chicago-author-date.csl b/tests/chicago-author-date.csl new file mode 100644 index 000000000..f16f82305 --- /dev/null +++ b/tests/chicago-author-date.csl @@ -0,0 +1,369 @@ +<?xml version="1.0" encoding="utf-8"?> +<style xmlns="http://purl.org/net/xbiblio/csl" class="in-text" version="1.0" page-range-format="chicago"> + <info> + <title>Chicago Manual of Style (Author-Date format)</title> + <id>http://www.zotero.org/styles/chicago-author-date</id> + <link href="http://www.zotero.org/styles/chicago-author-date" rel="self"/> + <author> + <name>Julian Onions</name> + <email>julian.onions@gmail.com</email> + </author> + <category citation-format="author-date"/> + <category field="generic-base"/> + <updated>2009-12-04T20:22:16+00:00</updated> + <summary>The author-date variant of the Chicago style</summary> + <link href="http://www.chicagomanualofstyle.org/tools_citationguide.html" rel="documentation"/> + </info> + <macro name="secondary-contributors"> + <choose> + <if match="none" type="chapter"> + <group delimiter=". "> + <choose> + <if variable="author"> + <names variable="editor"> + <label form="verb-short" prefix=" " suffix=". " text-case="capitalize-first" /> + <name and="text" delimiter=", " /> + </names> + </if> + </choose> + <choose> + <if match="any" variable="author editor"> + <names variable="translator"> + <label form="verb-short" prefix=" " suffix=". " text-case="capitalize-first" /> + <name and="text" delimiter=", " /> + </names> + </if> + </choose> + </group> + </if> + </choose> + </macro> + <macro name="container-contributors"> + <choose> + <if type="chapter"> + <group delimiter=", " prefix=","> + <choose> + <if variable="author"> + <names variable="editor"> + <label form="verb-short" prefix=" " suffix=". " text-case="lowercase" /> + <name and="text" delimiter=", " /> + </names> + </if> + </choose> + <choose> + <if match="any" variable="author editor"> + <names variable="translator"> + <label form="verb-short" prefix=" " suffix=". " text-case="lowercase" /> + <name and="text" delimiter=", " /> + </names> + </if> + </choose> + </group> + </if> + </choose> + </macro> + <macro name="anon"> + <choose> + <if match="none" variable="author editor translator"> + <text form="short" term="anonymous" text-case="capitalize-first" /> + </if> + </choose> + </macro> + <macro name="editor"> + <names variable="editor"> + <name and="text" delimiter=", " delimiter-precedes-last="always" name-as-sort-order="first" sort-separator=", " /> + <label form="short" prefix=", " suffix="." /> + </names> + </macro> + <macro name="translator"> + <names variable="translator"> + <name and="text" delimiter=", " delimiter-precedes-last="always" name-as-sort-order="first" sort-separator=", " /> + <label form="verb-short" prefix=", " suffix="." /> + </names> + </macro> + <macro name="recipient"> + <choose> + <if type="personal_communication"> + <choose> + <if variable="genre"> + <text text-case="capitalize-first" variable="genre" /> + </if> + <else> + <text term="letter" text-case="capitalize-first" /> + </else> + </choose> + </if> + </choose> + <names delimiter=", " variable="recipient"> + <label form="verb" prefix=" " suffix=" " text-case="lowercase" /> + <name and="text" delimiter=", " /> + </names> + </macro> + <macro name="contributors"> + <names variable="author"> + <name and="text" delimiter=", " delimiter-precedes-last="always" name-as-sort-order="first" sort-separator=", " /> + <label form="verb-short" prefix=", " suffix="." text-case="lowercase" /> + <substitute> + <text macro="editor" /> + <text macro="translator" /> + </substitute> + </names> + <text macro="anon" /> + <text macro="recipient" /> + </macro> + <macro name="contributors-short"> + <names variable="author"> + <name and="text" delimiter=", " form="short" /> + <substitute> + <names variable="editor" /> + <names variable="translator" /> + </substitute> + </names> + <text macro="anon" /> + </macro> + <macro name="interviewer"> + <names delimiter=", " variable="interviewer"> + <label form="verb" prefix=" " suffix=" " text-case="capitalize-first" /> + <name and="text" delimiter=", " /> + </names> + </macro> + <macro name="archive"> + <group delimiter=". "> + <text text-case="capitalize-first" variable="archive_location" /> + <text variable="archive" /> + <text variable="archive-place" /> + </group> + </macro> + <macro name="access"> + <group delimiter=". "> + <choose> + <if match="any" type="graphic report"> + <text macro="archive" /> + </if> + <else-if match="none" type="book thesis chapter article-journal article-newspaper article-magazine"> + <text macro="archive" /> + </else-if> + </choose> + <text prefix="doi:" variable="DOI" /> + <text variable="URL" /> + </group> + </macro> + <macro name="title"> + <choose> + <if match="none" variable="title"> + <choose> + <if match="none" type="personal_communication"> + <text text-case="capitalize-first" variable="genre" /> + </if> + </choose> + </if> + <else-if type="book"> + <text font-style="italic" variable="title" /> + </else-if> + <else> + <text variable="title" /> + </else> + </choose> + </macro> + <macro name="edition"> + <choose> + <if match="any" type="book chapter"> + <choose> + <if is-numeric="edition"> + <group delimiter=" "> + <number form="ordinal" variable="edition" /> + <text form="short" suffix="." term="edition" /> + </group> + </if> + <else> + <text suffix="." variable="edition" /> + </else> + </choose> + </if> + </choose> + </macro> + <macro name="locators"> + <choose> + <if type="article-journal"> + <text prefix=" " variable="volume" /> + <text prefix=", no. " variable="issue" /> + </if> + <else-if type="book"> + <group delimiter=". " prefix=". "> + <group> + <text form="short" suffix=". " term="volume" text-case="capitalize-first" /> + <number form="numeric" variable="volume" /> + </group> + <group> + <number form="numeric" variable="number-of-volumes" /> + <text form="short" plural="true" prefix=" " suffix="." term="volume" /> + </group> + </group> + </else-if> + </choose> + </macro> + <macro name="locators-chapter"> + <choose> + <if type="chapter"> + <group prefix=", "> + <text suffix=":" variable="volume" /> + <text variable="page" /> + </group> + </if> + </choose> + </macro> + <macro name="locators-article"> + <choose> + <if type="article-newspaper"> + <group delimiter=", " prefix=", "> + <group> + <text suffix=" " variable="edition" /> + <text prefix=" " term="edition" /> + </group> + <group> + <text form="short" suffix=". " term="section" /> + <text variable="section" /> + </group> + </group> + </if> + <else-if type="article-journal"> + <text prefix=": " variable="page" /> + </else-if> + </choose> + </macro> + <macro name="point-locators"> + <group> + <choose> + <if locator="page" match="none"> + <label form="short" suffix=" " variable="locator" /> + </if> + </choose> + <text variable="locator" /> + </group> + </macro> + <macro name="container-prefix"> + <text term="in" text-case="capitalize-first" /> + </macro> + <macro name="container-title"> + <choose> + <if type="chapter"> + <text macro="container-prefix" suffix=" " /> + </if> + </choose> + <text font-style="italic" variable="container-title" /> + </macro> + <macro name="publisher"> + <group delimiter=": "> + <text variable="publisher-place" /> + <text variable="publisher" /> + </group> + </macro> + <macro name="date"> + <date variable="issued"> + <date-part name="year" /> + </date> + </macro> + <macro name="day-month"> + <date variable="issued"> + <date-part name="month" /> + <date-part name="day" prefix=" " /> + </date> + </macro> + <macro name="collection-title"> + <text variable="collection-title" /> + <text prefix=" " variable="collection-number" /> + </macro> + <macro name="event"> + <group> + <text suffix=" " term="presented at" /> + <text variable="event" /> + </group> + </macro> + <macro name="description"> + <group delimiter=". "> + <text macro="interviewer" /> + <text text-case="capitalize-first" variable="medium" /> + </group> + <choose> + <if match="none" variable="title"> </if> + <else-if type="thesis"> </else-if> + <else> + <text prefix=". " text-case="capitalize-first" variable="genre" /> + </else> + </choose> + </macro> + <macro name="issue"> + <choose> + <if type="article-journal"> + <text macro="day-month" prefix=" (" suffix=")" /> + </if> + <else-if type="speech"> + <group delimiter=", " prefix=" "> + <text macro="event" /> + <text macro="day-month" /> + <text variable="event-place" /> + </group> + </else-if> + <else-if match="any" type="article-newspaper article-magazine"> + <text macro="day-month" prefix=", " /> + </else-if> + <else> + <group delimiter=", " prefix=". "> + <choose> + <if type="thesis"> + <text text-case="capitalize-first" variable="genre" /> + </if> + </choose> + <text macro="publisher" /> + <text macro="day-month" /> + </group> + </else> + </choose> + </macro> + <citation + disambiguate-add-givenname="true" + disambiguate-add-names="true" + disambiguate-add-year-suffix="true" + et-al-min="4" + et-al-subsequent-min="4" + et-al-subsequent-use-first="1" + et-al-use-first="1"> + <layout delimiter="; " prefix="(" suffix=")"> + <group delimiter=", "> + <group delimiter=" "> + <text macro="contributors-short" /> + <text macro="date" /> + </group> + <text macro="point-locators" /> + </group> + </layout> + </citation> + <bibliography + entry-spacing="0" + et-al-min="11" + et-al-use-first="7" + hanging-indent="true" + subsequent-author-substitute="---"> + <sort> + <key macro="contributors" /> + <key variable="issued" /> + <key variable="title" /> + </sort> + <layout suffix="."> + <text macro="contributors" suffix=". " /> + <text macro="date" suffix=". " /> + <text macro="title" /> + <text macro="description" /> + <text macro="secondary-contributors" prefix=". " /> + <text macro="container-title" prefix=". " /> + <text macro="container-contributors" /> + <text macro="locators-chapter" /> + <text macro="edition" prefix=". " /> + <text macro="locators" /> + <text macro="collection-title" prefix=". " /> + <text macro="issue" /> + <text macro="locators-article" /> + <text macro="access" prefix=". " /> + </layout> + </bibliography> +</style> diff --git a/tests/ieee.csl b/tests/ieee.csl new file mode 100644 index 000000000..2e0af1795 --- /dev/null +++ b/tests/ieee.csl @@ -0,0 +1,129 @@ +<?xml version="1.0" encoding="utf-8"?> +<style xmlns="http://purl.org/net/xbiblio/csl" class="numeric" version="1.0"> + <info> + <title>IEEE</title> + <id>http://www.zotero.org/styles/ieee</id> + <link href="http://www.zotero.org/styles/ieee" rel="self"/> + <author> + <name>Michael Berkowitz</name> + <email>mberkowi@gmu.edu</email> + </author> + <contributor> + <name>Julian Onions</name> + <email>julian.onions@gmail.com</email> + </contributor> + <contributor> + <name>Rintze Zelle</name> + <uri>http://forums.zotero.org/account/831/</uri> + </contributor> + <category field="engineering"/> + <category field="generic-base"/> + <category citation-format="numeric"/> + <updated>2010-02-06T06:35:40+00:00</updated> + <link href="http://www.ieee.org/portal/cms_docs_iportals/iportals/publications/authors/transjnl/stylemanual.pdf" rel="documentation"/> + </info> + <macro name="author"> + <names variable="author"> + <name initialize-with="." delimiter=", " and="text"/> + <label form="short" prefix=", " text-case="capitalize-first" suffix="." strip-periods="true"/> + <substitute> + <names variable="editor"/> + <names variable="translator"/> + </substitute> + </names> + </macro> + <macro name="editor"> + <names variable="editor"> + <name initialize-with="." delimiter=", " and="text" name-as-sort-order="all"/> + <label form="short" prefix=", " text-case="capitalize-first" suffix="." strip-periods="true"/> + </names> + </macro> + <macro name="title"> + <choose> + <if type="bill book graphic legal_case motion_picture report song" match="any"> + <text variable="title" font-style="italic"/> + </if> + <else> + <text variable="title" quotes="true"/> + </else> + </choose> + </macro> + <macro name="publisher"> + <text variable="publisher-place" suffix=": " prefix=" "/> + <text variable="publisher" suffix=", "/> + <date variable="issued"> + <date-part name="year"/> + </date> + </macro> + <macro name="access"> + <text variable="URL"/> + </macro> + <macro name="page"> + <group> + <label variable="page" form="short" suffix=". " strip-periods="true"/> + <text variable="page"/> + </group> + </macro> + <citation et-al-min="3" et-al-use-first="1" collapse="citation-number"> + <sort> + <key variable="citation-number"/> + </sort> + <layout delimiter=","> + <text variable="citation-number" prefix="[" suffix="]"/> + </layout> + </citation> + <bibliography entry-spacing="0" second-field-align="flush"> + <layout suffix="."> + <text variable="citation-number" prefix="[" suffix="]"/> + <text macro="author" prefix=" " suffix=", "/> + <choose> + <if type="bill book graphic legal_case motion_picture report song" match="any"> + <group delimiter=", "> + <text macro="title"/> + <text macro="publisher"/> + </group> + </if> + <else-if type="chapter paper-conference" match="any"> + <group delimiter=", "> + <text macro="title"/> + <text variable="container-title" font-style="italic"/> + <text macro="editor"/> + <text macro="publisher"/> + <text macro="page"/> + </group> + </else-if> + <else-if type="patent"> + <text macro="title" suffix=", "/> + <text variable="number" prefix="U.S. Patent "/> + <date variable="issued" prefix=", "> + <date-part name="month" suffix=" "/> + <date-part name="day" suffix=", "/> + <date-part name="year"/> + </date> + </else-if> + <else-if type="thesis"> + <group delimiter=", "> + <text macro="title"/> + <text variable="genre"/> + <text variable="publisher"/> + <date variable="issued"> + <date-part name="year"/> + </date> + </group> + </else-if> + <else> + <group delimiter=", "> + <text macro="title"/> + <text variable="container-title" font-style="italic"/> + <text variable="volume" prefix=" vol. "/> + <date variable="issued"> + <date-part name="month" form="short" suffix=". " strip-periods="true"/> + <date-part name="year"/> + </date> + <text macro="page"/> + </group> + </else> + </choose> + </layout> + </bibliography> +</style>
\ No newline at end of file diff --git a/tests/markdown-citations.plain b/tests/markdown-citations.plain new file mode 100644 index 000000000..35218d954 --- /dev/null +++ b/tests/markdown-citations.plain @@ -0,0 +1,37 @@ +Pandoc with citeproc-hs +======================= + +[@nonexistent] + +@nonexistent + +Doe (2005) says blah. Doe (2005, 30) says blah. Doe (2005; 2006, +30; see also Doe and Roe 2007) says blah. + +In a note.[^1] A citation group +(see Doe 2005, 34-35; also Doe and Roe 2007, chap. 3). Another one +(see Doe 2005, 34-35). And another one in a note.[^2] + +Now some modifiers.[^3] + +References +========== + +Doe, John. 2005. First Book. Cambridge: Cambridge University +Press. + +---. 2006. Article. Journal of Generic Studies 6: 33-34. + +Doe, John, and Jenny Roe. 2007. Why Water Is Wet. In Third Book, +ed. Sam Smith. Oxford: Oxford University Press. + +[^1]: + A citation without locators [Doe and Roe (2007)]. + +[^2]: + Some citations (see Doe 2006, chap. 3; Doe and Roe 2007; Doe + 2005). + +[^3]: + Like a citation without author: (2005), and now Doe with a + locator (2006, 44). diff --git a/tests/markdown-citations.txt b/tests/markdown-citations.txt new file mode 100644 index 000000000..59206f0a4 --- /dev/null +++ b/tests/markdown-citations.txt @@ -0,0 +1,28 @@ +# Pandoc with citeproc-hs + +[@nonexistent] + +@nonexistent + +@item1 says blah. +@item1 [p. 30] says blah. +@item1 [-@item2, p. 30; see also @item3] says blah. + +In a note.[^1] A citation group [see +@item1, p. 34-35; also @item3, chap. 3]. Another one [see +@item1, p. 34-35]. And another one in a note.[^2] + +Now some modifiers.[^3] + +[^1]: + A citation without locators [@item3]. + +[^2]: + Some citations [see @item2, chap. 3; @item3; @item1]. + +[^3]: + Like a citation without author: [-@item1], and now Doe with a + locator [-@item2, p. 44]. + +# References + diff --git a/tests/mhra.csl b/tests/mhra.csl new file mode 100644 index 000000000..4749cdcd7 --- /dev/null +++ b/tests/mhra.csl @@ -0,0 +1,390 @@ +<?xml version="1.0" encoding="utf-8"?> +<style xmlns="http://purl.org/net/xbiblio/csl" class="note" version="1.0"> + <info> + <title>Modern Humanities Research Association (Note with Bibliography)</title> + <id>http://www.zotero.org/styles/mhra</id> + <link href="http://www.zotero.org/styles/mhra" rel="self"/> + <link href="http://www.mhra.org.uk/Publications/Books/StyleGuide/download.shtml" rel="documentation"/> + <author> + <name>Rintze Zelle</name> + <uri>http://forums.zotero.org/account/831/</uri> + </author> + <contributor> + <name>Sebastian Karcher</name> + </contributor> + <summary>MHRA format with full notes and bibliography</summary> + <category field="generic-base"/> + <category citation-format="note"/> + <updated>2009-12-15T12:42:52+00:00</updated> + </info> + <locale xml:lang="en"> + <terms> + <term name="et-al">and others</term> + <term name="editor" form="verb-short">ed. by</term> + <term name="edition" form="short">edn</term> + <term name="translator" form="verb-short">trans. by</term> + </terms> + </locale> + <macro name="author"> + <names variable="author"> + <name name-as-sort-order="first" and="text" sort-separator=", " delimiter=", " delimiter-precedes-last="always"/> + <label form="short" prefix=", " suffix="." strip-periods="true"/> + <substitute> + <names variable="editor"/> + <names variable="translator"/> + <text macro="title-note"/> + </substitute> + </names> + </macro> + <macro name="contributors-note"> + <names variable="author"> + <name and="text" sort-separator=", " delimiter=", " delimiter-precedes-last="never"/> + </names> + <text macro="recipient-note"/> + </macro> + <macro name="title-note"> + <choose> + <if type="bill book graphic legal_case motion_picture report song" match="any"> + <text variable="title" font-style="italic"/> + </if> + <else> + <text variable="title" prefix="‘" suffix="’"/> + </else> + </choose> + </macro> + <macro name="editor-translator"> + <group delimiter=", "> + <names variable="editor" delimiter=", "> + <label form="verb-short" text-case="lowercase" suffix=" " strip-periods="true"/> + <name and="text" delimiter=", " delimiter-precedes-last="never"/> + </names> + <choose> + <if variable="author editor" match="any"> + <names variable="translator" delimiter=", "> + <label form="verb-short" text-case="lowercase" suffix=" " strip-periods="true"/> + <name and="text" delimiter=", " delimiter-precedes-last="never"/> + </names> + </if> + </choose> + </group> + </macro> + <macro name="collection-title"> + <text variable="collection-title"/> + <text variable="collection-number" prefix=", "/> + </macro> + <macro name="locators-note"> + <choose> + <if type="article-journal"> + <text variable="volume"/> + </if> + <else-if type="bill book graphic legal_case motion_picture report song chapter paper-conference" match="any"> + <group delimiter=", "> + <text macro="edition-note"/> + <group> + <number variable="number-of-volumes" form="numeric"/> + <text term="volume" form="short" prefix=" " plural="true" strip-periods="true"/> + </group> + </group> + </else-if> + </choose> + </macro> + <macro name="volume"> + <choose> + <if type="article-journal"> + <text variable="volume"/> + </if> + <else-if type="bill book graphic legal_case motion_picture report song chapter paper-conference" match="any"> + <group delimiter=", "> + <text macro="edition-note"/> + <group> + <number variable="number-of-volumes" form="numeric"/> + <text term="volume" form="short" prefix=" " plural="true" strip-periods="true"/> + </group> + </group> + </else-if> + </choose> + </macro> + <macro name="issue-note"> + <choose> + <if type="article-journal"> + <choose> + <if variable="volume"> + <text macro="issued" prefix=" (" suffix=")"/> + </if> + <else> + <text macro="issued" prefix=", "/> + </else> + </choose> + </if> + <else-if variable="publisher-place publisher" match="any"> + <group prefix=" (" suffix=")" delimiter=", "> + <group delimiter=" "> + <choose> + <if variable="title" match="none"/> + <else-if type="thesis speech" match="any"> + <text variable="genre" prefix="unpublished "/> + </else-if> + </choose> + <text macro="event"/> + </group> + <text macro="publisher"/> + <text macro="issued"/> + </group> + </else-if> + <else> + <text macro="issued" prefix=", "/> + </else> + </choose> + </macro> + <macro name="locators-specific-note"> + <choose> + <if type="bill book graphic legal_case motion_picture report song chapter paper-conference" match="any"> + <choose> + <if is-numeric="volume"> + <number variable="volume" form="roman" font-variant="small-caps"/> + </if> + </choose> + </if> + </choose> + </macro> + <macro name="container-title-note"> + <choose> + <if type="chapter paper-conference" match="any"> + <text term="in" text-case="lowercase" suffix=" "/> + </if> + </choose> + <text variable="container-title" font-style="italic"/> + </macro> + <macro name="edition-note"> + <choose> + <if type="bill book graphic legal_case motion_picture report song chapter paper-conference" match="any"> + <choose> + <if is-numeric="edition"> + <group delimiter=" "> + <number variable="edition" form="ordinal"/> + <text term="edition" form="short" strip-periods="true"/> + </group> + </if> + <else> + <text variable="edition"/> + </else> + </choose> + </if> + </choose> + </macro> + <macro name="editor-note"> + <names variable="editor"> + <name and="text" sort-separator=", " delimiter=", "/> + <label form="short" prefix=", " suffix="." strip-periods="true"/> + </names> + </macro> + <macro name="translator-note"> + <names variable="translator"> + <name and="text" sort-separator=", " delimiter=", "/> + <label form="verb-short" prefix=", " suffix="." strip-periods="true"/> + </names> + </macro> + <macro name="recipient-note"> + <names variable="recipient" delimiter=", "> + <label form="verb" prefix=" " text-case="lowercase" suffix=" "/> + <name and="text" delimiter=", "/> + </names> + </macro> + <macro name="recipient-short"> + <names variable="recipient"> + <label form="verb" prefix=" " text-case="lowercase" suffix=" "/> + <name form="short" and="text" delimiter=", "/> + </names> + </macro> + <macro name="contributors-short"> + <names variable="author"> + <name form="short" and="text" sort-separator=", " delimiter=", " delimiter-precedes-last="never"/> + <substitute> + <names variable="editor"/> + <names variable="translator"/> + </substitute> + </names> + <text macro="recipient-short"/> + </macro> + <macro name="interviewer-note"> + <names variable="interviewer" delimiter=", "> + <label form="verb" prefix=" " text-case="lowercase" suffix=" "/> + <name and="text" delimiter=", "/> + </names> + </macro> + <macro name="locators-newspaper"> + <choose> + <if type="article-newspaper"> + <group delimiter=", "> + <group> + <text variable="edition" suffix=" "/> + <text term="edition" prefix=" "/> + </group> + <group> + <text term="section" suffix=" "/> + <text variable="section"/> + </group> + </group> + </if> + </choose> + </macro> + <macro name="event"> + <group> + <text term="presented at" suffix=" "/> + <text variable="event"/> + </group> + </macro> + <macro name="publisher"> + <group delimiter=": "> + <text variable="publisher-place"/> + <text variable="publisher"/> + </group> + </macro> + <macro name="issued"> + <choose> + <if type="graphic report article-newspaper" match="any"> + <date variable="issued"> + <date-part name="day" suffix=" "/> + <date-part name="month" suffix=" "/> + <date-part name="year"/> + </date> + </if> + <else-if type="bill book graphic legal_case motion_picture report song thesis chapter paper-conference" match="any"> + <date variable="issued"> + <date-part name="year"/> + </date> + </else-if> + <else> + <date variable="issued"> + <date-part name="year"/> + </date> + </else> + </choose> + </macro> + <macro name="pages"> + <choose> + <if type="article-journal"> + <text variable="page" prefix=", "/> + </if> + <else> + <choose> + <if variable="volume"> + <text variable="page" prefix=", "/> + </if> + <else> + <label variable="page" form="short" prefix=", " suffix=" "/> + <text variable="page"/> + </else> + </choose> + </else> + </choose> + </macro> + <macro name="point-locators"> + <text macro="pages"/> + <choose> + <if variable="page"> + <group prefix=" (" suffix=")"> + <label variable="locator" form="short" suffix=" "/> + <text variable="locator"/> + </group> + </if> + <else> + <label variable="locator" form="short" prefix=", " suffix=" "/> + <text variable="locator"/> + </else> + </choose> + </macro> + <macro name="archive-note"> + <group delimiter=", "> + <text variable="archive_location"/> + <text variable="archive"/> + <text variable="archive-place"/> + </group> + </macro> + <macro name="access-note"> + <group delimiter=", "> + <choose> + <if type="graphic report" match="any"> + <text macro="archive-note" prefix=", "/> + </if> + <else-if type="bill book graphic legal_case motion_picture report song article-journal article-magazine article-newspaper thesis chapter paper-conference" match="none"> + <text macro="archive-note" prefix=", "/> + </else-if> + </choose> + </group> + <choose> + <if variable="DOI"> + <text variable="DOI" prefix=" <doi:" suffix=">"/> + </if> + <else> + <text variable="URL" prefix=" <" suffix=">"/> + <choose> + <if variable="accessed"> + <group prefix=" [" suffix="]"> + <text term="accessed" text-case="lowercase"/> + <date variable="accessed"> + <date-part name="day" prefix=" "/> + <date-part name="month" prefix=" "/> + <date-part name="year" prefix=" "/> + </date> + </group> + </if> + </choose> + </else> + </choose> + </macro> + <citation et-al-min="4" et-al-use-first="1" et-al-subsequent-min="4" et-al-subsequent-use-first="1" disambiguate-add-names="true" disambiguate-add-givenname="true" givenname-disambiguation-rule="by-cite"> + <layout prefix="" suffix="." delimiter="; "> + <choose> + <if position="subsequent"> + <group delimiter=", "> + <text macro="contributors-short"/> + <choose> + <if disambiguate="true"> + <text variable="title" form="short"/> + </if> + </choose> + </group> + <text macro="locators-specific-note" prefix=", "/> + <text macro="point-locators"/> + </if> + <else> + <group delimiter=", "> + <text macro="contributors-note"/> + <text macro="title-note"/> + <text macro="container-title-note"/> + <text macro="editor-translator"/> + <text macro="collection-title"/> + <text macro="locators-note"/> + </group> + <text macro="issue-note"/> + <text macro="locators-specific-note" prefix=", "/> + <text macro="locators-newspaper" prefix=", "/> + <text macro="point-locators"/> + <text macro="access-note"/> + </else> + </choose> + </layout> + </citation> + <bibliography hanging-indent="true" et-al-min="6" et-al-use-first="6" subsequent-author-substitute="---"> + <sort> + <key macro="author"/> + <key variable="title"/> + </sort> + <layout suffix="."> + <group delimiter=", "> + <text macro="author"/> + <text macro="title-note"/> + <text macro="container-title-note"/> + <text macro="editor-translator"/> + <text macro="collection-title"/> + <text macro="volume"/> + </group> + <text macro="issue-note"/> + <text macro="locators-specific-note" prefix=", "/> + <text macro="locators-newspaper" prefix=", "/> + <text macro="pages"/> + <text macro="access-note"/> + </layout> + </bibliography> +</style>
\ No newline at end of file |