pandoc-citeproc-0.10.5.1/compat/0000755000000000000000000000000013023023522014447 5ustar0000000000000000pandoc-citeproc-0.10.5.1/compat/Text/0000755000000000000000000000000013023023522015373 5ustar0000000000000000pandoc-citeproc-0.10.5.1/compat/Text/CSL/0000755000000000000000000000000013023023522016014 5ustar0000000000000000pandoc-citeproc-0.10.5.1/compat/Text/CSL/Compat/0000755000000000000000000000000013062566745017265 5ustar0000000000000000pandoc-citeproc-0.10.5.1/locales/0000755000000000000000000000000013111572661014621 5ustar0000000000000000pandoc-citeproc-0.10.5.1/man/0000755000000000000000000000000013114776324013757 5ustar0000000000000000pandoc-citeproc-0.10.5.1/man/man1/0000755000000000000000000000000013007644547014615 5ustar0000000000000000pandoc-citeproc-0.10.5.1/prelude/0000755000000000000000000000000012743760365014651 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/0000755000000000000000000000000012743760365014000 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/0000755000000000000000000000000012743760365014724 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/0000755000000000000000000000000013114774531015336 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Data/0000755000000000000000000000000013114774714016212 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval/0000755000000000000000000000000013067270145016224 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Input/0000755000000000000000000000000013114773714016437 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Output/0000755000000000000000000000000013111572372016632 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Proc/0000755000000000000000000000000013003500055016222 5ustar0000000000000000pandoc-citeproc-0.10.5.1/tests/0000755000000000000000000000000013115033673014340 5ustar0000000000000000pandoc-citeproc-0.10.5.1/tests/biblio2yaml/0000755000000000000000000000000013115031301016527 5ustar0000000000000000pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/0000755000000000000000000000000013063452061020146 5ustar0000000000000000pandoc-citeproc-0.10.5.1/src/Text/CSL/Pandoc.hs0000644000000000000000000004271213067270145017103 0ustar0000000000000000{-# LANGUAGE PatternGuards, OverloadedStrings, FlexibleInstances, ScopedTypeVariables, CPP #-} module Text.CSL.Pandoc (processCites, processCites') where import Text.Pandoc import Text.Pandoc.Walk import Text.Pandoc.Builder (setMeta, deleteMeta) import Text.Pandoc.Shared (stringify) import Text.HTML.TagSoup.Entity (lookupEntity) import qualified Data.ByteString.Lazy as L import System.SetEnv (setEnv) import System.Environment (getEnv) import Control.Applicative ((<|>)) import Data.Aeson import Data.Char ( isDigit, isPunctuation, toLower, isSpace ) import qualified Data.Map as M import Text.CSL.Reference hiding (processCites, Value) import Text.CSL.Input.Bibutils (readBiblioFile, convertRefs) import Text.CSL.Style hiding (Cite(..), Citation(..)) import Text.CSL.Proc import Text.CSL.Output.Pandoc (renderPandoc, renderPandoc') import qualified Text.CSL.Style as CSL import Text.CSL.Parser import Text.CSL.Output.Pandoc ( headInline, tailInline, initInline, toCapital ) import Text.CSL.Data (getDefaultCSL) import Text.Parsec hiding (State, (<|>)) import Control.Monad import qualified Control.Exception as E import Control.Monad.State import System.FilePath import System.Directory (getAppUserDataDirectory) import Text.CSL.Util (findFile, splitStrWhen, tr', parseRomanNumeral, trim) import System.IO.Error (isDoesNotExistError) import Data.Maybe (fromMaybe) -- | Process a 'Pandoc' document by adding citations formatted -- according to a CSL style. Add a bibliography (if one is called -- for) at the end of the document. processCites :: Style -> [Reference] -> Pandoc -> Pandoc processCites style refs (Pandoc m1 b1) = let metanocites = lookupMeta "nocite" m1 nocites = mkNociteWildcards refs . query getCitation <$> metanocites Pandoc m2 b2 = evalState (walkM setHashes $ Pandoc (deleteMeta "nocite" m1) b1) 1 grps = query getCitation (Pandoc m2 b2) ++ fromMaybe [] nocites locMap = locatorMap style result = citeproc procOpts{ linkCitations = isLinkCitations m2} style refs (setNearNote style $ map (map (toCslCite locMap)) grps) cits_map = tr' "cits_map" $ M.fromList $ zip grps (citations result) biblioList = map (renderPandoc' style) $ zip (bibliography result) (citationIds result) moveNotes = case lookupMeta "notes-after-punctuation" m1 of Just (MetaBool False) -> False _ -> True Pandoc m3 bs = bottomUp (mvPunct moveNotes style) . deNote . topDown (processCite style cits_map) $ Pandoc m2 b2 m = case metanocites of Nothing -> m3 Just x -> setMeta "nocite" x m3 in Pandoc m $ bottomUp (concatMap removeNocaseSpans) $ insertRefs m biblioList bs -- if document contains a Div with id="refs", insert -- references as its contents. Otherwise, insert references -- at the end of the document in a Div with id="refs" insertRefs :: Meta -> [Block] -> [Block] -> [Block] insertRefs _ [] bs = bs insertRefs meta refs bs = if isRefRemove meta then bs else case runState (walkM go bs) False of (bs', True) -> bs' (_, False) -> case reverse bs of (Header lev (id',classes,kvs) ys) : xs -> reverse xs ++ [Header lev (id',addUnNumbered classes,kvs) ys, Div ("refs",["references"],[]) refs] _ -> bs ++ refHeader ++ [Div ("refs",["references"],[]) refs] where go :: Block -> State Bool Block go (Div attr@("refs",_,_) xs) = do put True -- refHeader isn't used if you have an explicit references div return $ Div attr (xs ++ refs) go x = return x addUnNumbered cs = "unnumbered" : [c | c <- cs, c /= "unnumbered"] refHeader = case refTitle meta of Just ils -> [Header 1 ("bibliography", ["unnumbered"], []) ils] _ -> [] refTitle :: Meta -> Maybe [Inline] refTitle meta = case lookupMeta "reference-section-title" meta of Just (MetaString s) -> Just [Str s] Just (MetaInlines ils) -> Just ils Just (MetaBlocks [Plain ils]) -> Just ils Just (MetaBlocks [Para ils]) -> Just ils _ -> Nothing isRefRemove :: Meta -> Bool isRefRemove meta = case lookupMeta "suppress-bibliography" meta of Just (MetaBool True) -> True _ -> False isLinkCitations :: Meta -> Bool isLinkCitations meta = case lookupMeta "link-citations" meta of Just (MetaBool True) -> True Just (MetaString s) -> map toLower s `elem` yesValues Just (MetaInlines ils) -> map toLower (stringify ils) `elem` yesValues _ -> False where yesValues = ["true", "yes", "on"] -- if the 'nocite' Meta field contains a citation with id = '*', -- create a cite with to all the references. mkNociteWildcards :: [Reference] -> [[Citation]] -> [[Citation]] mkNociteWildcards refs nocites = map (\citgrp -> expandStar citgrp) nocites where expandStar cs = case [c | c <- cs , citationId c == "*"] of [] -> cs _ -> allcites allcites = map (\ref -> Citation{ citationId = unLiteral (refId ref), citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0 }) refs removeNocaseSpans :: Inline -> [Inline] removeNocaseSpans (Span ("",["nocase"],[]) xs) = xs removeNocaseSpans x = [x] -- | Process a 'Pandoc' document by adding citations formatted -- according to a CSL style. The style filename is derived from -- the `csl` field of the metadata, and the references are taken -- from the `references` field or read from a file in the `bibliography` -- field. processCites' :: Pandoc -> IO Pandoc processCites' (Pandoc meta blocks) = do mbcsldir <- E.catch (Just <$> getAppUserDataDirectory "csl") $ \e -> if isDoesNotExistError e then return Nothing else E.throwIO e mbpandocdir <- E.catch (Just <$> getAppUserDataDirectory "pandoc") $ \e -> if isDoesNotExistError e then return Nothing else E.throwIO e let inlineRefError s = error $ "Error parsing references: " ++ s let inlineRefs = either inlineRefError id $ convertRefs $ lookupMeta "references" meta let cslfile = (lookupMeta "csl" meta <|> lookupMeta "citation-style" meta) >>= toPath let mbLocale = (lookupMeta "lang" meta `mplus` lookupMeta "locale" meta) >>= toPath let tryReadCSLFile Nothing _ = mzero tryReadCSLFile (Just d) f = E.catch (readCSLFile mbLocale (d f)) (\(_ :: E.SomeException) -> mzero) csl <- case cslfile of Just f | not (null f) -> readCSLFile mbLocale f _ -> tryReadCSLFile mbpandocdir "default.csl" `mplus` tryReadCSLFile mbcsldir "chicago-author-date.csl" `mplus` (getDefaultCSL >>= localizeCSL mbLocale . parseCSL') -- set LANG environment from locale; this affects unicode collation -- if pandoc-citeproc compiled with unicode_collation flag case styleLocale csl of (l:_) -> do setEnv "LC_ALL" (localeLang l) setEnv "LANG" (localeLang l) [] -> do envlang <- getEnv "LANG" if null envlang then do -- Note that LANG needs to be set for bibtex conversion: setEnv "LANG" "en-US.UTF-8" setEnv "LC_ALL" "en-US.UTF-8" else do setEnv "LC_ALL" envlang bibRefs <- getBibRefs $ maybe (MetaList []) id $ lookupMeta "bibliography" meta let refs = inlineRefs ++ bibRefs let cslAbbrevFile = lookupMeta "citation-abbreviations" meta >>= toPath let skipLeadingSpace = L.dropWhile (\s -> s == 32 || (s >= 9 && s <= 13)) abbrevs <- maybe (return (Abbreviations M.empty)) (\f -> findFile (maybe ["."] (\g -> [".", g]) mbcsldir) f >>= maybe (error $ "Could not find " ++ f) return >>= L.readFile >>= either error return . eitherDecode . skipLeadingSpace) cslAbbrevFile let csl' = csl{ styleAbbrevs = abbrevs } return $ processCites csl' refs $ Pandoc meta blocks toPath :: MetaValue -> Maybe String toPath (MetaString s) = Just s -- take last in a list toPath (MetaList xs) = case reverse xs of [] -> Nothing (x:_) -> toPath x toPath (MetaInlines ils) = Just $ stringify ils toPath _ = Nothing getBibRefs :: MetaValue -> IO [Reference] getBibRefs (MetaList xs) = concat `fmap` mapM getBibRefs xs getBibRefs (MetaInlines xs) = getBibRefs (MetaString $ stringify xs) getBibRefs (MetaString s) = do path <- findFile ["."] s >>= maybe (error $ "Could not find " ++ s) return map unescapeRefId `fmap` readBiblioFile path getBibRefs _ = return [] -- unescape reference ids, which may contain XML entities, so -- that we can do lookups with regular string equality unescapeRefId :: Reference -> Reference unescapeRefId ref = ref{ refId = Literal $ decodeEntities (unLiteral $ refId ref) } decodeEntities :: String -> String decodeEntities [] = [] decodeEntities ('&':xs) = let (ys,zs) = break (==';') xs in case zs of ';':ws -> case lookupEntity ('&':ys ++ ";") of #if MIN_VERSION_tagsoup(0,13,0) Just s -> s ++ decodeEntities ws #else Just c -> [c] ++ decodeEntities ws #endif Nothing -> '&' : decodeEntities xs _ -> '&' : decodeEntities xs decodeEntities (x:xs) = x : decodeEntities xs -- | Substitute 'Cite' elements with formatted citations. processCite :: Style -> M.Map [Citation] Formatted -> Inline -> Inline processCite s cs (Cite t _) = case M.lookup t cs of Just (Formatted (x:xs)) -> Cite t (renderPandoc s (Formatted (x:xs))) _ -> Strong [Str "???"] -- TODO raise error instead? processCite _ _ x = x isNote :: Inline -> Bool isNote (Note _) = True isNote (Cite _ [Note _]) = True isNote _ = False mvPunctInsideQuote :: Inline -> Inline -> [Inline] mvPunctInsideQuote (Quoted qt ils) (Str s) | s `elem` [".", ","] = [Quoted qt (init ils ++ (mvPunctInsideQuote (last ils) (Str s)))] mvPunctInsideQuote il il' = [il, il'] isSpacy :: Inline -> Bool isSpacy Space = True isSpacy SoftBreak = True isSpacy _ = False mvPunct :: Bool -> Style -> [Inline] -> [Inline] mvPunct _ _ (x : Space : xs) | isSpacy x = x : xs mvPunct moveNotes _ (s : x : ys) | isSpacy s, isNote x, startWithPunct ys = if moveNotes then Str (headInline ys) : x : tailInline ys else x : ys mvPunct moveNotes _ (Cite cs ils : ys) | length ils > 1 , isNote (last ils) , startWithPunct ys , moveNotes = Cite cs (init ils ++ [Str (headInline ys) | not (endWithPunct False (init ils))] ++ [last ils]) : tailInline ys mvPunct moveNotes sty (q@(Quoted _ _) : w@(Str _) : x : ys) | isNote x, isPunctuationInQuote sty, moveNotes = mvPunctInsideQuote q w ++ (x : ys) mvPunct _ _ (s : x : ys) | isSpacy s, isNote x = x : ys mvPunct _ _ (s : x@(Cite _ (Superscript _ : _)) : ys) | isSpacy s = x : ys mvPunct _ _ xs = xs endWithPunct :: Bool -> [Inline] -> Bool endWithPunct _ [] = True endWithPunct onlyFinal xs@(_:_) = case reverse (stringify xs) of [] -> True -- covers .), .", etc.: (d:c:_) | isPunctuation d && not onlyFinal && isEndPunct c -> True (c:_) | isEndPunct c -> True | otherwise -> False where isEndPunct c = c `elem` (".,;:!?" :: String) startWithPunct :: [Inline] -> Bool startWithPunct = and . map (`elem` (".,;:!?" :: String)) . headInline deNote :: Pandoc -> Pandoc deNote = topDown go where go (Cite (c:cs) [Note [Para xs]]) = Cite (c:cs) [Note [Para $ toCapital xs]] go (Note xs) = Note $ topDown go' xs go x = x go' (x : Cite cs [Note [Para xs]] : ys) | not (isSpacy x) = x : Str "," : Space : comb (\zs -> [Cite cs zs]) xs ys go' (x : Note [Para xs] : ys) | not (isSpacy x) = x : Str "," : Space : comb id xs ys go' (Cite cs [Note [Para xs]] : ys) = comb (\zs -> [Cite cs zs]) xs ys go' (Note [Para xs] : ys) = comb id xs ys go' xs = xs comb :: ([Inline] -> [Inline]) -> [Inline] -> [Inline] -> [Inline] comb f xs ys = let xs' = if startWithPunct ys && endWithPunct True xs then initInline $ removeLeadingPunct xs else removeLeadingPunct xs removeLeadingPunct (Str [c] : s : zs) | isSpacy s && (c == ',' || c == '.' || c == ':') = zs removeLeadingPunct zs = zs in f xs' ++ ys -- | Retrieve all citations from a 'Pandoc' docuument. To be used with -- 'query'. getCitation :: Inline -> [[Citation]] getCitation i | Cite t _ <- i = [t] | otherwise = [] setHashes :: Inline -> State Int Inline setHashes i | Cite t ils <- i = do t' <- mapM setHash t return $ Cite t' ils | otherwise = return i setHash :: Citation -> State Int Citation setHash c = do ident <- get put $ ident + 1 return c{ citationHash = ident } toCslCite :: LocatorMap -> Citation -> CSL.Cite toCslCite locMap c = let (la, lo, s) = locatorWords locMap $ citationSuffix c s' = case (la,lo,s) of -- treat a bare locator as if it begins with space -- so @item1 [blah] is like [@item1, blah] ("","",(x:_)) | not (isPunct x) -> Space : s _ -> s isPunct (Str (x:_)) = isPunctuation x isPunct _ = False in emptyCite { CSL.citeId = citationId c , CSL.citePrefix = Formatted $ citationPrefix c , CSL.citeSuffix = Formatted s' , CSL.citeLabel = la , CSL.citeLocator = lo , CSL.citeNoteNumber = show $ citationNoteNum c , CSL.authorInText = citationMode c == AuthorInText , CSL.suppressAuthor = citationMode c == SuppressAuthor , CSL.citeHash = citationHash c } locatorWords :: LocatorMap -> [Inline] -> (String, String, [Inline]) locatorWords locMap inp = case parse (pLocatorWords locMap) "suffix" $ splitStrWhen (\c -> isLocatorPunct c || isSpace c) inp of Right r -> r Left _ -> ("","",inp) pLocatorWords :: LocatorMap -> Parsec [Inline] st (String, String, [Inline]) pLocatorWords locMap = do (la,lo) <- pLocator locMap s <- getInput -- rest is suffix return (la, lo, s) pMatch :: (Inline -> Bool) -> Parsec [Inline] st Inline pMatch condition = try $ do t <- anyToken guard $ condition t return t pSpace :: Parsec [Inline] st Inline pSpace = pMatch (\t -> isSpacy t || t == Str "\160") pLocator :: LocatorMap -> Parsec [Inline] st (String, String) pLocator locMap = try $ do optional $ pMatch (== Str ",") optional pSpace la <- try (do ts <- many1 (notFollowedBy (pWordWithDigits True) >> anyToken) case M.lookup (trim (stringify ts)) locMap of Just l -> return l Nothing -> mzero) <|> (lookAhead pDigit >> return "page") g <- pWordWithDigits True gs <- many (pWordWithDigits False) let lo = concat (g:gs) return (la, lo) pRoman :: Parsec [Inline] st String pRoman = try $ do t <- anyToken case t of Str xs -> case parseRomanNumeral xs of Nothing -> mzero Just _ -> return xs _ -> mzero -- we want to capture: 123, 123A, C22, XVII, 33-44, 22-33; 22-11 pWordWithDigits :: Bool -> Parsec [Inline] st String pWordWithDigits isfirst = try $ do punct <- if isfirst then return "" else stringify `fmap` pLocatorPunct sp <- option "" (pSpace >> return " ") s <- pRoman <|> try (do ts <- many1 (notFollowedBy pSpace >> notFollowedBy pLocatorPunct >> anyToken) let ts' = stringify ts guard (any isDigit ts') return ts') return $ punct ++ sp ++ s pDigit :: Parsec [Inline] st () pDigit = do t <- anyToken case t of Str (d:_) | isDigit d -> return () _ -> mzero pLocatorPunct :: Parsec [Inline] st Inline pLocatorPunct = pMatch isLocatorPunct' where isLocatorPunct' (Str [c]) = isLocatorPunct c isLocatorPunct' _ = False isLocatorPunct :: Char -> Bool isLocatorPunct ':' = False isLocatorPunct c = isPunctuation c type LocatorMap = M.Map String String locatorMap :: Style -> LocatorMap locatorMap sty = foldr (\term -> M.insert (termSingular term) (cslTerm term) . M.insert (termPlural term) (cslTerm term)) M.empty (concatMap localeTerms $ styleLocale sty) pandoc-citeproc-0.10.5.1/src/Text/CSL.hs0000644000000000000000000001033612743760365015704 0ustar0000000000000000----------------------------------------------------------------------------- -- | -- Module : Text.CSL -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- /citeproc-hs/ is a library for automatically formatting -- bibliographic reference citations into a variety of styles using a -- macro language called Citation Style Language (CSL). More details -- on CSL can be found here: . -- -- This module documents and exports the library API. -- ----------------------------------------------------------------------------- module Text.CSL ( -- * Introduction -- $intro -- * Overview: A Simple Example -- $overview -- * Reading Bibliographic Databases readBiblioFile , BibFormat (..) , readBiblioString -- ** Reference Representation , Reference (..) , getReference , setNearNote -- * CSL Parser, Representation, and Processing , readCSLFile , parseCSL , parseCSL' , localizeCSL -- ** The Style Types , Style (..) , Citation (..) , Bibliography (..) , Cite (..) , Abbreviations (..) , emptyCite -- ** High Level Processing , ProcOpts (..) , procOpts , BibOpts (..) , citeproc , processCitations , processBibliography , BiblioData (..) -- * The output and the rendering functions , renderPlain , renderPandoc , renderPandoc' ) where import Text.CSL.Proc import Text.CSL.Reference import Text.CSL.Style import Text.CSL.Parser import Text.CSL.Input.Bibutils import Text.CSL.Output.Pandoc import Text.CSL.Output.Plain -- $intro -- -- /citeproc-hs/ provides functions for reading bibliographic -- databases, for reading and parsing CSL files and for generating -- citations in an internal format, 'Formatted', that can be -- easily rendered into different final formats. At the present time -- only 'Pandoc' and plain text rendering functions are provided by -- the library. -- -- The library also provides a wrapper around hs-bibutils, the Haskell -- bindings to Chris Putnam's bibutils, a library that interconverts -- between various bibliography formats using a common MODS-format XML -- intermediate. For more information about hs-bibutils see here: -- . -- -- /citeproc-hs/ can natively read MODS and JSON formatted -- bibliographic databases. The JSON format is only partially -- documented. It is used by citeproc-js, by the CSL processor -- test-suite and is derived by the CSL scheme. More information can -- be read here: -- . -- -- A (git) repository of styles can be found here: -- . -- $overview -- -- The following example assumes you have installed citeproc-hs with -- hs-bibutils support (which is the default). -- -- Suppose you have a small bibliographic database, like this one: -- -- > @Book{Rossato2006, -- > author="Andrea Rossato", -- > title="My Second Book", -- > year="2006" -- > } -- > -- > @Book{Caso2007, -- > author="Roberto Caso", -- > title="Roberto's Book", -- > year="2007" -- > } -- -- Save it as @mybibdb.bib@. -- -- Then you can grab one of the CSL styles that come with the -- test-suite for CSL processors. Suppose this one: -- -- -- -- saved locally as @apa-x.csl@. -- -- This would be a simple program that formats a list of citations -- according to that style: -- -- > import Text.CSL -- > -- > cites :: [Cite] -- > cites = [emptyCite { citeId = "Caso2007" -- > , citeLabel = "page" -- > , citeLocator = "15"} -- > ,emptyCite { citeId = "Rossato2006" -- > , citeLabel = "page" -- > , citeLocator = "10"} -- > ] -- > -- > main :: IO () -- > main = do -- > m <- readBiblioFile "mybibdb.bib" -- > s <- readCSLFile Nothing "apa-x.csl" -- > let result = citeproc procOpts s m $ [cites] -- > putStrLn . unlines . map renderPlain . citations $ result -- -- The result would be: -- -- > (Caso, 2007, p. 15; Rossato, 2006, p. 10) pandoc-citeproc-0.10.5.1/src/Text/CSL/Reference.hs0000644000000000000000000007222513053647342017601 0ustar0000000000000000{-# LANGUAGE GeneralizedNewtypeDeriving, PatternGuards, OverloadedStrings, DeriveDataTypeable, ExistentialQuantification, FlexibleInstances, ScopedTypeVariables, GeneralizedNewtypeDeriving, IncoherentInstances, DeriveGeneric, CPP #-} #if MIN_VERSION_base(4,8,0) #define OVERLAPS {-# OVERLAPPING #-} #else {-# LANGUAGE OverlappingInstances #-} #define OVERLAPS #endif ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Reference -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The Reference type -- ----------------------------------------------------------------------------- module Text.CSL.Reference ( Literal(..) , Value(..) , ReferenceMap , mkRefMap , fromValue , isValueSet , Empty(..) , RefDate(..) , handleLiteral , toDatePart , setCirca , mkRefDate , RefType(..) , CNum(..) , CLabel(..) , Reference(..) , emptyReference , numericVars , getReference , processCites , setPageFirst , setNearNote ) where import Data.List ( elemIndex, intercalate ) import Data.List.Split ( splitWhen ) import Data.Maybe ( fromMaybe ) import Data.Generics hiding (Generic) import GHC.Generics (Generic) import Data.Aeson hiding (Value) import qualified Data.Aeson as Aeson import Data.Aeson.Types (Parser) import qualified Data.Yaml.Builder as Y import Data.Yaml.Builder (ToYaml(..)) import Control.Applicative ((<|>)) import qualified Data.Text as T import Data.Text (Text) import qualified Data.Vector as V import Data.Char (toLower, isDigit) import Text.CSL.Style hiding (Number) import Text.CSL.Util (parseString, parseInt, parseBool, safeRead, readNum, inlinesToString, capitalize, camelize, uncamelize, (&=), mapping') import Text.Pandoc (Inline(Str)) import Data.String import qualified Text.Parsec as P import qualified Text.Parsec.String as P import qualified Data.HashMap.Strict as H newtype Literal = Literal { unLiteral :: String } deriving ( Show, Read, Eq, Data, Typeable, Monoid, Generic ) instance FromJSON Literal where parseJSON v = Literal `fmap` parseString v instance ToJSON Literal where toJSON = toJSON . unLiteral instance ToYaml Literal where toYaml = Y.string . T.pack . unLiteral instance IsString Literal where fromString = Literal -- | An existential type to wrap the different types a 'Reference' is -- made of. This way we can create a map to make queries easier. data Value = forall a . Data a => Value a -- for debuging instance Show Value where show (Value a) = gshow a type ReferenceMap = [(String, Value)] mkRefMap :: Maybe Reference -> ReferenceMap mkRefMap Nothing = [] mkRefMap (Just r) = zip fields (gmapQ Value r) where fields = map uncamelize . constrFields . toConstr $ r fromValue :: Data a => Value -> Maybe a fromValue (Value a) = cast a isValueSet :: Value -> Bool isValueSet val | Just v <- fromValue val :: Maybe Literal = v /= mempty | Just v <- fromValue val :: Maybe String = v /= mempty | Just v <- fromValue val :: Maybe Formatted = v /= mempty | Just v <- fromValue val :: Maybe [Agent] = v /= [] | Just v <- fromValue val :: Maybe [RefDate] = v /= [] | Just v <- fromValue val :: Maybe Int = v /= 0 | Just v <- fromValue val :: Maybe CNum = v /= 0 | Just v <- fromValue val :: Maybe CLabel = v /= mempty | Just _ <- fromValue val :: Maybe Empty = True | otherwise = False data Empty = Empty deriving ( Typeable, Data, Generic ) data RefDate = RefDate { year :: Literal , month :: Literal , season :: Literal , day :: Literal , other :: Literal , circa :: Bool } deriving ( Show, Read, Eq, Typeable, Data, Generic ) instance FromJSON RefDate where parseJSON (Array v) = case fromJSON (Array v) of Success [y] -> RefDate <$> parseJSON y <*> pure "" <*> pure "" <*> pure "" <*> pure "" <*> pure False Success [y,m] -> RefDate <$> parseJSON y <*> parseJSON m <*> pure "" <*> pure "" <*> pure "" <*> pure False Success [y,m,d] -> RefDate <$> parseJSON y <*> parseJSON m <*> pure "" <*> parseJSON d <*> pure "" <*> pure False Error e -> fail $ "Could not parse RefDate: " ++ e _ -> fail "Could not parse RefDate" parseJSON (Object v) = RefDate <$> v .:? "year" .!= "" <*> v .:? "month" .!= "" <*> v .:? "season" .!= "" <*> v .:? "day" .!= "" <*> v .:? "literal" .!= "" <*> ((v .: "circa" >>= parseBool) <|> pure False) parseJSON _ = fail "Could not parse RefDate" {- instance ToJSON RefDate where toJSON refdate = object' $ [ "year" .= year refdate , "month" .= month refdate , "season" .= season refdate , "day" .= day refdate , "literal" .= other refdate ] ++ [ "circa" .= circa refdate | circa refdate ] -} instance ToYaml RefDate where toYaml r = mapping' [ "year" &= year r , "month" &= month r , "season" &= season r , "day" &= day r , "literal" &= other r , "circa" &= T.pack (if circa r then "1" else "") ] instance OVERLAPS FromJSON [RefDate] where parseJSON (Array xs) = mapM parseJSON $ V.toList xs parseJSON (Object v) = do dateParts <- v .:? "date-parts" circa' <- (v .: "circa" >>= parseBool) <|> pure False case dateParts of Just (Array xs) -> mapM (fmap (setCirca circa') . parseJSON) $ V.toList xs _ -> handleLiteral <$> parseJSON (Object v) parseJSON x = parseJSON x >>= mkRefDate -- Zotero doesn't properly support date ranges, so a common -- workaround is 2005_2007 or 2005_; support this as date range: handleLiteral :: RefDate -> [RefDate] handleLiteral d@(RefDate (Literal "") (Literal "") (Literal "") (Literal "") (Literal xs) b) = case splitWhen (=='_') xs of [x,y] | all isDigit x && all isDigit y && not (null x) -> [RefDate (Literal x) mempty mempty mempty mempty b, RefDate (Literal y) mempty mempty mempty mempty b] _ -> [d] handleLiteral d = [d] toDatePart :: RefDate -> [Int] toDatePart refdate = case (safeRead (unLiteral $ year refdate), safeRead (unLiteral $ month refdate), safeRead (unLiteral $ day refdate)) of (Just (y :: Int), Just (m :: Int), Just (d :: Int)) -> [y, m, d] (Just y, Just m, Nothing) -> [y, m] (Just y, Nothing, Nothing) -> [y] _ -> [] instance OVERLAPS ToJSON [RefDate] where toJSON [] = Array V.empty toJSON xs = object' $ case filter (not . null) (map toDatePart xs) of [] -> ["literal" .= intercalate "; " (map (unLiteral . other) xs)] dps -> (["date-parts" .= dps ] ++ ["circa" .= (1 :: Int) | or (map circa xs)] ++ ["season" .= s | s <- map season xs, s /= mempty]) setCirca :: Bool -> RefDate -> RefDate setCirca circa' rd = rd{ circa = circa' } mkRefDate :: Literal -> Parser [RefDate] mkRefDate z@(Literal xs) | all isDigit xs = return [RefDate z mempty mempty mempty mempty False] | otherwise = return [RefDate mempty mempty mempty mempty z False] data RefType = NoType | Article | ArticleMagazine | ArticleNewspaper | ArticleJournal | Bill | Book | Broadcast | Chapter | Dataset | Entry | EntryDictionary | EntryEncyclopedia | Figure | Graphic | Interview | Legislation | LegalCase | Manuscript | Map | MotionPicture | MusicalScore | Pamphlet | PaperConference | Patent | Post | PostWeblog | PersonalCommunication | Report | Review | ReviewBook | Song | Speech | Thesis | Treaty | Webpage deriving ( Read, Eq, Typeable, Data, Generic ) instance Show RefType where show x = map toLower . uncamelize . showConstr . toConstr $ x instance FromJSON RefType where parseJSON (String t) = (safeRead (capitalize . camelize . T.unpack $ t)) <|> fail ("'" ++ T.unpack t ++ "' is not a valid reference type") parseJSON v@(Array _) = fmap (capitalize . camelize . inlinesToString) (parseJSON v) >>= \t -> (safeRead t <|> fail ("'" ++ t ++ "' is not a valid reference type")) parseJSON _ = fail "Could not parse RefType" instance ToJSON RefType where toJSON reftype = toJSON (handleSpecialCases $ show reftype) instance ToYaml RefType where toYaml r = Y.string (T.pack $ handleSpecialCases $ show r) -- For some reason, CSL is inconsistent about hyphens and underscores: handleSpecialCases :: String -> String handleSpecialCases "motion-picture" = "motion_picture" handleSpecialCases "musical-score" = "musical_score" handleSpecialCases "personal-communication" = "personal_communication" handleSpecialCases "legal-case" = "legal_case" handleSpecialCases x = x newtype CNum = CNum { unCNum :: Int } deriving ( Show, Read, Eq, Num, Typeable, Data, Generic ) instance FromJSON CNum where parseJSON x = CNum `fmap` parseInt x instance ToJSON CNum where toJSON (CNum n) = toJSON n instance ToYaml CNum where toYaml r = Y.string (T.pack $ show $ unCNum r) newtype CLabel = CLabel { unCLabel :: String } deriving ( Show, Read, Eq, Typeable, Data, Generic ) instance Monoid CLabel where mempty = CLabel mempty mappend (CLabel a) (CLabel b) = CLabel (mappend a b) instance FromJSON CLabel where parseJSON x = CLabel `fmap` parseString x instance ToJSON CLabel where toJSON (CLabel s) = toJSON s instance ToYaml CLabel where toYaml (CLabel s) = toYaml $ T.pack s -- | The 'Reference' record. data Reference = Reference { refId :: Literal , refType :: RefType , author :: [Agent] , editor :: [Agent] , translator :: [Agent] , recipient :: [Agent] , interviewer :: [Agent] , composer :: [Agent] , director :: [Agent] , illustrator :: [Agent] , originalAuthor :: [Agent] , containerAuthor :: [Agent] , collectionEditor :: [Agent] , editorialDirector :: [Agent] , reviewedAuthor :: [Agent] , issued :: [RefDate] , eventDate :: [RefDate] , accessed :: [RefDate] , container :: [RefDate] , originalDate :: [RefDate] , submitted :: [RefDate] , title :: Formatted , titleShort :: Formatted , reviewedTitle :: Formatted , containerTitle :: Formatted , volumeTitle :: Formatted , collectionTitle :: Formatted , containerTitleShort :: Formatted , collectionNumber :: Formatted --Int , originalTitle :: Formatted , publisher :: Formatted , originalPublisher :: Formatted , publisherPlace :: Formatted , originalPublisherPlace :: Formatted , authority :: Formatted , jurisdiction :: Formatted , archive :: Formatted , archivePlace :: Formatted , archiveLocation :: Formatted , event :: Formatted , eventPlace :: Formatted , page :: Formatted , pageFirst :: Formatted , numberOfPages :: Formatted , version :: Formatted , volume :: Formatted , numberOfVolumes :: Formatted --Int , issue :: Formatted , chapterNumber :: Formatted , medium :: Formatted , status :: Formatted , edition :: Formatted , section :: Formatted , source :: Formatted , genre :: Formatted , note :: Formatted , annote :: Formatted , abstract :: Formatted , keyword :: Formatted , number :: Formatted , references :: Formatted , url :: Literal , doi :: Literal , isbn :: Literal , issn :: Literal , pmcid :: Literal , pmid :: Literal , callNumber :: Literal , dimensions :: Literal , scale :: Literal , categories :: [Literal] , language :: Literal , citationNumber :: CNum , firstReferenceNoteNumber :: Int , citationLabel :: CLabel } deriving ( Eq, Show, Read, Typeable, Data, Generic ) instance FromJSON Reference where parseJSON (Object v') = do v <- parseSuppFields v' <|> return v' addPageFirst <$> (Reference <$> v .:? "id" .!= "" <*> v .:? "type" .!= NoType <*> v .:? "author" .!= [] <*> v .:? "editor" .!= [] <*> v .:? "translator" .!= [] <*> v .:? "recipient" .!= [] <*> v .:? "interviewer" .!= [] <*> v .:? "composer" .!= [] <*> v .:? "director" .!= [] <*> v .:? "illustrator" .!= [] <*> v .:? "original-author" .!= [] <*> v .:? "container-author" .!= [] <*> v .:? "collection-editor" .!= [] <*> v .:? "editorial-director" .!= [] <*> v .:? "reviewed-author" .!= [] <*> v .:? "issued" .!= [] <*> v .:? "event-date" .!= [] <*> v .:? "accessed" .!= [] <*> v .:? "container" .!= [] <*> v .:? "original-date" .!= [] <*> v .:? "submitted" .!= [] <*> v .:? "title" .!= mempty <*> (v .: "shortTitle" <|> (v .:? "title-short" .!= mempty)) <*> v .:? "reviewed-title" .!= mempty <*> v .:? "container-title" .!= mempty <*> v .:? "volume-title" .!= mempty <*> v .:? "collection-title" .!= mempty <*> (v .: "journalAbbreviation" <|> v .:? "container-title-short" .!= mempty) <*> v .:? "collection-number" .!= mempty <*> v .:? "original-title" .!= mempty <*> v .:? "publisher" .!= mempty <*> v .:? "original-publisher" .!= mempty <*> v .:? "publisher-place" .!= mempty <*> v .:? "original-publisher-place" .!= mempty <*> v .:? "authority" .!= mempty <*> v .:? "jurisdiction" .!= mempty <*> v .:? "archive" .!= mempty <*> v .:? "archive-place" .!= mempty <*> v .:? "archive_location" .!= mempty <*> v .:? "event" .!= mempty <*> v .:? "event-place" .!= mempty <*> v .:? "page" .!= mempty <*> v .:? "page-first" .!= mempty <*> v .:? "number-of-pages" .!= mempty <*> v .:? "version" .!= mempty <*> v .:? "volume" .!= mempty <*> v .:? "number-of-volumes" .!= mempty <*> v .:? "issue" .!= mempty <*> v .:? "chapter-number" .!= mempty <*> v .:? "medium" .!= mempty <*> v .:? "status" .!= mempty <*> v .:? "edition" .!= mempty <*> v .:? "section" .!= mempty <*> v .:? "source" .!= mempty <*> v .:? "genre" .!= mempty <*> v .:? "note" .!= mempty <*> v .:? "annote" .!= mempty <*> v .:? "abstract" .!= mempty <*> v .:? "keyword" .!= mempty <*> v .:? "number" .!= mempty <*> v .:? "references" .!= mempty <*> v .:? "URL" .!= "" <*> v .:? "DOI" .!= "" <*> v .:? "ISBN" .!= "" <*> v .:? "ISSN" .!= "" <*> v .:? "PMCID" .!= "" <*> v .:? "PMID" .!= "" <*> v .:? "call-number" .!= "" <*> v .:? "dimensions" .!= "" <*> v .:? "scale" .!= "" <*> v .:? "categories" .!= [] <*> v .:? "language" .!= "" <*> v .:? "citation-number" .!= CNum 0 <*> ((v .: "first-reference-note-number" >>= parseInt) <|> return 0) <*> v .:? "citation-label" .!= mempty) where takeFirstNum (Formatted (Str xs : _)) = case takeWhile isDigit xs of [] -> mempty ds -> Formatted [Str ds] takeFirstNum x = x addPageFirst ref = if pageFirst ref == mempty && page ref /= mempty then ref{ pageFirst = takeFirstNum (page ref) } else ref parseJSON _ = fail "Could not parse Reference" -- Syntax for adding supplementary fields in note variable -- {:authority:Superior Court of California}{:section:A}{:original-date:1777} -- see http://gsl-nagoya-u.net/http/pub/citeproc-doc.html#supplementary-fields parseSuppFields :: Aeson.Object -> Parser Aeson.Object parseSuppFields o = do nt <- o .: "note" case P.parse noteFields "note" nt of Left err -> fail (show err) Right fs -> return $ foldr (\(k,v) x -> H.insert k v x) o fs noteFields :: P.Parser [(Text, Aeson.Value)] noteFields = do fs <- P.many noteField P.spaces rest <- P.getInput return (("note", Aeson.String (T.pack rest)) : fs) noteField :: P.Parser (Text, Aeson.Value) noteField = P.try $ do P.spaces P.char '{' P.char ':' k <- P.manyTill (P.letter <|> P.char '-') (P.char ':') v <- P.manyTill P.anyChar (P.char '}') return (T.pack k, Aeson.String (T.pack v)) instance ToJSON Reference where toJSON ref = object' [ "id" .= refId ref , "type" .= refType ref , "author" .= author ref , "editor" .= editor ref , "translator" .= translator ref , "recipient" .= recipient ref , "interviewer" .= interviewer ref , "composer" .= composer ref , "director" .= director ref , "illustrator" .= illustrator ref , "original-author" .= originalAuthor ref , "container-author" .= containerAuthor ref , "collection-editor" .= collectionEditor ref , "editorial-director" .= editorialDirector ref , "reviewed-author" .= reviewedAuthor ref , "issued" .= issued ref , "event-date" .= eventDate ref , "accessed" .= accessed ref , "container" .= container ref , "original-date" .= originalDate ref , "submitted" .= submitted ref , "title" .= title ref , "title-short" .= titleShort ref , "reviewed-title" .= reviewedTitle ref , "container-title" .= containerTitle ref , "volume-title" .= volumeTitle ref , "collection-title" .= collectionTitle ref , "container-title-short" .= containerTitleShort ref , "collection-number" .= collectionNumber ref , "original-title" .= originalTitle ref , "publisher" .= publisher ref , "original-publisher" .= originalPublisher ref , "publisher-place" .= publisherPlace ref , "original-publisher-place" .= originalPublisherPlace ref , "authority" .= authority ref , "jurisdiction" .= jurisdiction ref , "archive" .= archive ref , "archive-place" .= archivePlace ref , "archive_location" .= archiveLocation ref , "event" .= event ref , "event-place" .= eventPlace ref , "page" .= page ref , "page-first" .= (if page ref == mempty then pageFirst ref else mempty) , "number-of-pages" .= numberOfPages ref , "version" .= version ref , "volume" .= volume ref , "number-of-volumes" .= numberOfVolumes ref , "issue" .= issue ref , "chapter-number" .= chapterNumber ref , "medium" .= medium ref , "status" .= status ref , "edition" .= edition ref , "section" .= section ref , "source" .= source ref , "genre" .= genre ref , "note" .= note ref , "annote" .= annote ref , "abstract" .= abstract ref , "keyword" .= keyword ref , "number" .= number ref , "references" .= references ref , "URL" .= url ref , "DOI" .= doi ref , "ISBN" .= isbn ref , "ISSN" .= issn ref , "PMCID" .= pmcid ref , "PMID" .= pmid ref , "call-number" .= callNumber ref , "dimensions" .= dimensions ref , "scale" .= scale ref , "categories" .= categories ref , "language" .= language ref , "citation-number" .= citationNumber ref , "first-reference-note-number" .= firstReferenceNoteNumber ref , "citation-label" .= citationLabel ref ] instance ToYaml Reference where toYaml ref = mapping' [ "id" &= refId ref , (("type" Y..= refType ref) :) , "author" &= author ref , "editor" &= editor ref , "translator" &= translator ref , "recipient" &= recipient ref , "interviewer" &= interviewer ref , "composer" &= composer ref , "director" &= director ref , "illustrator" &= illustrator ref , "original-author" &= originalAuthor ref , "container-author" &= containerAuthor ref , "collection-editor" &= collectionEditor ref , "editorial-director" &= editorialDirector ref , "reviewed-author" &= reviewedAuthor ref , "issued" &= issued ref , "event-date" &= eventDate ref , "accessed" &= accessed ref , "container" &= container ref , "original-date" &= originalDate ref , "submitted" &= submitted ref , "title" &= title ref , "title-short" &= titleShort ref , "reviewed-title" &= reviewedTitle ref , "container-title" &= containerTitle ref , "volume-title" &= volumeTitle ref , "collection-title" &= collectionTitle ref , "container-title-short" &= containerTitleShort ref , "collection-number" &= collectionNumber ref , "original-title" &= originalTitle ref , "publisher" &= publisher ref , "original-publisher" &= originalPublisher ref , "publisher-place" &= publisherPlace ref , "original-publisher-place" &= originalPublisherPlace ref , "authority" &= authority ref , "jurisdiction" &= jurisdiction ref , "archive" &= archive ref , "archive-place" &= archivePlace ref , "archive_location" &= archiveLocation ref , "event" &= event ref , "event-place" &= eventPlace ref , "page" &= page ref , "page-first" &= (if page ref == mempty then pageFirst ref else mempty) , "number-of-pages" &= numberOfPages ref , "version" &= version ref , "volume" &= volume ref , "number-of-volumes" &= numberOfVolumes ref , "issue" &= issue ref , "chapter-number" &= chapterNumber ref , "medium" &= medium ref , "status" &= status ref , "edition" &= edition ref , "section" &= section ref , "source" &= source ref , "genre" &= genre ref , "note" &= note ref , "annote" &= annote ref , "abstract" &= abstract ref , "keyword" &= keyword ref , "number" &= number ref , "references" &= references ref , "URL" &= url ref , "DOI" &= doi ref , "ISBN" &= isbn ref , "ISSN" &= issn ref , "PMCID" &= pmcid ref , "PMID" &= pmid ref , "call-number" &= callNumber ref , "dimensions" &= dimensions ref , "scale" &= scale ref , "categories" &= categories ref , "language" &= language ref , if citationNumber ref == CNum 0 then id else (("citation-number" Y..= citationNumber ref) :) , if firstReferenceNoteNumber ref == 0 then id else (("first-reference-note-number" Y..= firstReferenceNoteNumber ref) :) , if citationLabel ref == mempty then id else (("citation-label" Y..= citationLabel ref) :) ] emptyReference :: Reference emptyReference = Reference { refId = mempty , refType = NoType , author = [] , editor = [] , translator = [] , recipient = [] , interviewer = [] , composer = [] , director = [] , illustrator = [] , originalAuthor = [] , containerAuthor = [] , collectionEditor = [] , editorialDirector = [] , reviewedAuthor = [] , issued = [] , eventDate = [] , accessed = [] , container = [] , originalDate = [] , submitted = [] , title = mempty , titleShort = mempty , reviewedTitle = mempty , containerTitle = mempty , volumeTitle = mempty , collectionTitle = mempty , containerTitleShort = mempty , collectionNumber = mempty , originalTitle = mempty , publisher = mempty , originalPublisher = mempty , publisherPlace = mempty , originalPublisherPlace = mempty , authority = mempty , jurisdiction = mempty , archive = mempty , archivePlace = mempty , archiveLocation = mempty , event = mempty , eventPlace = mempty , page = mempty , pageFirst = mempty , numberOfPages = mempty , version = mempty , volume = mempty , numberOfVolumes = mempty , issue = mempty , chapterNumber = mempty , medium = mempty , status = mempty , edition = mempty , section = mempty , source = mempty , genre = mempty , note = mempty , annote = mempty , abstract = mempty , keyword = mempty , number = mempty , references = mempty , url = mempty , doi = mempty , isbn = mempty , issn = mempty , pmcid = mempty , pmid = mempty , callNumber = mempty , dimensions = mempty , scale = mempty , categories = mempty , language = mempty , citationNumber = CNum 0 , firstReferenceNoteNumber = 0 , citationLabel = mempty } numericVars :: [String] numericVars = [ "edition", "volume", "number-of-volumes", "number", "issue", "citation-number" , "chapter-number", "collection-number", "number-of-pages"] getReference :: [Reference] -> Cite -> Maybe Reference getReference r c = case citeId c `elemIndex` map (unLiteral . refId) r of Just i -> Just $ setPageFirst $ r !! i Nothing -> Nothing processCites :: [Reference] -> [[Cite]] -> [[(Cite, Maybe Reference)]] processCites rs cs = procGr [[]] cs where procRef r = case filter ((==) (unLiteral $ refId r) . citeId) $ concat cs of x:_ -> r { firstReferenceNoteNumber = readNum $ citeNoteNumber x} [] -> r procGr _ [] = [] procGr a (x:xs) = let (a',res) = procCs a x in res : procGr (a' ++ [[]]) xs procCs a [] = (a,[]) procCs a (c:xs) | isIbid, isLocSet = go "ibid-with-locator" | isIbid = go "ibid" | isElem = go "subsequent" | otherwise = go "first" where go s = let addCite = init a ++ [last a ++ [c]] (a', rest) = procCs addCite xs in (a', (c { citePosition = s}, procRef <$> getReference rs c) : rest) isElem = citeId c `elem` map citeId (concat a) isIbid = case reverse (last a) of [] -> case reverse (init a) of [] -> False (zs:_) -> not (null zs) && all (== citeId c) (map citeId zs) (x:_) -> citeId c == citeId x isLocSet = citeLocator c /= "" setPageFirst :: Reference -> Reference setPageFirst ref = let Formatted ils = page ref ils' = takeWhile (\i -> i /= Str "–" && i /= Str "-") ils in if ils == ils' then ref else ref{ pageFirst = Formatted ils' } setNearNote :: Style -> [[Cite]] -> [[Cite]] setNearNote s cs = procGr [] cs where near_note = let nn = fromMaybe [] . lookup "near-note-distance" . citOptions . citation $ s in if nn == [] then 5 else readNum nn procGr _ [] = [] procGr a (x:xs) = let (a',res) = procCs a x in res : procGr a' xs procCs a [] = (a,[]) procCs a (c:xs) = (a', c { nearNote = isNear} : rest) where (a', rest) = procCs (c:a) xs isNear = case filter ((==) (citeId c) . citeId) a of x:_ -> citeNoteNumber c /= "0" && citeNoteNumber x /= "0" && readNum (citeNoteNumber c) - readNum (citeNoteNumber x) <= near_note _ -> False pandoc-citeproc-0.10.5.1/src/Text/CSL/Style.hs0000644000000000000000000010163113053647342016775 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, PatternGuards, DeriveDataTypeable, ScopedTypeVariables, FlexibleInstances, DeriveGeneric, GeneralizedNewtypeDeriving, CPP, MultiParamTypeClasses #-} #if MIN_VERSION_base(4,8,0) #define OVERLAPS {-# OVERLAPPING #-} #else {-# LANGUAGE OverlappingInstances #-} #define OVERLAPS #endif ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Style -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The Style types -- ----------------------------------------------------------------------------- module Text.CSL.Style ( readCSLString , writeCSLString , Formatted(..) , Style(..) , Locale(..) , mergeLocales , CslTerm(..) , newTerm , findTerm , findTerm' , Abbreviations(..) , MacroMap , Citation(..) , Bibliography(..) , Option , mergeOptions , Layout(..) , Element(..) , IfThen(..) , Condition(..) , Delimiter , Match(..) , match , DatePart(..) , defaultDate , Sort(..) , Sorting(..) , compare' , Form(..) , Gender(..) , NumericForm(..) , DateForm(..) , Plural(..) , Name(..) , NameAttrs , NamePart(..) , isPlural , isName , isNames , hasEtAl , Formatting(..) , emptyFormatting , rmTitleCase , Quote(..) , mergeFM , CSInfo(..) , CSAuthor(..) , CSCategory(..) , CiteprocError(..) , Output(..) , Citations , Cite(..) , emptyCite , CitationGroup(..) , BiblioData(..) , CiteData(..) , NameData(..) , isPunctuationInQuote , object' , Agent(..) , emptyAgent ) where import Data.Aeson hiding (Number) import GHC.Generics (Generic) import Data.String import Control.Arrow hiding (left, right) import Control.Monad (liftM, mplus) import Control.Applicative ((<|>)) import qualified Data.Aeson as Aeson import Data.Aeson.Types (Pair) import Data.List ( nubBy, isPrefixOf, isInfixOf, intersperse, intercalate ) import Data.List.Split ( splitWhen, wordsBy ) import Data.Generics ( Data, Typeable ) import Data.Maybe ( listToMaybe ) import qualified Data.Map as M import Data.Char (isPunctuation, isUpper, isLetter) import Text.CSL.Util (mb, parseBool, parseString, (.#?), (.#:), query, betterThan, trimr, tailInline, headInline, initInline, lastInline, splitStrWhen, mapping', (&=)) import Data.Yaml.Builder(ToYaml(..)) import qualified Data.Yaml.Builder as Y import Text.Pandoc.Definition hiding (Citation, Cite) import Text.Pandoc (bottomUp) import Text.CSL.Compat.Pandoc (readHtml, writeMarkdown) import qualified Text.Pandoc.Walk as Walk import qualified Text.Pandoc.Builder as B import qualified Data.Text as T import Text.Pandoc.XML (fromEntities) #ifdef UNICODE_COLLATION import qualified Data.Text as T import qualified Data.Text.ICU as T #else import Data.RFC5051 (compareUnicode) #endif import qualified Data.Vector as V -- Note: FromJSON reads HTML, ToJSON writes Markdown. -- This means that they aren't proper inverses of each other, which -- is odd, but it makes sense given the uses here. FromJSON is used -- for reading JSON citeproc bibliographies. ToJSON is used to create -- pandoc metadata bibliographies. readCSLString :: String -> [Inline] readCSLString s = Walk.walk handleSmallCapsSpans $ case readHtml (adjustScTags s) of Pandoc _ [Plain ils] -> ils Pandoc _ [Para ils] -> ils Pandoc _ x -> Walk.query (:[]) x -- this is needed for versions of pandoc that don't turn -- a span with font-variant:small-caps into a SmallCaps element: where handleSmallCapsSpans (Span ("",[],[("style",sty)]) ils) | filter (`notElem` (" \t;" :: String)) sty == "font-variant:small-caps" = SmallCaps ils handleSmallCapsSpans x = x -- is not a real HTML tag, but a CSL convention. So we -- replace it with a real tag that the HTML reader will understand. adjustScTags :: String -> String adjustScTags zs = case zs of ('<':'s':'c':'>':xs) -> "" ++ adjustScTags xs ('<':'/':'s':'c':'>':xs) -> "" ++ adjustScTags xs (x:xs) -> x : adjustScTags xs [] -> [] writeYAMLString :: [Inline] -> String writeYAMLString ils = trimr $ writeMarkdown $ Pandoc nullMeta [Plain $ bottomUp (concatMap (adjustCSL False)) ils] writeCSLString :: [Inline] -> String writeCSLString ils = trimr $ writeMarkdown $ Pandoc nullMeta [Plain $ bottomUp (concatMap (adjustCSL True)) ils] -- If the first param is True, we use special rich text conventions -- for CSL JSON, described here: -- http://docs.citationstyles.org/en/1.0/release-notes.html#rich-text-markup-within-fields adjustCSL :: Bool -> Inline -> [Inline] adjustCSL _ (Span ("",[],[]) xs) = xs adjustCSL _ (Span ("",["citeproc-no-output"],[]) _) = [Str "[CSL STYLE ERROR: reference with no printed form.]"] adjustCSL True (SmallCaps xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustCSL True (Subscript xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustCSL True (Superscript xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustCSL True (Emph xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustCSL True (Strong xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustCSL _ x = [x] -- We use a newtype wrapper so we can have custom ToJSON, FromJSON -- instances. newtype Formatted = Formatted { unFormatted :: [Inline] } deriving ( Show, Read, Eq, Ord, Data, Typeable, Generic ) instance FromJSON Formatted where parseJSON v@(Array _) = Formatted <$> (parseJSON v <|> ((query (:[]) :: [Block] -> [Inline]) <$> parseJSON v)) parseJSON v = fmap (Formatted . readCSLString) $ parseString v instance ToJSON Formatted where toJSON = toJSON . writeCSLString . unFormatted instance ToYaml Formatted where toYaml = Y.string . T.pack . writeYAMLString . unFormatted instance IsString Formatted where fromString = Formatted . toStr instance Monoid Formatted where mempty = Formatted [] mappend = appendWithPunct mconcat = foldr mappend mempty instance Walk.Walkable Inline Formatted where walk f = Formatted . Walk.walk f . unFormatted walkM f = liftM Formatted . Walk.walkM f . unFormatted query f = Walk.query f . unFormatted instance Walk.Walkable Formatted Formatted where walk f = f walkM f = f query f = f toStr :: String -> [Inline] toStr = intercalate [Str "\n"] . map (B.toList . B.text . tweak . fromEntities) . splitWhen (=='\n') where tweak ('«':' ':xs) = "«\8239" ++ tweak xs tweak (' ':'»':xs) = "\8239»" ++ tweak xs tweak (' ':';':xs) = "\8239;" ++ tweak xs tweak (' ':':':xs) = "\8239:" ++ tweak xs tweak (' ':'!':xs) = "\8239!" ++ tweak xs tweak (' ':'?':xs) = "\8239?" ++ tweak xs tweak ( x :xs ) = x : tweak xs tweak [] = [] appendWithPunct :: Formatted -> Formatted -> Formatted appendWithPunct (Formatted left) (Formatted right) = Formatted $ case concat [lastleft, firstright] of [' ',d] | d `elem` (",.:;" :: String) -> initInline left ++ right [c,d] | c `elem` (" ,.:;" :: String), d == c -> left ++ tailInline right [c,'.'] | c `elem` (",.!:;?" :: String) -> left ++ tailInline right [c,':'] | c `elem` (",!:;?" :: String) -> left ++ tailInline right -- Mich.: 2005 [c,'!'] | c `elem` (",.!:;?" :: String) -> left ++ tailInline right [c,'?'] | c `elem` (",.!:;?" :: String) -> left ++ tailInline right [c,';'] | c `elem` (",:;" :: String) -> left ++ tailInline right -- et al.; [':',c] | c `elem` (",.!:;?" :: String) -> left ++ tailInline right [';',c] | c `elem` (",.!:;?" :: String) -> left ++ tailInline right -- ".;" -> right -- e.g. et al.; _ -> left ++ right where lastleft = lastInline left firstright = headInline right -- | The representation of a parsed CSL style. data Style = Style { styleVersion :: String , styleClass :: String , styleInfo :: Maybe CSInfo , styleDefaultLocale :: String , styleLocale :: [Locale] , styleAbbrevs :: Abbreviations , csOptions :: [Option] , csMacros :: [MacroMap] , citation :: Citation , biblio :: Maybe Bibliography } deriving ( Show, Read, Typeable, Data, Generic ) data Locale = Locale { localeVersion :: String , localeLang :: String , localeOptions :: [Option] , localeTerms :: [CslTerm] , localeDate :: [Element] } deriving ( Show, Read, Eq, Typeable, Data, Generic ) -- | With the 'defaultLocale', the locales-xx-XX.xml loaded file and -- the parsed 'Style' cs:locale elements, produce the final 'Locale' -- as the only element of a list, taking into account CSL locale -- prioritization. mergeLocales :: String -> Locale -> [Locale] -> [Locale] mergeLocales s l ls = doMerge list where list = filter ((==) s . localeLang) ls ++ filter ((\x -> x /= [] && x `isPrefixOf` s) . localeLang) ls ++ filter ((==) [] . localeLang) ls doMerge x = return l { localeOptions = newOpt x , localeTerms = newTerms x , localeDate = newDate x } cht = cslTerm &&& termForm &&& termGenderForm checkedLoc = if hasOrdinals ls then rmOrdinals (localeTerms l) else localeTerms l newTerms x = nubBy (\a b -> cht a == cht b) (concatMap localeTerms x ++ checkedLoc) newOpt x = nubBy (\a b -> fst a == fst b) (concatMap localeOptions x ++ localeOptions l) newDate x = nubBy (\(Date _ a _ _ _ _) (Date _ b _ _ _ _) -> a == b) (concatMap localeDate x ++ localeDate l) data CslTerm = CT { cslTerm :: String , termForm :: Form , termGender :: Gender , termGenderForm :: Gender , termSingular :: String , termPlural :: String , termMatch :: String } deriving ( Show, Read, Eq, Typeable, Data, Generic ) newTerm :: CslTerm newTerm = CT [] Long Neuter Neuter [] [] [] findTerm :: String -> Form -> [CslTerm] -> Maybe CslTerm findTerm s f = findTerm'' s f Nothing findTerm' :: String -> Form -> Gender -> [CslTerm] -> Maybe CslTerm findTerm' s f g = findTerm'' s f (Just g) findTerm'' :: String -> Form -> Maybe Gender -> [CslTerm] -> Maybe CslTerm findTerm'' s f mbg ts = listToMaybe [ t | t <- ts, cslTerm t == s, termForm t == f, mbg == Nothing || mbg == Just (termGenderForm t) ] `mplus` -- fallback: http://citationstyles.org/downloads/specification.html#terms case f of VerbShort -> findTerm'' s Verb Nothing ts Symbol -> findTerm'' s Short Nothing ts Verb -> findTerm'' s Long Nothing ts Short -> findTerm'' s Long Nothing ts _ -> Nothing hasOrdinals :: [Locale] -> Bool hasOrdinals = any (any hasOrd . localeTerms) where hasOrd o | CT {cslTerm = t} <- o , "ordinal" `isInfixOf` t = True | otherwise = False rmOrdinals :: [CslTerm] -> [CslTerm] rmOrdinals [] = [] rmOrdinals (o:os) | CT {cslTerm = t} <- o , "ordinal" `isInfixOf` t = rmOrdinals os | otherwise = o:rmOrdinals os newtype Abbreviations = Abbreviations { unAbbreviations :: M.Map String (M.Map String (M.Map String String)) } deriving ( Show, Read, Typeable, Data, Generic ) instance FromJSON Abbreviations where parseJSON (Object v) = Abbreviations <$> parseJSON (Object v) parseJSON (Bool False) = return $ Abbreviations M.empty parseJSON _ = fail "Could not read Abbreviations" type MacroMap = (String,[Element]) data Citation = Citation { citOptions :: [Option] , citSort :: [Sort] , citLayout :: Layout } deriving ( Show, Read, Typeable, Data, Generic ) data Bibliography = Bibliography { bibOptions :: [Option] , bibSort :: [Sort] , bibLayout :: Layout } deriving ( Show, Read, Typeable, Data, Generic ) type Option = (String,String) mergeOptions :: [Option] -> [Option] -> [Option] mergeOptions os = nubBy (\x y -> fst x == fst y) . (++) os data Layout = Layout { layFormat :: Formatting , layDelim :: Delimiter , elements :: [Element] } deriving ( Show, Read, Typeable, Data, Generic ) data Element = Choose IfThen [IfThen] [Element] | Macro String Formatting | Const String Formatting | Variable [String] Form Formatting Delimiter | Term String Form Formatting Bool | Label String Form Formatting Plural | Number String NumericForm Formatting | Names [String] [Name] Formatting Delimiter [Element] | Substitute [Element] | Group Formatting Delimiter [Element] | Date [String] DateForm Formatting Delimiter [DatePart] String deriving ( Show, Read, Eq, Typeable, Data, Generic ) data IfThen = IfThen Condition Match [Element] deriving ( Eq, Show, Read, Typeable, Data, Generic ) data Condition = Condition { isType :: [String] , isSet :: [String] , isNumeric :: [String] , isUncertainDate :: [String] , isPosition :: [String] , disambiguation :: [String] , isLocator :: [String] } deriving ( Eq, Show, Read, Typeable, Data, Generic ) type Delimiter = String data Match = Any | All | None deriving ( Show, Read, Eq, Typeable, Data, Generic ) match :: Match -> [Bool] -> Bool match All = and match Any = or match None = and . map not data DatePart = DatePart { dpName :: String , dpForm :: String , dpRangeDelim :: String , dpFormatting :: Formatting } deriving ( Show, Read, Eq, Typeable, Data, Generic ) defaultDate :: [DatePart] defaultDate = [ DatePart "year" "" "-" emptyFormatting , DatePart "month" "" "-" emptyFormatting , DatePart "day" "" "-" emptyFormatting] data Sort = SortVariable String Sorting | SortMacro String Sorting Int Int String deriving ( Eq, Show, Read, Typeable, Data, Generic ) data Sorting = Ascending String | Descending String deriving ( Read, Show, Eq, Typeable, Data, Generic ) instance Ord Sorting where compare (Ascending []) (Ascending []) = EQ compare (Ascending []) (Ascending _) = GT compare (Ascending _) (Ascending []) = LT compare (Ascending a) (Ascending b) = compare' a b compare (Descending []) (Descending []) = EQ compare (Descending []) (Descending _) = GT compare (Descending _) (Descending []) = LT compare (Descending a) (Descending b) = compare' b a compare _ _ = EQ compare' :: String -> String -> Ordering compare' x y = case (x, y) of ('-':_,'-':_) -> comp (dropPunct y) (dropPunct x) ('-':_, _ ) -> LT (_ ,'-':_) -> GT _ -> comp (dropPunct x) (dropPunct y) where dropPunct = dropWhile isPunctuation #ifdef UNICODE_COLLATION comp a b = T.collate (T.collator T.Current) (T.pack a) (T.pack b) #else comp a b = compareUnicode a b #endif data Form = Long | Short | Count | Verb | VerbShort | Symbol | NotSet deriving ( Eq, Show, Read, Typeable, Data, Generic ) data Gender = Feminine | Masculine | Neuter deriving ( Eq, Show, Read, Typeable, Data, Generic ) data NumericForm = Numeric | Ordinal | Roman | LongOrdinal deriving ( Eq, Show, Read, Typeable, Data, Generic ) data DateForm = TextDate | NumericDate | NoFormDate deriving ( Eq, Show, Read, Typeable, Data, Generic ) data Plural = Contextual | Always | Never deriving ( Eq, Show, Read, Typeable, Data, Generic ) data Name = Name Form Formatting NameAttrs Delimiter [NamePart] | NameLabel Form Formatting Plural | EtAl Formatting String deriving ( Eq, Show, Read, Typeable, Data, Generic ) type NameAttrs = [(String, String)] data NamePart = NamePart String Formatting deriving ( Show, Read, Eq, Typeable, Data, Generic ) isPlural :: Plural -> Int -> Bool isPlural p l = case p of Always -> True Never -> False Contextual -> l > 1 isName :: Name -> Bool isName x = case x of Name {} -> True; _ -> False isNames :: Element -> Bool isNames x = case x of Names {} -> True; _ -> False hasEtAl :: [Name] -> Bool hasEtAl = any isEtAl where isEtAl (EtAl _ _) = True isEtAl _ = False data Formatting = Formatting { prefix :: String , suffix :: String , fontFamily :: String , fontStyle :: String , fontVariant :: String , fontWeight :: String , textDecoration :: String , verticalAlign :: String , textCase :: String , display :: String , quotes :: Quote , stripPeriods :: Bool , noCase :: Bool , noDecor :: Bool , hyperlink :: String -- null for no link } deriving ( Read, Eq, Ord, Typeable, Data, Generic ) -- custom instance to make debugging output less busy instance Show Formatting where show x | x == emptyFormatting = "emptyFormatting" | otherwise = "emptyFormatting{" ++ intercalate ", " [ k ++ " = " ++ f x | (k, f) <- [("prefix", show . prefix) ,("suffix", show . suffix) ,("fontFamily", show . fontFamily) ,("fontStyle", show . fontStyle) ,("fontVariant", show . fontVariant) ,("fontWeight", show . fontWeight) ,("textDecoration", show . textDecoration) ,("verticalAlign", show . verticalAlign) ,("textCase", show . textCase) ,("display", show . display) ,("quotes", show . quotes) ,("stripPeriods", show . stripPeriods) ,("noCase", show . noCase) ,("noDecor", show . noDecor) ,("hyperlink", show . hyperlink)], f x /= f emptyFormatting ] ++ "}" rmTitleCase :: Formatting -> Formatting rmTitleCase f = f{ textCase = if textCase f == "title" then "" else textCase f } data Quote = NativeQuote | ParsedQuote | NoQuote deriving ( Show, Read, Eq, Ord, Typeable, Data, Generic ) emptyFormatting :: Formatting emptyFormatting = Formatting [] [] [] [] [] [] [] [] [] [] NoQuote False False False [] mergeFM :: Formatting -> Formatting -> Formatting mergeFM (Formatting aa ab ac ad ae af ag ah ai aj ak al am an ahl) (Formatting ba bb bc bd be bf bg bh bi bj bk bl bm bn bhl) = Formatting (ba `betterThan` aa) (bb `betterThan` ab) (bc `betterThan` ac) (bd `betterThan` ad) (be `betterThan` ae) (bf `betterThan` af) (bg `betterThan` ag) (bh `betterThan` ah) (bi `betterThan` ai) (bj `betterThan` aj) (if bk == NoQuote then ak else bk) (bl || al) (bm || am) (bn || an) (bhl `mplus` ahl) data CSInfo = CSInfo { csiTitle :: String , csiAuthor :: CSAuthor , csiCategories :: [CSCategory] , csiId :: String , csiUpdated :: String } deriving ( Show, Read, Typeable, Data, Generic ) data CSAuthor = CSAuthor String String String deriving ( Show, Read, Eq, Typeable, Data, Generic ) data CSCategory = CSCategory String String String deriving ( Show, Read, Eq, Typeable, Data, Generic ) data CiteprocError = NoOutput | ReferenceNotFound String deriving ( Eq, Ord, Show, Typeable, Data, Generic ) -- | The 'Output' generated by the evaluation of a style. Must be -- further processed for disambiguation and collapsing. data Output = ONull | OSpace | OPan [Inline] | ODel String -- ^ A delimiter string. | OStr String Formatting -- ^ A simple 'String' | OErr CiteprocError -- ^ Warning message | OLabel String Formatting -- ^ A label used for roles | ONum Int Formatting -- ^ A number (used to count contributors) | OCitNum Int Formatting -- ^ The citation number | OCitLabel String Formatting -- ^ The citation label | ODate [Output] -- ^ A (possibly) ranged date | OYear String String Formatting -- ^ The year and the citeId | OYearSuf String String [Output] Formatting -- ^ The year suffix, the citeId and a holder for collision data | OName Agent [Output] [[Output]] Formatting -- ^ A (family) name with the list of given names. | OContrib String String [Output] [Output] [[Output]] -- ^ The citation key, the role (author, editor, etc.), the contributor(s), -- the output needed for year suf. disambiguation, and everything used for -- name disambiguation. | OLoc [Output] Formatting -- ^ The citation's locator | Output [Output] Formatting -- ^ Some nested 'Output' deriving ( Eq, Ord, Show, Typeable, Data, Generic ) type Citations = [[Cite]] data Cite = Cite { citeId :: String , citePrefix :: Formatted , citeSuffix :: Formatted , citeLabel :: String , citeLocator :: String , citeNoteNumber :: String , citePosition :: String , nearNote :: Bool , authorInText :: Bool , suppressAuthor :: Bool , citeHash :: Int } deriving ( Show, Eq, Typeable, Data, Generic ) instance FromJSON Cite where parseJSON (Object v) = Cite <$> v .#: "id" <*> v .:? "prefix" .!= mempty <*> v .:? "suffix" .!= mempty <*> v .#? "label" .!= "page" <*> v .#? "locator" .!= "" <*> v .#? "note-number" .!= "" <*> v .#? "position" .!= "" <*> (v .:? "near-note" >>= mb parseBool) .!= False <*> (v .:? "author-in-text" >>= mb parseBool) .!= False <*> (v .:? "suppress-author" >>= mb parseBool) .!= False <*> v .:? "cite-hash" .!= 0 parseJSON _ = fail "Could not parse Cite" instance OVERLAPS FromJSON [[Cite]] where parseJSON (Array v) = mapM parseJSON $ V.toList v parseJSON _ = return [] emptyCite :: Cite emptyCite = Cite [] mempty mempty [] [] [] [] False False False 0 -- | A citation group: the first list has a single member when the -- citation group starts with an "author-in-text" cite, the -- 'Formatting' to be applied, the 'Delimiter' between individual -- citations and the list of evaluated citations. data CitationGroup = CG [(Cite, Output)] Formatting Delimiter [(Cite, Output)] deriving ( Show, Eq, Typeable, Data, Generic ) data BiblioData = BD { citations :: [Formatted] , bibliography :: [Formatted] , citationIds :: [String] } deriving ( Show, Typeable, Data, Generic ) -- | A record with all the data to produce the 'Formatted' of a -- citation: the citation key, the part of the formatted citation that -- may be colliding with other citations, the form of the citation -- when a year suffix is used for disambiguation , the data to -- disambiguate it (all possible contributors and all possible given -- names), and, after processing, the disambiguated citation and its -- year, initially empty. data CiteData = CD { key :: String , collision :: [Output] , disambYS :: [Output] , disambData :: [[Output]] , disambed :: [Output] , sameAs :: [String] , citYear :: String } deriving ( Show, Typeable, Data, Generic ) instance Eq CiteData where (==) (CD ka ca _ _ _ _ _) (CD kb cb _ _ _ _ _) = ka == kb && ca == cb data NameData = ND { nameKey :: Agent , nameCollision :: [Output] , nameDisambData :: [[Output]] , nameDataSolved :: [Output] } deriving ( Show, Typeable, Data, Generic ) instance Eq NameData where (==) (ND ka ca _ _) (ND kb cb _ _) = ka == kb && ca == cb isPunctuationInQuote :: Style -> Bool isPunctuationInQuote sty = case styleLocale sty of (l:_) -> ("punctuation-in-quote","true") `elem` localeOptions l _ -> False object' :: [Pair] -> Aeson.Value object' = object . filter (not . isempty) where isempty (_, Array v) = V.null v isempty (_, String t) = T.null t isempty ("first-reference-note-number", Aeson.Number n) = n == 0 isempty ("citation-number", Aeson.Number n) = n == 0 isempty (_, _) = False data Agent = Agent { givenName :: [Formatted] , droppingPart :: Formatted , nonDroppingPart :: Formatted , familyName :: Formatted , nameSuffix :: Formatted , literal :: Formatted , commaSuffix :: Bool , parseNames :: Bool } deriving ( Show, Read, Eq, Ord, Typeable, Data, Generic ) emptyAgent :: Agent emptyAgent = Agent [] mempty mempty mempty mempty mempty False False instance FromJSON Agent where parseJSON (Object v) = nameTransform <$> (Agent <$> (v .: "given" <|> ((map Formatted . wordsBy isSpace . unFormatted) <$> v .: "given") <|> pure []) <*> v .:? "dropping-particle" .!= mempty <*> v .:? "non-dropping-particle" .!= mempty <*> v .:? "family" .!= mempty <*> v .:? "suffix" .!= mempty <*> v .:? "literal" .!= mempty <*> v .:? "comma-suffix" .!= False <*> v .:? "parse-names" .!= False) parseJSON _ = fail "Could not parse Agent" instance ToYaml Agent where toYaml ag = mapping' [ "family" &= familyName ag , case givenName ag of [] -> id xs -> "given" &= Formatted (intercalate [Space] (map unFormatted xs)) , "non-dropping-particle" &= nonDroppingPart ag , "dropping-particle" &= droppingPart ag , "suffix" &= nameSuffix ag , "literal" &= literal ag , "comma-suffix" &= T.pack (if commaSuffix ag then "true" else "") , "parse-names" &= T.pack (if parseNames ag then "true" else "") ] -- See http://gsl-nagoya-u.net/http/pub/citeproc-doc.html#id28 nameTransform :: Agent -> Agent nameTransform ag | parseNames ag = nonDroppingPartTransform . droppingPartTransform . suffixTransform $ ag{ parseNames = False } | otherwise = ag nonDroppingPartTransform :: Agent -> Agent nonDroppingPartTransform ag | nonDroppingPart ag == mempty = case break startWithCapital' (splitStrWhen (\c -> isPunctuation c || isUpper c) $ unFormatted $ familyName ag) of ([], _) -> ag (xs, ys) | lastInline xs `elem` [" ", "-", "'", "’"] -> ag { nonDroppingPart = Formatted $ trimSpace xs, familyName = Formatted ys } | otherwise -> ag | otherwise = ag trimSpace :: [Inline] -> [Inline] trimSpace = reverse . dropWhile isSpace . reverse . dropWhile isSpace isSpace :: Inline -> Bool isSpace Space = True isSpace SoftBreak = True isSpace _ = False droppingPartTransform :: Agent -> Agent droppingPartTransform ag | droppingPart ag == mempty = case break startWithCapital $ reverse $ givenName ag of ([],_) -> ag (ys,zs) -> ag{ droppingPart = mconcat $ intersperse (Formatted [Space]) $ reverse ys , givenName = reverse zs } | otherwise = ag startWithCapital' :: Inline -> Bool startWithCapital' (Str (c:_)) = isUpper c && isLetter c startWithCapital' _ = False startWithCapital :: Formatted -> Bool startWithCapital (Formatted (x:_)) = startWithCapital' x startWithCapital _ = False stripFinalComma :: Formatted -> (String, Formatted) stripFinalComma (Formatted ils) = case reverse $ splitStrWhen isPunctuation ils of Str ",":xs -> (",", Formatted $ reverse xs) Str "!":Str ",":xs -> (",!", Formatted $ reverse xs) _ -> ("", Formatted ils) suffixTransform :: Agent -> Agent suffixTransform ag | nameSuffix ag == mempty = fst $ foldl go (ag{ givenName = mempty , nameSuffix = mempty , commaSuffix = False }, False) (givenName ag) | otherwise = ag where go (ag', False) n = case stripFinalComma n of ("", _) -> (ag'{ givenName = givenName ag' ++ [n] }, False) (",",n') -> (ag'{ givenName = givenName ag' ++ [n'] }, True) (",!",n') -> (ag'{ givenName = givenName ag' ++ [n'] , commaSuffix = True }, True) _ -> error "stripFinalComma returned unexpected value" go (ag', True) n = (ag'{ nameSuffix = if nameSuffix ag' == mempty then n else nameSuffix ag' <> Formatted [Space] <> n }, True) instance ToJSON Agent where toJSON agent = object' $ [ "given" .= Formatted (intercalate [Space] $ map unFormatted $ givenName agent) , "dropping-particle" .= droppingPart agent , "non-dropping-particle" .= nonDroppingPart agent , "family" .= familyName agent , "suffix" .= nameSuffix agent , "literal" .= literal agent ] ++ ["comma-suffix" .= commaSuffix agent | nameSuffix agent /= mempty] ++ ["parse-names" .= True | parseNames agent ] instance OVERLAPS FromJSON [Agent] where parseJSON (Array xs) = mapM parseJSON $ V.toList xs parseJSON (Object v) = (:[]) `fmap` parseJSON (Object v) parseJSON _ = fail "Could not parse [Agent]" -- instance ToJSON [Agent] where -- toJSON xs = Array (V.fromList $ map toJSON xs) pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval.hs0000644000000000000000000005553213053652073016571 0ustar0000000000000000{-# LANGUAGE PatternGuards, FlexibleContexts, ScopedTypeVariables #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval ( evalLayout , evalSorting , module Text.CSL.Eval.Common , module Text.CSL.Eval.Output ) where import Control.Arrow import Control.Monad.State import Data.Monoid (Any(..)) import Data.Char ( toLower, isDigit, isLetter ) import Data.Maybe import Data.String ( fromString ) import Text.Pandoc.Definition (Inline(Str, Link), nullAttr) import Text.Pandoc.Walk (walk) import Text.Pandoc.Shared (stringify) import qualified Data.Text as T import Text.CSL.Eval.Common import Text.CSL.Eval.Output import Text.CSL.Eval.Date import Text.CSL.Eval.Names import Text.CSL.Output.Plain import Text.CSL.Reference import Text.CSL.Style hiding (Any) import Text.CSL.Util ( readNum, last', proc, proc', query, betterThan, safeRead, isRange ) -- | Produce the output with a 'Layout', the 'EvalMode', a 'Bool' -- 'True' if the evaluation happens for disambiguation purposes, the -- 'Locale', the 'MacroMap', the position of the cite and the -- 'Reference'. evalLayout :: Layout -> EvalMode -> Bool -> [Locale] -> [MacroMap] -> [Option] -> Abbreviations -> Maybe Reference -> [Output] evalLayout (Layout _ _ es) em b l m o a mbr = cleanOutput evalOut where evalOut = case evalState job initSt of x | isNothing mbr -> [noBibDataError cit] | null x -> [] | otherwise -> suppTC x locale = case l of [x] -> x _ -> Locale [] [] [] [] [] job = evalElements es cit = case em of EvalCite c -> c EvalSorting c -> c EvalBiblio c -> c initSt = EvalState (mkRefMap mbr) (Env cit (localeTerms locale) m (localeDate locale) o [] a) [] em b False [] [] False [] [] [] suppTC = let getLang = take 2 . map toLower in case (getLang $ localeLang locale, getLang . unLiteral . language <$> mbr) of (_, Just "en") -> id (_, Nothing) -> id ("en", Just "") -> id _ -> proc' rmTitleCase evalSorting :: EvalMode -> [Locale] -> [MacroMap] -> [Option] -> [Sort] -> Abbreviations -> Maybe Reference -> [Sorting] evalSorting m l ms opts ss as mbr = map (format . sorting) ss where render = renderPlain . formatOutputList format (s,e) = applaySort s . render $ uncurry eval e eval o e = evalLayout (Layout emptyFormatting [] [e]) m False l ms o as mbr applaySort c s | Ascending {} <- c = Ascending s | otherwise = Descending s unsetOpts ("et-al-min" ,_) = ("et-al-min" ,"") unsetOpts ("et-al-use-first" ,_) = ("et-al-use-first" ,"") unsetOpts ("et-al-subsequent-min" ,_) = ("et-al-subsequent-min","") unsetOpts ("et-al-subsequent-use-first",_) = ("et-al-subsequent-use-first","") unsetOpts x = x setOpts s i = if i /= 0 then (s, show i) else ([],[]) sorting s = case s of SortVariable str s' -> (s', ( ("name-as-sort-order","all") : opts , Variable [str] Long emptyFormatting [])) SortMacro str s' a b c -> (s', ( setOpts "et-al-min" a : ("et-al-use-last",c) : setOpts "et-al-use-first" b : proc unsetOpts opts , Macro str emptyFormatting)) evalElements :: [Element] -> State EvalState [Output] evalElements = concatMapM evalElement evalElement :: Element -> State EvalState [Output] evalElement el | Const s fm <- el = return $ addSpaces s $ if fm == emptyFormatting then [OPan (readCSLString s)] else [Output [OPan (readCSLString s)] fm] -- NOTE: this conditional seems needed for -- locator_SimpleLocators.json: | Number s f fm <- el = if s == "locator" then getLocVar >>= formatRange fm . snd else formatNumber f fm s =<< getStringVar s | Variable s f fm d <- el = return . addDelim d =<< concatMapM (getVariable f fm) s | Group fm d l <- el = outputList fm d <$> tryGroup l | Date _ _ _ _ _ _ <- el = evalDate el | Label s f fm _ <- el = formatLabel f fm True s -- FIXME !! | Term s f fm p <- el = formatTerm f fm p s | Names s n fm d sub <- el = modify (\st -> st { contNum = [] }) >> ifEmpty (evalNames False s n d) (withNames s el $ evalElements sub) (appendOutput fm) | Substitute (e:els) <- el = do res <- consuming $ substituteWith e if null res then if null els then return [ONull] else evalElement (Substitute els) else return res -- All macros and conditionals should have been expanded | Choose i ei xs <- el = do res <- evalIfThen i ei xs evalElements res | Macro s fm <- el = do ms <- gets (macros . env) case lookup s ms of Nothing -> error $ "Macro " ++ show s ++ " not found!" Just els -> do res <- concat <$> mapM evalElement els if null res then return [] else return [Output res fm] | otherwise = return [] where addSpaces strng = (if take 1 strng == " " then (OSpace:) else id) . (if last' strng == " " then (++[OSpace]) else id) substituteWith e = head <$> gets (names . env) >>= \(Names _ ns fm d _) -> do case e of Names rs [Name NotSet fm'' [] [] []] fm' d' [] -> let nfm = mergeFM fm'' $ mergeFM fm' fm in evalElement $ Names rs ns nfm (d' `betterThan` d) [] _ -> evalElement e -- from citeproc documentation: "cs:group implicitly acts as a -- conditional: cs:group and its child elements are suppressed if -- a) at least one rendering element in cs:group calls a variable -- (either directly or via a macro), and b) all variables that are -- called are empty. This accommodates descriptive cs:text elements." -- TODO: problem, this approach gives wrong results when the variable -- is in a conditional and the other branch is followed. the term -- provided by the other branch (e.g. 'n.d.') is not printed. we -- should ideally expand conditionals when we expand macros. tryGroup l = if getAny $ query hasVar l then do oldState <- get res <- evalElements (rmTermConst l) put oldState let numVars = [s | Number s _ _ <- l] nums <- mapM getStringVar numVars let pluralizeTerm (Term s f fm _) = Term s f fm $ case numVars of ["number-of-volumes"] -> not $ any (== "1") nums ["number-of-pages"] -> not $ any (== "1") nums _ -> any isRange nums pluralizeTerm x = x if null res then return [] else evalElements $ map pluralizeTerm l else evalElements l hasVar e | Variable {} <- e = Any True | Date {} <- e = Any True | Names {} <- e = Any True | Number {} <- e = Any True | otherwise = Any False rmTermConst = proc $ filter (not . isTermConst) isTermConst e | Term {} <- e = True | Const {} <- e = True | otherwise = False ifEmpty p t e = p >>= \r -> if r == [] then t else return (e r) withNames e n f = modify (\s -> s { authSub = e ++ authSub s , env = (env s) {names = n : names (env s)}}) >> f >>= \r -> modify (\s -> s { authSub = filter (not . flip elem e) (authSub s) , env = (env s) {names = tail $ names (env s)}}) >> return r getVariable f fm s | isTitleVar s || isTitleShortVar s = consumeVariable s >> formatTitle s f fm | otherwise = case map toLower s of "year-suffix" -> getStringVar "ref-id" >>= \k -> return . return $ OYearSuf [] k [] fm "page" -> getStringVar "page" >>= formatRange fm "locator" -> getLocVar >>= formatRange fm . snd "url" -> getStringVar "url" >>= \k -> if null k then return [] else return [Output [OPan [Link nullAttr [Str k] (k,"")]] fm] "doi" -> do d <- getStringVar "doi" let (prefixPart, linkPart) = T.breakOn (T.pack "http") (T.pack (prefix fm)) let u = if T.null linkPart then "https://doi.org/" ++ d else T.unpack linkPart ++ d if null d then return [] else return [Output [OPan [Link nullAttr [Str (T.unpack linkPart ++ d)] (u, "")]] fm{ prefix = T.unpack prefixPart, suffix = suffix fm }] "isbn" -> getStringVar "isbn" >>= \d -> if null d then return [] else return [Output [OPan [Link nullAttr [Str d] ("https://worldcat.org/isbn/" ++ d, "")]] fm] "pmid" -> getStringVar "pmid" >>= \d -> if null d then return [] else return [Output [OPan [Link nullAttr [Str d] ("http://www.ncbi.nlm.nih.gov/pubmed/" ++ d, "")]] fm] "pmcid" -> getStringVar "pmcid" >>= \d -> if null d then return [] else return [Output [OPan [Link nullAttr [Str d] ("http://www.ncbi.nlm.nih.gov/pmc/articles/" ++ d, "")]] fm] _ -> do (opts, as) <- gets (env >>> options &&& abbrevs) r <- getVar [] (getFormattedValue opts as f fm s) s consumeVariable s return r evalIfThen :: IfThen -> [IfThen] -> [Element] -> State EvalState [Element] evalIfThen (IfThen c' m' el') ei e = whenElse (evalCond m' c') (return el') rest where rest = case ei of [] -> return e (x:xs) -> evalIfThen x xs e evalCond m c = do t <- checkCond chkType isType c m v <- checkCond isVarSet isSet c m n <- checkCond chkNumeric isNumeric c m d <- checkCond chkDate isUncertainDate c m p <- checkCond chkPosition isPosition c m a <- checkCond chkDisambiguate disambiguation c m l <- checkCond chkLocator isLocator c m return $ match m $ concat [t,v,n,d,p,a,l] checkCond a f c m = case f c of [] -> case m of All -> return [True] _ -> return [False] xs -> mapM a xs chkType t = let chk = (==) (formatVariable t) . show . fromMaybe NoType . fromValue in getVar False chk "ref-type" chkNumeric v = do val <- getStringVar v as <- gets (abbrevs . env) let val' = if getAbbreviation as v val == [] then val else getAbbreviation as v val return (isNumericString val') chkDate v = getDateVar v >>= return . not . null . filter circa chkPosition s = if s == "near-note" then gets (nearNote . cite . env) else gets (citePosition . cite . env) >>= return . compPosition s chkDisambiguate s = gets disamb >>= return . (==) (formatVariable s) . map toLower . show chkLocator v = getLocVar >>= return . (==) v . fst isIbid s = not (s == "first" || s == "subsequent") compPosition a b | "first" <- a = b == "first" | "subsequent" <- a = b /= "first" | "ibid-with-locator" <- a = b == "ibid-with-locator" || b == "ibid-with-locator-c" | otherwise = isIbid b getFormattedValue :: [Option] -> Abbreviations -> Form -> Formatting -> String -> Value -> [Output] getFormattedValue o as f fm s val | Just v <- fromValue val :: Maybe Formatted = if v == mempty then [] else let ys = maybe (unFormatted v) (unFormatted . fromString) $ getAbbr (stringify $ unFormatted v) in if null ys then [] else [Output [OPan $ walk value' ys] fm] | Just v <- fromValue val :: Maybe String = (:[]) . flip OStr fm . maybe v id . getAbbr $ value v | Just v <- fromValue val :: Maybe Literal = (:[]) . flip OStr fm . maybe (unLiteral v) id . getAbbr $ value $ unLiteral v | Just v <- fromValue val :: Maybe Int = output fm (if v == 0 then [] else show v) | Just v <- fromValue val :: Maybe Int = output fm (if v == 0 then [] else show v) | Just v <- fromValue val :: Maybe CNum = if v == 0 then [] else [OCitNum (unCNum v) fm] | Just v <- fromValue val :: Maybe CLabel = if v == mempty then [] else [OCitLabel (unCLabel v) fm] | Just v <- fromValue val :: Maybe [RefDate] = formatDate (EvalSorting emptyCite) [] [] sortDate v | Just v <- fromValue val :: Maybe [Agent] = concatMap (formatName (EvalSorting emptyCite) True f fm nameOpts []) v | otherwise = [] where value = if stripPeriods fm then filter (/= '.') else id value' (Str x) = Str (value x) value' x = x getAbbr v = if f == Short then case getAbbreviation as s v of [] -> Nothing y -> Just y else Nothing nameOpts = ("name-as-sort-order","all") : o sortDate = [ DatePart "year" "numeric-leading-zeros" "" emptyFormatting , DatePart "month" "numeric-leading-zeros" "" emptyFormatting , DatePart "day" "numeric-leading-zeros" "" emptyFormatting] formatTitle :: String -> Form -> Formatting -> State EvalState [Output] formatTitle s f fm | Short <- f , isTitleVar s = try (getIt $ s ++ "-short") $ getIt s | isTitleShortVar s = try (getIt s) $ return . (:[]) . flip OStr fm =<< getTitleShort s | otherwise = getIt s where try g h = g >>= \r -> if r == [] then h else return r getIt x = do o <- gets (options . env) a <- gets (abbrevs . env) getVar [] (getFormattedValue o a f fm x) x formatNumber :: NumericForm -> Formatting -> String -> String -> State EvalState [Output] formatNumber f fm v n = gets (abbrevs . env) >>= \as -> if isNumericString (getAbbr as n) then gets (terms . env) >>= return . output fm . flip process (getAbbr as n) else return . output fm . getAbbr as $ n where getAbbr as = if getAbbreviation as v n == [] then id else getAbbreviation as v checkRange' ts = if v == "page" then checkRange ts else id process ts = checkRange' ts . printNumStr . map (renderNumber ts) . breakNumericString . words renderNumber ts x = if isTransNumber x then format ts x else x format tm = case f of Ordinal -> ordinal tm v LongOrdinal -> longOrdinal tm v Roman -> if readNum n < 6000 then roman else id _ -> id roman = foldr (++) [] . reverse . map (uncurry (!!)) . zip romanList . map (readNum . return) . take 4 . reverse romanList = [[ "", "i", "ii", "iii", "iv", "v", "vi", "vii", "viii", "ix" ] ,[ "", "x", "xx", "xxx", "xl", "l", "lx", "lxx", "lxxx", "xc" ] ,[ "", "c", "cc", "ccc", "cd", "d", "dc", "dcc", "dccc", "cm" ] ,[ "", "m", "mm", "mmm", "mmmm", "mmmmm"] ] checkRange :: [CslTerm] -> String -> String checkRange _ [] = [] checkRange ts (x:xs) = if x == '-' || x == '\x2013' then pageRange ts ++ checkRange ts xs else x : checkRange ts xs printNumStr :: [String] -> String printNumStr [] = [] printNumStr (x:[]) = x printNumStr (x:"-":y:xs) = x ++ "-" ++ y ++ printNumStr xs printNumStr (x:",":y:xs) = x ++ ", " ++ y ++ printNumStr xs printNumStr (x:xs) | x == "-" = x ++ printNumStr xs | otherwise = x ++ " " ++ printNumStr xs pageRange :: [CslTerm] -> String pageRange = maybe "\x2013" termPlural . findTerm "page-range-delimiter" Long isNumericString :: String -> Bool isNumericString [] = False isNumericString s = all (\c -> isNumber c || isSpecialChar c) $ words s isTransNumber, isSpecialChar,isNumber :: String -> Bool isTransNumber = all isDigit isSpecialChar = all (`elem` "&-,.\x2013") isNumber cs = case [c | c <- cs , not (isLetter c) , not (c `elem` "&-.,\x2013")] of [] -> False xs -> all isDigit xs breakNumericString :: [String] -> [String] breakNumericString [] = [] breakNumericString (x:xs) | isTransNumber x = x : breakNumericString xs | otherwise = let (a,b) = break (`elem` "&-\x2013,") x (c,d) = if null b then ("","") else span (`elem` "&-\x2013,") b in filter (/= []) $ a : c : breakNumericString (d : xs) formatRange :: Formatting -> String -> State EvalState [Output] formatRange _ [] = return [] formatRange fm p = do ops <- gets (options . env) ts <- gets (terms . env) let opt = getOptionVal "page-range-format" ops pages = tupleRange . breakNumericString . words $ p tupleRange [] = [] tupleRange (x:cs:[] ) | cs `elem` ["-", "--", "\x2013"] = return (x,[]) tupleRange (x:cs:y:xs) | cs `elem` ["-", "--", "\x2013"] = (x, y) : tupleRange xs tupleRange (x: xs) = (x,[]) : tupleRange xs joinRange (a, []) = a joinRange (a, b) = a ++ "-" ++ b process = checkRange ts . printNumStr . case opt of "expanded" -> map (joinRange . expandedRange) "chicago" -> map (joinRange . chicagoRange ) "minimal" -> map (joinRange . minimalRange 1) "minimal-two" -> map (joinRange . minimalRange 2) _ -> map joinRange return [flip OLoc fm $ [OStr (process pages) emptyFormatting]] -- Abbreviated page ranges are expanded to their non-abbreviated form: -- 42–45, 321–328, 2787–2816 expandedRange :: (String, String) -> (String, String) expandedRange (sa, []) = (sa,[]) expandedRange (sa, sb) | length sb < length sa = case (safeRead sa, safeRead sb) of -- check to make sure we have regular numbers (Just (_ :: Int), Just (_ :: Int)) -> (sa, take (length sa - length sb) sa ++ sb) _ -> (sa, sb) | otherwise = (sa, sb) -- All digits repeated in the second number are left out: -- 42–5, 321–8, 2787–816. The minDigits parameter indicates -- a minimum number of digits for the second number; thus, with -- minDigits = 2, we have 328-28. minimalRange :: Int -> (String, String) -> (String, String) minimalRange minDigits ((a:as), (b:bs)) | a == b , length as == length bs , length bs >= minDigits = let (_, bs') = minimalRange minDigits (as, bs) in (a:as, bs') minimalRange _ (as, bs) = (as, bs) -- Page ranges are abbreviated according to the Chicago Manual of Style-rules: -- First number Second number Examples -- Less than 100 Use all digits 3–10; 71–72 -- 100 or multiple of 100 Use all digits 100–104; 600–613; 1100–1123 -- 101 through 109 (in multiples of 100) Use changed part only 10002-6, 505-17 -- 110 through 199 Use 2 digits or more 321-25, 415-532 -- if numbers are 4 digits long or more and 3 digits change, use all digits -- 1496-1504 chicagoRange :: (String, String) -> (String, String) chicagoRange (sa, sb) = case (safeRead sa :: Maybe Int) of Just n | n < 100 -> expandedRange (sa, sb) | n `mod` 100 == 0 -> expandedRange (sa, sb) | n >= 1000 -> let (sa', sb') = minimalRange 1 (sa, sb) in if length sb' >= 3 then expandedRange (sa, sb) else (sa', sb') | n > 100 -> if n `mod` 100 < 10 then minimalRange 1 (sa, sb) else minimalRange 2 (sa, sb) _ -> expandedRange (sa, sb) pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval/Common.hs0000644000000000000000000001537213003500055020002 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} #if MIN_VERSION_base(4,9,0) {-# OPTIONS_GHC -fno-warn-redundant-constraints #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval.Common -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval.Common where import Control.Arrow ( (&&&), (>>>) ) import Control.Monad.State import Data.Char ( toLower ) import Data.List ( elemIndex ) import qualified Data.Map as M import Data.Maybe import Text.Pandoc.Shared ( stringify ) import Text.CSL.Reference import Text.CSL.Style import Debug.Trace data EvalState = EvalState { ref :: ReferenceMap , env :: Environment , debug :: [String] , mode :: EvalMode , disamb :: Bool , consume :: Bool , authSub :: [String] , consumed :: [String] , edtrans :: Bool , etal :: [[Output]] , contNum :: [Agent] , lastName :: [Output] } deriving ( Show ) data Environment = Env { cite :: Cite , terms :: [CslTerm] , macros :: [MacroMap] , dates :: [Element] , options :: [Option] , names :: [Element] , abbrevs :: Abbreviations } deriving ( Show ) data EvalMode = EvalSorting Cite | EvalCite Cite | EvalBiblio Cite -- for the reference position deriving ( Show, Eq ) isSorting :: EvalMode -> Bool isSorting m = case m of EvalSorting _ -> True; _ -> False -- | With the variable name and the variable value search for an -- abbreviation or return an empty string. getAbbreviation :: Abbreviations -> String -> String -> String getAbbreviation (Abbreviations as) s v = maybe [] id $ M.lookup "default" as >>= M.lookup (if s `elem` numericVars then "number" else s) >>= M.lookup v -- | If the first parameter is 'True' the plural form will be retrieved. getTerm :: Bool -> Form -> String -> State EvalState String getTerm b f s = maybe [] g . findTerm s f' <$> gets (terms . env) -- FIXME: vedere i fallback where g = if b then termPlural else termSingular f' = case f of NotSet -> Long; _ -> f getStringVar :: String -> State EvalState String getStringVar = getVar [] getStringValue getDateVar :: String -> State EvalState [RefDate] getDateVar = getVar [] getDateValue where getDateValue = maybe [] id . fromValue getLocVar :: State EvalState (String,String) getLocVar = gets (env >>> cite >>> citeLabel &&& citeLocator) getVar :: a -> (Value -> a) -> String -> State EvalState a getVar a f s = withRefMap $ maybe a f . lookup (formatVariable s) getAgents :: String -> State EvalState [Agent] getAgents s = do mv <- withRefMap (lookup s) case mv of Just v -> case fromValue v of Just x -> consumeVariable s >> return x _ -> return [] _ -> return [] getAgents' :: String -> State EvalState [Agent] getAgents' s = do mv <- withRefMap (lookup s) case mv of Just v -> case fromValue v of Just x -> return x _ -> return [] _ -> return [] getStringValue :: Value -> String getStringValue val = -- The second clause handles the case where we have a Formatted -- but need a String. This is currently needed for "page". It's a bit -- hackish; we should probably change the type in Reference for -- page to String. case fromValue val `mplus` ((stringify . unFormatted) `fmap` fromValue val) `mplus` (unLiteral `fmap` fromValue val) of Just v -> v Nothing -> Debug.Trace.trace ("Expecting string value, got " ++ show val) [] getOptionVal :: String -> [Option] -> String getOptionVal s = fromMaybe [] . lookup s isOptionSet :: String -> [Option] -> Bool isOptionSet s = maybe False (not . null) . lookup s isTitleVar, isTitleShortVar :: String -> Bool isTitleVar = flip elem ["title", "container-title", "collection-title"] isTitleShortVar = flip elem ["title-short", "container-title-short"] getTitleShort :: String -> State EvalState String getTitleShort s = do let s' = take (length s - 6) s -- drop '-short' v <- getStringVar s' abbrs <- gets (abbrevs . env) return $ getAbbreviation abbrs s' v isVarSet :: String -> State EvalState Bool isVarSet s | isTitleShortVar s = do r <- getVar False isValueSet s if r then return r else return . not . null =<< getTitleShort s | otherwise = if s /= "locator" then getVar False isValueSet s else getLocVar >>= return . (/=) "" . snd withRefMap :: (ReferenceMap -> a) -> State EvalState a withRefMap f = return . f =<< gets ref -- | Convert variable to lower case, translating underscores ("_") to dashes ("-") formatVariable :: String -> String formatVariable = foldr f [] where f x xs = if x == '_' then '-' : xs else toLower x : xs consumeVariable :: String -> State EvalState () consumeVariable s = do b <- gets consume when b $ modify $ \st -> st { consumed = s : consumed st } consuming :: State EvalState a -> State EvalState a consuming f = setConsume >> f >>= \a -> doConsume >> unsetConsume >> return a where setConsume = modify $ \s -> s {consume = True, consumed = [] } unsetConsume = modify $ \s -> s {consume = False } doConsume = do sl <- gets consumed modify $ \st -> st { ref = remove (ref st) sl } doRemove s (k,v) = if isValueSet v then [(formatVariable s,Value Empty)] else [(k,v)] remove rm sl | (s:ss) <- sl = case elemIndex (formatVariable s) (map fst rm) of Just i -> let nrm = take i rm ++ doRemove s (rm !! i) ++ drop (i + 1) rm in remove nrm ss Nothing -> remove rm ss | otherwise = rm when' :: Monad m => m Bool -> m [a] -> m [a] when' p f = whenElse p f (return []) whenElse :: Monad m => m Bool -> m a -> m a -> m a whenElse b f g = b >>= \ bool -> if bool then f else g concatMapM :: (Monad m, Functor m, Eq b) => (a -> m [b]) -> [a] -> m [b] concatMapM f l = concat . filter (/=[]) <$> mapM f l {- trace :: String -> State EvalState () trace d = modify $ \s -> s { debug = d : debug s } -} pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval/Date.hs0000644000000000000000000002715212743760365017454 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval.Date -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval.Date where import Control.Monad.State import Data.Char import Data.List import Data.List.Split import Data.Maybe import Text.CSL.Eval.Common import Text.CSL.Eval.Output import Text.CSL.Style import Text.CSL.Reference import Text.CSL.Util ( readNum, toRead, init', last' ) import Text.Pandoc.Definition ( Inline (Str) ) evalDate :: Element -> State EvalState [Output] evalDate (Date s f fm dl dp dp') = do tm <- gets $ terms . env k <- getStringVar "ref-id" em <- gets mode let updateFM (Formatting aa ab ac ad ae af ag ah ai aj ak al am an ahl) (Formatting _ _ bc bd be bf bg bh _ bj bk _ _ _ _) = Formatting aa ab (updateS ac bc) (updateS ad bd) (updateS ae be) (updateS af bf) (updateS ag bg) (updateS ah bh) ai (updateS aj bj) (if bk /= ak then bk else ak) al am an ahl updateS a b = if b /= a && b /= [] then b else a case f of NoFormDate -> mapM getDateVar s >>= return . outputList fm dl . concatMap (formatDate em k tm dp . concatMap parseRefDate) _ -> do Date _ _ lfm ldl ldp _ <- getDate f let go dps = return . outputList (updateFM fm lfm) (if ldl /= [] then ldl else dl) . concatMap (formatDate em k tm dps . concatMap parseRefDate) update l x@(DatePart a b c d) = case filter ((==) a . dpName) l of (DatePart _ b' c' d':_) -> DatePart a (updateS b b') (updateS c c') (updateFM d d') _ -> x updateDP = map (update dp) ldp date = mapM getDateVar s case dp' of "year-month" -> go (filter ((/=) "day" . dpName) updateDP) =<< date "year" -> go (filter ((==) "year" . dpName) updateDP) =<< date _ -> go updateDP =<< date evalDate _ = return [] getDate :: DateForm -> State EvalState Element getDate f = do x <- filter (\(Date _ df _ _ _ _) -> df == f) <$> gets (dates . env) case x of [x'] -> return x' _ -> return $ Date [] NoFormDate emptyFormatting [] [] [] formatDate :: EvalMode -> String -> [CslTerm] -> [DatePart] -> [RefDate] -> [Output] formatDate em k tm dp date | [d] <- date = concatMap (formatDatePart False d) dp | (a:b:_) <- date = addODate . concat $ doRange a b | otherwise = [] where addODate [] = [] addODate xs = [ODate xs] splitDate a b = case split (onSublist $ diff a b dp) dp of [x,y,z] -> (x,y,z) _ -> error "error in splitting date ranges" doRange a b = let (x,y,z) = splitDate a b in map (formatDatePart False a) x ++ map (formatDatePart False a) (init' y) ++ map (formatDatePart True a) (last' y) ++ map (formatDatePart False b) (rmPrefix y) ++ map (formatDatePart False b) z -- the point of rmPrefix is to remove the blank space that otherwise -- gets added after the delimiter in a range: 24- 26. rmPrefix (dp':rest) = dp'{ dpFormatting = (dpFormatting dp') { prefix = "" } } : rest rmPrefix [] = [] diff a b = filter (flip elem (diffDate a b) . dpName) diffDate (RefDate ya ma sa da _ _) (RefDate yb mb sb db _ _) = case () of _ | ya /= yb -> ["year","month","day"] | ma /= mb -> if da == mempty && db == mempty then ["month"] else ["month","day"] | da /= db -> ["day"] | sa /= sb -> ["month"] | otherwise -> ["year","month","day"] term f t = let f' = if f `elem` ["verb", "short", "verb-short", "symbol"] then read $ toRead f else Long in maybe [] termPlural $ findTerm t f' tm addZero n = if length n == 1 then '0' : n else n addZeros = reverse . take 5 . flip (++) (repeat '0') . reverse formatDatePart False (RefDate (Literal y) (Literal m) (Literal e) (Literal d) _ _) (DatePart n f _ fm) | "year" <- n, y /= mempty = return $ OYear (formatYear f y) k fm | "month" <- n, m /= mempty = output fm (formatMonth f fm m) | "day" <- n, d /= mempty = output fm (formatDay f m d) | "month" <- n, m == mempty , e /= mempty = output fm $ term f ("season-0" ++ e) formatDatePart True (RefDate (Literal y) (Literal m) (Literal e) (Literal d) _ _) (DatePart n f rd fm) | "year" <- n, y /= mempty = OYear (formatYear f y) k (fm {suffix = []}) : formatDelim | "month" <- n, m /= mempty = output (fm {suffix = []}) (formatMonth f fm m) ++ formatDelim | "day" <- n, d /= mempty = output (fm {suffix = []}) (formatDay f m d) ++ formatDelim | "month" <- n, m == mempty , e /= mempty = output (fm {suffix = []}) (term f $ "season-0" ++ e) ++ formatDelim where formatDelim = if rd == "-" then [OPan [Str "\x2013"]] else [OPan [Str rd]] formatDatePart _ (RefDate _ _ _ _ (Literal o) _) (DatePart n _ _ fm) | "year" <- n, o /= mempty = output fm o | otherwise = [] formatYear f y | "short" <- f = drop 2 y | isSorting em , iy < 0 = '-' : addZeros (tail y) | isSorting em = addZeros y | iy < 0 = show (abs iy) ++ term [] "bc" | length y < 4 , iy /= 0 = y ++ term [] "ad" | iy == 0 = [] | otherwise = y where iy = readNum y formatMonth f fm m | "short" <- f = getMonth $ period . termPlural | "long" <- f = getMonth termPlural | "numeric" <- f = m | otherwise = addZero m where period = if stripPeriods fm then filter (/= '.') else id getMonth g = maybe m g $ findTerm ("month-" ++ addZero m) (read $ toRead f) tm formatDay f m d | "numeric-leading-zeros" <- f = addZero d | "ordinal" <- f = ordinal tm ("month-" ++ addZero m) d | otherwise = d ordinal :: [CslTerm] -> String -> String -> String ordinal _ _ [] = [] ordinal ts v s | length s == 1 = let a = termPlural (getWith1 s) in if a == [] then setOrd (term []) else s ++ a | length s == 2 = let a = termPlural (getWith2 s) b = getWith1 [last s] in if a /= [] then s ++ a else if termPlural b == [] || (termMatch b /= [] && termMatch b /= "last-digit") then setOrd (term []) else setOrd b | otherwise = let a = getWith2 last2 b = getWith1 [last s] in if termPlural a /= [] && termMatch a /= "whole-number" then setOrd a else if termPlural b == [] || (termMatch b /= [] && termMatch b /= "last-digit") then setOrd (term []) else setOrd b where setOrd = (++) s . termPlural getWith1 = term . (++) "-0" getWith2 = term . (++) "-" last2 = reverse . take 2 . reverse $ s term t = getOrdinal v ("ordinal" ++ t) ts longOrdinal :: [CslTerm] -> String -> String -> String longOrdinal _ _ [] = [] longOrdinal ts v s | num > 10 || num == 0 = ordinal ts v s | otherwise = case last s of '1' -> term "01" '2' -> term "02" '3' -> term "03" '4' -> term "04" '5' -> term "05" '6' -> term "06" '7' -> term "07" '8' -> term "08" '9' -> term "09" _ -> term "10" where num = readNum s term t = termPlural $ getOrdinal v ("long-ordinal-" ++ t) ts getOrdinal :: String -> String -> [CslTerm] -> CslTerm getOrdinal v s ts = case findTerm' s Long gender ts of Just x -> x Nothing -> case findTerm' s Long Neuter ts of Just x -> x Nothing -> newTerm where gender = if v `elem` numericVars || "month" `isPrefixOf` v then maybe Neuter termGender $ findTerm v Long ts else Neuter parseRefDate :: RefDate -> [RefDate] parseRefDate r@(RefDate _ _ _ _ (Literal o) c) = if null o then return r else let (a,b) = break (== '-') o in if null b then return (parseRaw o) else [parseRaw a, parseRaw b] where parseRaw str = case words $ check str of [y'] | and (map isDigit y') -> RefDate (Literal y') mempty mempty mempty (Literal o) c [s',y'] | and (map isDigit y') , and (map isDigit s') -> RefDate (Literal y') (Literal s') mempty mempty (Literal o) c [s',y'] | s' `elem'` seasons -> RefDate (Literal y') mempty (Literal $ select s' seasons) mempty (Literal o) False [s',y'] | s' `elem'` months -> RefDate (Literal y') (Literal $ select s' months) mempty mempty (Literal o) c [s',d',y'] | and (map isDigit s') , and (map isDigit y') , and (map isDigit d') -> RefDate (Literal y') (Literal s') mempty (Literal d') (Literal o) c [s',d',y'] | s' `elem'` months , and (map isDigit y') , and (map isDigit d') -> RefDate (Literal y') (Literal $ select s' months) mempty (Literal d') (Literal o) c [s',d',y'] | s' `elem'` months , and (map isDigit y') , and (map isDigit d') -> RefDate (Literal y') (Literal $ select s' months) mempty (Literal d') (Literal o) c _ -> r check [] = [] check (x:xs) = if x `elem` ",/-" then ' ' : check xs else x : check xs select x = show . (+ 1) . fromJust . elemIndex' x elem' x = elem (map toLower $ take 3 x) elemIndex' x = elemIndex (map toLower $ take 3 x) months = ["jan","feb","mar","apr","may","jun","jul","aug","sep","oct","nov","dec"] seasons = ["spr","sum","fal","win"] pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval/Names.hs0000644000000000000000000004441213042725742017631 0ustar0000000000000000{-# LANGUAGE PatternGuards, FlexibleContexts #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval.Names -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval.Names where import Control.Monad.State import Data.Char ( isLower, isUpper, isLetter ) import Data.List ( nub, intersperse ) import Data.List.Split ( wordsBy ) import Data.Maybe ( isJust ) import Text.CSL.Eval.Common import Text.CSL.Eval.Output import Text.CSL.Util ( headInline, lastInline, readNum, (<^>), query, toRead, splitStrWhen, isRange ) import Text.CSL.Style import Text.Pandoc.Definition import Text.Pandoc.Shared ( stringify ) import qualified Text.Pandoc.Builder as B evalNames :: Bool -> [String] -> [Name] -> String -> State EvalState [Output] evalNames skipEdTrans ns nl d | [sa,sb] <- ns, not skipEdTrans , (sa == "editor" && sb == "translator") || (sb == "editor" && sa == "translator") = do aa <- getAgents' sa ab <- getAgents' sb if not (null aa) && aa == ab then modify (\s -> s { edtrans = True }) >> evalNames True [sa] nl d else evalNames True ns nl d | (s:xs) <- ns = do resetEtal ags <- getAgents s k <- getStringVar "ref-id" p <- gets (citePosition . cite . env) ops <- gets (options . env) aus <- gets authSub r <- do res <- agents p s ags st <- get fb <- agents "subsequent" s ags put st if null res then return [] else let role = if aus == ["author"] then "authorsub" else s in return . return . OContrib k role res fb =<< gets etal r' <- evalNames skipEdTrans xs nl d num <- gets contNum return $ if r /= [] && r' /= [] then count num (r ++ [ODel $ delim ops] ++ r') else count num $ cleanOutput (r ++ r') | otherwise = return [] where agents p s a = concatMapM (formatNames (hasEtAl nl) d p s a) nl delim ops = if d == [] then getOptionVal "names-delimiter" ops else d resetEtal = modify (\s -> s { etal = [] }) count num x = if hasCount nl && num /= [] -- FIXME!! le zero!! then [OContrib [] [] [ONum (length num) emptyFormatting] [] []] else x hasCount = or . query hasCount' hasCount' n | Name Count _ _ _ _ <- n = [True] | otherwise = [False] -- | The 'Bool' is 'True' when formatting a name with a final "et-al". -- The first 'String' represents the position and the second the role -- (e.i. editor, translator, etc.). formatNames :: Bool -> Delimiter -> String -> String -> [Agent] -> Name -> State EvalState [Output] formatNames ea del p s as n | Name f _ ns _ _ <- n, Count <- f = do b <- isBib <$> gets mode o <- gets (options . env) >>= return . mergeOptions ns modify $ \st -> st { contNum = nub $ (++) (take (snd $ isEtAl b o p as) as) $ contNum st } return [] | Name f fm ns d np <- n = do b <- isBib <$> gets mode o <- gets (options . env) >>= return . mergeOptions ns m <- gets mode let odel = if del /= [] then del else getOptionVal "name-delimiter" o del' = if d /= [] then d else if odel == [] then ", " else odel (_,i) = isEtAl b o p as form = case f of NotSet -> case getOptionVal "name-form" o of [] -> Long x -> read $ toRead x _ -> f genName x = do etal' <- formatEtAl o ea "et-al" fm del' x if null etal' then do t <- getTerm False Long "and" return $ delim t o del' $ format m o form fm np x else return $ (addDelim del' $ format m o form fm np x) ++ etal' setLastName o $ formatName m False f fm o np (last as) updateEtal =<< mapM genName [1 + i .. length as] genName i | NameLabel f fm pl <- n = when' (isVarSet s) $ do b <- gets edtrans res <- formatLabel f fm (isPlural pl $ length as) $ if b then "editortranslator" else s modify $ \st -> st { edtrans = False } -- Note: the following line was here previously. -- It produces spurious 'et al's and seems to have no function, -- so I have commented it out: -- updateEtal [tr' "res" res] return res | EtAl fm t <- n = do o <- gets (options . env) et <- gets etal let i = length as - length et t' = if null t then "et-al" else t r <- mapM (et_al o False t' fm del) [i .. length as] let (r',r'') = case r of (x:xs) -> (x, xs) [] -> ([],[]) updateEtal r'' return r' | otherwise = return [] where isBib (EvalBiblio _) = True isBib _ = False updateEtal x = modify $ \st -> let x' = if length x == 1 then repeat $ head x else x in st { etal = case etal st of [] -> x ys -> zipWith (++) ys x' } isWithLastName os | "true" <- getOptionVal "et-al-use-last" os , em <- readNum $ getOptionVal "et-al-min" os , uf <- readNum $ getOptionVal "et-al-use-first" os , em - uf > 1 = True | otherwise = False setLastName os x | as /= [] , isWithLastName os = modify $ \st -> st { lastName = x} | otherwise = return () format m os f fm np i | (a:xs) <- take i as = formatName m True f fm os np a ++ concatMap (formatName m False f fm os np) xs | otherwise = concatMap (formatName m True f fm os np) . take i $ as delim t os d x | "always" <- getOptionVal "delimiter-precedes-last" os , length x == 2 = addDelim d (init x) ++ ODel (d <^> andStr t os) : [last x] | length x == 2 = addDelim d (init x) ++ ODel (andStr' t d os) : [last x] | "never" <- getOptionVal "delimiter-precedes-last" os , length x > 2 = addDelim d (init x) ++ ODel (andStr' t d os) : [last x] | length x > 2 = addDelim d (init x) ++ ODel (d <^> andStr t os) : [last x] | otherwise = addDelim d x andStr t os | "text" <- getOptionVal "and" os = " " ++ t ++ " " | "symbol" <- getOptionVal "and" os = " & " | otherwise = [] andStr' t d os = if andStr t os == [] then d else andStr t os formatEtAl o b t fm d i = do ln <- gets lastName if isWithLastName o then case () of _ | (length as - i) == 1 -> et_al o b t fm d i -- is that correct? FIXME later | (length as - i) > 1 -> return $ [ODel d, OPan [Str "\x2026"], OSpace] ++ ln | otherwise -> return [] else et_al o b t fm d i et_al o b t fm d i = when' (gets mode >>= return . not . isSorting) $ if (b || length as <= i) then return [] else do x <- getTerm False Long t when' (return $ x /= []) $ case getOptionVal "delimiter-precedes-et-al" o of "never" -> return . (++) [OSpace] $ output fm x "always" -> return . (++) [ODel d] $ output fm x _ -> if i > 1 && not (null d) then return . (++) [ODel d] $ output fm x else return . (++) [OSpace] $ output fm x -- | The first 'Bool' is 'True' if we are evaluating the bibliography. -- The 'String' is the cite position. The function also returns the -- number of contributors to be displayed. isEtAl :: Bool -> [Option] -> String -> [Agent] -> (Bool, Int) isEtAl b os p as | p /= "first" , isOptionSet "et-al-subsequent-min" os , isOptionSet "et-al-subsequent-use-first" os , le <- etAlMin "et-al-subsequent-min" , le' <- etAlMin "et-al-subsequent-use-first" , length as >= le , length as > le' = (,) True le' | isOptionSet' "et-al-min" "et-al-subsequent-min" , isOptionSet' "et-al-use-first" "et-al-subsequent-use-first" , le <- etAlMin' "et-al-min" "et-al-subsequent-min" , le' <- etAlMin' "et-al-use-first" "et-al-subsequent-use-first" , length as >= le , length as > le' = (,) True le' | isOptionSet' "et-al-min" "et-al-subsequent-min" , le <- etAlMin' "et-al-min" "et-al-subsequent-min" , length as >= le , length as > 1 = (,) True getUseFirst | otherwise = (,) False $ length as where etAlMin x = read $ getOptionVal x os etAlMin' x y = if b then etAlMin x else read $ getOptionVal' x y isOptionSet' s1 s2 = if b then isOptionSet s1 os else or $ (isOptionSet s1 os) : [(isOptionSet s2 os)] getOptionVal' s1 s2 = if null (getOptionVal s1 os) then getOptionVal s2 os else getOptionVal s1 os getUseFirst = let u = if b then getOptionVal "et-al-use-first" os else getOptionVal' "et-al-use-first" "et-al-subsequent-min" in if null u then 1 else read u -- | Generate the 'Agent's names applying et-al options, with all -- possible permutations to disambiguate colliding citations. The -- 'Bool' indicate whether we are formatting the first name or not. formatName :: EvalMode -> Bool -> Form -> Formatting -> [Option] -> [NamePart] -> Agent -> [Output] formatName m b f fm ops np n | literal n /= mempty = return $ OName n institution [] fm | Short <- f = return $ OName n shortName disambdata fm | otherwise = return $ OName n (longName given) disambdata fm where institution = oPan' (unFormatted $ literal n) (form "family") when_ c o = if c /= mempty then o else mempty addAffixes (Formatted []) _ [] = [] addAffixes s sf ns = [Output (Output [OPan (unFormatted s)] (form sf){ prefix = mempty, suffix = mempty} : ns) emptyFormatting { prefix = prefix (form sf) , suffix = suffix (form sf)}] form s = case filter (\(NamePart n' _) -> n' == s) np of NamePart _ fm':_ -> fm' _ -> emptyFormatting hyphenate new [] = new hyphenate new accum = if getOptionVal "initialize-with-hyphen" ops == "false" then new ++ accum else trimsp new ++ [Str "-"] ++ accum isInit [Str [c]] = isUpper c isInit _ = False initial (Formatted x) = case lookup "initialize-with" ops of Just iw | getOptionVal "initialize" ops == "false" , isInit x -> addIn x $ B.toList $ B.text iw | getOptionVal "initialize" ops /= "false" , not (all isLower $ query (:[]) x) -> addIn x $ B.toList $ B.text iw Nothing | isInit x -> addIn x [Space] -- default _ -> Space : x ++ [Space] addIn x i = foldr hyphenate [] $ map (\z -> Str (headInline z) : i) $ wordsBy (== Str "-") $ splitStrWhen (=='-') x sortSep g s = when_ g $ separator ++ addAffixes (g <+> s) "given" mempty separator = if null (getOptionVal "sort-separator" ops) then [OPan [Str ",", Space]] else [OPan $ B.toList $ B.text $ getOptionVal "sort-separator" ops] suff = if commaSuffix n && nameSuffix n /= mempty then suffCom else suffNoCom suffCom = when_ (nameSuffix n) $ separator ++ oPan' (unFormatted $ nameSuffix n) fm suffNoCom = when_ (nameSuffix n) $ OSpace : oPan' (unFormatted $ nameSuffix n) fm onlyGiven = not (givenName n == mempty) && family == mempty given = if onlyGiven then givenLong else when_ (givenName n) . Formatted . trimsp . fixsp . concatMap initial $ givenName n fixsp (Space:Space:xs) = fixsp (Space:xs) fixsp (x:xs) = x : fixsp xs fixsp [] = [] trimsp = reverse . dropWhile (==Space) . reverse . dropWhile (==Space) givenLong = when_ (givenName n) . mconcat . intersperse (Formatted [Space]) $ givenName n family = familyName n dropping = droppingPart n nondropping = nonDroppingPart n -- see src/load.js ROMANESQUE_REGEX in citeproc-js: isByzantine c = not (isLetter c) || c <= '\x5FF' || (c >= '\x1e00' && c <= '\x1fff') shortName = oPan' (unFormatted $ nondropping <+> family) (form "family") longName g = if isSorting m then let firstPart = case getOptionVal "demote-non-dropping-particle" ops of "never" -> nondropping <+> family <+> dropping _ -> family <+> dropping <+> nondropping in oPan' (unFormatted firstPart) (form "family") <++> oPan' (unFormatted g) (form "given") <> suffCom else if (b && getOptionVal "name-as-sort-order" ops == "first") || getOptionVal "name-as-sort-order" ops == "all" then let (fam,par) = case getOptionVal "demote-non-dropping-particle" ops of "never" -> (nondropping <+> family, dropping) "sort-only" -> (nondropping <+> family, dropping) _ -> (family, dropping <+> nondropping) in oPan' (unFormatted fam) (form "family") <> sortSep g par <> suffCom else let fam = addAffixes (dropping <+> nondropping <+> family) "family" suff gvn = oPan' (unFormatted g) (form "given") in if all isByzantine $ stringify $ unFormatted family then gvn <++> fam else fam <> gvn disWithGiven = getOptionVal "disambiguate-add-givenname" ops == "true" initialize = isJust (lookup "initialize-with" ops) && not onlyGiven isLong = f /= Short && initialize givenRule = let gr = getOptionVal "givenname-disambiguation-rule" ops in if null gr then "by-cite" else gr disambdata = case () of _ | "all-names-with-initials" <- givenRule , disWithGiven, Short <- f, initialize -> [longName given] | "primary-name-with-initials" <- givenRule , disWithGiven, Short <- f, initialize, b -> [longName given] | disWithGiven, Short <- f, b , "primary-name" <- givenRule -> [longName given, longName givenLong] | disWithGiven, Short <- f , "all-names" <- givenRule -> [longName given, longName givenLong] | disWithGiven, Short <- f , "by-cite" <- givenRule -> [longName given, longName givenLong] | disWithGiven, isLong -> [longName givenLong] | otherwise -> [] formatTerm :: Form -> Formatting -> Bool -> String -> State EvalState [Output] formatTerm f fm p s = do t <- getTerm p f s return $ oStr' t fm formatLabel :: Form -> Formatting -> Bool -> String -> State EvalState [Output] formatLabel f fm p s | "locator" <- s = when' (gets (citeLocator . cite . env) >>= return . (/=) []) $ do (l,v) <- getLocVar form (\fm' -> return . flip OLoc emptyFormatting . output fm') id l (isRange v) | "page" <- s = checkPlural | "volume" <- s = checkPlural | "issue" <- s = checkPlural | "ibid" <- s = format s p | isRole s = do a <- getAgents' (if s == "editortranslator" then "editor" else s) if null a then return [] else form (\fm' x -> [OLabel x fm']) id s p | otherwise = format s p where isRole = flip elem ["author", "collection-editor", "composer", "container-author" ,"director", "editor", "editorial-director", "editortranslator" ,"illustrator", "interviewer", "original-author", "recipient" ,"reviewed-author", "translator"] checkPlural = when' (isVarSet s) $ do v <- getStringVar s format s (isRange v) format = form output id form o g t b = return . o fm =<< g . period <$> getTerm (b && p) f t period = if stripPeriods fm then filter (/= '.') else id (<+>) :: Formatted -> Formatted -> Formatted Formatted [] <+> ss = ss s <+> Formatted [] = s Formatted xs <+> Formatted ys = case lastInline xs of "’" -> Formatted (xs ++ ys) "-" -> Formatted (xs ++ ys) _ -> Formatted (xs ++ [Space] ++ ys) (<++>) :: [Output] -> [Output] -> [Output] [] <++> o = o o <++> [] = o o1 <++> o2 = o1 ++ [OSpace] ++ o2 pandoc-citeproc-0.10.5.1/src/Text/CSL/Eval/Output.hs0000644000000000000000000002161313067270145020063 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval.Output -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval.Output where import Text.CSL.Output.Pandoc (lastInline) import Text.CSL.Style import Data.Char (toLower, toUpper) import Text.CSL.Util (capitalize, titlecase, unTitlecase, isPunct) import Text.Pandoc.Definition import Text.Pandoc.Walk (walk) import Data.String (fromString) import Data.Maybe (mapMaybe) import Text.Parsec -- Parse affix or delimiter into Formatted, splitting out -- raw components in @{{format}}...{{/format}}@. formatString :: String -> Formatted formatString s = case parse pAffix s s of Left _ -> fromString s Right ils -> Formatted ils pAffix :: Parsec String () [Inline] pAffix = many (pRaw <|> pString <|> pSpace) pRaw :: Parsec String () Inline pRaw = try $ do string "{{" format <- many1 letter string "}}" contents <- manyTill anyChar (try (string ("{{/" ++ format ++ "}}"))) return $ RawInline (Format format) contents pString :: Parsec String () Inline pString = Str <$> (many1 (noneOf " \t\n\r{}") <|> count 1 (oneOf "{}")) pSpace :: Parsec String () Inline pSpace = Space <$ many1 (oneOf " \t\n\r") output :: Formatting -> String -> [Output] output fm s | ' ':xs <- s = OSpace : output fm xs | [] <- s = [] | otherwise = [OStr s fm] appendOutput :: Formatting -> [Output] -> [Output] appendOutput fm xs = if xs /= [] then [Output xs fm] else [] outputList :: Formatting -> Delimiter -> [Output] -> [Output] outputList fm d = appendOutput fm . addDelim d . mapMaybe cleanOutput' where cleanOutput' o | Output xs f <- o = case cleanOutput xs of [] -> Nothing ys -> Just (Output ys f) | otherwise = rmEmptyOutput o cleanOutput :: [Output] -> [Output] cleanOutput = flatten where flatten [] = [] flatten (o:os) | ONull <- o = flatten os | Output xs f <- o , f == emptyFormatting = flatten (mapMaybe rmEmptyOutput xs) ++ flatten os | Output xs f <- o = Output (flatten $ mapMaybe rmEmptyOutput xs) f : flatten os | otherwise = maybe id (:) (rmEmptyOutput o) $ flatten os rmEmptyOutput :: Output -> Maybe Output rmEmptyOutput o | Output [] _ <- o = Nothing | OStr [] _ <- o = Nothing | OPan [] <- o = Nothing | ODel [] <- o = Nothing | otherwise = Just o addDelim :: String -> [Output] -> [Output] addDelim "" = id addDelim d = foldr check [] where check ONull xs = xs check x [] = [x] check x (z:zs) = if formatOutput x == mempty || formatOutput z == mempty then x : z : zs else x : ODel d : z : zs noOutputError :: Output noOutputError = OErr NoOutput noBibDataError :: Cite -> Output noBibDataError c = OErr $ ReferenceNotFound (citeId c) oStr :: String -> [Output] oStr s = oStr' s emptyFormatting oStr' :: String -> Formatting -> [Output] oStr' [] _ = [] oStr' s f = [OStr s f] oPan :: [Inline] -> [Output] oPan [] = [] oPan ils = [OPan ils] oPan' :: [Inline] -> Formatting -> [Output] oPan' [] _ = [] oPan' ils f = [Output [OPan ils] f] formatOutputList :: [Output] -> Formatted formatOutputList = mconcat . map formatOutput -- | Convert evaluated 'Output' into 'Formatted', ready for the -- output filters. formatOutput :: Output -> Formatted formatOutput o = case o of OSpace -> Formatted [Space] OPan i -> Formatted i ODel [] -> Formatted [] ODel " " -> Formatted [Space] ODel s -> formatString s OStr [] _ -> Formatted [] OStr s f -> addFormatting f $ formatString s OErr NoOutput -> Formatted [Span ("",["citeproc-no-output"],[]) [Strong [Str "???"]]] OErr (ReferenceNotFound r) -> Formatted [Span ("",["citeproc-not-found"], [("data-reference-id",r)]) [Strong [Str "???"]]] OLabel [] _ -> Formatted [] OLabel s f -> addFormatting f $ formatString s ODate os -> formatOutputList os OYear s _ f -> addFormatting f $ formatString s OYearSuf s _ _ f -> addFormatting f $ formatString s ONum i f -> formatOutput (OStr (show i) f) OCitNum i f -> if i == 0 then Formatted [Strong [Str "???"]] else formatOutput (OStr (show i) f) OCitLabel s f -> if s == "" then Formatted [Strong [Str "???"]] else formatOutput (OStr s f) OName _ os _ f -> formatOutput (Output os f) OContrib _ _ os _ _ -> formatOutputList os OLoc os f -> formatOutput (Output os f) Output [] _ -> Formatted [] Output os f -> addFormatting f $ formatOutputList os _ -> Formatted [] addFormatting :: Formatting -> Formatted -> Formatted addFormatting f = addDisplay . addLink . addSuffix . pref . quote . font . text_case . strip_periods where addLink i = case hyperlink f of "" -> i url -> Formatted [Link nullAttr (unFormatted i) (url, "")] pref i = case prefix f of "" -> i x -> formatString x <> i addSuffix i | null (suffix f) = i | case suffix f of {(c:_) | isPunct c -> True; _ -> False} , case lastInline (unFormatted i) of {(c:_) | isPunct c -> True; _ -> False} = i <> formatString (tail $ suffix f) | otherwise = i <> formatString (suffix f) strip_periods (Formatted ils) = Formatted (walk removePeriod ils) removePeriod (Str xs) | stripPeriods f = Str (filter (/='.') xs) removePeriod x = x quote (Formatted []) = Formatted [] quote (Formatted ils) = case quotes f of NoQuote -> Formatted $ valign ils NativeQuote -> Formatted [Span ("",["csl-inquote"],[]) ils] _ -> Formatted [Quoted DoubleQuote $ valign ils] addDisplay (Formatted []) = Formatted [] addDisplay (Formatted ils) = case display f of "block" -> Formatted (LineBreak : ils ++ [LineBreak]) _ -> Formatted ils font (Formatted ils) | noDecor f = Formatted [Span ("",["nodecor"],[]) ils] | otherwise = Formatted $ font_variant . font_style . font_weight $ ils font_variant ils = case fontVariant f of "small-caps" -> [SmallCaps ils] _ -> ils font_style ils = case fontStyle f of "italic" -> [Emph ils] "oblique" -> [Emph ils] _ -> ils font_weight ils = case fontWeight f of "bold" -> [Strong ils] _ -> ils text_case (Formatted []) = Formatted [] text_case (Formatted ils@(i:is)) | noCase f = Formatted [Span ("",["nocase"],[]) ils] | otherwise = Formatted $ case textCase f of "lowercase" -> walk lowercaseStr ils "uppercase" -> walk uppercaseStr ils "capitalize-all" -> walk capitalizeStr ils "title" -> titlecase ils "capitalize-first" -> walk capitalizeStr i : is "sentence" -> unTitlecase ils _ -> ils lowercaseStr (Str xs) = Str $ map toLower xs lowercaseStr x = x uppercaseStr (Str xs) = Str $ map toUpper xs uppercaseStr x = x capitalizeStr (Str xs) = Str $ capitalize xs capitalizeStr x = x valign [] = [] valign ils | "sup" <- verticalAlign f = [Superscript ils] | "sub" <- verticalAlign f = [Subscript ils] | "baseline" <- verticalAlign f = [Span ("",["csl-baseline"],[]) ils] | otherwise = ils pandoc-citeproc-0.10.5.1/src/Text/CSL/Parser.hs0000644000000000000000000004103013032532307017114 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, TupleSections #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Parser -- Copyright : (C) 2014 John MacFarlane -- License : BSD-style (see LICENSE) -- -- Maintainer : John MacFarlane -- Stability : unstable -- Portability : unportable -- -- Parser for CSL XML files. ----------------------------------------------------------------------------- module Text.CSL.Parser (readCSLFile, parseCSL, parseCSL', parseLocale, localizeCSL) where import qualified Data.Text as T import qualified Data.ByteString.Lazy as L import qualified Data.Map as M import qualified Control.Exception as E import Control.Monad (when) import Data.Either (lefts, rights) import Data.Text (Text, unpack) import Text.CSL.Style hiding (parseNames) import Text.CSL.Util (toRead, findFile) import System.Directory (getAppUserDataDirectory) import qualified Text.XML as X import Data.Default import Text.Pandoc.Shared (safeRead) import Text.XML.Cursor import Data.Maybe (listToMaybe, fromMaybe) import Text.Pandoc.UTF8 (fromStringLazy) import Text.CSL.Compat.Pandoc (fetchItem) import Text.CSL.Data (getLocale) -- | Parse a 'String' into a 'Style' (with default locale). parseCSL :: String -> Style parseCSL = parseCSL' . fromStringLazy -- | Parse locale. Raises 'CSLLocaleException' on error. parseLocale :: String -> IO Locale parseLocale locale = parseLocaleElement . fromDocument . X.parseLBS_ def <$> getLocale locale -- | Merge locale into a CSL style. localizeCSL :: Maybe String -> Style -> IO Style localizeCSL mbLocale s = do let locale = fromMaybe (styleDefaultLocale s) mbLocale l <- parseLocale locale return s { styleLocale = mergeLocales locale l (styleLocale s) } -- | Read and parse a CSL style file into a localized sytle. readCSLFile :: Maybe String -> FilePath -> IO Style readCSLFile mbLocale src = do csldir <- getAppUserDataDirectory "csl" mbSrc <- findFile [".", csldir] src fetchRes <- fetchItem Nothing (fromMaybe src mbSrc) f <- case fetchRes of Left err -> E.throwIO err Right (rawbs, _) -> return $ L.fromChunks [rawbs] let cur = fromDocument $ X.parseLBS_ def f -- see if it's a dependent style, and if so, try to fetch its parent: let pickParentCur = get "link" >=> attributeIs (X.Name "rel" Nothing Nothing) "independent-parent" let parentCur = cur $/ get "info" &/ pickParentCur let parent' = concatMap (stringAttr "href") parentCur when (parent' == src) $ do error $ "Dependent CSL style " ++ src ++ " specifies itself as parent." case parent' of "" -> localizeCSL mbLocale $ parseCSLCursor cur y -> do -- note, we insert locale from the dependent style: let mbLocale' = case stringAttr "default-locale" cur of "" -> mbLocale x -> Just x readCSLFile mbLocale' y parseCSL' :: L.ByteString -> Style parseCSL' = parseCSLCursor . fromDocument . X.parseLBS_ def parseCSLCursor :: Cursor -> Style parseCSLCursor cur = Style{ styleVersion = version , styleClass = class_ , styleInfo = Just info , styleDefaultLocale = defaultLocale , styleLocale = locales , styleAbbrevs = Abbreviations M.empty , csOptions = filter (\(k,_) -> k `notElem` ["class", "xmlns", "version", "default-locale"]) $ parseOptions cur , csMacros = macros , citation = fromMaybe (Citation [] [] Layout{ layFormat = emptyFormatting , layDelim = "" , elements = [] }) $ listToMaybe $ cur $/ get "citation" &| parseCitation , biblio = listToMaybe $ cur $/ get "bibliography" &| parseBiblio } where version = unpack . T.concat $ cur $| laxAttribute "version" class_ = unpack . T.concat $ cur $| laxAttribute "class" defaultLocale = case cur $| laxAttribute "default-locale" of (x:_) -> unpack x [] -> "en-US" author = case (cur $// get "info" &/ get "author") of (x:_) -> CSAuthor (x $/ get "name" &/ string) (x $/ get "email" &/ string) (x $/ get "uri" &/ string) _ -> CSAuthor "" "" "" info = CSInfo { csiTitle = cur $/ get "info" &/ get "title" &/ string , csiAuthor = author , csiCategories = [] -- TODO we don't really use this, and the type -- in Style doesn't match current CSL at all , csiId = cur $/ get "info" &/ get "id" &/ string , csiUpdated = cur $/ get "info" &/ get "updated" &/ string } locales = cur $/ get "locale" &| parseLocaleElement macros = cur $/ get "macro" &| parseMacroMap get :: Text -> Axis get name = element (X.Name name (Just "http://purl.org/net/xbiblio/csl") Nothing) string :: Cursor -> String string = unpack . T.concat . content attrWithDefault :: Read a => Text -> a -> Cursor -> a attrWithDefault t d cur = case safeRead (toRead $ stringAttr t cur) of Just x -> x Nothing -> d stringAttr :: Text -> Cursor -> String stringAttr t cur = case node cur of X.NodeElement e -> case M.lookup (X.Name t Nothing Nothing) (X.elementAttributes e) of Just x -> unpack x Nothing -> "" _ -> "" parseCslTerm :: Cursor -> CslTerm parseCslTerm cur = let body = unpack $ T.dropAround (`elem` (" \t\r\n" :: String)) $ T.concat $ cur $/ content in CT { cslTerm = stringAttr "name" cur , termForm = attrWithDefault "form" Long cur , termGender = attrWithDefault "gender" Neuter cur , termGenderForm = attrWithDefault "gender-form" Neuter cur , termSingular = if null body then cur $/ get "single" &/ string else body , termPlural = if null body then cur $/ get "multiple" &/ string else body , termMatch = stringAttr "match" cur } parseLocaleElement :: Cursor -> Locale parseLocaleElement cur = Locale { localeVersion = unpack $ T.concat version , localeLang = unpack $ T.concat lang , localeOptions = concat $ cur $/ get "style-options" &| parseOptions , localeTerms = terms , localeDate = concat $ cur $/ get "date" &| parseElement } where version = cur $| laxAttribute "version" lang = cur $| laxAttribute "lang" terms = cur $/ get "terms" &/ get "term" &| parseCslTerm parseElement :: Cursor -> [Element] parseElement cur = case node cur of X.NodeElement e -> case X.nameLocalName $ X.elementName e of "term" -> parseTerm cur "text" -> parseText cur "choose" -> parseChoose cur "group" -> parseGroup cur "label" -> parseLabel cur "number" -> parseNumber cur "substitute" -> parseSubstitute cur "names" -> parseNames cur "date" -> parseDate cur _ -> [] _ -> [] getFormatting :: Cursor -> Formatting getFormatting cur = emptyFormatting{ prefix = stringAttr "prefix" cur , suffix = stringAttr "suffix" cur , fontFamily = stringAttr "font-family" cur , fontStyle = stringAttr "font-style" cur , fontVariant = stringAttr "font-variant" cur , fontWeight = stringAttr "font-weight" cur , textDecoration = stringAttr "text-decoration" cur , verticalAlign = stringAttr "vertical-align" cur , textCase = stringAttr "text-case" cur , display = stringAttr "display" cur , quotes = if attrWithDefault "quotes" False cur then NativeQuote else NoQuote , stripPeriods = attrWithDefault "strip-periods" False cur , noCase = attrWithDefault "no-case" False cur , noDecor = attrWithDefault "no-decor" False cur } parseDate :: Cursor -> [Element] parseDate cur = [Date (words variable) form format delim parts partsAttr] where variable = stringAttr "variable" cur form = case stringAttr "form" cur of "text" -> TextDate "numeric" -> NumericDate _ -> NoFormDate format = getFormatting cur delim = stringAttr "delimiter" cur parts = cur $/ get "date-part" &| (parseDatePart form) partsAttr = stringAttr "date-parts" cur parseDatePart :: DateForm -> Cursor -> DatePart parseDatePart defaultForm cur = DatePart { dpName = stringAttr "name" cur , dpForm = case stringAttr "form" cur of "" -> case defaultForm of TextDate -> "long" NumericDate -> "numeric" _ -> "long" x -> x , dpRangeDelim = case stringAttr "range-delimiter" cur of "" -> "-" x -> x , dpFormatting = getFormatting cur } parseNames :: Cursor -> [Element] parseNames cur = [Names (words variable) names formatting delim others] where variable = stringAttr "variable" cur formatting = getFormatting cur delim = stringAttr "delimiter" cur elts = cur $/ parseName names = case rights elts of [] -> [Name NotSet emptyFormatting [] [] []] xs -> xs others = lefts elts parseName :: Cursor -> [Either Element Name] parseName cur = case node cur of X.NodeElement e -> case X.nameLocalName $ X.elementName e of "name" -> [Right $ Name (attrWithDefault "form" NotSet cur) format (nameAttrs e) delim nameParts] "label" -> [Right $ NameLabel (attrWithDefault "form" Long cur) format plural] "et-al" -> [Right $ EtAl format $ stringAttr "term" cur] _ -> map Left $ parseElement cur _ -> map Left $ parseElement cur where format = getFormatting cur plural = attrWithDefault "plural" Contextual cur delim = stringAttr "delimiter" cur nameParts = cur $/ get "name-part" &| parseNamePart nameAttrs x = [(T.unpack n, T.unpack v) | (X.Name n _ _, v) <- M.toList (X.elementAttributes x), n `elem` nameAttrKeys] nameAttrKeys = [ "et-al-min" , "et-al-use-first" , "et-al-subsequent-min" , "et-al-subsequent-use-first" , "et-al-use-last" , "delimiter-precedes-et-al" , "and" , "delimiter-precedes-last" , "sort-separator" , "initialize" , "initialize-with" , "name-as-sort-order" ] parseNamePart :: Cursor -> NamePart parseNamePart cur = NamePart s format where format = getFormatting cur s = stringAttr "name" cur parseSubstitute :: Cursor -> [Element] parseSubstitute cur = [Substitute (cur $/ parseElement)] parseTerm :: Cursor -> [Element] parseTerm cur = let termForm' = attrWithDefault "form" Long cur formatting = getFormatting cur plural = attrWithDefault "plural" True cur name = stringAttr "name" cur in [Term name termForm' formatting plural] parseText :: Cursor -> [Element] parseText cur = let term = stringAttr "term" cur variable = stringAttr "variable" cur macro = stringAttr "macro" cur value = stringAttr "value" cur delim = stringAttr "delimiter" cur formatting = getFormatting cur plural = attrWithDefault "plural" True cur textForm = attrWithDefault "form" Long cur in if not (null term) then [Term term textForm formatting plural] else if not (null macro) then [Macro macro formatting] else if not (null variable) then [Variable (words variable) textForm formatting delim] else if not (null value) then [Const value formatting] else [] parseChoose :: Cursor -> [Element] parseChoose cur = let ifPart = cur $/ get "if" &| parseIf elseIfPart = cur $/ get "else-if" &| parseIf elsePart = cur $/ get "else" &/ parseElement in [Choose (head ifPart) elseIfPart elsePart] parseIf :: Cursor -> IfThen parseIf cur = IfThen cond mat elts where cond = Condition { isType = go "type" , isSet = go "variable" , isNumeric = go "is-numeric" , isUncertainDate = go "is-uncertain-date" , isPosition = go "position" , disambiguation = go "disambiguate" , isLocator = go "locator" } mat = attrWithDefault "match" All cur elts = cur $/ parseElement go x = words $ stringAttr x cur parseLabel :: Cursor -> [Element] parseLabel cur = [Label variable form formatting plural] where variable = stringAttr "variable" cur form = attrWithDefault "form" Long cur formatting = getFormatting cur plural = attrWithDefault "plural" Contextual cur parseNumber :: Cursor -> [Element] parseNumber cur = [Number variable numForm formatting] where variable = stringAttr "variable" cur numForm = attrWithDefault "form" Numeric cur formatting = getFormatting cur parseGroup :: Cursor -> [Element] parseGroup cur = let elts = cur $/ parseElement delim = stringAttr "delimiter" cur formatting = getFormatting cur in [Group formatting delim elts] parseMacroMap :: Cursor -> MacroMap parseMacroMap cur = (name, elts) where name = cur $| stringAttr "name" elts = cur $/ parseElement parseCitation :: Cursor -> Citation parseCitation cur = Citation{ citOptions = parseOptions cur , citSort = concat $ cur $/ get "sort" &| parseSort , citLayout = case cur $/ get "layout" &| parseLayout of (x:_) -> x [] -> Layout { layFormat = emptyFormatting , layDelim = "" , elements = [] } } parseSort :: Cursor -> [Sort] parseSort cur = concat $ cur $/ get "key" &| parseKey parseKey :: Cursor -> [Sort] parseKey cur = case stringAttr "variable" cur of "" -> case stringAttr "macro" cur of "" -> [] x -> [SortMacro x sorting (attrWithDefault "names-min" 0 cur) (attrWithDefault "names-use-first" 0 cur) (stringAttr "names-use-last" cur)] x -> [SortVariable x sorting] where sorting = case stringAttr "sort" cur of "descending" -> Descending "" _ -> Ascending "" parseBiblio :: Cursor -> Bibliography parseBiblio cur = Bibliography{ bibOptions = parseOptions cur, bibSort = concat $ cur $/ get "sort" &| parseSort, bibLayout = case cur $/ get "layout" &| parseLayout of (x:_) -> x [] -> Layout { layFormat = emptyFormatting , layDelim = "" , elements = [] } } parseOptions :: Cursor -> [Option] parseOptions cur = case node cur of X.NodeElement e -> [(T.unpack n, T.unpack v) | (X.Name n _ _, v) <- M.toList (X.elementAttributes e)] _ -> [] parseLayout :: Cursor -> Layout parseLayout cur = Layout { layFormat = getFormatting cur , layDelim = stringAttr "delimiter" cur , elements = cur $/ parseElement } pandoc-citeproc-0.10.5.1/src/Text/CSL/Proc.hs0000644000000000000000000004562113053647342016606 0ustar0000000000000000{-# LANGUAGE PatternGuards, OverloadedStrings #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Proc -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- This module provides functions for processing the evaluated -- 'Output' for disambiguation and citation collapsing. -- ----------------------------------------------------------------------------- module Text.CSL.Proc where import Control.Arrow ( (&&&), (>>>), second ) import Data.Char ( toLower, isLetter, isDigit ) import Data.List import Data.Ord ( comparing ) import Data.Maybe ( mapMaybe ) import Text.CSL.Eval import Text.CSL.Util ( proc, proc', query, uncamelize, tr' ) import Text.CSL.Proc.Collapse import Text.CSL.Proc.Disamb import Text.CSL.Reference import Text.CSL.Style import Data.Aeson import Control.Applicative ((<|>)) import Text.Pandoc.Definition (Inline(Space, Str, Note), Block(Para)) data ProcOpts = ProcOpts { bibOpts :: BibOpts , linkCitations :: Bool } deriving ( Show, Read, Eq ) data BibOpts = Select [(String, String)] [(String, String)] | Include [(String, String)] [(String, String)] | Exclude [(String, String)] [(String, String)] deriving ( Show, Read, Eq ) newtype FieldVal = FieldVal{ unFieldVal :: (String, String) } deriving Show instance FromJSON FieldVal where parseJSON (Object v) = do x <- v .: "field" y <- v .: "value" return $ FieldVal (x,y) parseJSON _ = fail "Could not parse FieldVal" instance FromJSON BibOpts where parseJSON (Object v) = do quash <- v .:? "quash".!= [] let quash' = map unFieldVal quash (v .: "select" >>= \x -> return $ Select (map unFieldVal x) quash') <|> (v .: "include" >>= \x -> return $ Include (map unFieldVal x) quash') <|> (v .: "exclude" >>= \x -> return $ Exclude (map unFieldVal x) quash') <|> return (Select [] quash') parseJSON _ = return $ Select [] [] procOpts :: ProcOpts procOpts = ProcOpts { bibOpts = Select [] [] , linkCitations = False } -- | With a 'Style', a list of 'Reference's and the list of citation -- groups (the list of citations with their locator), produce the -- 'Formatted' for each citation group. processCitations :: ProcOpts -> Style -> [Reference] -> Citations -> [Formatted] processCitations ops s rs = citations . citeproc ops s rs -- | With a 'Style' and the list of 'Reference's produce the -- 'Formatted' for the bibliography. processBibliography :: ProcOpts -> Style -> [Reference] -> [Formatted] processBibliography ops s rs = bibliography $ citeproc ops s rs [map (\r -> emptyCite { citeId = unLiteral $ refId r}) rs] -- | With a 'Style', a list of 'Reference's and the list of -- 'Citations', produce the 'Formatted' for each citation group -- and the bibliography. citeproc :: ProcOpts -> Style -> [Reference] -> Citations -> BiblioData citeproc ops s rs cs = BD citsOutput biblioOutput $ map (unLiteral . refId) biblioRefs where -- the list of bib entries, as a list of Reference, with -- position, locator and year suffix set. biblioRefs = procRefs s . mapMaybe (getReference rs) . nubBy (\a b -> citeId a == citeId b) . concat $ cs biblioOutput = if "disambiguate-add-year-suffix" `elem` getCitDisambOptions s then map (formatOutputList . proc (updateYearSuffixes yearS) . map addYearSuffix) $ procBiblio (bibOpts ops) s biblioRefs else map formatOutputList $ tr' "citeproc:after procBiblio" $ procBiblio (bibOpts ops) s biblioRefs citsAndRefs = processCites biblioRefs cs (yearS,citG) = disambCitations s biblioRefs cs $ map (procGroup s) citsAndRefs citsOutput = map (formatCitLayout s) . tr' "citeproc:collapsed" . collapseCitGroups s . (if linkCitations ops && styleClass s == "in-text" then proc addLink else id) . tr' "citeproc:citG" $ citG addLink :: (Cite, Output) -> (Cite, Output) addLink (cit, outp) = (cit, proc (addLink' (citeId cit)) outp) addLink' citeid (OYear y _ f) = OYear y citeid f{hyperlink = "#ref-" ++ citeid} addLink' citeid (OYearSuf y _ d f) = OYearSuf y citeid d f{hyperlink = "#ref-" ++ citeid} addLink' citeid (OCitNum n f) = OCitNum n f{hyperlink = "#ref-" ++ citeid} addLink' citeid (OCitLabel l f) = OCitLabel l f{hyperlink = "#ref-" ++ citeid} addLink' _ x = x -- | Given the CSL 'Style' and the list of 'Reference's sort the list -- according to the 'Style' and assign the citation number to each -- 'Reference'. procRefs :: Style -> [Reference] -> [Reference] procRefs (Style {biblio = mb, csMacros = ms , styleLocale = l, styleAbbrevs = as, csOptions = opts}) rs = maybe (setCNum rs) process mb where opts' b = mergeOptions (bibOptions b) opts setCNum = map (\(x,y) -> x { citationNumber = fromIntegral y }) . flip zip ([1..] :: [Int]) sort_ b = evalSorting (EvalSorting emptyCite {citePosition = "first"}) l ms (opts' b) (bibSort b) as process b = setCNum . sortItems . map (id &&& sort_ b . Just) $ rs sortItems :: Show a => [(a,[Sorting])] -> [a] sortItems [] = [] sortItems l = case head . concatMap (map snd) $ result of [] -> concatMap (map fst) result _ -> if any ((<) 1 . length) result then concatMap sortItems result else concatMap (map fst) result where result = process l process = sortBy (comparing $ take 1 . snd) >>> groupBy (\a b -> take 1 (snd a) == take 1 (snd b)) >>> map (map $ second (drop 1)) -- | With a 'Style' and a sorted list of 'Reference's produce the -- evaluated output for the bibliography. procBiblio :: BibOpts -> Style -> [Reference] -> [[Output]] procBiblio bos (Style {biblio = mb, csMacros = ms , styleLocale = l, styleAbbrevs = as, csOptions = opts}) rs = map addSpaceAfterCitNum $ maybe [] process mb where -- handle second-field-align (sort of) addSpaceAfterCitNum [Output (OCitNum n f : xs) f'] | secondFieldAlign == Just "flush" = [Output (OCitNum n f : OSpace : xs) f'] | secondFieldAlign == Just "margin" = [Output (OCitNum n f : OSpace : xs) f'] | otherwise = [Output (OCitNum n f : xs) f'] addSpaceAfterCitNum xs = xs secondFieldAlign = lookup "second-field-align" $ maybe [] bibOptions mb process :: Bibliography -> [[Output]] process b = map (formatBiblioLayout (layFormat $ bibLayout b) (layDelim $ bibLayout b)) $ render b render :: Bibliography -> [[Output]] render b = subsequentAuthorSubstitute b . map (evalBib b) . filterRefs bos $ rs evalBib :: Bibliography -> Reference -> [Output] evalBib b = evalLayout (bibLayout b) (EvalBiblio emptyCite {citePosition = "first"}) False l ms (mergeOptions (bibOptions b) opts) as . Just subsequentAuthorSubstitute :: Bibliography -> [[Output]] -> [[Output]] subsequentAuthorSubstitute b = if null subAuthStr then id else chkCreator where subAuthStr = getOptionVal "subsequent-author-substitute" (bibOptions b) subAuthRule = getOptionVal "subsequent-author-substitute-rule" (bibOptions b) queryContrib = proc' rmLabel . query contribsQ getContrib = if null subAuthStr then const [] else case subAuthRule of "partial-first" -> take 1 . query namesQ . queryContrib "partial-each" -> query namesQ . queryContrib _ -> queryContrib getPartialEach x xs = concat . take 1 . map fst . sortBy (flip (comparing $ length . snd)) . filter ((<) 0 . length . snd) . zip xs . map (takeWhile id . map (uncurry (==)) . zip x) $ xs chkCreator = if subAuthRule == "partial-each" then chPartialEach [] else chkCr [] chkCr _ [] = [] chkCr a (x:xs) = let contribs = getContrib x in if contribs `elem` a then substituteAuth [] x : chkCr a xs else x : chkCr (contribs : a) xs chPartialEach _ [] = [] chPartialEach a (x:xs) = let contribs = getContrib x partial = getPartialEach contribs a in if not $ null partial then substituteAuth partial x : if length partial < length contribs then chPartialEach (contribs : a) xs else chPartialEach a xs else x : chPartialEach (contribs : a) xs substituteAuth a = if subAuthRule == "complete-each" then proc chNamas else proc (updateContribs a) updateContribs a o@(OContrib i r y ds os) = if r == "author" || r == "authorsub" then OContrib i r upCont ds os else o where upCont = case subAuthRule of "partial-first" -> rmFirstName y "partial-each" -> rmSelectedName a y _ -> OStr subAuthStr emptyFormatting : proc rmNames y updateContribs _ o = o contribsQ o | OContrib _ r c _ _ <- o = if r == "author" || r == "authorsub" then c else [] | otherwise = [] namesQ o | OName {} <- o = [o] | otherwise = [] rmSelectedName _ [] = [] rmSelectedName a (o:os) | OName {} <- o = (if o `elem` a then OStr subAuthStr emptyFormatting else o) : rmSelectedName a os | otherwise = o : rmSelectedName a os rmFirstName [] = [] rmFirstName (o:os) | OName {} <- o = OStr subAuthStr emptyFormatting : os | otherwise = o : rmFirstName os chNamas o | OName s _ os f <- o = OName s [OStr subAuthStr emptyFormatting] os f | otherwise = o rmNames o | OName {} <- o = ONull | OStr {} <- o = ONull | ODel {} <- o = ONull | otherwise = o rmLabel [] = [] rmLabel (o:os) | OLabel {} <- o = rmLabel os | otherwise = o : rmLabel os filterRefs :: BibOpts -> [Reference] -> [Reference] filterRefs bos refs | Select s q <- bos = filter (select s) . filter (quash q) $ refs | Include i q <- bos = filter (include i) . filter (quash q) $ refs | Exclude e q <- bos = filter (exclude e) . filter (quash q) $ refs | otherwise = refs where quash [] _ = True quash q r = not . and . flip map q $ \(f,v) -> lookup_ r f v select s r = and . flip map s $ \(f,v) -> lookup_ r f v include i r = or . flip map i $ \(f,v) -> lookup_ r f v exclude e r = and . flip map e $ \(f,v) -> not $ lookup_ r f v lookup_ r f v = case f of "type" -> look "ref-type" "id" -> look "ref-id" "categories" -> look "categories" x -> look x where look s = case lookup s (mkRefMap (Just r)) of Just x | Just v' <- (fromValue x :: Maybe RefType ) -> v == uncamelize (show v') | Just v' <- (fromValue x :: Maybe String ) -> v == v' | Just v' <- (fromValue x :: Maybe [String] ) -> v `elem` v' | Just v' <- (fromValue x :: Maybe [Agent] ) -> null v && null v' || v == show v' | Just v' <- (fromValue x :: Maybe [RefDate]) -> null v && null v' || v == show v' _ -> False -- | Given the CSL 'Style' and the list of 'Cite's coupled with their -- 'Reference's, generate a 'CitationGroup'. The citations are sorted -- according to the 'Style'. procGroup :: Style -> [(Cite, Maybe Reference)] -> CitationGroup procGroup (Style {citation = ct, csMacros = ms , styleLocale = l, styleAbbrevs = as, csOptions = opts}) cr = CG authIn (layFormat $ citLayout ct) (layDelim $ citLayout ct) (authIn ++ co) where (co, authIn) = case cr of (c:_) -> if authorInText (fst c) then (filter (eqCites (/=) c) result, take 1 . filter (eqCites (==) c) $ result) else (result, []) _ -> (result, []) eqCites eq c = fst >>> citeId &&& citeHash >>> eq (citeId &&& citeHash $ fst c) opts' = mergeOptions (citOptions ct) opts format (c,r) = (c, evalLayout (citLayout ct) (EvalCite c) False l ms opts' as r) sort_ (c,r) = evalSorting (EvalSorting c) l ms opts' (citSort ct) as r process = map (second (flip Output emptyFormatting) . format &&& sort_) result = sortItems $ process cr formatBiblioLayout :: Formatting -> Delimiter -> [Output] -> [Output] formatBiblioLayout f d = appendOutput f . addDelim d formatCitLayout :: Style -> CitationGroup -> Formatted formatCitLayout s (CG co f d cs) | [a] <- co = combine (formatAuth a) (formatCits $ (fst >>> citeId &&& citeHash >>> setAsSupAu $ a) cs) | otherwise = formatCits cs where isNote = styleClass s == "note" toNote (Formatted xs) = Formatted [Note [Para xs]] combine (Formatted []) ys = ys combine xs ys = case ys of Formatted [] -> xs Formatted (Note _ : _) -> xs <> ys Formatted (Str [c]:_) | c `elem` (", ;:" :: String) -> xs <> ys _ -> xs <> Formatted [Space] <> ys formatAuth = formatOutput . localMod formatCits = (if isNote then toNote else id) . formatOutputList . appendOutput formatting . addAffixes f . addDelim d . map (fst &&& localMod >>> uncurry addCiteAffixes) formatting = f{ prefix = [], suffix = [], verticalAlign = if isAuthorInText cs then "" else verticalAlign f } isAuthorInText [] = False isAuthorInText ((c,_):_) = authorInText c localMod = uncurry $ localModifiers s (not $ null co) setAsSupAu h = map $ \(c,o) -> if (citeId c, citeHash c) == h then (c { authorInText = False , suppressAuthor = True }, o) else (c, o) addAffixes :: Formatting -> [Output] -> [Output] addAffixes f os | [] <- os = [] | [ONull] <- os = [] | [Output [ONull] _] <- os = [] | otherwise = pref ++ suff where pref = if not (null (prefix f)) then OStr (prefix f) emptyFormatting : os else os suff = case suffix f of [] -> [] (c:cs) | isLetter c || isDigit c || c == '(' || c == '[' -> [OSpace, OStr (c:cs) emptyFormatting] | otherwise -> [OStr (c:cs) emptyFormatting] -- | The 'Bool' is 'True' if we are formatting a textual citation (in -- pandoc terminology). localModifiers :: Style -> Bool -> Cite -> Output -> Output localModifiers s b c | authorInText c = check . return . contribOnly s | suppressAuthor c = check . rmContrib . return | otherwise = id where isPunct' [] = False isPunct' xs = all (`elem` (".,;:!? " :: String)) xs check o = case cleanOutput o of [] -> ONull x -> case trim' x of [] -> ONull x' -> Output x' emptyFormatting hasOutput o | Output [] _ <- o = [False] | ODel _ <- o = [False] | OSpace <- o = [False] | ONull <- o = [False] | otherwise = [True] trim' [] = [] trim' (o:os) | Output ot f <- o, p <- prefix f, p /= [] , isPunct' p = trim' $ Output ot f { prefix = []} : os | Output ot f <- o = if or (query hasOutput ot) then Output (trim' ot) f : os else Output ot f : trim' os | ODel _ <- o = trim' os | OSpace <- o = trim' os | OStr x f <- o = OStr x (if isPunct' (prefix f) then f { prefix = []} else f) : os | otherwise = o:os rmCitNum o | OCitNum {} <- o = ONull | otherwise = o rmContrib [] = [] rmContrib o | b, isNumStyle o = proc rmCitNum o | otherwise = rmContrib' o rmContrib' [] = [] rmContrib' (o:os) | Output ot f <- o = Output (rmContrib' ot) f : rmContrib' os | ODel _ <- o , OContrib _ "author" _ _ _ : xs <- os = rmContrib' xs | ODel _ <- o , OContrib _ "authorsub" _ _ _ : xs <- os = rmContrib' xs | OContrib _ "author" _ _ _ <- o , ODel _ : xs <- os = rmContrib' xs | OContrib _ "authorsub" _ _ _ <- o , ODel _ : xs <- os = rmContrib' xs | OContrib _ "author" _ _ _ <- o = rmContrib' os | OContrib _ "authorsub" _ _ _ <- o = rmContrib' os | OStr x _ <- o , "ibid" <- filter (/= '.') (map toLower x) = rmContrib' os | otherwise = o : rmContrib' os contribOnly :: Style -> Output -> Output contribOnly s o | isNumStyle [o] , OCitNum n f <- o = Output [ OCitNum n f{ verticalAlign = "", prefix = "", suffix = "" } ] emptyFormatting | OContrib _ "author" _ _ _ <- o = o | OContrib _ "authorsub" _ _ _ <- o = o | Output ot f <- o = Output (cleanOutput $ map (contribOnly s) ot) f{ verticalAlign = "", prefix = "", suffix = "" } | OStr x _ <- o , "ibid" <- filter (/= '.') (map toLower x) = o | otherwise = ONull pandoc-citeproc-0.10.5.1/src/Text/CSL/Proc/Collapse.hs0000644000000000000000000002217312743760365020353 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Proc.Collapse -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- This module provides functions for processing the evaluated -- 'Output' for citation collapsing. -- ----------------------------------------------------------------------------- module Text.CSL.Proc.Collapse where import Data.Ord (comparing) import Data.Monoid (Any(..)) import Control.Arrow ( (&&&), (>>>), second ) import Data.Char import Data.List ( groupBy, sortBy ) import Text.CSL.Util ( query, proc, proc', betterThan ) import Text.CSL.Eval import Text.CSL.Proc.Disamb import Text.CSL.Style hiding (Any) import Text.Pandoc.Definition ( Inline (Str) ) -- | Collapse citations according to the style options. collapseCitGroups :: Style -> [CitationGroup] -> [CitationGroup] collapseCitGroups s = map doCollapse where doCollapse = case getCollapseOptions s of "year" : _ -> collapseYear s [] "year-suffix" : _ -> collapseYear s "year-suffix" "year-suffix-ranged" : _ -> collapseYear s "year-suffix-ranged" "citation-number" : _ -> collapseNumber _ -> id -- | Get the collapse option set in the 'Style' for citations. getCollapseOptions :: Style -> [String] getCollapseOptions = map snd . filter ((==) "collapse" . fst) . citOptions . citation collapseNumber :: CitationGroup -> CitationGroup collapseNumber (CG _ f d os) = mapCitationGroup process $ CG [] f d os -- note: for numerical styles, we treat author-in-text citations just -- like any others. where hasLocator = or . query hasLocator' hasLocator' o | OLoc _ _ <- o = [True] | otherwise = [False] citNums (OCitNum i _) = [i] citNums (Output xs _) = concatMap citNums xs citNums _ = [] numOf = foldr (\x _ -> x) 0 . citNums process xs = if hasLocator xs then xs else flip concatMap (groupConsecWith numOf xs) $ \ys -> if length ys > 2 then [ Output [ head ys , OPan [Str "\x2013"] , last ys ] emptyFormatting ] else ys groupCites :: [(Cite, Output)] -> [(Cite, Output)] groupCites [] = [] groupCites (x:xs) = let equal = filter ((==) (namesOf $ snd x) . namesOf . snd) xs notequal = filter ((/=) (namesOf $ snd x) . namesOf . snd) xs in x : equal ++ groupCites notequal where contribsQ o | OContrib _ _ c _ _ <- o = [c] | otherwise = [] namesOf y = case query contribsQ y of [] -> [] (z:_) -> proc rmHashAndGivenNames z getYearAndSuf :: Output -> Output getYearAndSuf x = case query getOYear x of [] -> noOutputError x' -> Output x' emptyFormatting where getOYear o | OYear {} : _ <- o = [head o] | OYearSuf {} : _ <- o = [head o] | OLoc {} : _ <- o = [head o] | ODel _ : OLoc {} : _ <- o = [head o] | otherwise = [] collapseYear :: Style -> String -> CitationGroup -> CitationGroup collapseYear s ranged (CG cs f d os) = CG cs f [] (process os) where styleYSD = getOptionVal "year-suffix-delimiter" . citOptions . citation $ s yearSufDel = styleYSD `betterThan` (layDelim . citLayout . citation $ s) afterCD = getOptionVal "after-collapse-delimiter" . citOptions . citation $ s afterColDel = afterCD `betterThan` d format [] = [] format (x:xs) = x : map getYearAndSuf xs isRanged = case ranged of "year-suffix-ranged" -> True _ -> False collapseRange = if null ranged then map (uncurry addCiteAffixes) else collapseYearSuf isRanged yearSufDel rmAffixes x = x {citePrefix = mempty, citeSuffix = mempty} delim = let d' = getOptionVal "cite-group-delimiter" . citOptions . citation $ s -- FIXME: see https://bitbucket.org/bdarcus/citeproc-test/issue/15 -- in if null d' then if null d then ", " else d else d' in if null d' then ", " else d' collapsYS a = case a of [] -> (emptyCite, ONull) [x] -> rmAffixes . fst &&& uncurry addCiteAffixes $ x _ -> (,) (rmAffixes $ fst $ head a) . flip Output emptyFormatting . addDelim delim . collapseRange . uncurry zip . second format . unzip $ a doCollapse [] = [] doCollapse (x:[]) = [collapsYS x] doCollapse (x:xs) = let (a,b) = collapsYS x in if length x > 1 then (a, Output (b : [ODel afterColDel]) emptyFormatting) : doCollapse xs else (a, Output (b : [ODel d ]) emptyFormatting) : doCollapse xs contribsQ o | OContrib _ _ c _ _ <- o = [proc' rmHashAndGivenNames c] | otherwise = [] namesOf = query contribsQ process = doCollapse . groupBy (\a b -> namesOf (snd a) == namesOf (snd b)) . groupCites collapseYearSuf :: Bool -> String -> [(Cite,Output)] -> [Output] collapseYearSuf ranged ysd = process where yearOf = concat . query getYear getYear o | OYear y _ _ <- o = [y] | otherwise = [] processYS = if ranged then collapseYearSufRanged else id process = map (flip Output emptyFormatting . getYS) . groupBy comp checkAffix (Formatted []) = True checkAffix _ = False comp a b = yearOf (snd a) == yearOf (snd b) && checkAffix (citePrefix $ fst a) && checkAffix (citeSuffix $ fst a) && checkAffix (citePrefix $ fst b) && checkAffix (citeSuffix $ fst b) && null (citeLocator $ fst a) && null (citeLocator $ fst b) getYS [] = [] getYS (x:[]) = return $ uncurry addCiteAffixes x getYS (x:xs) = if ranged then proc rmOYearSuf (snd x) : addDelim ysd (processYS $ (snd x) : query rmOYear (map snd xs)) else addDelim ysd $ (snd x) : (processYS $ query rmOYear (map snd xs)) rmOYearSuf o | OYearSuf {} <- o = ONull | otherwise = o rmOYear o | OYearSuf {} <- o = [o] | otherwise = [] collapseYearSufRanged :: [Output] -> [Output] collapseYearSufRanged = process where getOYS o | OYearSuf s _ _ f <- o = [(if s /= [] then ord (head s) else 0, f)] | otherwise = [] sufOf = foldr (\x _ -> x) (0,emptyFormatting) . query getOYS newSuf = map sufOf >>> (map fst >>> groupConsec) &&& map snd >>> uncurry zip process xs = flip concatMap (newSuf xs) $ \(x,f) -> if length x > 2 then return $ Output [ OStr [chr $ head x] f , OPan [Str "\x2013"] , OStr [chr $ last x] f ] emptyFormatting else map (\y -> if y == 0 then ONull else flip OStr f . return . chr $ y) x addCiteAffixes :: Cite -> Output -> Output addCiteAffixes c x = if isNumStyle [x] then x else Output ( addCiteAff True (citePrefix c) ++ [x] ++ addCiteAff False (citeSuffix c)) emptyFormatting where addCiteAff isprefix y = case y of Formatted [] -> [] Formatted ils | isprefix -> [OPan ils, OSpace] | otherwise -> case ils of (Str (z:_):_) | isAlphaNum z || z == '(' -> [OSpace, OPan ils] _ -> [OPan ils] isNumStyle :: [Output] -> Bool isNumStyle = getAny . query ocitnum where ocitnum (OCitNum {}) = Any True ocitnum _ = Any False -- | Group consecutive integers: -- -- > groupConsec [1,2,3,5,6,8,9] == [[1,2,3],[5,6],[8,9]] groupConsec :: [Int] -> [[Int]] groupConsec = groupConsecWith id groupConsecWith :: (a -> Int) -> [a] -> [[a]] groupConsecWith f = foldr go [] . sortBy (comparing f) where go x [] = [[x]] go x ((y:ys):gs) = if (f x + 1) == (f y) then ((x:y:ys):gs) else ([x]:(y:ys):gs) go _ ([]:_) = error "groupConsec: head of list is empty" pandoc-citeproc-0.10.5.1/src/Text/CSL/Proc/Disamb.hs0000644000000000000000000004231013003500055017755 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} #if MIN_VERSION_base(4,9,0) {-# OPTIONS_GHC -fno-warn-redundant-constraints #-} #endif ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Proc.Disamb -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- This module provides functions for processing the evaluated -- 'Output' for citation disambiguation. -- -- Describe the disambiguation process. -- ----------------------------------------------------------------------------- module Text.CSL.Proc.Disamb where import Control.Arrow ( (&&&), (>>>), second ) import Data.Char ( chr ) import Data.List ( elemIndex, find, findIndex, sortBy, mapAccumL , nub, nubBy, groupBy, isPrefixOf ) import Data.Maybe import Data.Ord ( comparing ) import Text.CSL.Eval import Text.CSL.Reference import Text.CSL.Style import Text.CSL.Util (query, proc) -- | Given the 'Style', the list of references and the citation -- groups, disambiguate citations according to the style options. disambCitations :: Style -> [Reference] -> Citations -> [CitationGroup] -> ([(String, String)], [CitationGroup]) disambCitations s bibs cs groups = (,) yearSuffs citOutput where -- utils when_ b f = if b then f else [] filter_ f = concatMap (map fst) . map (filter f) . map (uncurry zip) -- the list of the position and the reference of each citation -- for each citation group. refs = processCites bibs cs -- name data of name duplicates nameDupls = getDuplNameData groups -- citation data of ambiguous cites duplics = getDuplCiteData hasNamesOpt hasYSuffOpt groups -- check the options set in the style isByCite = let gno = getOptionVal "givenname-disambiguation-rule" (citOptions $ citation s) in gno == "by-cite" || gno == [] disOpts = getCitDisambOptions s hasNamesOpt = "disambiguate-add-names" `elem` disOpts hasGNameOpt = "disambiguate-add-givenname" `elem` disOpts hasYSuffOpt = "disambiguate-add-year-suffix" `elem` disOpts givenNames = if hasGNameOpt then if isByCite then ByCite else AllNames else NoGiven clean = if hasGNameOpt then id else proc rmHashAndGivenNames withNames = flip map duplics $ same . clean . map (if hasNamesOpt then disambData else return . disambYS) needNames = filter_ (not . snd) $ zip duplics withNames needYSuff = filter_ snd $ zip duplics withNames newNames :: [CiteData] newNames = when_ (hasNamesOpt || hasGNameOpt) $ disambAddNames givenNames $ needNames ++ if hasYSuffOpt && givenNames == NoGiven then [] else needYSuff newGName :: [NameData] newGName = when_ hasGNameOpt $ concatMap disambAddGivenNames nameDupls -- the list of citations that need re-evaluation with the -- \"disambiguate\" condition set to 'True' reEval = let chk = if hasYSuffOpt then filter ((==) [] . citYear) else id in chk needYSuff reEvaluated = if or (query hasIfDis s) && not (null reEval) then zipWith (reEvaluate s reEval) refs groups else groups withYearS = addNames $ if hasYSuffOpt then map (mapCitationGroup $ setYearSuffCollision hasNamesOpt needYSuff) $ reEvaluated else rmYearSuff $ reEvaluated yearSuffs = when_ hasYSuffOpt . generateYearSuffix bibs . concatMap getYearSuffixes $ withYearS addNames = proc (updateContrib givenNames newNames newGName) processed = if hasYSuffOpt then proc (updateYearSuffixes yearSuffs) $ withYearS else withYearS citOutput = if disOpts /= [] then processed else reEvaluated mapDisambData :: (Output -> Output) -> CiteData -> CiteData mapDisambData f (CD k c ys d r s y) = CD k c ys (proc f d) r s y mapCitationGroup :: ([Output] -> [Output]) -> CitationGroup -> CitationGroup mapCitationGroup f (CG cs fm d os) = CG cs fm d (zip (map fst os) . f $ map snd os) data GiveNameDisambiguation = NoGiven | ByCite | AllNames deriving (Show, Eq) disambAddNames :: GiveNameDisambiguation -> [CiteData] -> [CiteData] disambAddNames b needName = addLNames where clean = if b == NoGiven then proc rmHashAndGivenNames else id disSolved = zip needName' . disambiguate . map disambData $ needName' needName' = nub' needName [] addLNames = map (\(c,n) -> c { disambed = if null n then collision c else head n }) disSolved nub' [] r = r nub' (x:xs) r = case elemIndex (disambData $ clean x) (map (disambData . clean) r) of Nothing -> nub' xs (x:r) Just i -> let y = r !! i in nub' xs (y {sameAs = key x : sameAs y} : filter (/= y) r) disambAddGivenNames :: [NameData] -> [NameData] disambAddGivenNames needName = addGName where disSolved = zip needName (disambiguate $ map nameDisambData needName) addGName = map (\(c,n) -> c { nameDataSolved = if null n then nameCollision c else head n }) disSolved updateContrib :: GiveNameDisambiguation -> [CiteData] -> [NameData] -> Output -> Output updateContrib g c n o | OContrib k r s d dd <- o = case filter (key &&& sameAs >>> uncurry (:) >>> elem k) c of x:_ | clean (disambData x) == clean (d:dd) -> OContrib k r (map processGNames $ disambed x) [] dd _ | null c, AllNames <- g -> OContrib k r (map processGNames s) d dd | otherwise -> o | otherwise = o where clean = if g == NoGiven then proc rmHashAndGivenNames else id processGNames = if g /= NoGiven then updateOName n else id updateOName :: [NameData] -> Output -> Output updateOName n o | OName _ _ [] _ <- o = o | OName k x _ f <- o = case elemIndex (ND k (clean x) [] []) n of Just i -> OName emptyAgent (nameDataSolved $ n !! i) [] f _ -> o | otherwise = o where clean = proc rmGivenNames -- | Evaluate again a citation group with the 'EvalState' 'disamb' -- field set to 'True' (for matching the @\"disambiguate\"@ -- condition). reEvaluate :: Style -> [CiteData] -> [(Cite, Maybe Reference)] -> CitationGroup -> CitationGroup reEvaluate (Style {citation = ct, csMacros = ms , styleLocale = lo, styleAbbrevs = as}) l cr (CG a f d os) = CG a f d . flip concatMap (zip cr os) $ \((c,mbr),out) -> case mbr of Just r | unLiteral (refId r) `elem` lkeys -> return . second (flip Output emptyFormatting) $ (,) c $ evalLayout (citLayout ct) (EvalCite c) True lo ms (citOptions ct) as mbr _ -> [out] where lkeys = map key l -- | Check if the 'Style' has any conditional for disambiguation. In -- this case the conditional will be try after all other -- disambiguation strategies have failed. To be used with the generic -- 'query' function. hasIfDis :: IfThen -> [Bool] hasIfDis (IfThen (Condition {disambiguation = (_:_)}) _ _) = [True] hasIfDis _ = [False] -- | Get the list of disambiguation options set in the 'Style' for -- citations. getCitDisambOptions :: Style -> [String] getCitDisambOptions = map fst . filter ((==) "true" . snd) . filter (isPrefixOf "disambiguate" . fst) . citOptions . citation -- | Group citation data (with possible alternative names) of -- citations which have a duplicate (same 'collision', and same -- 'citYear' if year suffix disambiiguation is used). If the first -- 'Bool' is 'False', then we need to retrieve data for year suffix -- disambiguation. The second 'Bool' is 'True' when comparing both -- year and contributors' names for finding duplicates (when the -- year-suffix option is set). getDuplCiteData :: Bool -> Bool -> [CitationGroup] -> [[CiteData]] getDuplCiteData b1 b2 g = groupBy (\x y -> collide x == collide y) . sortBy (comparing collide) $ duplicates where whatToGet = if b1 then collision else disambYS collide = proc rmExtras . proc rmHashAndGivenNames . whatToGet citeData = nubBy (\a b -> collide a == collide b && key a == key b) $ concatMap (mapGroupOutput $ getCiteData) g duplicates = [c | c <- citeData , d <- citeData , collides c d] collides x y = x /= y && (collide x == collide y) && (not b2 || citYear x == citYear y) rmExtras :: [Output] -> [Output] rmExtras os | Output x _ : xs <- os = case rmExtras x of [] -> rmExtras xs ys -> ys ++ rmExtras xs | OContrib _ _ x _ _ : xs <- os = OContrib [] [] x [] [] : rmExtras xs | OYear y _ f : xs <- os = OYear y [] f : rmExtras xs | ODel _ : xs <- os = rmExtras xs | OLoc _ _ : xs <- os = rmExtras xs | x : xs <- os = x : rmExtras xs | otherwise = [] -- | For an evaluated citation get its 'CiteData'. The disambiguated -- citation and the year fields are empty. Only the first list of -- contributors' disambiguation data are collected for disambiguation -- purposes. getCiteData :: Output -> [CiteData] getCiteData out = (contribs &&& years >>> zipData) out where contribs x = case query contribsQ x of [] -> [CD [] [out] [] [] [] [] []] -- allow title to disambiguate xs -> xs years o = case query getYears o of [] -> [([],[])] r -> r zipData = uncurry . zipWith $ \c y -> if key c /= [] then c {citYear = snd y} else c {key = fst y ,citYear = snd y} contribsQ o | OContrib k _ _ d dd <- o = [CD k [out] d (d:dd) [] [] []] | otherwise = [] getYears :: Output -> [(String,String)] getYears o | OYear x k _ <- o = [(k,x)] | otherwise = [] getDuplNameData :: [CitationGroup] -> [[NameData]] getDuplNameData g = groupBy (\a b -> collide a == collide b) . sortBy (comparing collide) $ duplicates where collide = nameCollision nameData = nub $ concatMap (mapGroupOutput getName) g duplicates = filter (flip elem (getDuplNames g) . collide) nameData getDuplNames :: [CitationGroup] -> [[Output]] getDuplNames xs = nub . catMaybes . snd . mapAccumL dupl [] . getData $ xs where getData = concatMap (mapGroupOutput getName) dupl a c = if nameCollision c `elem` map nameCollision a then (a,Just $ nameCollision c) else (c:a,Nothing) getName :: Output -> [NameData] getName = query getName' where getName' o | OName i n ns _ <- o = [ND i n (n:ns) []] | otherwise = [] generateYearSuffix :: [Reference] -> [(String, [Output])] -> [(String,String)] generateYearSuffix refs = concatMap (flip zip suffs) . -- sort clashing cites using their position in the sorted bibliography getFst . map sort' . map (filter ((/=) 0 . snd)) . map (map getP) . -- group clashing cites getFst . filter (\grp -> length grp >= 2) . map nub . groupBy (\a b -> snd a == snd b) . sort' . filter ((/=) [] . snd) where sort' :: (Ord a, Ord b) => [(a,b)] -> [(a,b)] sort' = sortBy (comparing snd) getFst = map $ map fst getP k = case findIndex ((==) k . unLiteral . refId) refs of Just x -> (k, x + 1) _ -> (k, 0) suffs = l ++ [x ++ y | x <- l, y <- l ] l = map (return . chr) [97..122] setYearSuffCollision :: Bool -> [CiteData] -> [Output] -> [Output] setYearSuffCollision b cs = proc (setYS cs) . (map $ \x -> if hasYearSuf x then x else addYearSuffix x) where setYS c o | OYearSuf _ k _ f <- o = OYearSuf [] k (getCollision k c) f | otherwise = o collide = if b then disambed else disambYS getCollision k c = case find ((==) k . key) c of Just x -> if collide x == [] then [OStr (citYear x) emptyFormatting] else collide x _ -> [] updateYearSuffixes :: [(String, String)] -> Output -> Output updateYearSuffixes yss o | OYearSuf _ k c f <- o = case lookup k yss of Just x -> OYearSuf x k c f _ -> ONull | otherwise = o getYearSuffixes :: CitationGroup -> [(String,[Output])] getYearSuffixes (CG _ _ _ d) = map go d where go (c,x) = (citeId c, relevant False [x]) relevant :: Bool -> [Output] -> [Output] -- bool is true if has contrib -- we're only interested in OContrib and OYear, unless there is no OContrib relevant c (Output xs _ : rest) = relevant c xs ++ relevant c rest relevant c (OYear n _ _ : rest) = OStr n emptyFormatting : relevant c rest relevant False (OStr s _ : rest) = OStr s emptyFormatting : relevant False rest relevant False (OSpace : rest) = OSpace : relevant False rest relevant False (OPan ils : rest) = OPan ils : relevant False rest relevant _ (OContrib _ _ v _ _ : rest ) = relevant False v ++ relevant True rest relevant c (OName _ v _ _ : rest ) = relevant c v ++ relevant c rest relevant c (_ : rest) = relevant c rest relevant _ [] = [] rmYearSuff :: [CitationGroup] -> [CitationGroup] rmYearSuff = proc rmYS where rmYS o | OYearSuf _ _ _ _ <- o = ONull | otherwise = o -- List Utilities -- | Try to disambiguate a list of lists by returning the first non -- colliding element, if any, of each list: -- -- > disambiguate [[1,2],[1,3],[2]] = [[2],[3],[2]] disambiguate :: (Eq a) => [[a]] -> [[a]] disambiguate [] = [] disambiguate l = if hasMult l && not (allTheSame l) && hasDuplicates heads then disambiguate (rest l) else heads where heads = map (take 1) l rest = map (\(b,x) -> if b then tail_ x else take 1 x) . zip (same heads) hasMult [] = False hasMult (x:xs) = length x > 1 || hasMult xs tail_ [x] = [x] tail_ x = if null x then x else tail x -- | For each element a list of 'Bool': 'True' if the element has a -- duplicate in the list: -- -- > same [1,2,1] = [True,False,True] same :: Eq a => [a] -> [Bool] same l = map (`elem` dupl) l where dupl = catMaybes . snd . macc [] $ l macc = mapAccumL $ \a x -> if x `elem` a then (a,Just x) else (x:a,Nothing) hasDuplicates :: Eq a => [a] -> Bool hasDuplicates = or . same allTheSame :: Eq a => [a] -> Bool allTheSame [] = True allTheSame (x:xs) = all (== x) xs -- | Add the year suffix to the year. Needed for disambiguation. addYearSuffix :: Output -> Output addYearSuffix o | OYear y k f <- o = Output [OYear y k emptyFormatting,OYearSuf [] k [] emptyFormatting] f | ODate (x:xs) <- o = if or $ map hasYear xs then Output (x : [addYearSuffix $ ODate xs]) emptyFormatting else addYearSuffix (Output (x:xs) emptyFormatting) | Output (x:xs) f <- o = if or $ map hasYearSuf (x : xs) then Output (x : xs) f else if hasYear x then Output (addYearSuffix x : xs) f else Output (x : [addYearSuffix $ Output xs emptyFormatting]) f | otherwise = o hasYear :: Output -> Bool hasYear = not . null . query getYear where getYear o | OYear _ _ _ <- o = [o] | otherwise = [] hasYearSuf :: Output -> Bool hasYearSuf = not . null . query getYearSuf where getYearSuf :: Output -> [String] getYearSuf o | OYearSuf _ _ _ _ <- o = ["a"] | otherwise = [] -- | Removes all given names and name hashes from OName elements. rmHashAndGivenNames :: Output -> Output rmHashAndGivenNames (OName _ s _ f) = OName emptyAgent s [] f rmHashAndGivenNames o = o rmGivenNames :: Output -> Output rmGivenNames (OName a s _ f) = OName a s [] f rmGivenNames o = o -- | Add, with 'proc', a give name to the family name. Needed for -- disambiguation. addGivenNames :: [Output] -> [Output] addGivenNames = addGN True where addGN _ [] = [] addGN b (o:os) | OName i _ xs f <- o , xs /= [] = if b then OName i (head xs) (tail xs) f : addGN False os else o:os | otherwise = o : addGN b os -- | Map the evaluated output of a citation group. mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a] mapGroupOutput f (CG _ _ _ os) = concatMap f $ map snd os pandoc-citeproc-0.10.5.1/src/Text/CSL/Input/Bibutils.hs0000644000000000000000000001426413046402505020546 0ustar0000000000000000{-# LANGUAGE CPP, ForeignFunctionInterface, PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Input.Bibutils -- Copyright : (C) 2008 Andrea Rossato -- License : BSD3 -- -- Maintainer : andrea.rossato@unitn.it -- Stability : unstable -- Portability : unportable -- ----------------------------------------------------------------------------- module Text.CSL.Input.Bibutils ( readBiblioFile , readBiblioString , BibFormat (..) , convertRefs ) where import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc hiding (readMarkdown) import Text.CSL.Compat.Pandoc (readMarkdown) import Data.Char import System.FilePath ( takeExtension ) import Text.CSL.Reference hiding ( Value ) import Text.CSL.Input.Bibtex import qualified Data.ByteString.Lazy as BL import qualified Data.Map as M import Data.Aeson #ifdef USE_BIBUTILS import qualified Control.Exception as E import Control.Exception ( bracket, catch ) import Control.Monad.Trans ( liftIO ) import System.FilePath ( (), (<.>) ) import System.IO.Error ( isAlreadyExistsError ) import System.Directory import Text.Bibutils #endif -- | Read a file with a bibliographic database. The database format -- is recognized by the file extension. -- -- Supported formats are: @json@, @mods@, @bibtex@, @biblatex@, @ris@, -- @endnote@, @endnotexml@, @isi@, @medline@, and @copac@. readBiblioFile :: FilePath -> IO [Reference] readBiblioFile f = case getExt f of ".json" -> BL.readFile f >>= either error return . eitherDecode ".yaml" -> UTF8.readFile f >>= either error return . readYamlBib ".bib" -> readBibtex False True f ".bibtex" -> readBibtex True True f ".biblatex" -> readBibtex False True f #ifdef USE_BIBUTILS ".mods" -> readBiblioFile' f mods_in ".ris" -> readBiblioFile' f ris_in ".enl" -> readBiblioFile' f endnote_in ".xml" -> readBiblioFile' f endnotexml_in ".wos" -> readBiblioFile' f isi_in ".medline" -> readBiblioFile' f medline_in ".copac" -> readBiblioFile' f copac_in _ -> error $ "citeproc: the format of the bibliographic database could not be recognized\n" ++ "using the file extension." #else _ -> error $ "citeproc: Bibliography format not supported.\n" #endif data BibFormat = Json | Yaml | Bibtex | BibLatex #ifdef USE_BIBUTILS | Ris | Endnote | EndnotXml | Isi | Medline | Copac | Mods #endif readBiblioString :: BibFormat -> String -> IO [Reference] readBiblioString b s | Json <- b = either error return $ eitherDecode $ UTF8.fromStringLazy s | Yaml <- b = either error return $ readYamlBib s | Bibtex <- b = readBibtexString True True s | BibLatex <- b = readBibtexString False True s #ifdef USE_BIBUTILS | Ris <- b = go ris_in | Endnote <- b = go endnote_in | EndnotXml <- b = go endnotexml_in | Isi <- b = go isi_in | Medline <- b = go medline_in | Copac <- b = go copac_in | Mods <- b = go mods_in #endif | otherwise = error "in readBiblioString" #ifdef USE_BIBUTILS where go f = withTempDir "citeproc" $ \tdir -> do let tfile = tdir "bibutils-tmp.biblio" UTF8.writeFile tfile s readBiblioFile' tfile f #endif #ifdef USE_BIBUTILS readBiblioFile' :: FilePath -> BiblioIn -> IO [Reference] readBiblioFile' fin bin | bin == biblatex_in = readBibtex False True fin | otherwise = E.handle handleBibfileError $ withTempDir "citeproc" $ \tdir -> do let tfile = tdir "bibutils-tmp" param <- bibl_initparams bin bibtex_out "hs-bibutils" bibl <- bibl_init unsetBOM param setCharsetIn param bibl_charset_unicode setCharsetOut param bibl_charset_unicode _ <- bibl_read param bibl fin _ <- bibl_write param bibl tfile bibl_free bibl bibl_freeparams param refs <- readBibtex True False tfile return $! refs where handleBibfileError :: E.SomeException -> IO [Reference] handleBibfileError e = error $ "Error reading " ++ fin ++ "\n" ++ show e -- | Perform a function in a temporary directory and clean up. withTempDir :: FilePath -> (FilePath -> IO a) -> IO a withTempDir baseName = bracket (createTempDir 0 baseName) (removeDirectoryRecursive) -- | Create a temporary directory with a unique name. createTempDir :: Integer -> FilePath -> IO FilePath createTempDir num baseName = do sysTempDir <- getTemporaryDirectory let dirName = sysTempDir baseName <.> show num liftIO $ Control.Exception.catch (createDirectory dirName >> return dirName) $ \e -> if isAlreadyExistsError e then createTempDir (num + 1) baseName else ioError e #endif getExt :: String -> String getExt = takeExtension . map toLower readYamlBib :: String -> Either String [Reference] readYamlBib s = case readMarkdown s of (Pandoc meta _) -> convertRefs (lookupMeta "references" meta) convertRefs :: Maybe MetaValue -> Either String [Reference] convertRefs Nothing = Right [] convertRefs (Just v) = case fromJSON (metaValueToJSON v) of Data.Aeson.Error s -> -- check for empty string and treat it as empty list: -- --- -- references: -- ... case fromJSON (metaValueToJSON v) of Success "" -> Right [] _ -> Left s Success x -> Right x metaValueToJSON :: MetaValue -> Value metaValueToJSON (MetaMap m) = toJSON $ M.map metaValueToJSON m metaValueToJSON (MetaList xs) = toJSON $ map metaValueToJSON xs metaValueToJSON (MetaString t) = toJSON t metaValueToJSON (MetaBool b) = toJSON b metaValueToJSON (MetaInlines ils) = toJSON ils metaValueToJSON (MetaBlocks bs) = toJSON bs pandoc-citeproc-0.10.5.1/src/Text/CSL/Input/Bibtex.hs0000644000000000000000000020143613114773714020216 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables #-} {-# OPTIONS_GHC -fno-warn-unused-do-bind #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Input.Bibtex -- Copyright : (c) John MacFarlane -- License : BSD-style (see LICENSE) -- -- Maintainer : John MacFarlane -- Stability : unstable-- Portability : unportable -- ----------------------------------------------------------------------------- module Text.CSL.Input.Bibtex ( readBibtex , readBibtexString , readBibtexString' , Lang(..) , langToLocale , getLangFromEnv ) where import Text.Parsec hiding (optional, (<|>), many, State) import Control.Applicative import Text.CSL.Compat.Pandoc (readLaTeX) import Text.Pandoc.Definition import Text.Pandoc.Generic (bottomUp) import Data.List.Split (splitOn, splitWhen, wordsBy) import Data.List (intercalate) import Data.Maybe import Data.Char (toLower, isUpper, toUpper, isDigit, isAlphaNum) import Control.Monad import Control.Monad.RWS import System.Environment (getEnvironment) import Text.CSL.Reference import Text.CSL.Style (Formatted(..), Locale(..), CslTerm(..), Agent(..)) import Text.CSL.Util (trim, onBlocks, unTitlecase, protectCase, splitStrWhen, safeRead) import Text.CSL.Parser (parseLocale) import qualified Text.Pandoc.Walk as Walk import qualified Text.Pandoc.UTF8 as UTF8 blocksToFormatted :: [Block] -> Bib Formatted blocksToFormatted bs = case bs of [Plain xs] -> inlinesToFormatted xs [Para xs] -> inlinesToFormatted xs _ -> inlinesToFormatted $ Walk.query (:[]) bs adjustSpans :: Lang -> Inline -> [Inline] adjustSpans _ (Span ("",[],[]) xs) = xs adjustSpans lang (RawInline (Format "latex") s) | s == "\\hyphen" || s == "\\hyphen " = [Str "-"] | otherwise = bottomUp (concatMap (adjustSpans lang)) $ parseRawLaTeX lang s adjustSpans _ x = [x] parseRawLaTeX :: Lang -> String -> [Inline] parseRawLaTeX lang ('\\':xs) = case latex' contents of [Para ys] -> f command ys [Plain ys] -> f command ys _ -> [] where (command', contents') = break (=='{') xs command = trim command' contents = drop 1 $ reverse $ drop 1 $ reverse contents' f "mkbibquote" ils = [Quoted DoubleQuote ils] f "mkbibemph" ils = [Emph ils] f "mkbibitalic" ils = [Emph ils] -- TODO: italic/=emph f "mkbibbold" ils = [Strong ils] f "mkbibparens" ils = [Str "("] ++ ils ++ [Str ")"] -- TODO: ... f "mkbibbrackets" ils = [Str "["] ++ ils ++ [Str "]"] -- TODO: ... -- ... both should be nestable & should work in year fields f "autocap" ils = ils -- TODO: should work in year fields f "textnormal" ils = [Span ("",["nodecor"],[]) ils] f "bibstring" [Str s] = [Str $ resolveKey' lang s] f _ ils = [Span nullAttr ils] parseRawLaTeX _ _ = [] inlinesToFormatted :: [Inline] -> Bib Formatted inlinesToFormatted ils = do lang <- gets localeLanguage return $ Formatted $ bottomUp (concatMap (adjustSpans lang)) ils data Item = Item{ identifier :: String , entryType :: String , fields :: [(String, String)] } -- | Get 'Lang' from the environment variable LANG, defaulting to en-US. getLangFromEnv :: IO Lang getLangFromEnv = do env <- getEnvironment return $ case lookup "LANG" env of Just x -> case splitWhen (\c -> c == '.' || c == '_' || c == '-') x of (w:z:_) -> Lang w z [w] | not (null w) -> Lang w mempty _ -> Lang "en" "US" Nothing -> Lang "en" "US" -- | Parse a BibTeX or BibLaTeX file into a list of 'Reference's. -- If the first parameter is true, the file will be treated as -- BibTeX; otherwse as BibLaTeX. If the second parameter is -- true, an "untitlecase" transformation will be performed. readBibtex :: Bool -> Bool -> FilePath -> IO [Reference] readBibtex isBibtex caseTransform f = UTF8.readFile f >>= readBibtexString isBibtex caseTransform -- | Like 'readBibtex' but operates on a String rather than a file. readBibtexString :: Bool -> Bool -> String -> IO [Reference] readBibtexString isBibtex caseTransform contents = do lang <- getLangFromEnv locale <- parseLocale (langToLocale lang) return $ readBibtexString' isBibtex caseTransform lang locale contents -- | Pure version of readBibtexString (does not try to get the language -- from the environment). readBibtexString' :: Bool -> Bool -> Lang -> Locale -> String -> [Reference] readBibtexString' isBibtex caseTransform lang locale bibstring = let items = case runParser (bibEntries <* eof) [] "stdin" bibstring of Left err -> error (show err) Right xs -> resolveCrossRefs isBibtex xs in mapMaybe (itemToReference lang locale isBibtex caseTransform) items type BibParser = Parsec [Char] [(String, String)] bibEntries :: BibParser [Item] bibEntries = many (try (skipMany nonEntry >> bibItem)) <* skipMany nonEntry where nonEntry = bibSkip <|> bibComment <|> bibPreamble <|> bibString bibSkip :: BibParser () bibSkip = skipMany1 (satisfy (/='@')) bibComment :: BibParser () bibComment = try $ do char '@' cistring "comment" skipMany (satisfy (/='\n')) bibPreamble :: BibParser () bibPreamble = try $ do char '@' cistring "preamble" spaces void inBraces return () bibString :: BibParser () bibString = try $ do char '@' cistring "string" spaces char '{' spaces f <- entField spaces char '}' updateState $ (f:) return () inBraces :: BibParser String inBraces = try $ do char '{' res <- manyTill ( many1 (noneOf "{}\\") <|> (char '\\' >> ( (char '{' >> return "\\{") <|> (char '}' >> return "\\}") <|> return "\\")) <|> (braced <$> inBraces) ) (char '}') return $ concat res braced :: String -> String braced s = "{" ++ s ++ "}" inQuotes :: BibParser String inQuotes = do char '"' concat <$> manyTill ( many1 (noneOf "\"\\{") <|> (char '\\' >> (\c -> ['\\',c]) <$> anyChar) <|> braced <$> inBraces ) (char '"') fieldName :: BibParser String fieldName = (map toLower) <$> many1 (letter <|> digit <|> oneOf "-_:+") isBibtexKeyChar :: Char -> Bool isBibtexKeyChar c = isAlphaNum c || c `elem` ".:;?!`'()/*@_+=-[]*&" bibItem :: BibParser Item bibItem = do char '@' enttype <- map toLower <$> many1 letter spaces char '{' spaces entid <- many (satisfy isBibtexKeyChar) spaces char ',' spaces entfields <- entField `sepEndBy` (char ',') spaces char '}' return $ Item entid enttype entfields entField :: BibParser (String, String) entField = try $ do spaces k <- fieldName spaces char '=' spaces vs <- (expandString <|> inQuotes <|> inBraces <|> rawWord) `sepBy` (try $ spaces >> char '#' >> spaces) spaces return (k, concat vs) rawWord :: BibParser String rawWord = many1 alphaNum expandString :: BibParser String expandString = do k <- fieldName strs <- getState case lookup k strs of Just v -> return v Nothing -> return k -- return raw key if not found cistring :: String -> BibParser String cistring [] = return [] cistring (c:cs) = do x <- (char (toLower c) <|> char (toUpper c)) xs <- cistring cs return (x:xs) resolveCrossRefs :: Bool -> [Item] -> [Item] resolveCrossRefs isBibtex entries = map (resolveCrossRef isBibtex entries) entries splitKeys :: String -> [String] splitKeys = wordsBy (\c -> c == ' ' || c == ',') getXrefFields :: Bool -> Item -> [Item] -> String -> [(String, String)] getXrefFields isBibtex baseEntry entries keys = do let keys' = splitKeys keys xrefEntry <- [e | e <- entries, identifier e `elem` keys'] (k, v) <- fields xrefEntry if k == "crossref" || k == "xdata" then do xs <- mapM (getXrefFields isBibtex baseEntry entries) (splitKeys v) (x, y) <- xs guard $ isNothing $ lookup x $ fields xrefEntry return (x, y) else do k' <- if isBibtex then return k else transformKey (entryType xrefEntry) (entryType baseEntry) k guard $ isNothing $ lookup k' $ fields baseEntry return (k',v) resolveCrossRef :: Bool -> [Item] -> Item -> Item resolveCrossRef isBibtex entries entry = foldr go entry (fields entry) where go (key, val) entry' = if key == "crossref" || key == "xdata" then entry'{ fields = fields entry' ++ getXrefFields isBibtex entry entries val } else entry' -- transformKey source target key -- derived from Appendix C of bibtex manual transformKey :: String -> String -> String -> [String] transformKey _ _ "ids" = [] transformKey _ _ "crossref" = [] transformKey _ _ "xref" = [] transformKey _ _ "entryset" = [] transformKey _ _ "entrysubtype" = [] transformKey _ _ "execute" = [] transformKey _ _ "label" = [] transformKey _ _ "options" = [] transformKey _ _ "presort" = [] transformKey _ _ "related" = [] transformKey _ _ "relatedoptions" = [] transformKey _ _ "relatedstring" = [] transformKey _ _ "relatedtype" = [] transformKey _ _ "shorthand" = [] transformKey _ _ "shorthandintro" = [] transformKey _ _ "sortkey" = [] transformKey x y "author" | x `elem` ["mvbook", "book"] && y `elem` ["inbook", "bookinbook", "suppbook"] = ["bookauthor", "author"] -- note: this next clause is not in the biblatex manual, but it makes -- sense in the context of CSL conversion: transformKey x y "author" | x == "mvbook" && y == "book" = ["bookauthor", "author"] transformKey "mvbook" y z | y `elem` ["book", "inbook", "bookinbook", "suppbook"] = standardTrans z transformKey x y z | x `elem` ["mvcollection", "mvreference"] && y `elem` ["collection", "reference", "incollection", "inreference", "suppcollection"] = standardTrans z transformKey "mvproceedings" y z | y `elem` ["proceedings", "inproceedings"] = standardTrans z transformKey "book" y z | y `elem` ["inbook", "bookinbook", "suppbook"] = bookTrans z transformKey x y z | x `elem` ["collection", "reference"] && y `elem` ["incollection", "inreference", "suppcollection"] = bookTrans z transformKey "proceedings" "inproceedings" z = bookTrans z transformKey "periodical" y z | y `elem` ["article", "suppperiodical"] = case z of "title" -> ["journaltitle"] "subtitle" -> ["journalsubtitle"] "shorttitle" -> [] "sorttitle" -> [] "indextitle" -> [] "indexsorttitle" -> [] _ -> [z] transformKey _ _ x = [x] standardTrans :: String -> [String] standardTrans z = case z of "title" -> ["maintitle"] "subtitle" -> ["mainsubtitle"] "titleaddon" -> ["maintitleaddon"] "shorttitle" -> [] "sorttitle" -> [] "indextitle" -> [] "indexsorttitle" -> [] _ -> [z] bookTrans :: String -> [String] bookTrans z = case z of "title" -> ["booktitle"] "subtitle" -> ["booksubtitle"] "titleaddon" -> ["booktitleaddon"] "shorttitle" -> [] "sorttitle" -> [] "indextitle" -> [] "indexsorttitle" -> [] _ -> [z] -- | A representation of a language and localization. data Lang = Lang String String -- e.g. "en" "US" -- | Prints a 'Lang' in BCP 47 format. langToLocale :: Lang -> String langToLocale (Lang x y) = x ++ ('-':y) -- Biblatex Localization Keys (see Biblatex manual) -- Currently we only map a subset likely to be used in Biblatex *databases* -- (in fields such as `type`, and via `\bibstring{}` commands). resolveKey :: Lang -> Formatted -> Formatted resolveKey lang (Formatted ils) = Formatted (Walk.walk go ils) where go (Str s) = Str $ resolveKey' lang s go x = x -- biblatex localization keys, from files at -- http://github.com/plk/biblatex/tree/master/tex/latex/biblatex/lbx -- Some keys missing in these were added from csl locale files at -- http://github.com/citation-style-language/locales -- labeled "csl" resolveKey' :: Lang -> String -> String resolveKey' (Lang "ca" "AD") k = case map toLower k of "inpreparation" -> "en preparació" "submitted" -> "enviat" "forthcoming" -> "disponible en breu" "inpress" -> "a impremta" "prepublished" -> "pre-publicat" "mathesis" -> "tesi de màster" "phdthesis" -> "tesi doctoral" "candthesis" -> "tesi de candidatura" "techreport" -> "informe tècnic" "resreport" -> "informe de recerca" "software" -> "programari" "datacd" -> "CD de dades" "audiocd" -> "CD d’àudio" "patent" -> "patent" "patentde" -> "patent alemana" "patenteu" -> "patent europea" "patentfr" -> "patent francesa" "patentuk" -> "patent britànica" "patentus" -> "patent estatunidenca" "patreq" -> "soŀlicitud de patent" "patreqde" -> "soŀlicitud de patent alemana" "patreqeu" -> "soŀlicitud de patent europea" "patreqfr" -> "soŀlicitud de patent francesa" "patrequk" -> "soŀlicitud de patent britànica" "patrequs" -> "soŀlicitud de patent estatunidenca" "countryde" -> "Alemanya" "countryeu" -> "Unió Europea" "countryep" -> "Unió Europea" "countryfr" -> "França" "countryuk" -> "Regne Unit" "countryus" -> "Estats Units d’Amèrica" "newseries" -> "sèrie nova" "oldseries" -> "sèrie antiga" _ -> k resolveKey' (Lang "da" "DK") k = case map toLower k of -- "inpreparation" -> "" -- missing -- "submitted" -> "" -- missing "forthcoming" -> "kommende" -- csl "inpress" -> "i tryk" -- csl -- "prepublished" -> "" -- missing "mathesis" -> "speciale" "phdthesis" -> "ph.d.-afhandling" "candthesis" -> "kandidatafhandling" "techreport" -> "teknisk rapport" "resreport" -> "forskningsrapport" "software" -> "software" "datacd" -> "data-cd" "audiocd" -> "lyd-cd" "patent" -> "patent" "patentde" -> "tysk patent" "patenteu" -> "europæisk patent" "patentfr" -> "fransk patent" "patentuk" -> "britisk patent" "patentus" -> "amerikansk patent" "patreq" -> "ansøgning om patent" "patreqde" -> "ansøgning om tysk patent" "patreqeu" -> "ansøgning om europæisk patent" "patreqfr" -> "ansøgning om fransk patent" "patrequk" -> "ansøgning om britisk patent" "patrequs" -> "ansøgning om amerikansk patent" "countryde" -> "Tyskland" "countryeu" -> "Europæiske Union" "countryep" -> "Europæiske Union" "countryfr" -> "Frankrig" "countryuk" -> "Storbritanien" "countryus" -> "USA" "newseries" -> "ny serie" "oldseries" -> "gammel serie" _ -> k resolveKey' (Lang "de" "DE") k = case map toLower k of "inpreparation" -> "in Vorbereitung" "submitted" -> "eingereicht" "forthcoming" -> "im Erscheinen" "inpress" -> "im Druck" "prepublished" -> "Vorveröffentlichung" "mathesis" -> "Magisterarbeit" "phdthesis" -> "Dissertation" -- "candthesis" -> "" -- missing "techreport" -> "Technischer Bericht" "resreport" -> "Forschungsbericht" "software" -> "Computer-Software" "datacd" -> "CD-ROM" "audiocd" -> "Audio-CD" "patent" -> "Patent" "patentde" -> "deutsches Patent" "patenteu" -> "europäisches Patent" "patentfr" -> "französisches Patent" "patentuk" -> "britisches Patent" "patentus" -> "US-Patent" "patreq" -> "Patentanmeldung" "patreqde" -> "deutsche Patentanmeldung" "patreqeu" -> "europäische Patentanmeldung" "patreqfr" -> "französische Patentanmeldung" "patrequk" -> "britische Patentanmeldung" "patrequs" -> "US-Patentanmeldung" "countryde" -> "Deutschland" "countryeu" -> "Europäische Union" "countryep" -> "Europäische Union" "countryfr" -> "Frankreich" "countryuk" -> "Großbritannien" "countryus" -> "USA" "newseries" -> "neue Folge" "oldseries" -> "alte Folge" _ -> k resolveKey' (Lang "en" "US") k = case map toLower k of "audiocd" -> "audio CD" "by" -> "by" "candthesis" -> "Candidate thesis" "countryde" -> "Germany" "countryep" -> "European Union" "countryeu" -> "European Union" "countryfr" -> "France" "countryuk" -> "United Kingdom" "countryus" -> "United States of America" "datacd" -> "data CD" "edition" -> "ed." "forthcoming" -> "forthcoming" "inpreparation" -> "in preparation" "inpress" -> "in press" "introduction" -> "introduction" "jourser" -> "ser." "mathesis" -> "Master’s thesis" "newseries" -> "new series" "nodate" -> "n. d." "number" -> "no." "numbers" -> "nos." "oldseries" -> "old series" "patent" -> "patent" "patentde" -> "German patent" "patenteu" -> "European patent" "patentfr" -> "French patent" "patentuk" -> "British patent" "patentus" -> "U.S. patent" "patreq" -> "patent request" "patreqde" -> "German patent request" "patreqeu" -> "European patent request" "patreqfr" -> "French patent request" "patrequk" -> "British patent request" "patrequs" -> "U.S. patent request" "phdthesis" -> "PhD thesis" "prepublished" -> "pre-published" "pseudonym" -> "pseud." "recorded" -> "recorded" "resreport" -> "research report" "reviewof" -> "Review of" "revisededition" -> "rev. ed." "software" -> "computer software" "submitted" -> "submitted" "techreport" -> "technical report" "volume" -> "vol." _ -> k resolveKey' (Lang "es" "ES") k = case map toLower k of -- "inpreparation" -> "" -- missing -- "submitted" -> "" -- missing "forthcoming" -> "previsto" -- csl "inpress" -> "en imprenta" -- csl -- "prepublished" -> "" -- missing "mathesis" -> "Tesis de licenciatura" "phdthesis" -> "Tesis doctoral" -- "candthesis" -> "" -- missing "techreport" -> "informe técnico" -- "resreport" -> "" -- missing -- "software" -> "" -- missing -- "datacd" -> "" -- missing -- "audiocd" -> "" -- missing "patent" -> "patente" "patentde" -> "patente alemana" "patenteu" -> "patente europea" "patentfr" -> "patente francesa" "patentuk" -> "patente británica" "patentus" -> "patente americana" "patreq" -> "solicitud de patente" "patreqde" -> "solicitud de patente alemana" "patreqeu" -> "solicitud de patente europea" "patreqfr" -> "solicitud de patente francesa" "patrequk" -> "solicitud de patente británica" "patrequs" -> "solicitud de patente americana" "countryde" -> "Alemania" "countryeu" -> "Unión Europea" "countryep" -> "Unión Europea" "countryfr" -> "Francia" "countryuk" -> "Reino Unido" "countryus" -> "Estados Unidos de América" "newseries" -> "nueva época" "oldseries" -> "antigua época" _ -> k resolveKey' (Lang "fi" "FI") k = case map toLower k of -- "inpreparation" -> "" -- missing -- "submitted" -> "" -- missing "forthcoming" -> "tulossa" -- csl "inpress" -> "painossa" -- csl -- "prepublished" -> "" -- missing "mathesis" -> "tutkielma" "phdthesis" -> "tohtorinväitöskirja" "candthesis" -> "kandidat" "techreport" -> "tekninen raportti" "resreport" -> "tutkimusraportti" "software" -> "ohjelmisto" "datacd" -> "data-CD" "audiocd" -> "ääni-CD" "patent" -> "patentti" "patentde" -> "saksalainen patentti" "patenteu" -> "Euroopan Unionin patentti" "patentfr" -> "ranskalainen patentti" "patentuk" -> "englantilainen patentti" "patentus" -> "yhdysvaltalainen patentti" "patreq" -> "patenttihakemus" "patreqde" -> "saksalainen patenttihakemus" "patreqeu" -> "Euroopan Unionin patenttihakemus" "patreqfr" -> "ranskalainen patenttihakemus" "patrequk" -> "englantilainen patenttihakemus" "patrequs" -> "yhdysvaltalainen patenttihakemus" "countryde" -> "Saksa" "countryeu" -> "Euroopan Unioni" "countryep" -> "Euroopan Unioni" "countryfr" -> "Ranska" "countryuk" -> "Iso-Britannia" "countryus" -> "Yhdysvallat" "newseries" -> "uusi sarja" "oldseries" -> "vanha sarja" _ -> k resolveKey' (Lang "fr" "FR") k = case map toLower k of "inpreparation" -> "en préparation" "submitted" -> "soumis" "forthcoming" -> "à paraître" "inpress" -> "sous presse" "prepublished" -> "prépublié" "mathesis" -> "mémoire de master" "phdthesis" -> "thèse de doctorat" "candthesis" -> "thèse de candidature" "techreport" -> "rapport technique" "resreport" -> "rapport scientifique" "software" -> "logiciel" "datacd" -> "cédérom" "audiocd" -> "disque compact audio" "patent" -> "brevet" "patentde" -> "brevet allemand" "patenteu" -> "brevet européen" "patentfr" -> "brevet français" "patentuk" -> "brevet britannique" "patentus" -> "brevet américain" "patreq" -> "demande de brevet" "patreqde" -> "demande de brevet allemand" "patreqeu" -> "demande de brevet européen" "patreqfr" -> "demande de brevet français" "patrequk" -> "demande de brevet britannique" "patrequs" -> "demande de brevet américain" "countryde" -> "Allemagne" "countryeu" -> "Union européenne" "countryep" -> "Union européenne" "countryfr" -> "France" "countryuk" -> "Royaume-Uni" "countryus" -> "États-Unis" "newseries" -> "nouvelle série" "oldseries" -> "ancienne série" _ -> k resolveKey' (Lang "it" "IT") k = case map toLower k of -- "inpreparation" -> "" -- missing -- "submitted" -> "" -- missing "forthcoming" -> "futuro" -- csl "inpress" -> "in stampa" -- "prepublished" -> "" -- missing "mathesis" -> "tesi di laurea magistrale" "phdthesis" -> "tesi di dottorato" -- "candthesis" -> "" -- missing "techreport" -> "rapporto tecnico" "resreport" -> "rapporto di ricerca" -- "software" -> "" -- missing -- "datacd" -> "" -- missing -- "audiocd" -> "" -- missing "patent" -> "brevetto" "patentde" -> "brevetto tedesco" "patenteu" -> "brevetto europeo" "patentfr" -> "brevetto francese" "patentuk" -> "brevetto britannico" "patentus" -> "brevetto americano" "patreq" -> "brevetto richiesto" "patreqde" -> "brevetto tedesco richiesto" "patreqeu" -> "brevetto europeo richiesto" "patreqfr" -> "brevetto francese richiesto" "patrequk" -> "brevetto britannico richiesto" "patrequs" -> "brevetto U.S.A. richiesto" "countryde" -> "Germania" "countryeu" -> "Unione Europea" "countryep" -> "Unione Europea" "countryfr" -> "Francia" "countryuk" -> "Regno Unito" "countryus" -> "Stati Uniti d’America" "newseries" -> "nuova serie" "oldseries" -> "vecchia serie" _ -> k resolveKey' (Lang "nl" "NL") k = case map toLower k of "inpreparation" -> "in voorbereiding" "submitted" -> "ingediend" "forthcoming" -> "onderweg" "inpress" -> "in druk" "prepublished" -> "voorpublicatie" "mathesis" -> "masterscriptie" "phdthesis" -> "proefschrift" -- "candthesis" -> "" -- missing "techreport" -> "technisch rapport" "resreport" -> "onderzoeksrapport" "software" -> "computersoftware" "datacd" -> "cd-rom" "audiocd" -> "audio-cd" "patent" -> "patent" "patentde" -> "Duits patent" "patenteu" -> "Europees patent" "patentfr" -> "Frans patent" "patentuk" -> "Brits patent" "patentus" -> "Amerikaans patent" "patreq" -> "patentaanvraag" "patreqde" -> "Duitse patentaanvraag" "patreqeu" -> "Europese patentaanvraag" "patreqfr" -> "Franse patentaanvraag" "patrequk" -> "Britse patentaanvraag" "patrequs" -> "Amerikaanse patentaanvraag" "countryde" -> "Duitsland" "countryeu" -> "Europese Unie" "countryep" -> "Europese Unie" "countryfr" -> "Frankrijk" "countryuk" -> "Verenigd Koninkrijk" "countryus" -> "Verenigde Staten van Amerika" "newseries" -> "nieuwe reeks" "oldseries" -> "oude reeks" _ -> k resolveKey' (Lang "pl" "PL") k = case map toLower k of "inpreparation" -> "przygotowanie" "submitted" -> "prezentacja" "forthcoming" -> "przygotowanie" "inpress" -> "wydrukowane" "prepublished" -> "przedwydanie" "mathesis" -> "praca magisterska" "phdthesis" -> "praca doktorska" "techreport" -> "sprawozdanie techniczne" "resreport" -> "sprawozdanie naukowe" "software" -> "oprogramowanie" "datacd" -> "CD-ROM" "audiocd" -> "audio CD" "patent" -> "patent" "patentde" -> "patent Niemiec" "patenteu" -> "patent Europy" "patentfr" -> "patent Francji" "patentuk" -> "patent Wielkiej Brytanji" "patentus" -> "patent USA" "patreq" -> "podanie na patent" "patreqeu" -> "podanie na patent Europy" "patrequs" -> "podanie na patent USA" "countryde" -> "Niemcy" "countryeu" -> "Unia Europejska" "countryep" -> "Unia Europejska" "countryfr" -> "Francja" "countryuk" -> "Wielka Brytania" "countryus" -> "Stany Zjednoczone Ameryki" "newseries" -> "nowa serja" "oldseries" -> "stara serja" _ -> k resolveKey' (Lang "pt" "PT") k = case map toLower k of -- "candthesis" -> "" -- missing "techreport" -> "relatório técnico" "resreport" -> "relatório de pesquisa" "software" -> "software" "datacd" -> "CD-ROM" "patent" -> "patente" "patentde" -> "patente alemã" "patenteu" -> "patente européia" "patentfr" -> "patente francesa" "patentuk" -> "patente britânica" "patentus" -> "patente americana" "patreq" -> "pedido de patente" "patreqde" -> "pedido de patente alemã" "patreqeu" -> "pedido de patente européia" "patreqfr" -> "pedido de patente francesa" "patrequk" -> "pedido de patente britânica" "patrequs" -> "pedido de patente americana" "countryde" -> "Alemanha" "countryeu" -> "União Europeia" "countryep" -> "União Europeia" "countryfr" -> "França" "countryuk" -> "Reino Unido" "countryus" -> "Estados Unidos da América" "newseries" -> "nova série" "oldseries" -> "série antiga" -- "inpreparation" -> "" -- missing "forthcoming" -> "a publicar" -- csl "inpress" -> "na imprensa" -- "prepublished" -> "" -- missing "mathesis" -> "tese de mestrado" "phdthesis" -> "tese de doutoramento" "audiocd" -> "CD áudio" _ -> k resolveKey' (Lang "pt" "BR") k = case map toLower k of -- "candthesis" -> "" -- missing "techreport" -> "relatório técnico" "resreport" -> "relatório de pesquisa" "software" -> "software" "datacd" -> "CD-ROM" "patent" -> "patente" "patentde" -> "patente alemã" "patenteu" -> "patente européia" "patentfr" -> "patente francesa" "patentuk" -> "patente britânica" "patentus" -> "patente americana" "patreq" -> "pedido de patente" "patreqde" -> "pedido de patente alemã" "patreqeu" -> "pedido de patente européia" "patreqfr" -> "pedido de patente francesa" "patrequk" -> "pedido de patente britânica" "patrequs" -> "pedido de patente americana" "countryde" -> "Alemanha" "countryeu" -> "União Europeia" "countryep" -> "União Europeia" "countryfr" -> "França" "countryuk" -> "Reino Unido" "countryus" -> "Estados Unidos da América" "newseries" -> "nova série" "oldseries" -> "série antiga" "inpreparation" -> "em preparação" "forthcoming" -> "aceito para publicação" "inpress" -> "no prelo" "prepublished" -> "pré-publicado" "mathesis" -> "dissertação de mestrado" "phdthesis" -> "tese de doutorado" "audiocd" -> "CD de áudio" _ -> k resolveKey' (Lang "sv" "SE") k = case map toLower k of -- "inpreparation" -> "" -- missing -- "submitted" -> "" -- missing "forthcoming" -> "kommande" -- csl "inpress" -> "i tryck" -- csl -- "prepublished" -> "" -- missing "mathesis" -> "examensarbete" "phdthesis" -> "doktorsavhandling" "candthesis" -> "kandidatavhandling" "techreport" -> "teknisk rapport" "resreport" -> "forskningsrapport" "software" -> "datorprogram" "datacd" -> "data-cd" "audiocd" -> "ljud-cd" "patent" -> "patent" "patentde" -> "tyskt patent" "patenteu" -> "europeiskt patent" "patentfr" -> "franskt patent" "patentuk" -> "brittiskt patent" "patentus" -> "amerikanskt patent" "patreq" -> "patentansökan" "patreqde" -> "ansökan om tyskt patent" "patreqeu" -> "ansökan om europeiskt patent" "patreqfr" -> "ansökan om franskt patent" "patrequk" -> "ansökan om brittiskt patent" "patrequs" -> "ansökan om amerikanskt patent" "countryde" -> "Tyskland" "countryeu" -> "Europeiska unionen" "countryep" -> "Europeiska unionen" "countryfr" -> "Frankrike" "countryuk" -> "Storbritannien" "countryus" -> "USA" "newseries" -> "ny följd" "oldseries" -> "gammal följd" _ -> k resolveKey' _ k = resolveKey' (Lang "en" "US") k parseMonth :: String -> String parseMonth s = case map toLower s of "jan" -> "1" "feb" -> "2" "mar" -> "3" "apr" -> "4" "may" -> "5" "jun" -> "6" "jul" -> "7" "aug" -> "8" "sep" -> "9" "oct" -> "10" "nov" -> "11" "dec" -> "12" _ -> s data BibState = BibState{ untitlecase :: Bool , localeLanguage :: Lang } type Bib = RWST Item () BibState Maybe notFound :: String -> Bib a notFound f = fail $ f ++ " not found" getField :: String -> Bib Formatted getField f = do fs <- asks fields case lookup f fs of Just x -> latex x Nothing -> notFound f getPeriodicalTitle :: String -> Bib Formatted getPeriodicalTitle f = do fs <- asks fields case lookup f fs of Just x -> blocksToFormatted $ onBlocks protectCase $ latex' $ trim x Nothing -> notFound f getTitle :: String -> Bib Formatted getTitle f = do fs <- asks fields case lookup f fs of Just x -> latexTitle x Nothing -> notFound f getShortTitle :: Bool -> String -> Bib Formatted getShortTitle requireColon f = do fs <- asks fields utc <- gets untitlecase let processTitle = if utc then onBlocks unTitlecase else id case lookup f fs of Just x -> case processTitle $ latex' x of bs | not requireColon || containsColon bs -> blocksToFormatted $ upToColon bs | otherwise -> return mempty Nothing -> notFound f containsColon :: [Block] -> Bool containsColon [Para xs] = (Str ":") `elem` xs containsColon [Plain xs] = containsColon [Para xs] containsColon _ = False upToColon :: [Block] -> [Block] upToColon [Para xs] = [Para $ takeWhile (/= (Str ":")) xs] upToColon [Plain xs] = upToColon [Para xs] upToColon bs = bs getDates :: String -> Bib [RefDate] getDates f = getRawField f >>= parseDates parseDates :: Monad m => String-> m [RefDate] parseDates s | '/' `elem` s = mapM parseDate . splitWhen (== '/') $ s -- 199u EDTF format for a range: | 'u' `elem` s = let s1 = map (\c -> if c == 'u' then '0' else c) s s2 = map (\c -> if c == 'u' then '9' else c) s in mapM parseDate [s1, s2] | otherwise = mapM parseDate [s] parseDate :: Monad m => String -> m RefDate -- EDTF format for year of more than 4 digits, starts with 'y': parseDate ('y':xs) = parseDate xs parseDate "open" = return RefDate { year = mempty, month = mempty, season = mempty, day = mempty, other = mempty, circa = False } parseDate "unknown" = return RefDate { year = mempty, month = mempty, season = mempty, day = mempty, other = mempty, circa = False } parseDate s = do let circa' = '~' `elem` s let (year', month', day') = case splitWhen (== '-') $ filter (`notElem` "~?") -- drop time component: $ takeWhile (/='T') s of -- initial - is negative year: ["",y] -> ('-':y, mempty, mempty) ["",y,m] -> ('-':y, m, mempty) ["",y,m,d] -> ('-':y, m, d) [y] -> (y, mempty, mempty) [y,m] -> (y, m, mempty) [y,m,d] -> (y, m, d) _ -> (mempty, mempty, mempty) let year'' = case safeRead year' of -- EDTF 0 == CSL JSON -1 (1 BCE) Just (n :: Integer) | n <= 0 -> show (n - 1) _ -> year' let (season'', month'') = case month' of "21" -> ("1","") "22" -> ("2","") "23" -> ("3","") "24" -> ("4","") _ -> ("", month') return RefDate { year = Literal $ dropWhile (=='0') year'' , month = Literal $ dropWhile (=='0') month'' , season = Literal season'' , day = Literal $ dropWhile (=='0') day' , other = mempty , circa = circa' } isNumber :: String -> Bool isNumber ('-':d:ds) = all isDigit (d:ds) isNumber (d:ds) = all isDigit (d:ds) isNumber _ = False -- A negative (BC) year might be written with -- or --- in bibtex: fixLeadingDash :: String -> String fixLeadingDash (c:d:ds) | (c == '–' || c == '—') && isDigit d = '-':d:ds fixLeadingDash xs = xs getOldDates :: String -> Bib [RefDate] getOldDates prefix = do year' <- fixLeadingDash <$> getRawField (prefix ++ "year") month' <- (parseMonth <$> getRawField (prefix ++ "month")) <|> return "" day' <- getRawField (prefix ++ "day") <|> return mempty endyear' <- fixLeadingDash <$> getRawField (prefix ++ "endyear") <|> return "" endmonth' <- (parseMonth <$> getRawField (prefix ++ "endmonth")) <|> return "" endday' <- getRawField (prefix ++ "endday") <|> return "" let start' = RefDate { year = Literal $ if isNumber year' then year' else "" , month = Literal $ month' , season = mempty , day = Literal day' , other = Literal $ if isNumber year' then "" else year' , circa = False } let end' = if null endyear' then [] else [RefDate { year = Literal $ if isNumber endyear' then endyear' else "" , month = Literal $ endmonth' , day = Literal $ endday' , season = mempty , other = Literal $ if isNumber endyear' then "" else endyear' , circa = False }] return (start':end') getRawField :: String -> Bib String getRawField f = do fs <- asks fields case lookup f fs of Just x -> return x Nothing -> notFound f getAuthorList :: Options -> String -> Bib [Agent] getAuthorList opts f = do fs <- asks fields case lookup f fs of Just x -> latexAuthors opts x Nothing -> notFound f getLiteralList :: String -> Bib [Formatted] getLiteralList f = do fs <- asks fields case lookup f fs of Just x -> toLiteralList $ latex' x Nothing -> notFound f -- separates items with semicolons getLiteralList' :: String -> Bib Formatted getLiteralList' f = (Formatted . intercalate [Str ";", Space] . map unFormatted) <$> getLiteralList f splitByAnd :: [Inline] -> [[Inline]] splitByAnd = splitOn [Space, Str "and", Space] toLiteralList :: [Block] -> Bib [Formatted] toLiteralList [Para xs] = mapM inlinesToFormatted $ splitByAnd xs toLiteralList [Plain xs] = toLiteralList [Para xs] toLiteralList _ = mzero toAuthorList :: Options -> [Block] -> Bib [Agent] toAuthorList opts [Para xs] = mapM (toAuthor opts) $ splitByAnd xs toAuthorList opts [Plain xs] = toAuthorList opts [Para xs] toAuthorList _ _ = mzero toAuthor :: Options -> [Inline] -> Bib Agent toAuthor _ [Str "others"] = return $ Agent { givenName = [] , droppingPart = mempty , nonDroppingPart = mempty , familyName = mempty , nameSuffix = mempty , literal = Formatted [Str "others"] , commaSuffix = False , parseNames = False } toAuthor _ [Span ("",[],[]) ils] = return $ -- corporate author Agent { givenName = [] , droppingPart = mempty , nonDroppingPart = mempty , familyName = mempty , nameSuffix = mempty , literal = Formatted ils , commaSuffix = False , parseNames = False } -- First von Last -- von Last, First -- von Last, Jr ,First -- NOTE: biblatex and bibtex differ on: -- Drummond de Andrade, Carlos -- bibtex takes "Drummond de" as the von; -- biblatex takes the whole as a last name. -- See https://github.com/plk/biblatex/issues/236 -- Here we implement the more sensible biblatex behavior. toAuthor opts ils = do let useprefix = optionSet "useprefix" opts let usecomma = optionSet "juniorcomma" opts let bibtex = optionSet "bibtex" opts let words' = wordsBy (\x -> x == Space || x == Str "\160") let commaParts = map words' $ splitWhen (== Str ",") $ splitStrWhen (\c -> c == ',' || c == '\160') ils let (first, vonlast, jr) = case commaParts of --- First is the longest sequence of white-space separated -- words starting with an uppercase and that is not the -- whole string. von is the longest sequence of whitespace -- separated words whose last word starts with lower case -- and that is not the whole string. [fvl] -> let (caps', rest') = span isCapitalized fvl in if null rest' && not (null caps') then (init caps', [last caps'], []) else (caps', rest', []) [vl,f] -> (f, vl, []) (vl:j:f:_) -> (f, vl, j ) [] -> ([], [], []) let (von, lastname) = if bibtex then case span isCapitalized $ reverse vonlast of ([],(w:ws)) -> (reverse ws, [w]) (vs, ws) -> (reverse ws, reverse vs) else case span (not . isCapitalized) vonlast of (vs@(_:_), []) -> (init vs, [last vs]) (vs, ws) -> (vs, ws) let prefix = Formatted $ intercalate [Space] von let family = Formatted $ intercalate [Space] lastname let suffix = Formatted $ intercalate [Space] jr let givens = map Formatted first return $ Agent { givenName = givens , droppingPart = if useprefix then mempty else prefix , nonDroppingPart = if useprefix then prefix else mempty , familyName = family , nameSuffix = suffix , literal = mempty , commaSuffix = usecomma , parseNames = False } isCapitalized :: [Inline] -> Bool isCapitalized (Str (c:cs) : rest) | isUpper c = True | isDigit c = isCapitalized (Str cs : rest) | otherwise = False isCapitalized (_:rest) = isCapitalized rest isCapitalized [] = True optionSet :: String -> Options -> Bool optionSet key opts = case lookup key opts of Just "true" -> True Just s -> s == mempty _ -> False latex' :: String -> [Block] latex' s = Walk.walk removeSoftBreak bs where Pandoc _ bs = readLaTeX s removeSoftBreak :: Inline -> Inline removeSoftBreak SoftBreak = Space removeSoftBreak x = x latex :: String -> Bib Formatted latex s = blocksToFormatted $ latex' $ trim s latexTitle :: String -> Bib Formatted latexTitle s = do utc <- gets untitlecase let processTitle = if utc then onBlocks unTitlecase else id blocksToFormatted $ processTitle $ latex' s latexAuthors :: Options -> String -> Bib [Agent] latexAuthors opts = toAuthorList opts . latex' . trim bib :: Bib Reference -> Item -> Maybe Reference bib m entry = fmap fst $ evalRWST m entry (BibState True (Lang "en" "US")) toLocale :: String -> String toLocale "english" = "en-US" -- "en-EN" unavailable in CSL toLocale "usenglish" = "en-US" toLocale "american" = "en-US" toLocale "british" = "en-GB" toLocale "ukenglish" = "en-GB" toLocale "canadian" = "en-US" -- "en-CA" unavailable in CSL toLocale "australian" = "en-GB" -- "en-AU" unavailable in CSL toLocale "newzealand" = "en-GB" -- "en-NZ" unavailable in CSL toLocale "afrikaans" = "af-ZA" toLocale "arabic" = "ar" toLocale "basque" = "eu" toLocale "bulgarian" = "bg-BG" toLocale "catalan" = "ca-AD" toLocale "croatian" = "hr-HR" toLocale "czech" = "cs-CZ" toLocale "danish" = "da-DK" toLocale "dutch" = "nl-NL" toLocale "estonian" = "et-EE" toLocale "finnish" = "fi-FI" toLocale "canadien" = "fr-CA" toLocale "acadian" = "fr-CA" toLocale "french" = "fr-FR" toLocale "francais" = "fr-FR" toLocale "austrian" = "de-AT" toLocale "naustrian" = "de-AT" toLocale "german" = "de-DE" toLocale "germanb" = "de-DE" toLocale "ngerman" = "de-DE" toLocale "greek" = "el-GR" toLocale "polutonikogreek" = "el-GR" toLocale "hebrew" = "he-IL" toLocale "hungarian" = "hu-HU" toLocale "icelandic" = "is-IS" toLocale "italian" = "it-IT" toLocale "japanese" = "ja-JP" toLocale "latvian" = "lv-LV" toLocale "lithuanian" = "lt-LT" toLocale "magyar" = "hu-HU" toLocale "mongolian" = "mn-MN" toLocale "norsk" = "nb-NO" toLocale "nynorsk" = "nn-NO" toLocale "farsi" = "fa-IR" toLocale "polish" = "pl-PL" toLocale "brazil" = "pt-BR" toLocale "brazilian" = "pt-BR" toLocale "portugues" = "pt-PT" toLocale "portuguese" = "pt-PT" toLocale "romanian" = "ro-RO" toLocale "russian" = "ru-RU" toLocale "serbian" = "sr-RS" toLocale "serbianc" = "sr-RS" toLocale "slovak" = "sk-SK" toLocale "slovene" = "sl-SL" toLocale "spanish" = "es-ES" toLocale "swedish" = "sv-SE" toLocale "thai" = "th-TH" toLocale "turkish" = "tr-TR" toLocale "ukrainian" = "uk-UA" toLocale "vietnamese" = "vi-VN" toLocale "latin" = "la" toLocale x = x concatWith :: Char -> [Formatted] -> Formatted concatWith sep = Formatted . foldl go mempty . map unFormatted where go :: [Inline] -> [Inline] -> [Inline] go accum [] = accum go accum s = case reverse accum of [] -> s (Str x:_) | not (null x) && last x `elem` "!?.,:;" -> accum ++ (Space : s) _ -> accum ++ (Str [sep] : Space : s) type Options = [(String, String)] parseOptions :: String -> Options parseOptions = map breakOpt . splitWhen (==',') where breakOpt x = case break (=='=') x of (w,v) -> (map toLower $ trim w, map toLower $ trim $ drop 1 v) ordinalize :: Locale -> String -> String ordinalize locale n = case [termSingular c | c <- terms, cslTerm c == ("ordinal-" ++ pad0 n)] ++ [termSingular c | c <- terms, cslTerm c == "ordinal"] of (suff:_) -> n ++ suff [] -> n where pad0 [c] = ['0',c] pad0 s = s terms = localeTerms locale itemToReference :: Lang -> Locale -> Bool -> Bool -> Item -> Maybe Reference itemToReference lang locale bibtex caseTransform = bib $ do modify $ \st -> st{ localeLanguage = lang, untitlecase = case lang of Lang "en" _ -> caseTransform _ -> False } id' <- asks identifier et <- asks entryType guard $ et /= "xdata" opts <- (parseOptions <$> getRawField "options") <|> return [] let getAuthorList' = getAuthorList (("bibtex", map toLower $ show bibtex):opts) st <- getRawField "entrysubtype" <|> return mempty isEvent <- (True <$ (getRawField "eventdate" <|> getRawField "eventtitle" <|> getRawField "venue")) <|> return False reftype' <- resolveKey lang <$> getField "type" <|> return mempty let (reftype, refgenre) = case et of "article" | st == "magazine" -> (ArticleMagazine,mempty) | st == "newspaper" -> (ArticleNewspaper,mempty) | otherwise -> (ArticleJournal,mempty) "book" -> (Book,mempty) "booklet" -> (Pamphlet,mempty) "bookinbook" -> (Chapter,mempty) "collection" -> (Book,mempty) "electronic" -> (Webpage,mempty) "inbook" -> (Chapter,mempty) "incollection" -> (Chapter,mempty) "inreference" -> (EntryEncyclopedia,mempty) "inproceedings" -> (PaperConference,mempty) "manual" -> (Book,mempty) "mastersthesis" -> (Thesis, if reftype' == mempty then Formatted [Str $ resolveKey' lang "mathesis"] else reftype') "misc" -> (NoType,mempty) "mvbook" -> (Book,mempty) "mvcollection" -> (Book,mempty) "mvproceedings" -> (Book,mempty) "mvreference" -> (Book,mempty) "online" -> (Webpage,mempty) "patent" -> (Patent,mempty) "periodical" | st == "magazine" -> (ArticleMagazine,mempty) | st == "newspaper" -> (ArticleNewspaper,mempty) | otherwise -> (ArticleJournal,mempty) "phdthesis" -> (Thesis, if reftype' == mempty then Formatted [Str $ resolveKey' lang "phdthesis"] else reftype') "proceedings" -> (Book,mempty) "reference" -> (Book,mempty) "report" -> (Report,mempty) "suppbook" -> (Chapter,mempty) "suppcollection" -> (Chapter,mempty) "suppperiodical" | st == "magazine" -> (ArticleMagazine,mempty) | st == "newspaper" -> (ArticleNewspaper,mempty) | otherwise -> (ArticleJournal,mempty) "techreport" -> (Report,mempty) "thesis" -> (Thesis,mempty) "unpublished" -> (if isEvent then Speech else Manuscript,mempty) "www" -> (Webpage,mempty) -- biblatex, "unsupported" "artwork" -> (Graphic,mempty) "audio" -> (Song,mempty) -- for audio *recordings* "commentary" -> (Book,mempty) "image" -> (Graphic,mempty) -- or "figure" ? "jurisdiction" -> (LegalCase,mempty) "legislation" -> (Legislation,mempty) -- or "bill" ? "legal" -> (Treaty,mempty) "letter" -> (PersonalCommunication,mempty) "movie" -> (MotionPicture,mempty) "music" -> (Song,mempty) -- for musical *recordings* "performance" -> (Speech,mempty) "review" -> (Review,mempty) -- or "review-book" ? "software" -> (Book,mempty) -- for lack of any better match "standard" -> (Legislation,mempty) "video" -> (MotionPicture,mempty) -- biblatex-apa: "data" -> (Dataset,mempty) "letters" -> (PersonalCommunication,mempty) "newsarticle" -> (ArticleNewspaper,mempty) _ -> (NoType,mempty) -- hyphenation: let defaultHyphenation = case lang of Lang x y -> x ++ "-" ++ y let getLangId = do langid <- (trim . map toLower) <$> getRawField "langid" idopts <- (trim . map toLower) <$> getRawField "langidopts" <|> return "" case (langid, idopts) of ("english","variant=british") -> return "british" ("english","variant=american") -> return "american" ("english","variant=us") -> return "american" ("english","variant=usmax") -> return "american" ("english","variant=uk") -> return "british" ("english","variant=australian") -> return "australian" ("english","variant=newzealand") -> return "newzealand" (x,_) -> return x hyphenation <- ((toLocale . map toLower) <$> (getLangId <|> getRawField "hyphenation")) <|> return mempty -- authors: author' <- getAuthorList' "author" <|> return [] containerAuthor' <- getAuthorList' "bookauthor" <|> return [] translator' <- getAuthorList' "translator" <|> return [] editortype <- getRawField "editortype" <|> return mempty editor'' <- getAuthorList' "editor" <|> return [] director'' <- getAuthorList' "director" <|> return [] let (editor', director') = case editortype of "director" -> ([], editor'') _ -> (editor'', director'') -- FIXME: add same for editora, editorb, editorc -- titles let isArticle = et `elem` ["article", "periodical", "suppperiodical", "review"] let isPeriodical = et == "periodical" let isChapterlike = et `elem` ["inbook","incollection","inproceedings","inreference","bookinbook"] hasMaintitle <- (True <$ (getRawField "maintitle")) <|> return False let hyphenation' = if null hyphenation then defaultHyphenation else hyphenation let la = case splitWhen (== '-') hyphenation' of (x:_) -> x [] -> mempty modify $ \s -> s{ untitlecase = caseTransform && la == "en" } title' <- (guard isPeriodical >> getTitle "issuetitle") <|> (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "maintitle") <|> getTitle "title" <|> return mempty subtitle' <- (guard isPeriodical >> getTitle "issuesubtitle") <|> (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "mainsubtitle") <|> getTitle "subtitle" <|> return mempty titleaddon' <- (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "maintitleaddon") <|> getTitle "titleaddon" <|> return mempty volumeTitle' <- (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "title") <|> (guard hasMaintitle >> guard isChapterlike >> getTitle "booktitle") <|> return mempty volumeSubtitle' <- (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "subtitle") <|> (guard hasMaintitle >> guard isChapterlike >> getTitle "booksubtitle") <|> return mempty volumeTitleAddon' <- (guard hasMaintitle >> guard (not isChapterlike) >> getTitle "titleaddon") <|> (guard hasMaintitle >> guard isChapterlike >> getTitle "booktitleaddon") <|> return mempty containerTitle' <- (guard isPeriodical >> getPeriodicalTitle "title") <|> (guard isChapterlike >> getTitle "maintitle") <|> (guard isChapterlike >> getTitle "booktitle") <|> getPeriodicalTitle "journaltitle" <|> getPeriodicalTitle "journal" <|> return mempty containerSubtitle' <- (guard isPeriodical >> getPeriodicalTitle "subtitle") <|> (guard isChapterlike >> getTitle "mainsubtitle") <|> (guard isChapterlike >> getTitle "booksubtitle") <|> getPeriodicalTitle "journalsubtitle" <|> return mempty containerTitleAddon' <- (guard isPeriodical >> getPeriodicalTitle "titleaddon") <|> (guard isChapterlike >> getTitle "maintitleaddon") <|> (guard isChapterlike >> getTitle "booktitleaddon") <|> return mempty containerTitleShort' <- (guard isPeriodical >> guard (not hasMaintitle) >> getField "shorttitle") <|> getPeriodicalTitle "shortjournal" <|> return mempty -- change numerical series title to e.g. 'series 3' let fixSeriesTitle (Formatted [Str xs]) | all isDigit xs = Formatted [Str (ordinalize locale xs), Space, Str (resolveKey' lang "ser.")] fixSeriesTitle x = x seriesTitle' <- (fixSeriesTitle . resolveKey lang) <$> getTitle "series" <|> return mempty shortTitle' <- (guard (not hasMaintitle || isChapterlike) >> getTitle "shorttitle") <|> if (subtitle' /= mempty || titleaddon' /= mempty) && (not hasMaintitle) then getShortTitle False "title" else getShortTitle True "title" <|> return mempty eventTitle' <- getTitle "eventtitle" <|> return mempty origTitle' <- getTitle "origtitle" <|> return mempty -- publisher pubfields <- mapM (\f -> Just `fmap` (if bibtex || f == "howpublished" then getField f else getLiteralList' f) <|> return Nothing) ["school","institution","organization", "howpublished","publisher"] let publisher' = concatWith ';' [p | Just p <- pubfields] origpublisher' <- getField "origpublisher" <|> return mempty -- places venue' <- getField "venue" <|> return mempty address' <- (if bibtex then getField "address" else getLiteralList' "address" <|> (guard (et /= "patent") >> getLiteralList' "location")) <|> return mempty origLocation' <- (if bibtex then getField "origlocation" else getLiteralList' "origlocation") <|> return mempty jurisdiction' <- if et == "patent" then ((concatWith ';' . map (resolveKey lang)) <$> getLiteralList "location") <|> return mempty else return mempty -- locators pages' <- getField "pages" <|> return mempty volume' <- getField "volume" <|> return mempty part' <- getField "part" <|> return mempty volumes' <- getField "volumes" <|> return mempty pagetotal' <- getField "pagetotal" <|> return mempty chapter' <- getField "chapter" <|> return mempty edition' <- getField "edition" <|> return mempty version' <- getField "version" <|> return mempty (number', collectionNumber', issue') <- (getField "number" <|> return mempty) >>= \x -> if et `elem` ["book","collection","proceedings","reference", "mvbook","mvcollection","mvproceedings", "mvreference", "bookinbook","inbook", "incollection","inproceedings", "inreference", "suppbook","suppcollection"] then return (mempty,x,mempty) else if isArticle then (getField "issue" >>= \y -> return (mempty,mempty,concatWith ',' [x,y])) <|> return (mempty,mempty,x) else return (x,mempty,mempty) -- dates issued' <- getDates "date" <|> getOldDates mempty <|> return [] eventDate' <- getDates "eventdate" <|> getOldDates "event" <|> return [] origDate' <- getDates "origdate" <|> getOldDates "orig" <|> return [] accessed' <- getDates "urldate" <|> getOldDates "url" <|> return [] -- url, doi, isbn, etc.: -- note that with eprinttype = arxiv, we take eprint to be a partial url url' <- (guard (et == "online" || lookup "url" opts /= Just "false") >> getRawField "url") <|> (do etype <- getRawField "eprinttype" eprint <- getRawField "eprint" case map toLower etype of "arxiv" -> return $ "http://arxiv.org/abs/" ++ eprint "googlebooks" -> return $ "http://books.google.com?id=" ++ eprint _ -> mzero) <|> return mempty doi' <- (guard (lookup "doi" opts /= Just "false") >> getRawField "doi") <|> return mempty isbn' <- getRawField "isbn" <|> return mempty issn' <- getRawField "issn" <|> return mempty pmid' <- getRawField "pmid" <|> return mempty pmcid' <- getRawField "pmcid" <|> return mempty callNumber' <- getRawField "library" <|> return mempty -- notes annotation' <- getField "annotation" <|> getField "annote" <|> return mempty abstract' <- getField "abstract" <|> return mempty keywords' <- getField "keywords" <|> return mempty note' <- if et == "periodical" then return mempty else (getField "note" <|> return mempty) addendum' <- if bibtex then return mempty else getField "addendum" <|> return mempty pubstate' <- resolveKey lang `fmap` ( getField "pubstate" <|> case issued' of (x:_) | other x == Literal "forthcoming" -> return (Formatted [Str "forthcoming"]) _ -> return mempty ) let convertEnDash (Str s) = Str (map (\c -> if c == '–' then '-' else c) s) convertEnDash x = x let takeDigits (Str xs : _) = case takeWhile isDigit xs of [] -> [] ds -> [Str ds] takeDigits x = x return $ emptyReference { refId = Literal id' , refType = reftype , author = author' , editor = editor' , translator = translator' -- , recipient = undefined -- :: [Agent] -- , interviewer = undefined -- :: [Agent] -- , composer = undefined -- :: [Agent] , director = director' -- , illustrator = undefined -- :: [Agent] -- , originalAuthor = undefined -- :: [Agent] , containerAuthor = containerAuthor' -- , collectionEditor = undefined -- :: [Agent] -- , editorialDirector = undefined -- :: [Agent] -- , reviewedAuthor = undefined -- :: [Agent] , issued = issued' , eventDate = eventDate' , accessed = accessed' -- , container = undefined -- :: [RefDate] , originalDate = origDate' -- , submitted = undefined -- :: [RefDate] , title = concatWith '.' [ concatWith ':' [title', subtitle'] , titleaddon' ] , titleShort = shortTitle' -- , reviewedTitle = undefined -- :: String , containerTitle = concatWith '.' [ concatWith ':' [ containerTitle' , containerSubtitle'] , containerTitleAddon' ] , collectionTitle = seriesTitle' , volumeTitle = concatWith '.' [ concatWith ':' [ volumeTitle' , volumeSubtitle'] , volumeTitleAddon' ] , containerTitleShort = containerTitleShort' , collectionNumber = collectionNumber' , originalTitle = origTitle' , publisher = publisher' , originalPublisher = origpublisher' , publisherPlace = address' , originalPublisherPlace = origLocation' , jurisdiction = jurisdiction' , event = eventTitle' , eventPlace = venue' , page = Formatted $ Walk.walk convertEnDash $ unFormatted pages' , pageFirst = Formatted $ takeDigits $ unFormatted pages' , numberOfPages = pagetotal' , version = version' , volume = Formatted $ intercalate [Str "."] $ filter (not . null) [unFormatted volume', unFormatted part'] , numberOfVolumes = volumes' , issue = issue' , chapterNumber = chapter' -- , medium = undefined -- :: String , status = pubstate' , edition = edition' -- , section = undefined -- :: String -- , source = undefined -- :: String , genre = if refgenre == mempty then reftype' else refgenre , note = concatWith '.' [note', addendum'] , annote = annotation' , abstract = abstract' , keyword = keywords' , number = number' , url = Literal url' , doi = Literal doi' , isbn = Literal isbn' , issn = Literal issn' , pmcid = Literal pmcid' , pmid = Literal pmid' , language = Literal hyphenation , callNumber = Literal callNumber' } pandoc-citeproc-0.10.5.1/src/Text/CSL/Output/Pandoc.hs0000644000000000000000000001444713043217625020405 0ustar0000000000000000{-# LANGUAGE PatternGuards, DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Output.Pandoc -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The pandoc output formatter for CSL -- ----------------------------------------------------------------------------- module Text.CSL.Output.Pandoc ( renderPandoc , renderPandoc' , headInline , initInline , lastInline , tailInline , tailFirstInlineStr , toCapital ) where import Text.CSL.Util ( proc, proc', tailInline, lastInline, initInline, tailFirstInlineStr, headInline, toCapital ) import Data.Maybe ( fromMaybe ) import Text.CSL.Style import Text.Pandoc.Definition import Text.Pandoc.XML (fromEntities) renderPandoc :: Style -> Formatted -> [Inline] renderPandoc sty = proc (convertQuoted sty) . proc' (clean' sty) . flipFlop . fixBreaks . unFormatted -- remove leading/trailing LineBreak fixBreaks :: [Inline] -> [Inline] fixBreaks = dropWhile (== LineBreak) . reverse . dropWhile (== LineBreak) . reverse renderPandoc' :: Style -> (Formatted, String) -> Block renderPandoc' sty (form, citId) = Div ("ref-" ++ citId, [], []) [Para $ renderPandoc sty form] clean' :: Style -> [Inline] -> [Inline] clean' _ [] = [] clean' sty (i:is) = case (i:is) of (Str "" : rest) -> clean' sty rest (Str xs : Str ys : rest) -> clean' sty $ Str (xs ++ ys) : rest (Link a1 lab1 ('#':r1, "") : Str "\8211" : Link a2 lab2 ('#':r2, "") : rest) | r1 == r2, a1 == a2 -> Link a1 (lab1 ++ [Str "\8211"] ++ lab2) ('#':r1, "") : clean' sty rest (Span ("",[],[]) inls : _) -> inls ++ clean' sty is (Span ("",["csl-inquote"],kvs) inls : _) -> let isOuter = lookup "position" kvs == Just "outer" in case headInline is of [x] -> if x `elem` ".," && isPunctuationInQuote sty then if lastInline inls `elem` [".",",",";",":","!","?"] then quoted isOuter inls ++ clean' sty (tailInline is) else quoted isOuter (inls ++ [Str [x]]) ++ clean' sty (tailInline is) else quoted isOuter inls ++ clean' sty is _ -> quoted isOuter inls ++ clean' sty is (Quoted t inls : _) -> quoted (t == DoubleQuote) inls ++ clean' sty is _ -> if lastInline [i] == headInline is && isPunct then i : clean' sty (tailInline is) else i : clean' sty is where isPunct = all (`elem` ".,;:!? ") $ headInline is locale = case styleLocale sty of (x:_) -> x [] -> Locale [] [] [] [] [] -- should not happen getQuote s d = case [term | term <- localeTerms locale, cslTerm term == s] of (x:_) -> Str (termSingular x) _ -> Str d openQuoteOuter = getQuote "open-quote" "“" openQuoteInner = getQuote "open-inner-quote" "‘" closeQuoteOuter = getQuote "close-quote" "”" closeQuoteInner = getQuote "close-inner-quote" "’" quoted True ils = openQuoteOuter : ils ++ [closeQuoteOuter] quoted False ils = openQuoteInner : ils ++ [closeQuoteInner] convertQuoted :: Style -> [Inline] -> [Inline] convertQuoted s = convertQuoted' where locale = let l = styleLocale s in case l of [x] -> x; _ -> Locale [] [] [] [] [] getQuote x y = fromEntities . termSingular . fromMaybe newTerm {termSingular = x} . findTerm y Long . localeTerms $ locale doubleQuotesO = getQuote "\"" "open-quote" doubleQuotesC = getQuote "\"" "close-quote" singleQuotesO = getQuote "'" "open-inner-quote" singleQuotesC = getQuote "'" "close-inner-quote" convertQuoted' o | (Quoted DoubleQuote t:xs) <- o = Str doubleQuotesO : t ++ Str doubleQuotesC : convertQuoted' xs | (Quoted SingleQuote t:xs) <- o = Str singleQuotesO : t ++ Str singleQuotesC : convertQuoted' xs | (x :xs) <- o = x : convertQuoted' xs | otherwise = [] -- flip-flop data FlipFlopState = FlipFlopState { inEmph :: Bool , inStrong :: Bool , inSmallCaps :: Bool , inOuterQuotes :: Bool } flipFlop :: [Inline] -> [Inline] flipFlop = map (flipFlop' $ FlipFlopState False False False False) flipFlop' :: FlipFlopState -> Inline -> Inline flipFlop' st (Emph ils) = (if inEmph st then Span ("",["csl-no-emph"],[]) else Emph) $ map (flipFlop' st{ inEmph = not $ inEmph st }) ils flipFlop' st (Strong ils) = (if inStrong st then Span ("",["csl-no-strong"],[]) else Strong) $ map (flipFlop' st{ inStrong = not $ inStrong st }) ils flipFlop' st (SmallCaps ils) = (if inSmallCaps st then Span ("",["csl-no-smallcaps"],[]) else SmallCaps) $ map (flipFlop' st{ inSmallCaps = not $ inSmallCaps st }) ils flipFlop' st (Strikeout ils) = Strikeout $ map (flipFlop' st) ils flipFlop' st (Superscript ils) = Superscript $ map (flipFlop' st) ils flipFlop' st (Subscript ils) = Subscript $ map (flipFlop' st) ils flipFlop' st (Quoted _ ils) = Quoted (if inOuterQuotes st then SingleQuote else DoubleQuote) $ map (flipFlop' st{ inOuterQuotes = not $ inOuterQuotes st }) ils flipFlop' st (Span (_, ["csl-inquote"], _) ils) = Span ("", ["csl-inquote"], [("position", if inOuterQuotes st then "inner" else "outer")]) $ map (flipFlop' st{ inOuterQuotes = not $ inOuterQuotes st }) ils flipFlop' st (Span (id',classes,kvs) ils) | "nodecor" `elem` classes = Span (id',classes',kvs) $ map (flipFlop' st) ils | otherwise = Span (id',classes,kvs) $ map (flipFlop' st) ils where classes' = filter (/= "nodecor") classes ++ ["csl-no-emph" | inEmph st] ++ ["csl-no-strong" | inStrong st] ++ ["csl-no-smallcaps" | inSmallCaps st] flipFlop' st (Link attr ils t) = Link attr (map (flipFlop' st) ils) t flipFlop' st (Note [Para ils]) = Note [Para $ map (flipFlop' st) ils] flipFlop' _ il = il pandoc-citeproc-0.10.5.1/src/Text/CSL/Output/Plain.hs0000644000000000000000000000146713046402505020236 0ustar0000000000000000{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Output.Plain -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The plain ascii output formatter for CSL -- ----------------------------------------------------------------------------- module Text.CSL.Output.Plain ( renderPlain ) where import Text.CSL.Style import Text.CSL.Compat.Pandoc (writePlain) import Text.Pandoc (Block(Plain), Pandoc(..), nullMeta) -- | Render the 'Formatted' into a plain text string. renderPlain :: Formatted -> String renderPlain (Formatted ils) = writePlain $ Pandoc nullMeta [Plain ils] pandoc-citeproc-0.10.5.1/src/Text/CSL/Data.hs0000644000000000000000000001026313063460660016543 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Data -- Copyright : (c) John MacFarlane -- License : BSD-style (see LICENSE) -- -- Maintainer : John MacFarlane -- Stability : unstable -- Portability : unportable -- ----------------------------------------------------------------------------- module Text.CSL.Data ( getLocale , CSLLocaleException(..) , getDefaultCSL , getManPage , getLicense , langBase ) where import System.FilePath () import Data.Typeable import qualified Data.ByteString.Lazy as L import qualified Control.Exception as E #ifdef EMBED_DATA_FILES import Data.Maybe (fromMaybe) import Text.CSL.Data.Embedded (localeFiles, defaultCSL, manpage, license) #else import Paths_pandoc_citeproc (getDataFileName) import System.Directory (doesFileExist) #endif data CSLLocaleException = CSLLocaleNotFound String | CSLLocaleReadError E.IOException deriving Typeable instance Show CSLLocaleException where show (CSLLocaleNotFound s) = "Could not find locale data for " ++ s show (CSLLocaleReadError e) = show e instance E.Exception CSLLocaleException -- | Raises 'CSLLocaleException' on error. getLocale :: String -> IO L.ByteString getLocale s = do #ifdef EMBED_DATA_FILES let toLazy x = L.fromChunks [x] case length s of 0 -> maybe (E.throwIO $ CSLLocaleNotFound "en-US") (return . toLazy) $ lookup "locales-en-US.xml" localeFiles 2 -> let fn = ("locales-" ++ fromMaybe s (lookup s langBase) ++ ".xml") in case lookup fn localeFiles of Just x' -> return $ toLazy x' _ -> E.throwIO $ CSLLocaleNotFound s _ -> case lookup ("locales-" ++ take 5 s ++ ".xml") localeFiles of Just x' -> return $ toLazy x' _ -> -- try again with 2-letter locale let s' = take 2 s in case lookup ("locales-" ++ fromMaybe s' (lookup s' langBase) ++ ".xml") localeFiles of Just x'' -> return $ toLazy x'' _ -> E.throwIO $ CSLLocaleNotFound s #else f <- case length s of 0 -> return "locales/locales-en-US.xml" 2 -> getDataFileName ("locales/locales-" ++ maybe s id (lookup s langBase) ++ ".xml") _ -> getDataFileName ("locales/locales-" ++ take 5 s ++ ".xml") exists <- doesFileExist f if not exists && length s > 2 then getLocale $ take 2 s -- try again with base locale else E.handle (\e -> E.throwIO (CSLLocaleReadError e)) $ L.readFile f #endif getDefaultCSL :: IO L.ByteString getDefaultCSL = #ifdef EMBED_DATA_FILES return $ L.fromChunks [defaultCSL] #else getDataFileName "chicago-author-date.csl" >>= L.readFile #endif getManPage :: IO L.ByteString getManPage = #ifdef EMBED_DATA_FILES return $ L.fromChunks [manpage] #else getDataFileName "man/man1/pandoc-citeproc.1" >>= L.readFile #endif getLicense :: IO L.ByteString getLicense = #ifdef EMBED_DATA_FILES return $ L.fromChunks [license] #else getDataFileName "LICENSE" >>= L.readFile #endif langBase :: [(String, String)] langBase = [("af", "af-ZA") ,("bg", "bg-BG") ,("ca", "ca-AD") ,("cs", "cs-CZ") ,("da", "da-DK") ,("de", "de-DE") ,("el", "el-GR") ,("en", "en-US") ,("es", "es-ES") ,("et", "et-EE") ,("fa", "fa-IR") ,("fi", "fi-FI") ,("fr", "fr-FR") ,("he", "he-IL") ,("hr", "hr-HR") ,("hu", "hu-HU") ,("is", "is-IS") ,("it", "it-IT") ,("ja", "ja-JP") ,("km", "km-KH") ,("ko", "ko-KR") ,("lt", "lt-LT") ,("lv", "lv-LV") ,("mn", "mn-MN") ,("nb", "nb-NO") ,("nl", "nl-NL") ,("nn", "nn-NO") ,("pl", "pl-PL") ,("pt", "pt-PT") ,("ro", "ro-RO") ,("ru", "ru-RU") ,("sk", "sk-SK") ,("sl", "sl-SI") ,("sr", "sr-RS") ,("sv", "sv-SE") ,("th", "th-TH") ,("tr", "tr-TR") ,("uk", "uk-UA") ,("vi", "vi-VN") ,("zh", "zh-CN") ] pandoc-citeproc-0.10.5.1/src/Text/CSL/Util.hs0000644000000000000000000004404313076677105016622 0ustar0000000000000000{-# LANGUAGE ScopedTypeVariables, PatternGuards, FlexibleContexts #-} module Text.CSL.Util ( safeRead , readNum , (<^>) , capitalize , camelize , uncamelize , isPunct , last' , init' , words' , trim , triml , trimr , parseBool , parseString , parseInt , mb , (.#?) , (.#:) , onBlocks , titlecase , unTitlecase , protectCase , splitStrWhen , proc , proc' , procM , query , betterThan , toRead , inlinesToString , headInline , lastInline , tailInline , initInline , tailFirstInlineStr , toCapital , mapHeadInline , tr' , findFile , (&=) , mapping' , parseRomanNumeral , isRange ) where import Data.Aeson import Data.Aeson.Types (Parser) import Data.Text (Text) import qualified Data.Text as T import Data.Char (toLower, toUpper, isLower, isUpper, isPunctuation, isAscii) import qualified Data.Traversable import Text.Pandoc.Shared (safeRead, stringify) import Text.Pandoc.Walk (walk) import Text.Pandoc import Data.List.Split (wordsBy) import Control.Monad.State import Data.Generics ( Typeable, Data, everywhere, everywhereM, mkM, everywhere', everything, mkT, mkQ ) import System.FilePath import System.Directory (doesFileExist) import qualified Data.Yaml.Builder as Y import Data.Yaml.Builder (ToYaml(..), YamlBuilder) import qualified Text.Parsec as P #ifdef TRACE import qualified Debug.Trace import Text.Show.Pretty (ppShow) #endif #ifdef TRACE tr' :: Show a => String -> a -> a tr' note' x = Debug.Trace.trace ("=== " ++ note' ++ "\n" ++ ppShow x ++ "\n") x #else tr' :: String -> a -> a tr' _ x = x #endif readNum :: String -> Int readNum s = case reads s of [(x,"")] -> x _ -> 0 -- | Conjoin strings, avoiding repeated punctuation. (<^>) :: String -> String -> String [] <^> sb = sb sa <^> [] = sa sa <^> (s:xs) | s `elem` puncts && last sa `elem` puncts = sa ++ xs where puncts = ";:,. " sa <^> sb = sa ++ sb capitalize :: String -> String capitalize [] = [] capitalize (c:cs) = toUpper c : cs isPunct :: Char -> Bool isPunct c = c `elem` ".;?!" camelize :: String -> String camelize ('-':y:ys) = toUpper y : camelize ys camelize ('_':y:ys) = toUpper y : camelize ys camelize (y:ys) = y : camelize ys camelize _ = [] uncamelize :: String -> String uncamelize = foldr g [] . f where g x xs = if isUpper x then '-' : toLower x : xs else x : xs f ( x:xs) = toLower x : xs f [] = [] last' :: [a] -> [a] last' [] = [] last' xs = [last xs] init' :: [a] -> [a] init' [] = [] init' xs = init xs -- | Like words, but doesn't break on nonbreaking spaces etc. words' :: String -> [String] words' = wordsBy (\c -> c == ' ' || c == '\t' || c == '\r' || c == '\n') -- | Remove leading and trailing space (including newlines) from string. trim :: String -> String trim = triml . trimr triml :: String -> String triml = dropWhile (`elem` " \r\n\t") trimr :: String -> String trimr = reverse . triml . reverse -- | Parse JSON Boolean or Number as Bool. parseBool :: Value -> Parser Bool parseBool (Bool b) = return b parseBool (Number n) = case fromJSON (Number n) of Success (0 :: Int) -> return False Success _ -> return True Error e -> fail $ "Could not read boolean: " ++ e parseBool _ = fail "Could not read boolean" -- | Parse JSON value as String. parseString :: Value -> Parser String parseString (String s) = return $ T.unpack s parseString (Number n) = case fromJSON (Number n) of Success (x :: Int) -> return $ show x Error _ -> case fromJSON (Number n) of Success (x :: Double) -> return $ show x Error e -> fail $ "Could not read string: " ++ e parseString (Bool b) = return $ map toLower $ show b parseString v@(Array _)= inlinesToString `fmap` parseJSON v parseString v = fail $ "Could not read as string: " ++ show v -- | Parse JSON value as Int. parseInt :: Value -> Parser Int parseInt (String s) = case safeRead (T.unpack s) of Just n -> return n Nothing -> fail "Could not read Int" parseInt (Number n) = case fromJSON (Number n) of Success (x :: Int) -> return x Error e -> fail $ "Could not read string: " ++ e parseInt _ = fail "Could not read string" mb :: Monad m => (b -> m a) -> (Maybe b -> m (Maybe a)) mb = Data.Traversable.mapM -- | Parse as a string (even if the value is a number). (.#?) :: Object -> Text -> Parser (Maybe String) x .#? y = (x .:? y) >>= mb parseString (.#:) :: Object -> Text -> Parser String x .#: y = (x .: y) >>= parseString onBlocks :: ([Inline] -> [Inline]) -> [Block] -> [Block] onBlocks f bs = walk f' bs where f' (Para ils) = Para (f ils) f' (Plain ils) = Plain (f ils) f' x = x hasLowercaseWord :: [Inline] -> Bool hasLowercaseWord = any startsWithLowercase . splitStrWhen isPunctuation where startsWithLowercase (Str (x:_)) = isLower x startsWithLowercase _ = False splitUpStr :: [Inline] -> [Inline] splitUpStr ils = case reverse (combineInternalPeriods (splitStrWhen (\c -> isPunctuation c || c == '\160') ils)) of [] -> [] (x:xs) -> reverse $ Span ("",["lastword"],[]) [x] : xs -- We want to make sure that the periods in www.example.com, for -- example, are not interpreted as sentence-ending punctuation. combineInternalPeriods :: [Inline] -> [Inline] combineInternalPeriods [] = [] combineInternalPeriods (Str xs:Str ".":Str ys:zs) = combineInternalPeriods $ Str (xs ++ "." ++ ys) : zs combineInternalPeriods (x:xs) = x : combineInternalPeriods xs unTitlecase :: [Inline] -> [Inline] unTitlecase zs = evalState (caseTransform untc zs) SentenceBoundary where untc w = do st <- get case (w, st) of (y, NoBoundary) -> return y (Str (x:xs), LastWordBoundary) | isUpper x -> return $ Str (map toLower (x:xs)) (Str (x:xs), WordBoundary) | isUpper x -> return $ Str (map toLower (x:xs)) (Str (x:xs), SentenceBoundary) | isLower x -> return $ Str (toUpper x : xs) (Span ("",[],[]) xs, _) | hasLowercaseWord xs -> return $ Span ("",["nocase"],[]) xs _ -> return w protectCase :: [Inline] -> [Inline] protectCase zs = evalState (caseTransform protect zs) SentenceBoundary where protect (Span ("",[],[]) xs) | hasLowercaseWord xs = do st <- get case st of NoBoundary -> return $ Span ("",[],[]) xs _ -> return $ Span ("",["nocase"],[]) xs protect x = return x -- From CSL docs: -- "Title case conversion (with text-case set to “title”) for English-language -- items is performed by: -- -- For uppercase strings, the first character of each word remains capitalized. -- All other letters are lowercased. -- For lower or mixed case strings, the first character of each lowercase word -- is capitalized. The case of words in mixed or uppercase stays the same. -- In both cases, stop words are lowercased, unless they are the first or last -- word in the string, or follow a colon. The stop words are “a”, “an”, “and”, -- “as”, “at”, “but”, “by”, “down”, “for”, “from”, “in”, “into”, “nor”, “of”, -- “on”, “onto”, “or”, “over”, “so”, “the”, “till”, “to”, “up”, “via”, “with”, -- and “yet”. titlecase :: [Inline] -> [Inline] titlecase zs = evalState (caseTransform tc zs) SentenceBoundary where tc (Str (x:xs)) = do st <- get return $ case st of LastWordBoundary -> case (x:xs) of s | not (isAscii x) -> Str s | isShortWord s -> Str s | all isUpper s -> Str s | isMixedCase s -> Str s | otherwise -> Str (toUpper x:map toLower xs) WordBoundary -> case (x:xs) of s | not (isAscii x) -> Str s | all isUpper s -> Str s | isShortWord s -> Str (map toLower s) | isMixedCase s -> Str s | otherwise -> Str (toUpper x:map toLower xs) SentenceBoundary -> if isMixedCase (x:xs) || (all isUpper (x:xs)) then Str (x:xs) else Str (toUpper x : xs) _ -> Str (x:xs) tc (Span ("",["nocase"],[]) xs) = return $ Span ("",["nocase"],[]) xs tc x = return x isShortWord s = map toLower s `elem` ["a","an","and","as","at","but","by","c","ca","d","de" ,"down","et","for","from" ,"in","into","nor","of","on","onto","or","over","so" ,"the","till","to","up","van","von","via","with","yet"] isMixedCase :: String -> Bool isMixedCase xs = any isUpper xs && any isLower xs data CaseTransformState = WordBoundary | LastWordBoundary | SentenceBoundary | NoBoundary caseTransform :: (Inline -> State CaseTransformState Inline) -> [Inline] -> State CaseTransformState [Inline] caseTransform xform = fmap reverse . foldM go [] . splitUpStr where go acc s | s == Space || s == SoftBreak = do modify (\st -> case st of SentenceBoundary -> SentenceBoundary _ -> case acc of (Str [x]:_) | x `elem` "?!:" -> SentenceBoundary _ -> WordBoundary) return $ Space : acc go acc LineBreak = do put WordBoundary return $ Space : acc go acc (Str [c]) | c `elem` "-/\x2013\x2014\160" = do put WordBoundary return $ Str [c] : acc | isPunctuation c = do -- leave state unchanged return $ Str [c] : acc go acc (Str []) = return acc go acc (Str xs) = do res <- xform (Str xs) put NoBoundary return $ res : acc go acc (Span ("",["lastword"],[]) [x]) = do b <- get case b of WordBoundary -> put LastWordBoundary _ -> return () go acc x go acc (Span ("",classes,[]) xs) | null classes || classes == ["nocase"] = do res <- xform (Span ("",classes,[]) xs) put NoBoundary return $ res : acc go acc (Quoted qt xs) = (:acc) <$> (Quoted qt <$> caseTransform xform xs) go acc (Emph xs) = (:acc) <$> (Emph <$> caseTransform xform xs) go acc (Strong xs) = (:acc) <$> (Strong <$> caseTransform xform xs) go acc (Link at xs t) = (:acc) <$> (Link at <$> caseTransform xform xs <*> pure t) go acc (Image at xs t) = (:acc) <$> (Link at <$> caseTransform xform xs <*> pure t) go acc (Span attr xs) = (:acc) <$> (Span attr <$> caseTransform xform xs) go acc x = return $ x : acc splitStrWhen :: (Char -> Bool) -> [Inline] -> [Inline] splitStrWhen _ [] = [] splitStrWhen p (Str xs : ys) = go xs ++ splitStrWhen p ys where go [] = [] go s = case break p s of ([],[]) -> [] (zs,[]) -> [Str zs] ([],(w:ws)) -> Str [w] : go ws (zs,(w:ws)) -> Str zs : Str [w] : go ws splitStrWhen p (x : ys) = x : splitStrWhen p ys -- | A generic processing function. proc :: (Typeable a, Data b) => (a -> a) -> b -> b proc f = everywhere (mkT f) -- | A generic processing function: process a data structure in -- top-down manner. proc' :: (Typeable a, Data b) => (a -> a) -> b -> b proc' f = everywhere' (mkT f) -- | A generic monadic processing function. procM :: (Monad m, Typeable a, Data b) => (a -> m a) -> b -> m b procM f = everywhereM (mkM f) -- | A generic query function. query :: (Typeable a, Data b, Monoid m) => (a -> m) -> b -> m query f = everything mappend (mempty `mkQ` f) betterThan :: [a] -> [a] -> [a] betterThan [] b = b betterThan a _ = a toRead :: String -> String toRead [] = [] toRead (s:ss) = toUpper s : camel ss where camel x | '-':y:ys <- x = toUpper y : camel ys | '_':y:ys <- x = toUpper y : camel ys | y:ys <- x = y : camel ys | otherwise = [] inlinesToString :: [Inline] -> String inlinesToString = stringify headInline :: [Inline] -> String headInline = take 1 . stringify lastInline :: [Inline] -> String lastInline xs = case stringify xs of [] -> [] ys -> [last ys] initInline :: [Inline] -> [Inline] initInline [] = [] initInline (i:[]) | Str s <- i = return $ Str (init' s) | Emph is <- i = return $ Emph (initInline is) | Strong is <- i = return $ Strong (initInline is) | Superscript is <- i = return $ Superscript (initInline is) | Subscript is <- i = return $ Subscript (initInline is) | Quoted q is <- i = return $ Quoted q (initInline is) | SmallCaps is <- i = return $ SmallCaps (initInline is) | Strikeout is <- i = return $ Strikeout (initInline is) | Link at is t <- i = return $ Link at (initInline is) t | Span at is <- i = return $ Span at (initInline is) | otherwise = [] initInline (i:xs) = i : initInline xs tailInline :: [Inline] -> [Inline] tailInline (Space:xs) = xs tailInline (SoftBreak:xs) = xs tailInline xs = removeEmpty $ tailFirstInlineStr xs where removeEmpty = dropWhile (== Str "") tailFirstInlineStr :: [Inline] -> [Inline] tailFirstInlineStr = mapHeadInline (drop 1) toCapital :: [Inline] -> [Inline] toCapital ils@(Span (_,["nocase"],_) _:_) = ils toCapital ils = mapHeadInline capitalize ils mapHeadInline :: (String -> String) -> [Inline] -> [Inline] mapHeadInline _ [] = [] mapHeadInline f (i:xs) | Str [] <- i = mapHeadInline f xs | Str s <- i = Str (f s) : xs | Emph is <- i = Emph (mapHeadInline f is) : xs | Strong is <- i = Strong (mapHeadInline f is) : xs | Superscript is <- i = Superscript (mapHeadInline f is) : xs | Subscript is <- i = Subscript (mapHeadInline f is) : xs | Quoted q is <- i = Quoted q (mapHeadInline f is) : xs | SmallCaps is <- i = SmallCaps (mapHeadInline f is) : xs | Strikeout is <- i = Strikeout (mapHeadInline f is) : xs | Link at is t <- i = Link at (mapHeadInline f is) t : xs | Span at is <- i = Span at (mapHeadInline f is) : xs | otherwise = i : xs findFile :: [FilePath] -> FilePath -> IO (Maybe FilePath) findFile [] _ = return Nothing findFile (p:ps) f | isAbsolute f = do exists <- doesFileExist f if exists then return (Just f) else return Nothing | otherwise = do exists <- doesFileExist (p f) if exists then return $ Just (p f) else findFile ps f (&=) :: (ToYaml a, Monoid a, Eq a) => Text -> a -> [(Text, YamlBuilder)] -> [(Text, YamlBuilder)] x &= y = \acc -> if y == mempty then acc else (x Y..= y) : acc mapping' :: [[(Text, YamlBuilder)] -> [(Text, YamlBuilder)]] -> YamlBuilder mapping' = Y.mapping . foldr ($) [] -- TODO: romanNumeral is defined in Text.Pandoc.Parsing, but it's -- not exported there. Eventually we should remove this code duplication -- by exporting something from pandoc. parseRomanNumeral :: String -> Maybe Int parseRomanNumeral s = case P.parse (pRomanNumeral <* P.eof) "" s of Left _ -> Nothing Right x -> Just x -- | Parses a roman numeral (uppercase or lowercase), returns number. pRomanNumeral :: P.Stream s m Char => P.ParsecT s st m Int pRomanNumeral = do let lowercaseRomanDigits = ['i','v','x','l','c','d','m'] let uppercaseRomanDigits = ['I','V','X','L','C','D','M'] c <- P.lookAhead $ P.oneOf (lowercaseRomanDigits ++ uppercaseRomanDigits) let romanDigits = if isUpper c then uppercaseRomanDigits else lowercaseRomanDigits let [one, five, ten, fifty, hundred, fivehundred, thousand] = map P.char romanDigits thousands <- P.many thousand >>= (return . (1000 *) . length) ninehundreds <- P.option 0 $ P.try $ hundred >> thousand >> return 900 fivehundreds <- P.many fivehundred >>= (return . (500 *) . length) fourhundreds <- P.option 0 $ P.try $ hundred >> fivehundred >> return 400 hundreds <- P.many hundred >>= (return . (100 *) . length) nineties <- P.option 0 $ P.try $ ten >> hundred >> return 90 fifties <- P.many fifty >>= (return . (50 *) . length) forties <- P.option 0 $ P.try $ ten >> fifty >> return 40 tens <- P.many ten >>= (return . (10 *) . length) nines <- P.option 0 $ P.try $ one >> ten >> return 9 fives <- P.many five >>= (return . (5 *) . length) fours <- P.option 0 $ P.try $ one >> five >> return 4 ones <- P.many one >>= (return . length) let total = thousands + ninehundreds + fivehundreds + fourhundreds + hundreds + nineties + fifties + forties + tens + nines + fives + fours + ones if total == 0 then fail "not a roman numeral" else return total isRange :: String -> Bool isRange s = ',' `elem` s || '-' `elem` s || '\x2013' `elem` s pandoc-citeproc-0.10.5.1/prelude/Prelude.hs0000644000000000000000000000116512743760365016610 0ustar0000000000000000{-# LANGUAGE PackageImports #-} {-# LANGUAGE CPP #-} module Prelude ( module P , Monoid(..) , Applicative(..) #if MIN_VERSION_base(4,8,0) #else , (<$>) , (<$) #endif , (<>) ) where #if MIN_VERSION_base(4,8,0) import "base" Prelude as P import Data.Monoid ((<>)) #elif MIN_VERSION_base(4,6,0) import "base" Prelude as P import Control.Applicative import Data.Monoid #else import "base" Prelude as P hiding (catch) import Control.Applicative import Data.Monoid #endif #if MIN_VERSION_base(4,5,0) #else infixr 6 <> -- | An infix synonym for 'mappend'. (<>) :: Monoid m => m -> m -> m (<>) = mappend {-# INLINE (<>) #-} #endif pandoc-citeproc-0.10.5.1/compat/Text/CSL/Compat/Pandoc.hs0000644000000000000000000000713113046402505021010 0ustar0000000000000000{-# LANGUAGE CPP, ScopedTypeVariables #-} -- | Compatibility module to work around differences in the -- types of functions between pandoc < 2.0 and pandoc >= 2.0. module Text.CSL.Compat.Pandoc ( writeMarkdown, writePlain, writeNative, writeHtmlString, readNative, readHtml, readMarkdown, readLaTeX, fetchItem, pipeProcess ) where import qualified Control.Exception as E import System.Exit (ExitCode) import Data.ByteString.Lazy as BL import Data.ByteString as B import Text.Pandoc (Pandoc, ReaderOptions(..), def, WrapOption(..), WriterOptions(..)) import qualified Text.Pandoc as Pandoc import qualified Text.Pandoc.Process #if MIN_VERSION_pandoc(2,0,0) import Text.Pandoc.MIME (MimeType) import Text.Pandoc.Error (PandocError) import Text.Pandoc.Class (runPure, runIO) import qualified Text.Pandoc.Class (fetchItem) import Control.Monad.Except (runExceptT, lift) import Text.Pandoc.Extensions (extensionsFromList, Extension(..), pandocExtensions, disableExtension) #else import System.IO (stderr) import qualified Text.Pandoc.Shared (fetchItem) type MimeType = String #endif readHtml, readLaTeX, readMarkdown, readNative :: String -> Pandoc writeMarkdown, writePlain, writeNative, writeHtmlString :: Pandoc -> String #if MIN_VERSION_pandoc(2,0,0) readHtml = either mempty id . runPure . Pandoc.readHtml def{ readerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html, Ext_smart] } readMarkdown = either mempty id . runPure . Pandoc.readMarkdown def{ readerExtensions = pandocExtensions, readerStandalone = True } readLaTeX = either mempty id . runPure . Pandoc.readLaTeX def{ readerExtensions = extensionsFromList [Ext_raw_tex, Ext_smart] } readNative = either mempty id . runPure . Pandoc.readNative def writeMarkdown = either mempty id . runPure . Pandoc.writeMarkdown def{ writerExtensions = disableExtension Ext_smart pandocExtensions, writerWrapText = WrapNone } writePlain = either mempty id . runPure . Pandoc.writePlain def writeNative = either mempty id . runPure . Pandoc.writeNative def writeHtmlString = either mempty id . runPure . Pandoc.writeHtml4String def{ writerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html] } #else readHtml = either mempty id . Pandoc.readHtml def{ readerSmart = True, readerParseRaw = True } readMarkdown = either mempty id . Pandoc.readMarkdown def{ readerSmart = True, readerStandalone = True} readLaTeX = either mempty id . Pandoc.readLaTeX def{ readerSmart = True, readerParseRaw = True } readNative = either mempty id . Pandoc.readNative writeMarkdown = Pandoc.writeMarkdown def{ writerWrapText = WrapNone } writePlain = Pandoc.writePlain def writeNative = Pandoc.writeNative def writeHtmlString = Pandoc.writeHtmlString def #endif pipeProcess :: Maybe [(String, String)] -> FilePath -> [String] -> BL.ByteString -> IO (ExitCode,BL.ByteString) #if MIN_VERSION_pandoc(2,0,0) pipeProcess = Text.Pandoc.Process.pipeProcess #else pipeProcess e f a b = do (ec, out, err) <- Text.Pandoc.Process.pipeProcess e f a b BL.hPutStr stderr err return (ec, out) #endif fetchItem :: Maybe String -> String -> IO (Either E.SomeException (B.ByteString, Maybe MimeType)) #if MIN_VERSION_pandoc(2,0,0) fetchItem mbd s = do res <- runIO $ runExceptT $ lift $ Text.Pandoc.Class.fetchItem mbd s return $ case res of Left e -> Left (E.toException e) Right (Left (e :: PandocError)) -> Left (E.toException e) Right (Right r) -> Right r #else fetchItem = Text.Pandoc.Shared.fetchItem #endif pandoc-citeproc-0.10.5.1/src/Text/CSL/Data/Embedded.hs0000644000000000000000000000077213114774700020240 0ustar0000000000000000{-# LANGUAGE TemplateHaskell #-} -- to be processed using hsb2hs module Text.CSL.Data.Embedded (localeFiles, defaultCSL, manpage, license) where import Data.FileEmbed import qualified Data.ByteString.Char8 as S localeFiles :: [(FilePath, S.ByteString)] localeFiles = $(embedDir "locales") defaultCSL :: S.ByteString defaultCSL = $(embedFile "chicago-author-date.csl") manpage :: S.ByteString manpage = $(embedFile "man/man1/pandoc-citeproc.1") license :: S.ByteString license = $(embedFile "LICENSE") pandoc-citeproc-0.10.5.1/tests/test-citeproc.hs0000644000000000000000000002223513115023466017464 0ustar0000000000000000{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, FlexibleInstances, ScopedTypeVariables, CPP #-} import Text.Printf import System.Exit import qualified Control.Exception as E import Text.Pandoc (Block(..), Inline(..), Format(..), bottomUp, nullMeta, Pandoc(..)) import Text.CSL.Compat.Pandoc (writeHtmlString) import Data.Char (isSpace, toLower) import System.Environment (getArgs) import System.Process import System.IO.Temp (withSystemTempDirectory) import qualified Text.Pandoc.UTF8 as UTF8 import Data.Aeson import System.FilePath import System.Directory import Data.List (sort, isInfixOf) import qualified Data.Map as M import Text.CSL.Style hiding (Number) import Text.CSL.Reference import Text.CSL import Control.Monad import qualified Data.ByteString.Lazy as BL data TestCase = TestCase{ testMode :: Mode -- mode , testBibopts :: BibOpts -- bibsection , testCitations :: [CiteObject] -- citations , testCitationItems :: Citations -- citation-items , testCsl :: Style -- csl , testAbbreviations :: Abbreviations -- abbreviations , testReferences :: [Reference] -- input , testResult :: String -- result } deriving (Show) data Mode = CitationMode | BibliographyMode | BibliographyHeaderMode | BibliographyNoSortMode deriving Show instance FromJSON Mode where parseJSON (String "citation") = return CitationMode parseJSON (String "bibliography") = return BibliographyMode parseJSON (String "bibliography-header") = return BibliographyHeaderMode parseJSON (String "bibliography-nosort") = return BibliographyNoSortMode parseJSON _ = fail "Unknown mode" instance FromJSON TestCase where parseJSON (Object v) = TestCase <$> v .: "mode" <*> v .:? "bibsection" .!= Select [] [] <*> v .:? "citations" .!= [] <*> v .:? "citation_items" .!= [] <*> (parseCSL <$> (v .: "csl")) <*> v .:? "abbreviations" .!= (Abbreviations M.empty) <*> v .: "input" <*> v .: "result" parseJSON _ = fail "Could not parse test case" newtype CiteObject = CiteObject { unCiteObject :: [Cite] } deriving Show instance FromJSON CiteObject where parseJSON (Array v) = case fromJSON (Array v) of Success [Object x, Array _, Array _] -> CiteObject <$> x .: "citationItems" Error e -> fail $ "Could not parse CiteObject: " ++ e x -> fail $ "Could not parse CiteObject" ++ show x parseJSON x = fail $ "Could not parse CiteObject " ++ show x #if MIN_VERSION_aeson(0,10,0) #else instance FromJSON [CiteObject] where parseJSON (Array v) = mapM parseJSON $ V.toList v parseJSON _ = return [] #endif data TestResult = Passed | Skipped | Failed | Errored deriving (Show, Eq) testDir :: FilePath testDir = "citeproc-test" "processor-tests" "machines" handler :: FilePath -> E.SomeException -> IO TestResult handler path e = do putStrLn $ "[ERROR] " ++ path ++ "\n" ++ show e return Errored runTest :: FilePath -> IO TestResult runTest path = E.handle (handler path) $ do raw <- BL.readFile path let testCase = either error id $ eitherDecode raw let procOpts' = ProcOpts (testBibopts testCase) False style <- localizeCSL Nothing $ (testCsl testCase) { styleAbbrevs = testAbbreviations testCase } let refs = testReferences testCase let cites = map unCiteObject (testCitations testCase) ++ testCitationItems testCase let cites' = if null cites then [map (\ref -> emptyCite{ citeId = unLiteral $ refId ref}) refs] else cites let expected = adjustEntities $ fixBegins $ trimEnd $ testResult testCase let mode = testMode testCase let assemble BibliographyMode xs = "
\n" ++ unlines (map (\x -> "
" ++ x ++ "
") xs) ++ "
\n" assemble _ xs = unlines xs case mode of BibliographyHeaderMode -> do putStrLn $ "[SKIPPED] " ++ path ++ "\n" return Skipped BibliographyNoSortMode -> do putStrLn $ "[SKIPPED] " ++ path ++ "\n" return Skipped _ -> do let result = assemble mode $ map (inlinesToString . renderPandoc style) $ (case mode of {CitationMode -> citations; _ -> bibliography}) $ citeproc procOpts' style refs cites' if result == expected then do putStrLn $ "[PASSED] " ++ path ++ "\n" return Passed else do putStrLn $ "[FAILED] " ++ path showDiff expected result putStrLn "" return Failed trimEnd :: String -> String trimEnd = reverse . ('\n':) . dropWhile isSpace . reverse -- this is designed to mimic the test suite's output: inlinesToString :: [Inline] -> String inlinesToString ils = writeHtmlString $ bottomUp (concatMap adjustSpans) $ Pandoc nullMeta [Plain ils] -- We want & instead of & etc. adjustEntities :: String -> String adjustEntities ('&':'#':'3':'8':';':xs) = "&" ++ adjustEntities xs adjustEntities (x:xs) = x : adjustEntities xs adjustEntities [] = [] -- citeproc-js test suite expects "citations" to be formatted like -- .. [0] Smith (2007) -- >> [1] Jones (2008) -- To get a meaningful comparison, we remove this. fixBegins :: String -> String fixBegins = unlines . map fixLine . lines where fixLine ('.':'.':'[':xs) = dropWhile isSpace $ dropWhile (not . isSpace) xs fixLine ('>':'>':'[':xs) = dropWhile isSpace $ dropWhile (not . isSpace) xs fixLine xs = xs -- adjust the spans so we fit what the test suite expects. adjustSpans :: Inline -> [Inline] adjustSpans (Note [Para xs]) = xs adjustSpans (Link _ ils _) = ils adjustSpans (Span ("",[],[]) xs) = xs adjustSpans (Span ("",["nocase"],[]) xs) = xs adjustSpans (Span ("",["citeproc-no-output"],[]) _) = [Str "[CSL STYLE ERROR: reference with no printed form.]"] adjustSpans (Span (id',classes,kvs) ils) = [Span (id',classes',kvs') ils] where classes' = filter (`notElem` ["csl-no-emph","csl-no-strong","csl-no-smallcaps"]) classes kvs' = if null styles then kvs else (("style", concat styles) : kvs) styles = ["font-style:normal;" | "csl-no-emph" `elem` classes] ++ ["font-weight:normal;" | "csl-no-strong" `elem` classes] ++ ["font-variant:normal;" | "csl-no-smallcaps" `elem` classes] adjustSpans (Emph xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustSpans (Strong xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustSpans (SmallCaps xs) = RawInline (Format "html") "" : xs ++ [RawInline (Format "html") ""] adjustSpans x = [x] showDiff :: String -> String -> IO () showDiff expected' result' = withSystemTempDirectory "test-pandoc-citeproc-XXX" $ \fp -> do let expectedf = fp "expected" let actualf = fp "actual" UTF8.writeFile expectedf expected' UTF8.writeFile actualf result' withDirectory fp $ void $ rawSystem "diff" ["-u","expected","actual"] withDirectory :: FilePath -> IO a -> IO a withDirectory fp action = do oldDir <- getCurrentDirectory setCurrentDirectory fp result <- action setCurrentDirectory oldDir return result main :: IO () main = do args <- getArgs let matchesPattern x | null args = True | otherwise = any (`isInfixOf` (map toLower x)) (map (map toLower . takeBaseName) args) exists <- doesDirectoryExist testDir unless exists $ do putStrLn "Downloading test suite" rawSystem "hg" ["clone", "https://bitbucket.org/bdarcus/citeproc-test"] withDirectory "citeproc-test" $ void $ rawSystem "python" ["processor.py", "--grind"] testFiles <- if any ('/' `elem`) args then return args else (map (testDir ) . sort . filter matchesPattern . filter (\f -> takeExtension f == ".json")) <$> getDirectoryContents testDir results <- mapM runTest testFiles let numpasses = length $ filter (== Passed) results let numskipped = length $ filter (== Skipped) results let numfailures = length $ filter (== Failed) results let numerrors = length $ filter (== Errored) results putStrLn $ show numpasses ++ " passed; " ++ show numfailures ++ " failed; " ++ show numskipped ++ " skipped; " ++ show numerrors ++ " errored." let summary = unlines $ zipWith (\fp res -> printf "%-10s %s" (show res) fp) testFiles results when (null args) $ do -- write log if complete test suite run ex <- doesFileExist "test-citeproc.log" when ex $ do putStrLn "Copying existing test-citeproc.log to test-citeproc.log.old" copyFile "test-citeproc.log" "test-citeproc.log.old" putStrLn "Writing test-citeproc.log." UTF8.writeFile "test-citeproc.log" summary exitWith $ if numfailures == 0 then ExitSuccess else ExitFailure $ numfailures + numerrors pandoc-citeproc-0.10.5.1/tests/JSON.hs0000644000000000000000000000061212743760365015457 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} -- ToJSON/FromJSON instances for Style module JSON where import Data.Aeson import Text.CSL.Style import Text.CSL.Parser import qualified Data.Text.Encoding as T import qualified Data.ByteString.Lazy as L instance FromJSON Style where parseJSON (String s) = return $ parseCSL' $ L.fromChunks [T.encodeUtf8 s] parseJSON _ = fail "Could not parse Style" pandoc-citeproc-0.10.5.1/prelude/Prelude.hs0000644000000000000000000000116512743760365016610 0ustar0000000000000000{-# LANGUAGE PackageImports #-} {-# LANGUAGE CPP #-} module Prelude ( module P , Monoid(..) , Applicative(..) #if MIN_VERSION_base(4,8,0) #else , (<$>) , (<$) #endif , (<>) ) where #if MIN_VERSION_base(4,8,0) import "base" Prelude as P import Data.Monoid ((<>)) #elif MIN_VERSION_base(4,6,0) import "base" Prelude as P import Control.Applicative import Data.Monoid #else import "base" Prelude as P hiding (catch) import Control.Applicative import Data.Monoid #endif #if MIN_VERSION_base(4,5,0) #else infixr 6 <> -- | An infix synonym for 'mappend'. (<>) :: Monoid m => m -> m -> m (<>) = mappend {-# INLINE (<>) #-} #endif pandoc-citeproc-0.10.5.1/compat/Text/CSL/Compat/Pandoc.hs0000644000000000000000000000713113046402505021010 0ustar0000000000000000{-# LANGUAGE CPP, ScopedTypeVariables #-} -- | Compatibility module to work around differences in the -- types of functions between pandoc < 2.0 and pandoc >= 2.0. module Text.CSL.Compat.Pandoc ( writeMarkdown, writePlain, writeNative, writeHtmlString, readNative, readHtml, readMarkdown, readLaTeX, fetchItem, pipeProcess ) where import qualified Control.Exception as E import System.Exit (ExitCode) import Data.ByteString.Lazy as BL import Data.ByteString as B import Text.Pandoc (Pandoc, ReaderOptions(..), def, WrapOption(..), WriterOptions(..)) import qualified Text.Pandoc as Pandoc import qualified Text.Pandoc.Process #if MIN_VERSION_pandoc(2,0,0) import Text.Pandoc.MIME (MimeType) import Text.Pandoc.Error (PandocError) import Text.Pandoc.Class (runPure, runIO) import qualified Text.Pandoc.Class (fetchItem) import Control.Monad.Except (runExceptT, lift) import Text.Pandoc.Extensions (extensionsFromList, Extension(..), pandocExtensions, disableExtension) #else import System.IO (stderr) import qualified Text.Pandoc.Shared (fetchItem) type MimeType = String #endif readHtml, readLaTeX, readMarkdown, readNative :: String -> Pandoc writeMarkdown, writePlain, writeNative, writeHtmlString :: Pandoc -> String #if MIN_VERSION_pandoc(2,0,0) readHtml = either mempty id . runPure . Pandoc.readHtml def{ readerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html, Ext_smart] } readMarkdown = either mempty id . runPure . Pandoc.readMarkdown def{ readerExtensions = pandocExtensions, readerStandalone = True } readLaTeX = either mempty id . runPure . Pandoc.readLaTeX def{ readerExtensions = extensionsFromList [Ext_raw_tex, Ext_smart] } readNative = either mempty id . runPure . Pandoc.readNative def writeMarkdown = either mempty id . runPure . Pandoc.writeMarkdown def{ writerExtensions = disableExtension Ext_smart pandocExtensions, writerWrapText = WrapNone } writePlain = either mempty id . runPure . Pandoc.writePlain def writeNative = either mempty id . runPure . Pandoc.writeNative def writeHtmlString = either mempty id . runPure . Pandoc.writeHtml4String def{ writerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html] } #else readHtml = either mempty id . Pandoc.readHtml def{ readerSmart = True, readerParseRaw = True } readMarkdown = either mempty id . Pandoc.readMarkdown def{ readerSmart = True, readerStandalone = True} readLaTeX = either mempty id . Pandoc.readLaTeX def{ readerSmart = True, readerParseRaw = True } readNative = either mempty id . Pandoc.readNative writeMarkdown = Pandoc.writeMarkdown def{ writerWrapText = WrapNone } writePlain = Pandoc.writePlain def writeNative = Pandoc.writeNative def writeHtmlString = Pandoc.writeHtmlString def #endif pipeProcess :: Maybe [(String, String)] -> FilePath -> [String] -> BL.ByteString -> IO (ExitCode,BL.ByteString) #if MIN_VERSION_pandoc(2,0,0) pipeProcess = Text.Pandoc.Process.pipeProcess #else pipeProcess e f a b = do (ec, out, err) <- Text.Pandoc.Process.pipeProcess e f a b BL.hPutStr stderr err return (ec, out) #endif fetchItem :: Maybe String -> String -> IO (Either E.SomeException (B.ByteString, Maybe MimeType)) #if MIN_VERSION_pandoc(2,0,0) fetchItem mbd s = do res <- runIO $ runExceptT $ lift $ Text.Pandoc.Class.fetchItem mbd s return $ case res of Left e -> Left (E.toException e) Right (Left (e :: PandocError)) -> Left (E.toException e) Right (Right r) -> Right r #else fetchItem = Text.Pandoc.Shared.fetchItem #endif pandoc-citeproc-0.10.5.1/pandoc-citeproc.hs0000644000000000000000000001510013063460526016604 0ustar0000000000000000{-# LANGUAGE CPP #-} module Main where import Text.CSL.Input.Bibutils (readBiblioString, BibFormat(..)) import Text.CSL.Reference (Reference(refId), Literal(..)) import Data.List (group, sort) import Data.Char (chr, toLower) import Data.Yaml.Builder (toByteString) import Control.Applicative ((<|>), many) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Char8 as B8 import Data.Attoparsec.ByteString.Char8 as Attoparsec import qualified Data.Text as T import Data.Text.Encoding (encodeUtf8) import Data.Aeson.Encode.Pretty (encodePretty', Config(..), Indent(Spaces), NumberFormat(Generic)) import System.Console.GetOpt import Control.Monad import System.IO import System.FilePath (takeExtension) import System.Environment (getArgs) import System.Exit import Data.Version (showVersion) import Paths_pandoc_citeproc (version) import Text.CSL.Pandoc (processCites') import Text.CSL.Data (getManPage, getLicense) import Text.Pandoc.JSON hiding (Format) import Text.Pandoc.Walk import qualified Text.Pandoc.UTF8 as UTF8 main :: IO () main = do argv <- getArgs let (flags, args, errs) = getOpt Permute options argv let header = "Usage: pandoc-citeproc [options] [file..]" unless (null errs) $ do UTF8.hPutStrLn stderr $ usageInfo (unlines $ errs ++ [header]) options exitWith $ ExitFailure 1 when (Version `elem` flags) $ do UTF8.putStrLn $ "pandoc-citeproc " ++ showVersion version exitWith ExitSuccess when (Help `elem` flags) $ do UTF8.putStrLn $ usageInfo header options exitWith ExitSuccess when (Man `elem` flags) $ do getManPage >>= BL.putStr exitWith ExitSuccess when (License `elem` flags) $ do getLicense >>= BL.putStr exitWith ExitSuccess if Bib2YAML `elem` flags || Bib2JSON `elem` flags then do let mbformat = case [f | Format f <- flags] of [x] -> readFormat x _ -> Nothing bibformat <- case mbformat <|> msum (map formatFromExtension args) of Just f -> return f Nothing -> do UTF8.hPutStrLn stderr $ usageInfo ("Unknown format\n" ++ header) options exitWith $ ExitFailure 3 bibstring <- case args of [] -> UTF8.getContents xs -> mconcat <$> mapM UTF8.readFile xs readBiblioString bibformat bibstring >>= warnDuplicateKeys >>= if Bib2YAML `elem` flags then outputYamlBlock . B8.intercalate (B.singleton 10) . map (unescapeTags . toByteString . (:[])) else B8.putStrLn . unescapeUnicode . B.concat . BL.toChunks . encodePretty' Config{ confIndent = Spaces 2 , confCompare = compare , confNumFormat = Generic } else toJSONFilter doCites formatFromExtension :: FilePath -> Maybe BibFormat formatFromExtension = readFormat . dropWhile (=='.') . takeExtension readFormat :: String -> Maybe BibFormat readFormat = go . map toLower where go "biblatex" = Just BibLatex go "bib" = Just BibLatex go "bibtex" = Just Bibtex go "json" = Just Json go "yaml" = Just Yaml #ifdef USE_BIBUTILS go "ris" = Just Ris go "endnote" = Just Endnote go "enl" = Just Endnote go "endnotexml" = Just EndnotXml go "xml" = Just EndnotXml go "wos" = Just Isi go "isi" = Just Isi go "medline" = Just Medline go "copac" = Just Copac go "mods" = Just Mods #endif go _ = Nothing doCites :: Pandoc -> IO Pandoc doCites doc = do doc' <- processCites' doc let warnings = query findWarnings doc' mapM_ (UTF8.hPutStrLn stderr) warnings return doc' findWarnings :: Inline -> [String] findWarnings (Span (_,["citeproc-not-found"],[("data-reference-id",ref)]) _) = ["pandoc-citeproc: reference " ++ ref ++ " not found" | ref /= "*"] findWarnings (Span (_,["citeproc-no-output"],_) _) = ["pandoc-citeproc: reference with no printed form"] findWarnings _ = [] data Option = Help | Man | License | Version | Convert | Format String | Bib2YAML | Bib2JSON deriving (Ord, Eq, Show) options :: [OptDescr Option] options = [ Option ['h'] ["help"] (NoArg Help) "show usage information" , Option [] ["man"] (NoArg Man) "print man page to stdout" , Option [] ["license"] (NoArg License) "print license to stdout" , Option ['V'] ["version"] (NoArg Version) "show program version" , Option ['y'] ["bib2yaml"] (NoArg Bib2YAML) "convert bibliography to YAML" , Option ['j'] ["bib2json"] (NoArg Bib2JSON) "convert bibliography to JSON" , Option ['f'] ["format"] (ReqArg Format "FORMAT") "bibliography format" ] warnDuplicateKeys :: [Reference] -> IO [Reference] warnDuplicateKeys refs = mapM_ warnDup dupKeys >> return refs where warnDup k = UTF8.hPutStrLn stderr $ "biblio2yaml: duplicate key " ++ k allKeys = map (unLiteral . refId) refs dupKeys = [x | (x:_:_) <- group (sort allKeys)] outputYamlBlock :: B.ByteString -> IO () outputYamlBlock contents = do UTF8.putStrLn "---\nreferences:" B.putStr contents UTF8.putStrLn "..." -- turn -- id: ! "\u043F\u0443\u043D\u043A\u04423" -- into -- id: пункт3 unescapeTags :: B.ByteString -> B.ByteString unescapeTags bs = case parseOnly (many $ tag <|> other) bs of Left e -> error e Right r -> B.concat r unescapeUnicode :: B.ByteString -> B.ByteString unescapeUnicode bs = case parseOnly (many other) bs of Left e -> error e Right r -> B.concat r tag :: Attoparsec.Parser B.ByteString tag = do _ <- string $ B8.pack ": ! " c <- char '\'' <|> char '"' cs <- manyTill (escaped c <|> other) (char c) return $ B8.pack ": " <> B8.singleton c <> B.concat cs <> B8.singleton c escaped :: Char -> Attoparsec.Parser B.ByteString escaped c = string $ B8.pack ['\\',c] other :: Attoparsec.Parser B.ByteString other = uchar <|> Attoparsec.takeWhile1 notspecial <|> regchar where notspecial = not . inClass ":!\\\"'" uchar :: Attoparsec.Parser B.ByteString uchar = do _ <- char '\\' num <- (2 <$ char 'x') <|> (4 <$ char 'u') <|> (8 <$ char 'U') cs <- count num $ satisfy $ inClass "0-9a-fA-F" let n = read ('0':'x':cs) return $ encodeUtf8 $ T.pack [chr n] regchar :: Attoparsec.Parser B.ByteString regchar = B8.singleton <$> anyChar pandoc-citeproc-0.10.5.1/prelude/Prelude.hs0000644000000000000000000000116512743760365016610 0ustar0000000000000000{-# LANGUAGE PackageImports #-} {-# LANGUAGE CPP #-} module Prelude ( module P , Monoid(..) , Applicative(..) #if MIN_VERSION_base(4,8,0) #else , (<$>) , (<$) #endif , (<>) ) where #if MIN_VERSION_base(4,8,0) import "base" Prelude as P import Data.Monoid ((<>)) #elif MIN_VERSION_base(4,6,0) import "base" Prelude as P import Control.Applicative import Data.Monoid #else import "base" Prelude as P hiding (catch) import Control.Applicative import Data.Monoid #endif #if MIN_VERSION_base(4,5,0) #else infixr 6 <> -- | An infix synonym for 'mappend'. (<>) :: Monoid m => m -> m -> m (<>) = mappend {-# INLINE (<>) #-} #endif pandoc-citeproc-0.10.5.1/tests/test-pandoc-citeproc.hs0000644000000000000000000001151413115033673020725 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} module Main where import System.Exit import System.Directory import System.FilePath import Data.Maybe (fromMaybe) import System.IO import System.IO.Temp (withSystemTempDirectory) import System.Process (rawSystem) import qualified Data.Aeson as Aeson import Text.Pandoc.Definition import qualified Text.Pandoc.UTF8 as UTF8 import Text.CSL.Compat.Pandoc (writeNative, pipeProcess) import Data.List (isSuffixOf) import System.Environment import Control.Monad (when) #if MIN_VERSION_pandoc(2,0,0) import qualified Control.Exception as E #endif main :: IO () main = do args <- getArgs let regenerate = args == ["--regenerate"] testnames <- fmap (map (dropExtension . takeBaseName) . filter (".in.native" `isSuffixOf`)) $ getDirectoryContents "tests" citeprocTests <- mapM (testCase regenerate) testnames fs <- filter (\f -> takeExtension f `elem` [".bibtex",".biblatex"]) `fmap` getDirectoryContents "tests/biblio2yaml" biblio2yamlTests <- mapM biblio2yamlTest fs let allTests = citeprocTests ++ biblio2yamlTests let numpasses = length $ filter (== Passed) allTests let numskipped = length $ filter (== Skipped) allTests let numfailures = length $ filter (== Failed) allTests let numerrors = length $ filter (== Errored) allTests putStrLn $ show numpasses ++ " passed; " ++ show numfailures ++ " failed; " ++ show numskipped ++ " skipped; " ++ show numerrors ++ " errored." exitWith $ if numfailures == 0 && numerrors == 0 then ExitSuccess else ExitFailure $ numfailures + numerrors err :: String -> IO () err = hPutStrLn stderr data TestResult = Passed | Skipped | Failed | Errored deriving (Show, Eq) testCase :: Bool -> String -> IO TestResult testCase regenerate csl = do hPutStr stderr $ "[" ++ csl ++ ".in.native] " indataNative <- UTF8.readFile $ "tests/" ++ csl ++ ".in.native" expectedNative <- UTF8.readFile $ "tests/" ++ csl ++ ".expected.native" let jsonIn = Aeson.encode $ (read indataNative :: Pandoc) let expectedDoc = read expectedNative testProgPath <- getExecutablePath let pandocCiteprocPath = takeDirectory testProgPath ".." "pandoc-citeproc" "pandoc-citeproc" (ec, jsonOut) <- pipeProcess (Just [("LANG","en_US.UTF-8"),("HOME",".")]) pandocCiteprocPath [] jsonIn if ec == ExitSuccess then do let outDoc = fromMaybe mempty $ Aeson.decode $ jsonOut if outDoc == expectedDoc then err "PASSED" >> return Passed else do err $ "FAILED" showDiff (writeNative expectedDoc) (writeNative outDoc) when regenerate $ UTF8.writeFile ("tests/" ++ csl ++ ".expected.native") $ #if MIN_VERSION_pandoc(1,19,0) writeNative outDoc #else writeNative outDoc #endif return Failed else do err "ERROR" err $ "Error status " ++ show ec return Errored showDiff :: String -> String -> IO () showDiff expected result = withSystemTempDirectory "test-pandoc-citeproc-XXX" $ \fp -> do let expectedf = fp "expected" let actualf = fp "actual" UTF8.writeFile expectedf expected UTF8.writeFile actualf result oldDir <- getCurrentDirectory setCurrentDirectory fp rawSystem "diff" ["-U1","expected","actual"] setCurrentDirectory oldDir biblio2yamlTest :: String -> IO TestResult biblio2yamlTest fp = do hPutStr stderr $ "[biblio2yaml/" ++ fp ++ "] " let yamld = "tests/biblio2yaml/" #if MIN_VERSION_pandoc(2,0,0) -- in a few cases we need different test output for pandoc >= 2 -- because smallcaps render differently, for example. raw <- E.catch (UTF8.readFile (yamld ++ "/pandoc-2/" ++ fp)) (\(_ :: E.SomeException) -> (UTF8.readFile (yamld ++ fp))) #else raw <- UTF8.readFile (yamld ++ fp) #endif let yamlStart = "---" let (biblines, yamllines) = break (== yamlStart) $ lines raw let bib = unlines biblines let expected = unlines yamllines testProgPath <- getExecutablePath let pandocCiteprocPath = takeDirectory testProgPath ".." "pandoc-citeproc" "pandoc-citeproc" (ec, result') <- pipeProcess (Just [("LANG","en_US.UTF-8"),("HOME",".")]) pandocCiteprocPath ["--bib2yaml", "-f", drop 1 $ takeExtension fp] (UTF8.fromStringLazy bib) let result = UTF8.toStringLazy result' if ec == ExitSuccess then do if expected == result then err "PASSED" >> return Passed else do err $ "FAILED" showDiff expected result return Failed else do err "ERROR" err $ "Error status " ++ show ec return Errored pandoc-citeproc-0.10.5.1/tests/JSON.hs0000644000000000000000000000061212743760365015457 0ustar0000000000000000{-# OPTIONS_GHC -fno-warn-orphans #-} -- ToJSON/FromJSON instances for Style module JSON where import Data.Aeson import Text.CSL.Style import Text.CSL.Parser import qualified Data.Text.Encoding as T import qualified Data.ByteString.Lazy as L instance FromJSON Style where parseJSON (String s) = return $ parseCSL' $ L.fromChunks [T.encodeUtf8 s] parseJSON _ = fail "Could not parse Style" pandoc-citeproc-0.10.5.1/prelude/Prelude.hs0000644000000000000000000000116512743760365016610 0ustar0000000000000000{-# LANGUAGE PackageImports #-} {-# LANGUAGE CPP #-} module Prelude ( module P , Monoid(..) , Applicative(..) #if MIN_VERSION_base(4,8,0) #else , (<$>) , (<$) #endif , (<>) ) where #if MIN_VERSION_base(4,8,0) import "base" Prelude as P import Data.Monoid ((<>)) #elif MIN_VERSION_base(4,6,0) import "base" Prelude as P import Control.Applicative import Data.Monoid #else import "base" Prelude as P hiding (catch) import Control.Applicative import Data.Monoid #endif #if MIN_VERSION_base(4,5,0) #else infixr 6 <> -- | An infix synonym for 'mappend'. (<>) :: Monoid m => m -> m -> m (<>) = mappend {-# INLINE (<>) #-} #endif pandoc-citeproc-0.10.5.1/compat/Text/CSL/Compat/Pandoc.hs0000644000000000000000000000713113046402505021010 0ustar0000000000000000{-# LANGUAGE CPP, ScopedTypeVariables #-} -- | Compatibility module to work around differences in the -- types of functions between pandoc < 2.0 and pandoc >= 2.0. module Text.CSL.Compat.Pandoc ( writeMarkdown, writePlain, writeNative, writeHtmlString, readNative, readHtml, readMarkdown, readLaTeX, fetchItem, pipeProcess ) where import qualified Control.Exception as E import System.Exit (ExitCode) import Data.ByteString.Lazy as BL import Data.ByteString as B import Text.Pandoc (Pandoc, ReaderOptions(..), def, WrapOption(..), WriterOptions(..)) import qualified Text.Pandoc as Pandoc import qualified Text.Pandoc.Process #if MIN_VERSION_pandoc(2,0,0) import Text.Pandoc.MIME (MimeType) import Text.Pandoc.Error (PandocError) import Text.Pandoc.Class (runPure, runIO) import qualified Text.Pandoc.Class (fetchItem) import Control.Monad.Except (runExceptT, lift) import Text.Pandoc.Extensions (extensionsFromList, Extension(..), pandocExtensions, disableExtension) #else import System.IO (stderr) import qualified Text.Pandoc.Shared (fetchItem) type MimeType = String #endif readHtml, readLaTeX, readMarkdown, readNative :: String -> Pandoc writeMarkdown, writePlain, writeNative, writeHtmlString :: Pandoc -> String #if MIN_VERSION_pandoc(2,0,0) readHtml = either mempty id . runPure . Pandoc.readHtml def{ readerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html, Ext_smart] } readMarkdown = either mempty id . runPure . Pandoc.readMarkdown def{ readerExtensions = pandocExtensions, readerStandalone = True } readLaTeX = either mempty id . runPure . Pandoc.readLaTeX def{ readerExtensions = extensionsFromList [Ext_raw_tex, Ext_smart] } readNative = either mempty id . runPure . Pandoc.readNative def writeMarkdown = either mempty id . runPure . Pandoc.writeMarkdown def{ writerExtensions = disableExtension Ext_smart pandocExtensions, writerWrapText = WrapNone } writePlain = either mempty id . runPure . Pandoc.writePlain def writeNative = either mempty id . runPure . Pandoc.writeNative def writeHtmlString = either mempty id . runPure . Pandoc.writeHtml4String def{ writerExtensions = extensionsFromList [Ext_native_divs, Ext_native_spans, Ext_raw_html] } #else readHtml = either mempty id . Pandoc.readHtml def{ readerSmart = True, readerParseRaw = True } readMarkdown = either mempty id . Pandoc.readMarkdown def{ readerSmart = True, readerStandalone = True} readLaTeX = either mempty id . Pandoc.readLaTeX def{ readerSmart = True, readerParseRaw = True } readNative = either mempty id . Pandoc.readNative writeMarkdown = Pandoc.writeMarkdown def{ writerWrapText = WrapNone } writePlain = Pandoc.writePlain def writeNative = Pandoc.writeNative def writeHtmlString = Pandoc.writeHtmlString def #endif pipeProcess :: Maybe [(String, String)] -> FilePath -> [String] -> BL.ByteString -> IO (ExitCode,BL.ByteString) #if MIN_VERSION_pandoc(2,0,0) pipeProcess = Text.Pandoc.Process.pipeProcess #else pipeProcess e f a b = do (ec, out, err) <- Text.Pandoc.Process.pipeProcess e f a b BL.hPutStr stderr err return (ec, out) #endif fetchItem :: Maybe String -> String -> IO (Either E.SomeException (B.ByteString, Maybe MimeType)) #if MIN_VERSION_pandoc(2,0,0) fetchItem mbd s = do res <- runIO $ runExceptT $ lift $ Text.Pandoc.Class.fetchItem mbd s return $ case res of Left e -> Left (E.toException e) Right (Left (e :: PandocError)) -> Left (E.toException e) Right (Right r) -> Right r #else fetchItem = Text.Pandoc.Shared.fetchItem #endif pandoc-citeproc-0.10.5.1/chicago-author-date.csl0000644000000000000000000005215313063456124017521 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/locales/locales-af-ZA.xml0000644000000000000000000002427313063456126017674 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 toegang verkry en and others anonymous anon at available at by circa c. cited edition editions ed et al. voorhande van ibid. in in press internet interview letter no date n.d. online presented at the reference references ref. refs. opgehaal scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers reël reëls note notes opus opera bladsy bladsye bladsy bladsye paragraaf paragrawe part parts section sections sub verbo sub verbis verse verses volume volumes bk chap col fig f no l. n. op bl bll bl bll para pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors redakteur redakteurs editor editors illustrator illustrators vertaler vertalers editor & translator editors & translators dir. dirs. red reds ed. eds. ill. ills. vert verts ed. & tran. eds. & trans. by directed by onder redaksie van edited by illustrated by interview by to by vertaal deur edited & translated by dir. red ed. illus. verts ed. & trans. by Januarie Februarie Maart April Mei Junie Julie Augustus September Oktober November Desember Jan Feb Mrt Apr Mei Jun Jul Aug Sep Okt Nov Des Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-ar.xml0000644000000000000000000002550713063456126017401 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 تاريخ الوصول و وآخرون مجهول مجهول عند موجود في عن طريق حوالي حو. وثق الطبعة الطبعات ط. وآخ. التالي من المرجع السابق في قيد النشر انترنت مقابلة خطاب دون تاريخ د.ت على الخط المباشر قُدَّم في مرجع مراجع مرجع مراجع استرجع في scale version ب.م. ق.م. " " ' ' الاول الثاني الثالث الرابع الخامس السادس السابع الثامن التاسع العاشر كتاب كتب فصل فصول عمود أعمدة رسم توضيحي رسوم توضيحية ورقة أوراق عدد أعداد سطر أسطر ملاحظة ملاحظات نوته موسيقية نوت موسيقية صفحة صفحات صفحة صفحات فقرة فقرات جزء أجزاء قسم أقسام تفسير فرعي تفسيرات فرعية بيت شعر أبيات شعر مجلد مجلدات كتاب فصل عمود رسم توضيحي مطوية عدد l. n. نوتة موسيقية ص ص.ص. ص ص.ص. فقرة ج. قسم تفسير فرعي تفسيرات فرعية بيت شعر أبيات شعر مج. مج. ¶¶ § §§ مدور مدورين محرر محررين رئيس التحرير رؤساء التحرير illustrator illustrators مترجم مترجمين مترجم ومحرر مترجمين ومحررين dir. dirs. محرر محررين مشرف على الطبعة مشرفين على الطبعة ill. ills. مترجم مترجمين مترجم ومشرف على الطباعه مترجمين ومشرفين على الطباعه directed by تحرير اعداد illustrated by مقابلة بواسطة مرسل الى بـ ترجمة اعداد وترجمة dir. تحرير اشرف على الطبعة illus. ترجمة ترجمه واشرف على الطباعه يناير فبراير مارس ابريل مايو يونيو يوليو اغسطس سبتمبر اكتوبر نوفمبر ديسمبر يناير فبراير مارس ابريل مايو يونيو يوليو اغسطس سبتمبر اكتوبر نوفمبر ديسمبر الربيع الصيف الخريف الشتاء pandoc-citeproc-0.10.5.1/locales/locales-bg-BG.xml0000644000000000000000000002534313063456126017653 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 отворен на и и други анонимен анон в available at by circa c. цитиран издание издания изд и съавт. предстоящ от пак там в под печат интернет интервю писмо no date без дата онлайн представен на reference references ref. refs. изтеглен на scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth книга книги глава глави колона колони фигура фигури фолио фолия брой броеве ред редове бележка бележки опус опуси страница страници страница страници параграф параграфи част части раздел раздели sub verbo sub verbis стих стихове том томове кн гл кол фиг фол бр l. n. оп с с-ци с с-ци п ч разд s.v. s.vv. ст ст-ове том т-ове ¶¶ § §§ director directors редактор редактори editor editors illustrator illustrators преводач преводачи editor & translator editors & translators dir. dirs. ред ред-ри ed. eds. ill. ills. прев прев-чи ed. & tran. eds. & trans. by directed by редактиран от edited by illustrated by интервюиран от до by преведен от edited & translated by dir. ред ed. illus. прев ed. & trans. by Януари Февруари Март Април Май Юни Юли Август Септември Октомври Ноември Декември Яну Фев Мар Апр Май Юни Юли Авг Сеп Окт Ное Дек Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-ca-AD.xml0000644000000000000000000002370213063456126017637 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 consulta i i altres anònim anòn. a disponible a per circa c. citat edició edicions ed. et al. previst de ibíd. en en impremta internet entrevista carta sense data s.d. en línia presentat a referència referències ref. ref. recuperat escala versió dC aC « » - a primera segona tercera quarta cinquena sisena setena vuitena novena desena llibre llibres capítol capítols columna columnes figura figures foli folis número números línia línies nota notes opus opera pàgina pàgines pàgina pàgines paràgraf paràgrafs part parts secció seccions sub voce sub vocibus vers versos volum volums llib. cap. col. fig. f. núm. l. n. op. p. p. p. p. par. pt. sec. s.v. s.v. v. v. vol. vol. § § § § director directors editor editors editor editors il·lustrador il·lustradors traductor traductors editor i traductor editors i traductors dir. dir. ed. ed. ed. ed. il·lust. il·lust. trad. trad. ed. i trad. ed. i trad. per dirigit per editat per editat per il·lustrat per entrevistat per a per traduït per editat i traduït per dir. ed. ed. il·lust. trad. ed. i trad. per gener febrer març abril maig juny juliol agost setembre octubre novembre desembre gen. feb. març abr. maig juny jul. ago. set. oct. nov. des. primavera estiu tardor hivern pandoc-citeproc-0.10.5.1/locales/locales-cs-CZ.xml0000644000000000000000000002412413063456126017710 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 viděno vid. a a další anonym anon. v dostupné z od asi cca. citován vydání vydání vyd. et al. nadcházející z ibid. in v tisku internet interview dopis nedatováno b.r. online prezentováno v reference reference ref. ref. získáno měřítko verze n. l. př. n. l. " ´ . první druhé třetí čtvrté páté šesté sedmé osmé deváté desáté kniha knihy kapitola kapitoly sloupec sloupce obrázek obrázky list listy číslo čísla řádek řádky poznámka poznámky opus opusy strana strany strana strany odstavec odstavce část části sekce sekce pod heslem pod hesly verš verše ročník ročníky k. kap. sl. obr. l. č. ř. pozn. op. s. s. s. s. odst. č. sek. s.v. s.v. v. v. roč. roč. ¶¶ § §§ ředitel ředitelé editor editoři vedoucí editor vedoucí editoři ilustrátor ilustrátoři překladatel překladatelé editor a překladatel editoři a překladatelé řed. řed. ed. ed. ed. ed. il. il. přel. přel. ed. a přel. ed. a přel. řídil editoval editoval ilustroval rozhovor vedl pro recenzoval přeložil editoval a přeložil řed. ed. ed. ilust. přel. ed. a přel. leden únor březen duben květen červen červenec srpen září říjen listopad prosinec led. úno. bře. dub. kvě. čer. čvc. srp. zář. říj. lis. pro. jaro léto podzim zima pandoc-citeproc-0.10.5.1/locales/locales-cy-GB.xml0000644000000000000000000002452313063456126017675 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-10-08T12:00:00+00:00 gwelwyd a/ac ac eraill di-enw dienw at ar gael gan circa c. dyfynnwyd argraffiad argraffiadau arg. et al. ar fin ymddangos gan ibid. yn yn y wasg rhyngrwyd cyfweliad llythyr dim dyddiad d.d. arlein cyflwynwyd yn cyfeirnod cyfeirnodau cyf. cyf’au. gwelwyd graddfa fersiwn OC CC th af il ydd ed ed ed cyntaf ail trydydd pedwerydd pumed chweched seithfed wythfed nawfed degfed llyfr llyfrau pennod penodau colofn colofnau ffigwr ffigyrau ffolio ffolios rhifyn rhifynnau llinell llinellau nodyn nodiadau opus opera tudalen tudalennau tudalen tudalennau paragraff paragraffau rhan rhannau adran adrannau sub verbo sub verbis pennill penillion cyfrol cyfrolau llyfr. pen. col. ffig. ff. rhif. ll. n. op. t. tt. t. tt. para. rhan. adr. s.v. s.vv. p. pp. rhif. rhifu. ¶¶ § §§ cyfarwyddwr cyfarwyddwyr golygydd golygyddion cyfarwyddwr-golygyddol cyfarwyddwyr-golygyddol darlunydd darlunwyr cyfieithydd cyfieithwyr golygydd a chyfieithydd golygyddion a chyfieithwyr cyf. cyfy. gol. goln. gol. goln. darlun. darlun. cyf. cyf. gol. a chyf. goln. a chyf. gan cyfarwyddwyd gan golygwyd gan cyfarwyddwyd a golygwyd gan darlunwyd gan cyfweliad gan i gan cyfieithwyd gan golygwyd a chyfieithwyd gan cyf. gan gol. gan cyf.-gol. gan darlun. gan cyf. gan gol. a chyf. gan Ionawr Chwefror Mawrth Ebrill Mai Mehefin Gorffennaf Awst Medi Hydref Tachwedd Rhagfyr Ion. Chwe. Maw. Ebr. Mai Meh. Gorff. Aws. Med. Hyd. Tach. Rhag. Gwanwyn Haf Hydref Gaeaf pandoc-citeproc-0.10.5.1/locales/locales-da-DK.xml0000644000000000000000000002403213063456126017647 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 set og med flere anonym anon. tilgængelig hos af cirka ca. henvist udgave udgaver udg. m.fl. kommende fra ibid. i i trykken internet interview brev uden år u.å. online præsenteret ved reference referencer ref. refr. hentet skala version e.v.t. f.v.t. . første anden tredje fjerde femte sjette syvende ottende niende tiende bog bøger kapitel kapitler kolonne kolonner figur figurer folio folio nummer numre linje linjer note noter opus opus side sider side sider afsnit afsnit del dele paragraf paragraffer sub voce sub voce vers vers bind bind b. kap. kol. fig. fol. nr. l. n. op. s. s. s. s. afs. d. par. s.v. s.v. v. v. bd. bd. ¶¶ § §§ instruktør instruktører redaktør redaktører redaktør redaktører illustrator illustratorer oversætter oversættere redaktør & oversætter redaktører & oversættere instr. instr. red. red. red. red. ill. ill. overs. overs. red. & overs. red. & overs. af instrueret af redigeret af redigeret af illustreret af interviewet af modtaget af af oversat af redigeret & oversat af instr. red. red. illus. overs. red. & overs. af januar februar marts april maj juni juli august september oktober november december jan. feb. mar. apr. maj jun. jul. aug. sep. okt. nov. dec. Forår Sommer Efterår Vinter pandoc-citeproc-0.10.5.1/locales/locales-de-AT.xml0000644000000000000000000002505613063456126017670 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 zugegriffen und und andere ohne Autor o. A. auf verfügbar unter von circa ca. zitiert Auflage Auflagen Aufl. u. a. i. E. von ebd. in im Druck Internet Interview Brief ohne Datum o. J. online gehalten auf der Referenz Referenzen Ref. Ref. abgerufen Maßstab Version  n. Chr.  v. Chr. . erster zweiter dritter vierter fünfter sechster siebter achter neunter zehnter Buch Bücher Kapitel Kapitel Spalte Spalten Abbildung Abbildungen Blatt Blätter Nummer Nummern Zeile Zeilen Note Noten Opus Opera Seite Seiten Seite Seiten Absatz Absätze Teil Teile Abschnitt Abschnitte sub verbo sub verbis Vers Verse Band Bände B. Kap. Sp. Abb. Fol. Nr. l. n. op. S. S. S. S. Abs. Teil Abschn. s. v. s. vv. V. V. Bd. Bd. ¶¶ § §§ Regisseur Regisseure Herausgeber Herausgeber Reihenherausgeber Reihenherausgeber Herausgeber Herausgeber Illustrator Illustratoren Übersetzer Übersetzer Herausgeber & Übersetzer Herausgeber & Übersetzer Reg. Reg. Hrsg. Hrsg. Hrsg. Hrsg. Hrsg. Hrsg. Ill. Ill. Übers. Übers. Hrsg. & Übers. Hrsg. & Übers von Regie von herausgegeben von herausgegeben von herausgegeben von illustriert von interviewt von an von übersetzt von herausgegeben und übersetzt von Reg. hg. von hg. von hg. von illus. von übers. von hg. & übers. von Jänner Februar März April Mai Juni Juli August September Oktober November Dezember Jän. Feb. März Apr. Mai Juni Juli Aug. Sep. Okt. Nov. Dez. Frühjahr Sommer Herbst Winter pandoc-citeproc-0.10.5.1/locales/locales-de-CH.xml0000644000000000000000000002423513063456126017654 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 zugegriffen und und andere ohne Autor o. A. auf verfügbar unter von circa ca. zitiert Auflage Auflagen Aufl. u. a. i. E. von ebd. in im Druck Internet Interview Brief ohne Datum o. J. online gehalten auf der Referenz Referenzen Ref. Ref. abgerufen Massstab Version  n. Chr.  v. Chr. « » . erster zweiter dritter vierter fünfter sechster siebter achter neunter zehnter Buch Bücher Kapitel Kapitel Spalte Spalten Abbildung Abbildungen Blatt Blätter Nummer Nummern Zeile Zeilen Note Noten Opus Opera Seite Seiten Seite Seiten Absatz Absätze Teil Teile Abschnitt Abschnitte sub verbo sub verbis Vers Verse Band Bände B. Kap. Sp. Abb. Fol. Nr. l. n. op. S. S. S. S. Abs. Teil Abschn. s. v. s. vv. V. V. Bd. Bd. ¶¶ § §§ Regisseur Regisseure Herausgeber Herausgeber Herausgeber Herausgeber Illustrator Illustratoren Übersetzer Übersetzer Herausgeber & Übersetzer Herausgeber & Übersetzer Reg. Reg. Hrsg. Hrsg. Hrsg. Hrsg. Ill. Ill. Übers. Übers. Hrsg. & Übers. Hrsg. & Übers von Regie von herausgegeben von herausgegeben von illustriert von interviewt von an von übersetzt von herausgegeben und übersetzt von Reg. hg. von hg. von illus. von übers. von hg. & übers. von Januar Februar März April Mai Juni Juli August September Oktober November Dezember Jan. Feb. März Apr. Mai Juni Juli Aug. Sep. Okt. Nov. Dez. Frühjahr Sommer Herbst Winter pandoc-citeproc-0.10.5.1/locales/locales-de-DE.xml0000644000000000000000000002505513063456126017653 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 zugegriffen und und andere ohne Autor o. A. auf verfügbar unter von circa ca. zitiert Auflage Auflagen Aufl. u. a. i. E. von ebd. in im Druck Internet Interview Brief ohne Datum o. J. online gehalten auf der Referenz Referenzen Ref. Ref. abgerufen Maßstab Version  n. Chr.  v. Chr. . erster zweiter dritter vierter fünfter sechster siebter achter neunter zehnter Buch Bücher Kapitel Kapitel Spalte Spalten Abbildung Abbildungen Blatt Blätter Nummer Nummern Zeile Zeilen Note Noten Opus Opera Seite Seiten Seite Seiten Absatz Absätze Teil Teile Abschnitt Abschnitte sub verbo sub verbis Vers Verse Band Bände B. Kap. Sp. Abb. Fol. Nr. Z. N. op. S. S. S. S. Abs. Teil Abschn. s. v. s. vv. V. V. Bd. Bde. ¶¶ § §§ Regisseur Regisseure Herausgeber Herausgeber Reihenherausgeber Reihenherausgeber Herausgeber Herausgeber Illustrator Illustratoren Übersetzer Übersetzer Herausgeber & Übersetzer Herausgeber & Übersetzer Reg. Reg. Hrsg. Hrsg. Hrsg. Hrsg. Hrsg. Hrsg. Ill. Ill. Übers. Übers. Hrsg. & Übers. Hrsg. & Übers von Regie von herausgegeben von herausgegeben von herausgegeben von illustriert von interviewt von an von übersetzt von herausgegeben und übersetzt von Reg. hg. von hg. von hg. von illus. von übers. von hg. & übers. von Januar Februar März April Mai Juni Juli August September Oktober November Dezember Jan. Feb. März Apr. Mai Juni Juli Aug. Sep. Okt. Nov. Dez. Frühjahr Sommer Herbst Winter pandoc-citeproc-0.10.5.1/locales/locales-el-GR.xml0000755000000000000000000002711413063456126017704 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2013-11-08T20:31:02+00:00 ημερομηνία πρόσβασης και και άλλοι ανώνυμο ανών. εφ. διαθέσιμο στο από περίπου περ. παρατίθεται έκδοση εκδόσεις έκδ. κ.ά. προσεχές από στο ίδιο στο υπό έκδοση διαδίκτυο συνέντευξη επιστολή χωρίς χρονολογία χ.χ. έκδοση σε ψηφιακή μορφή παρουσιάστηκε στο παραπομπή παραπομπές παρ. παρ. ανακτήθηκε κλίμακα εκδοχή μ.Χ. π.Χ. ' ' ο η ος πρώτος δεύτερος τρίτος τέταρτος πέμπτος έκτος έβδομος όγδοος ένατος δέκατος βιβλίο βιβλία κεφάλαιο κεφάλαια στήλη στήλες εικόνα εικόνες φάκελος φάκελοι τεύχος τεύχη σειρά σειρές σημείωση σημειώσεις έργο έργα σελίδα σελίδες σελίδα σελίδες παράγραφος παράγραφοι μέρος μέρη τμήμα τμήματα λήμμα λήμματα στίχος στίχοι τόμος τόμοι βιβ. κεφ. στ. εικ. φάκ τχ. γρ. σημ. έργ. σ σσ σ σσ παρ. μέρ. τμ. λήμ. λήμ. στ. στ. τ. τ. ¶¶ § §§ Διευθυντής Διευθυντές επιμελητής επιμελητές διευθυντής σειράς διευθυντές σειράς εικονογράφος εικονογράφοι μεταφραστής μεταφραστές μεταφραστής και επιμελητής μεταφραστές και επιμελητές δ/ντης. δ/ντές. επιμ. επιμ. δ/ντής σειράς δ/ντές σειρας εικ. εικ.. μτφ. μτφ. μτφ. και επιμ. μτφ. και επιμ. στον συλλ. τόμο διεύθυνση επιμέλεια διεύθυνση σειράς εικονογράφηση: συνέντευξη παραλήπτης συγγραφέας: μετάφραση μετάφραση και επιμέλεια διευθ. επιμέλ. δ/νση σειράς εικον. μετάφρ. μετάφρ. και επιμέλ. Ιανουάριος Φεβρουάριος Μάρτιος Απρίλιος Μάιος Ιούνιος Ιούλιος Αύγουστος Σεπτέμβριος Οκτώβριος Νοέμβριος Δεκέμβριος Ιανουαρίου Φεβρουαρίου Μαρτίου Απριλίου Μαΐου Ιουνίου Ιουλίου Αυγούστου Σεπτεμβρίου Οκτωβρίου Νοεμβρίου Δεκεμβρίου Άνοιξη Καλοκαίρι Φθινόπωρο Χειμώνας pandoc-citeproc-0.10.5.1/locales/locales-en-GB.xml0000755000000000000000000002561413063456126017671 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2015-10-10T23:31:02+00:00 accessed and and others anonymous anon. at available at by circa c. cited edition editions ed. et al. forthcoming from ibid. in in press internet interview letter no date n.d. online presented at the reference references ref. refs. retrieved scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers line lines note notes opus opera page pages page pages paragraph paragraphs part parts section sections sub verbo sub verbis verse verses volume volumes bk. bks chap. chaps col. cols fig. figs fol. fols no. nos. l. ll. n. nn. op. opp. p. pp. p. pp. para. paras pt. pts sec. secs s.v. s.vv. v. vv. vol. vols ¶¶ § §§ director directors editor editors editor editors illustrator illustrators translator translators editor & translator editors & translators dir. dirs. ed. eds. ed. eds. ill. ills. tran. trans. ed. & tran. eds. & trans. by directed by edited by edited by illustrated by interview by to by translated by edited & translated by dir. by ed. by ed. by illus. by trans. by ed. & trans. by January February March April May June July August September October November December Jan. Feb. Mar. Apr. May Jun. Jul. Aug. Sep. Oct. Nov. Dec. Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-en-US.xml0000755000000000000000000002562513063456126017732 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2015-10-10T23:31:02+00:00 accessed and and others anonymous anon. at available at by circa c. cited edition editions ed. et al. forthcoming from ibid. in in press internet interview letter no date n.d. online presented at the reference references ref. refs. retrieved scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers line lines note notes opus opera page pages page pages paragraph paragraphs part parts section sections sub verbo sub verbis verse verses volume volumes bk. bks. chap. chaps. col. cols. fig. figs. fol. fols. no. nos. l. ll. n. nn. op. opp. p. pp. p. pp. para. paras. pt. pts. sec. secs. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ director directors editor editors editor editors illustrator illustrators translator translators editor & translator editors & translators dir. dirs. ed. eds. ed. eds. ill. ills. tran. trans. ed. & tran. eds. & trans. by directed by edited by edited by illustrated by interview by to by translated by edited & translated by dir. by ed. by ed. by illus. by trans. by ed. & trans. by January February March April May June July August September October November December Jan. Feb. Mar. Apr. May Jun. Jul. Aug. Sep. Oct. Nov. Dec. Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-es-CL.xml0000644000000000000000000002424313063456126017676 0ustar0000000000000000 Scott Sadowsky http://sadowsky.cl/ This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2013-10-28T13:57:31-04:00 accedido y et al. anónimo anón. en disponible en de circa c. citado edición ediciones ed. et al. en preparación a partir de ibid. en en imprenta internet entrevista carta sin fecha s. f. en línea presentado en referencia referencias ref. refs. recuperado escala versión d. C. a. C. ª primera segunda tercera cuarta quinta sexta séptima octava novena décima libro libros capítulo capítulos columna columnas figura figuras folio folios número números línea líneas nota notas opus opera página páginas página páginas párrafo párrafos parte partes sección secciones sub voce sub vocibus verso versos volumen volúmenes lib. cap. col. fig. f. l. n. op. p. pp. p. pp. párr. pt. sec. s. v. s. vv. v. vv. vol. vols. § § § § director directores editor editores coordinador coordinadores ilustrador ilustradores traductor traductores editor y traductor editores y traductores dir. dirs. ed. eds. coord. coords. ilust. ilusts. trad. trads. ed. y trad. eds. y trads. de dirigido por editado por coordinado por ilustrado por entrevistado por a por traducido por editado y traducido por dir. ed. coord. ilust. trad. ed. y trad. enero febrero marzo abril mayo junio julio agosto septiembre octubre noviembre diciembre ene. feb. mar. abr. may jun. jul. ago. sep. oct. nov. dic. primavera verano otoño invierno pandoc-citeproc-0.10.5.1/locales/locales-es-ES.xml0000644000000000000000000002402613063456126017706 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 accedido y y otros anónimo anón. en disponible en de circa c. citado edición ediciones ed. et al. previsto a partir de ibid. en en imprenta internet entrevista carta sin fecha s. f. en línea presentado en referencia referencias ref. refs. recuperado escala versión d. C. a. C. « » - primera segunda tercera cuarta quinta sexta séptima octava novena décima libro libros capítulo capítulos columna columnas figura figuras folio folios número números línea líneas nota notas opus opera página páginas página páginas párrafo párrafos parte partes sección secciones sub voce sub vocibus verso versos volumen volúmenes lib. cap. col. fig. f. n.º l. n. op. p. pp. p. pp. párr. pt. sec. s. v. s. vv. v. vv. vol. vols. § § § § director directores editor editores editor editores ilustrador ilustradores traductor traductores editor y traductor editores y traductores dir. dirs. ed. eds. ed. eds. ilust. ilusts. trad. trads. ed. y trad. eds. y trads. de dirigido por editado por editado por ilustrado por entrevistado por a por traducido por editado y traducido por dir. ed. ed. ilust. trad. ed. y trad. enero febrero marzo abril mayo junio julio agosto septiembre octubre noviembre diciembre ene. feb. mar. abr. may jun. jul. ago. sep. oct. nov. dic. primavera verano otoño invierno pandoc-citeproc-0.10.5.1/locales/locales-es-MX.xml0000755000000000000000000002633713063456126017735 0ustar0000000000000000 Juan Ignacio Flores Salgado https://www.mendeley.com/profiles/juan-ignacio-flores-salgado/ This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2015-06-13T13:57:31-04:00 consultado y et al. anónimo anón. en disponible en de circa c. citado edición ediciones ed. eds. et al. en preparación a partir de ibid. en en imprenta internet entrevista carta sin fecha s/f en línea presentado en referencia referencias ref. refs. recuperado escala versión d. C. a. C. a a o primera segunda tercera cuarta quinta sexta séptima octava novena décima libro libros capítulo capítulos columna columnas figura figuras folio folios número números línea líneas nota notas opus opera página páginas página páginas párrafo párrafos parte partes sección secciones sub voce sub vocibus verso versos volumen volúmenes lib. libs. cap. caps. col. cols. fig. figs. f. ff. núm. núms. l. ls. n. nn. op. opp. p. pp. p. pp. párr. párrs. pt. pts. sec. secs. s. v. s. vv. v. vv. vol. vols. § § director directores editor editores coordinador coordinadores ilustrador ilustradores traductor traductores editor y traductor editores y traductores dir. dirs. ed. eds. coord. coords. ilust. ilusts. trad. trads. ed. y trad. eds. y trads. de dirigido por editado por coordinado por ilustrado por entrevistado por a por traducido por editado y traducido por dir. ed. coord. ilust. trad. ed. y trad. enero febrero marzo abril mayo junio julio agosto septiembre octubre noviembre diciembre ene. feb. mar. abr. may jun. jul. ago. sep. oct. nov. dic. primavera verano otoño invierno pandoc-citeproc-0.10.5.1/locales/locales-et-EE.xml0000644000000000000000000002373313063456126017675 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 vaadatud ja ja teised anonüümne anon available at umbes u tsiteeritud väljaanne väljaanded tr et al. ilmumisel ibid. trükis internet intervjuu kiri s.a. s.a. online esitatud viide viited viide viited salvestatud scale version pKr eKr . esimene teine kolmas neljas viies kuues seitsmes kaheksas üheksas kümnes raamat raamatud peatükk peatükid veerg veerud joonis joonised foolio fooliod number numbrid rida read viide viited opus opera lehekülg leheküljed lehekülg leheküljed lõik lõigud osa osad alajaotis alajaotised sub verbo sub verbis värss värsid köide köited rmt ptk v joon f nr l. n. op lk lk lk lk lõik osa alajaot. s.v. s.vv. v vv kd kd ¶¶ § §§ director directors toimetaja toimetajad toimetaja toimetajad illustrator illustrators tõlkija tõlkijad toimetaja & tõlkija toimetajad & tõlkijad dir. dirs. toim toim toim toim ill. ills. tõlk tõlk toim & tõlk toim & tõlk directed by toimetanud toimetanud illustrated by intervjueerinud by tõlkinud toimetanud & tõlkinud dir. toim toim illus. tõlk toim & tõlk jaanuar veebruar märts aprill mai juuni juuli august september oktoober november detsember jaan veebr märts apr mai juuni juuli aug sept okt nov dets kevad suvi sügis talv pandoc-citeproc-0.10.5.1/locales/locales-eu.xml0000644000000000000000000002431713063456126017406 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 eskuratua eta eta beste ezezaguna ezez. -(e)n available at -(e)k egina inguru ing. aipatua argitalpena argitalpenak arg. et al. bidean -(e)tik ibíd. in moldiztegian internet elkarrizketa gutuna datarik gabe d. g. sarean -(e)n aurkeztua aipamena aipamenak aip. aip. berreskuratua scale version K.a. K.o. « » . lehengo bigarren hirugarren laugarren bosgarren seigarren zazpigarren zortzigarren bederatzigarren hamargarren liburua liburuak kapitulua kapituluak zutabea zutabeak irudia irudiak orria orriak zenbakia zenbakiak lerroa lerroak oharra oharrak obra obrak orrialdea orrialdeak orrialdea orrialdeak paragrafoa paragrafoak zatia zatiak atala atalak sub voce sub vocem bertsoa bertsoak luburikia luburukiak lib. kap. zut. iru. or. zenb. l. n. op. or. or. or. or. par. zt. atal. s.v. s.v. b. bb. libk. libk. ¶¶ § § director directors argitaratzailea argitaratzaileak argitaratzailea argitaratzaileak illustrator illustrators itzultzailea itzultzaileak argitaratzaile eta itzultzailea argitaratzaile eta itzultzaileak dir. dirs. arg. arg. arg. arg. ill. ills. itzul. itzul. arg. eta itzul. arg. eta itzul. directed by -(e)k argitaratua -(e)k argitaratua illustrated by -(e)k elkarrizketatua -(r)entzat by -(e)k itzulia -(e)k argitaratu eta itzulia dir. arg. arg. illus. itzul. -(e)k arg. eta itzul. urtarrilak otsailak martxoak apirilak maiatzak ekainak uztailak abuztuak irailak urriak azaroak abenduak urt. ots. martx. apr. mai. eka. uzt. abz. ira. urr. aza. abe. udaberria uda udazkena negua pandoc-citeproc-0.10.5.1/locales/locales-fa-IR.xml0000644000000000000000000002567713063456126017705 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 دسترسی و و دیگران ناشناس ناشناس در قابل دسترس در توسط تقریباً c. ارجاع شده ویرایش ویرایش‌های ویرایش و همکاران در دست انتشار از همان در زیر چاپ اینترنت مصاحبه نامه بدون تاریخ بدون تاریخ آنلاین ارائه شده در مرجع مراجع مرجع مراجع retrieved scale نسخه بعد از میلاد قبل از میلاد اول دوم سوم چهارم پنجم ششم هفتم هشتم نهم دهم کتاب کتاب‌های فصل فصل‌های ستون ستون‌های تصویر تصاویر برگ برگ‌های شماره شماره‌های خط خطوط یادداشت یادداشت‌های قطعه قطعات صفحه صفحات صفحه صفحات پاراگراف پاراگراف‌های بخش بخش‌های قسمت قسمت‌های در ذیلِ واژه در ذیلِ واژه‌های بیت بیت‌های جلد جلدهای کتاب فصل ستون تصویر برگ ش خط یادداشت قطعه ص صص ص صص پاراگراف بخش قسمت s.v s.vv بیت ابیات ج جج ¶¶ § §§ director directors ویراستار ویراستاران ویراستار ویراستاران طراح گرافیک طراحان گرافیک مترجم مترجمین ویراستار و مترجم ویراستاران و مترجمین dir. dirs. ویراستار ویراستاران ویراستار ویراستاران تصویرگر تصویرگران مترجم مترجمین ویراستار و مترجم ویراستاران و مترجمین توسط زیر نظر ویراسته‌ی ویراسته‌ی طراحی گرافیکی از مصاحبه توسط به بازبینی توسط ترجمه‌ی ترجمه و ویراسته‌ی dir. ویراسته‌ی ویراسته‌ی طراحی از ترجمه‌ی ترجمه و ویراسته‌ی ژانویه فوریه مارس آوریل می ژوئن جولای آگوست سپتامبر اکتبر نوامبر دسامبر ژانویه فوریه مارس آوریل می ژوئن جولای آگوست سپتامبر اکتبر نوامبر دسامبر بهار تابستان پاییز زمستان pandoc-citeproc-0.10.5.1/locales/locales-fi-FI.xml0000755000000000000000000002413713063456126017672 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 viitattu ja ym. tuntematon tuntematon osoitteessa saatavissa tekijä noin n. viitattu painos painokset p. ym. tulossa osoitteesta mt. teoksessa painossa internet haastattelu kirje ei päivämäärää ei pvm. verkossa esitetty tilaisuudessa viittaus viittaukset viit. viit. noudettu mittakaava versio eaa. jaa. . ensimmäinen toinen kolmas neljäs viides kuudes seitsemäs kahdeksas yhdeksäs kymmenes kirja kirjat luku luvut palsta palstat kuvio kuviot folio foliot numero numerot rivi rivit huomautus huomautukset opus opukset sivu sivut sivu sivut kappale kappaleet osa osat osa osat sub verbo sub verbis säkeistö säkeistöt vuosikerta vuosikerrat kirja luku palsta kuv. fol. nro r. huom. op. s. ss. s. ss. kappale osa osa s.v. s.vv. säk. säk. vsk. vsk. ¶¶ § §§ ohjaaja ohjaajat toimittaja toimittajat toimittaja toimittajat kuvittaja kuvittajat kääntäjä kääntäjät toimittaja ja kääntäjä toimittajat ja kääntäjät ohj. ohj. toim. toim. toim. toim. kuv. kuv. käänt. käänt. toim. ja käänt. toim. ja käänt. ohjannut toimittanut toimittanut kuvittanut haastatellut vastaanottaja kääntänyt toimittanut ja kääntänyt ohj. toim. toim. kuv. käänt. toim. ja käänt. tammikuuta helmikuuta maaliskuuta huhtikuuta toukokuuta kesäkuuta heinäkuuta elokuuta syyskuuta lokakuuta marraskuuta joulukuuta tammi helmi maalis huhti touko kesä heinä elo syys loka marras joulu kevät kesä syksy talvi pandoc-citeproc-0.10.5.1/locales/locales-fr-CA.xml0000644000000000000000000002552113063456126017663 0ustar0000000000000000 Grégoire Colly This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 consulté le et et autres anonyme anon. sur disponible à par vers v. cité édition éditions éd. et al. à paraître à l'adresse ibid. dans sous presse Internet entretien lettre sans date s. d. en ligne présenté à référence références réf. réf. consulté échelle version apr. J.-C. av. J.-C. «   » ʳᵉ ᵉʳ premier deuxième troisième quatrième cinquième sixième septième huitième neuvième dixième livre livres chapitre chapitres colonne colonnes figure figures folio folios numéro numéros ligne lignes note notes opus opus page pages page pages paragraphe paragraphes partie parties section sections sub verbo sub verbis verset versets volume volumes liv. chap. col. fig. fᵒ fᵒˢ nᵒ nᵒˢ l. n. op. p. p. p. p. paragr. part. sect. s. v. s. vv. v. v. vol. vol. § § § § réalisateur réalisateurs éditeur éditeurs directeur directeurs illustrateur illustrateurs traducteur traducteurs éditeur et traducteur éditeurs et traducteurs réal. réal. éd. éd. dir. dir. ill. ill. trad. trad. éd. et trad. éd. et trad. par réalisé par édité par sous la direction de illustré par entretien réalisé par à par traduit par édité et traduit par réal. par éd. par ss la dir. de ill. par trad. par éd. et trad. par janvier février mars avril mai juin juillet août septembre octobre novembre décembre janv. févr. mars avr. mai juin juill. août sept. oct. nov. déc. printemps été automne hiver pandoc-citeproc-0.10.5.1/locales/locales-fr-FR.xml0000644000000000000000000002552413063456126017712 0ustar0000000000000000 Grégoire Colly This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 consulté le et et autres anonyme anon. sur disponible sur par vers v. cité édition éditions éd. et al. à paraître à l'adresse ibid. in sous presse Internet entretien lettre sans date s. d. en ligne présenté à référence références réf. réf. consulté échelle version apr. J.-C. av. J.-C. «   » ʳᵉ ᵉʳ premier deuxième troisième quatrième cinquième sixième septième huitième neuvième dixième livre livres chapitre chapitres colonne colonnes figure figures folio folios numéro numéros ligne lignes note notes opus opus page pages page pages paragraphe paragraphes partie parties section sections sub verbo sub verbis verset versets volume volumes liv. chap. col. fig. fᵒ fᵒˢ nᵒ nᵒˢ l. n. op. p. p. p. p. paragr. part. sect. s. v. s. vv. v. v. vol. vol. § § § § réalisateur réalisateurs éditeur éditeurs directeur directeurs illustrateur illustrateurs traducteur traducteurs éditeur et traducteur éditeurs et traducteurs réal. réal. éd. éd. dir. dir. ill. ill. trad. trad. éd. et trad. éd. et trad. par réalisé par édité par sous la direction de illustré par entretien réalisé par à par traduit par édité et traduit par réal. par éd. par ss la dir. de ill. par trad. par éd. et trad. par janvier février mars avril mai juin juillet août septembre octobre novembre décembre janv. févr. mars avr. mai juin juill. août sept. oct. nov. déc. printemps été automne hiver pandoc-citeproc-0.10.5.1/locales/locales-he-IL.xml0000644000000000000000000002500113063456126017662 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 נבדק לאחרונה ו ואחרים אלמוני anon זמין ב על-ידי לערך c. מצוטט ב מהדורה מהדורות ed ואחרים צפוי מתוך שם בתוך בהדפסה אינטרנט ראיון מכתב אין נתונים nd מקוון הוצג ב הפניה הפניות ref. refs. אוחזר scale גירסה לספירה לפני הספירה th st nd rd th th th ראשון שני שלישי רביעי חמישי שישי שביעי שמיני תשיעי עשירי ספר ספרים פרק פרקים טור טורים figure figures פוליו פוליו מספר מספרים שורה שורות הערה הערות אופוס אופרה עמוד עמודים עמוד עמודים פיסקה פיסקאות חלק חלקים סעיף סעיפים sub verbo sub verbis בית בתים כרך כרכים bk chap col fig f no l. n. op 'עמ 'עמ 'עמ 'עמ para pt ס' s.v. s.vv. v vv vol vols ¶¶ § §§ במאי במאים עורך עורכים עורך ראשי עורכים ראשיים מאייר מאיירים מתרגם מתרגמים editor & translator editors & translators dir. dirs. ed eds ed. eds. ill. ills. tran trans ed. & tran. eds. & trans. by בוים ע"י נערך ע"י בוים ע"י אויר ע"י רואיין ע"י אל ע"י תורגם ע"י edited & translated by dir. ed ed. illus. trans ed. & trans. by ינואר פברואר מרץ אפריל מאי יוני יולי אוגוסט ספטמבר אוקטובר נובמבר דצמבר Jan Feb Mar Apr May Jun Jul Aug Sep Oct Nov Dec Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-hr-HR.xml0000644000000000000000000002407713063456126017720 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 pristupljeno i i ostali anonimno anon. na dostupno na od oko oko citirano izdanje izdanja izd. i ostali u pripremi od ibid. u u tisku internet intervju pismo bez datuma bez dat. na internetu predstavljeno na reference reference ref. ref. preuzeto skala verzija pr. Kr. . prvi drugi treći četvrti peti šesti sedmi osmi deveti deseti knjiga knjige poglavlje poglavlja stupac stupci crtež crteži folija folije izdanje izdanja red redovi bilješka bilješke djelo djela stranica stranice stranica stranice pasus pasusi dio dijelova odjeljak odjeljci sub verbo sub verbis stih stihovi svezak svesci knj. pogl. stup. crt. fol. izd. red bilj. sv. str. str. str. str. par. dio od. s.v. s.vv. st. st. sv. sv. ¶¶ § §§ voditelj voditelji urednik urednici urednik urednici ilustrator ilustratori prevoditelj prevoditelji urednik & prevoditelj urednici & prevoditelji vod. vod. ur. ur. ur.-vod. ur.-vod. il. il. prev. prev. ur. & prev. ur. & prev. od vodio uredio uredio ilustrirao intervjuirao primatelj pregledao preveo uredio & preveo vod. ur. ur. vod. ilus. prev. ur. & prev. siječanj veljača ožujak travanj svibanj lipanj srpanj kolovoz rujan listopad studeni prosinac sij. velj. ožu. tra. svi. lip. srp. kol. ruj. lis. stu. pros. proljeće ljeto jesen zima pandoc-citeproc-0.10.5.1/locales/locales-hu-HU.xml0000644000000000000000000002437413063456126017726 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-06-17T09:56:35+02:00 elérés és és mások szerző nélkül sz. n. elérhető by körülbelül kb. idézi kiadás kiadás kiad. és mtsai. megjelenés alatt forrás uo. in nyomtatás alatt internet interjú levél évszám nélkül é. n. online előadás hivatkozás hivatkozás hiv. hiv. elérés skála verzió Kr. u. Kr. e. i. sz. i. e. » « . első második harmadik negyedik ötödik hatodik hetedik nyolcadik kilencedik tizedik könyv könyv fejezet fejezet oszlop oszlop ábra ábra fóliáns fóliáns szám szám sor sor jegyzet jegyzet oldal oldal oldal oldal bekezdés bekezdés rész rész szakasz szakasz sub verbo sub verbis versszak versszak kötet kötet könyv fej. oszl. ábr. fol. sz. s. j. op. o. o. o. o. bek. rész szak. s. v. s. vv. vsz. vsz. köt. köt. ¶¶ § §§ igazgató igazgató szerkesztő szerkesztő szerkesztőségi igazgató szerkesztőségi igazgató illusztrátor illusztrátor fordító fordító szerkesztő & fordító szerkesztő & fordító ig. ig. szerk. szerk. szerk. ig. szerk. ig. ill. ill. ford. ford. szerk. & ford. szerk. & ford. by directed by szerkesztette edited by illusztrálta interjúkészítő címzett by fordította szerkesztette & fordította ig. szerk. ed. ill. ford. szerk. & ford. január február március április május június július augusztus szeptember október november december jan. febr. márc. ápr. máj. jún. júl. aug. szept. okt. nov. dec. tavasz nyár ősz tél pandoc-citeproc-0.10.5.1/locales/locales-id-ID.xml0000755000000000000000000002427513063456126017671 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2015-08-05T23:31:02+00:00 diakses dan dan lainnya anonim anon. pada tersedia pada by circa c. dikutip edisi edisi ed. et al. mendatang dari ibid. in in press internet wawancara surat tanpa tanggal n.d. daring dipresentasikan pada reference references ref. ref. diambil skala versi M SM pertama kedua ketiga keempat kelima keenam ketujuh kedelapan kesembilan kesepuluh buku buku bab bab kolom kolom gambar gambar folio folio nomor nomor baris baris catatan catatan opus opera halaman halaman halaman halaman paragraf paragraf bagian bagian section section sub verbo sub verbis ayat ayat volume volume bk. chap. col. gam. f. no. l. n. op. hal. hal. hal. hal. para. pt. sec. s.v. s.vv. a. a. vol. vol. ¶¶ § §§ direktur direktur editor editor editor editor ilustrator ilustrator penerjemah penerjemah editor & penerjemah editor & penerjemah dir. dirs. ed. ed. ed. ed. il. il. penerj. penerj. ed. & tran. ed. & tran. oleh diarahkan oleh diedit oleh diedit oleh diilustrasi oleh interview oleh kepada oleh diterjemahkan oleh disunting & diterjemahkan oleh dir. oleh ed. oleh ed. oleh illus. oleh trans. oleh ed. & trans. oleh Januari Februari Maret April Mei Juni Juli Agustus September Oktober November Desember Jan Feb Mar Apr Mei Jun Jul Agu Sep Okt Nov Des Semi Panas Gugur Dingin pandoc-citeproc-0.10.5.1/locales/locales-is-IS.xml0000644000000000000000000002414413063456126017717 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 sótt og og fleiri nafnlaus nafnl. af aðgengilegt á eftir sirka u.þ.b. tilvitnun útgáfa útgáfur útg. o.fl. óbirt af sama heimild í í prentun rafrænt viðtal bréf engin dagsetning e.d. rafrænt flutt á tilvitnun tilvitnanir tilv. tilv. sótt scale útgáfa e.Kr. f.Kr. . fyrsti annar þriðji fjórði fimmti sjötti sjöundi áttundi níundi tíundi bók bækur kafli kaflar dálkur dálkar mynd myndir handrit handrit tölublað tölublöð lína línur athugasemd athugasemdir tónverk tónverk blaðsíða blaðsíður blaðsíða blaðsíður málsgrein málsgreinar hluti hlutar hluti hlutar sub verbo sub verbis vers vers bindi bindi bók k. d. mynd. handr. tbl. l. ath. tónv. bls. bls. bls. bls. málsgr. hl. hl. s.v. s.vv. v. v. b. b. ¶¶ § §§ leikstjóri leikstjórar ritstjóri ritstjórar ritstjóri ritstjórar höfundur myndskreytinga höfundar myndskreytinga þýðandi þýðendur ritstjóri og þýðandi ritstjórar og þýðendur leikstj. leikstj. ritstj. ritstj. ritstj. ritstj. höf. mynd. höf. mynd. þýð. þýð. ritstj. og þýð. ritstj. og þýð. eftir leikstýrt af ritstýrt af ritstýrt af myndskreytt af viðtal tók til by þýddi ritstýrt og þýtt af leikstj. ritstj. ritstj. myndskr. þýð. ritstj. og þýð. janúar febrúar mars apríl maí júní júlí ágúst september október nóvember desember jan. feb. mar. apr. maí jún. júl. ágú. sep. okt. nóv. des. vor sumar haust vetur pandoc-citeproc-0.10.5.1/locales/locales-it-IT.xml0000644000000000000000000002373713063456126017730 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 consultato e e altri anonimo anon. a available at di circa c. citato edizione edizioni ed. et al. futuro da ibid. in in stampa internet intervista lettera senza data s.d. in linea presentato al reference references ref. refs. recuperato scale version d.C. a.C. « » ° prima seconda terza quarta quinta sesta settima ottava nona decima libro libri capitolo capitoli colonna colonne figura figure foglio fogli numero numeri riga righe nota note opera opere pagina pagine pagina pagine capoverso capoversi parte parti paragrafo paragrafi sub verbo sub verbis verso versi volume volumi lib. cap. col. fig. fgl. n. l. n. op. pag. pagg. pag. pagg. cpv. pt. par. s.v. s.vv. v. vv. vol. vol. ¶¶ § §§ director directors curatore curatori editor editors illustrator illustrators traduttore traduttori curatore e traduttore curatori e tradutori dir. dirs. a c. di a c. di ed. eds. ill. ills. trad. trad. a c. di e trad. da a c. di e trad. da di directed by a cura di edited by illustrated by intervista di a by tradotto da a cura di e tradotto da dir. a c. di ed. illus. trad. da a c. di e trad. da gennaio febbraio marzo aprile maggio giugno luglio agosto settembre ottobre novembre dicembre gen. feb. mar. apr. mag. giu. lug. ago. set. ott. nov. dic. primavera estate autunno inverno pandoc-citeproc-0.10.5.1/locales/locales-ja-JP.xml0000644000000000000000000002424513063456126017676 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 参照 and others anonymous anon at available at by circa c. cited ほか 近刊 から 前掲 in press internet interview letter no date 日付なし online presented at the reference references ref. refs. 読み込み scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers note notes opus opera ページ ページ ページ ページ 段落 段落 part parts section sections sub verbo sub verbis verse verses volume volumes bk. chap. col. fig. f. no. l. n. op. p. pp. p. pp. para. pt. sec. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ director directors editor editors illustrator illustrators 翻訳者 翻訳者 editor & translator editors & translators dir. dirs. ed. eds. ill. ills. 翻訳者 翻訳者 ed. & tran. eds. & trans. by directed by 編集者: edited by illustrated by interview by to by 翻訳者: edited & translated by dir. 編集者: ed. illus. 翻訳者: ed. & trans. by 1月 2月 3月 4月 5月 6月 7月 8月 9月 10月 11月 12月 1月 2月 3月 4月 5月 6月 7月 8月 9月 10月 11月 12月 Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-km-KH.xml0000644000000000000000000002532313063456126017702 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 accessed and and others anonymous anon. at available at by circa c. cited edition editions ed. et al. forthcoming from ibid in in press internet interview letter no date n.d. online presented at the reference references ref. refs. retrieved scale version AD BC th st nd rd th th th ទីមួយ ទីពីរ ទីបី ទីបួន ទីប្រាំ ទីប្រាំមួយ ទីប្រាំពីរ ទីប្រាំបី ទីប្រាំបួន ទីដប់មួយ សៀវភៅ សៀវភៅ ជំពូក ជំពូក កាឡោន កាឡោន តួលេខ តួលេខ folio folios ចំនួន ចំនួន បន្ទាត់ បន្ទាត់ កំណត់ចំណាំ កំណត់ចំណាំ opus opera ទំព័រ ទំព័រ ទំព័រ ទំព័រ កថាខណ្ឌ កថាខណ្ឌ ជំពូក ជំពូក ផ្នែក ផ្នែក sub verbo sub verbis verse verses វ៉ុល វ៉ុល bk. chap. col. fig. f. no. l. n. op. p. pp. p. pp. para. pt. sec. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ director directors editor editors editors illustrator illustrators translator translator editor & translator editors & translators dir. dirs. ed. eds. ed. eds. ill. ills. tran. trans. ed. & tran. eds. & trans. by directed by edited by edited by illustrated by interview by to by translated by edited & translated by dir. ed. ed. illus. trans. ed. & trans. by មករា កុម្ភៈ មីនា មេសា ឧសភា មិថុនា កក្កដា សីហា កញ្ញា តុលា វិច្ឆិកា ធ្នូ Jan. Feb. Mar. Apr. May Jun. Jul. Aug. Sep. Oct. Nov. Dec. Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-ko-KR.xml0000644000000000000000000002427513063456126017723 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 접근된 와/과 and others anonymous anon at available at by circa c. cited edition editions ed 기타 근간 (으)로부터 ibid. in in press internet interview letter no date 일자 없음 online presented at the reference references ref. refs. retrieved scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers note notes opus opera 페이지 페이지 페이지 페이지 단락 단락 part parts section sections sub verbo sub verbis verse verses volume volumes bk chap col fig f l. n. op p pp p pp para pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors 편집자 편집자 editor editors illustrator illustrators 번역자 번역자 editor & translator editors & translators dir. dirs. 편집자 편집자 ed. eds. ill. ills. 번역자 번역자 ed. & tran. eds. & trans. by directed by 편집자: edited by illustrated by interview by to by 번역자: edited & translated by dir. ed ed. illus. trans ed. & trans. by 1월 2월 3월 4월 5월 6월 7월 8월 9월 10월 11월 12월 1 2 3 4 5 6 7 8 9 10 11 12 Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-lt-LT.xml0000644000000000000000000002673513063456126017737 0ustar0000000000000000 Valdemaras Klumbys This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2017-01-18T10:31:02+00:00 žiūrėta ir ir kt. anonimas anon. adresas apie apie žiūrėta leidimas leidimai leid. ir kt. ruošiamas ten pat priimta spaudai prieiga per internetą interviu laiškas sine anno s.a. interaktyvus pristatytas nuoroda nuorodos nuor. nuor. gauta mastelis versija po Kr. pr. Kr. , -asis -asis -oji -iasis -asis -ioji -oji pirmasis antrasis trečiasis ketvirtasis penktasis šeštasis septintasis aštuntasis devintasis dešimtasis pirmoji antroji trečioji ketvirtoji penktoji šeštoji septintoji aštuntoji devintoji dešimtoji knyga knygos skyrius skyriai skiltis skiltys iliustracija iliustracijos lapas lapai numeris numeriai eilutė eilutės pastaba pastabos kūrinys kūriniai puslapis puslapiai puslapis puslapiai pastraipa pastraipos dalis dalys poskyris poskyriai žiūrėk žiūrėk eilėraštis eilėraščiai tomas tomai kn. sk. skilt. il. l. nr. eil. pstb. kūr. p. p. p. p. pastr. d. posk. žr. žr. eilėr. eilėr. t. t. ¶¶ § §§ vadovas vadovai sudarytojas sudarytojai atsakingasis redaktorius atsakingieji redaktoriai iliustratorius iliustratoriai vertėjas vertėjai sudarytojas ir vertėjas sudarytojai ir vertėjai vad. vad. sud. sud. ats. red. ats. red. iliustr. iliustr. vert. vert. sud. ir vert. sud. ir vert. vadovavo sudarė parengė iliustravo interviu ėmė gavo recenzavo vertė sudarė ir vertė vad. sud. pareng. iliustr. vert. sud. ir vert. sausio vasario kovo balandžio gegužės birželio liepos rugpjūčio rugsėjo spalio lapkričio gruodžio saus. vas. kovo bal. geg. birž. liep. rugpj. rugs. spal. lapkr. gruodž. pavasaris vasara ruduo žiema pandoc-citeproc-0.10.5.1/locales/locales-lv-LV.xml0000644000000000000000000003023513063456126017731 0ustar0000000000000000 Andris Lupgins This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-12-27T11:40:58+02:00 skatīts m.ē. un un citi anonīms anon. pieejams p.m.ē. apmēram apm. citēts redakcija redakcijas red. u.c. gaidāms no turpat no presē internets intervija vēstule bez datuma b.g. tiešsaiste iesniegts atsauce atsauces ats. ats. iegūts mērogs versija " " " " -ais pirmais otrais trešais ceturtais piektais sestais septītais astotais devītais desmitais pirmā otrā trešā ceturtā piektā sestā septītā astotā devītā desmitā grāmata grāmatas nodaļa nodaļas sleja slejas ilustrācija ilustrācijas folio folio numurs numuri rinda rindas piezīme piezīmes opuss opusi lappuse lappuses lappuse lappuses rindkopa rindkopas daļa daļas apakšnodaļa apakšnodaļas skatīt skatīt pants panti sējums sējumi grām. nod. sl. il. fo. nr. r. piez. op. lpp. lpp. lpp. lpp. rindk. d. apakšnod. sk. sk. p. p. sēj. sēj. ¶¶ § §§ krājuma redaktors krājuma redaktori sastādītājs sastādītāji pamatmateriāla autors pamatmateriāla autori vadītājs vadītāji redaktors redaktors galvenais redaktors galvenie redaktori redaktors un tulkotājs redaktors un tulkotājs ilustrators ilustratori intervētājs intervētāji saņēmējs saņēmēji tulkotājs tulkotāji kr. red. kr. red. sast. sast. pamatmat. aut. pamatmat. aut. vad. vad. red. red. galv. red. galv. red. red. un tulk. red. un tulk. ilustr. ilustr. interv. interv. saņ. saņ. tulk. tulk. sastādīja vadīja sagatavoja sagatavoja sagatavoja un tulkoja ilustrēja intervēja saņēma tulkoja sast. sag. sag. ilustr. tulk. sag. un tulk. janvārī februārī martā aprīlī maijā jūnijā jūlijā augustā septembrī oktobrī novembrī decembrī janv. febr. mar. apr. mai. jūn. jūl. aug. sept. okt. nov. dec. pavasaris vasara rudens ziema pandoc-citeproc-0.10.5.1/locales/locales-mn-MN.xml0000644000000000000000000002417213063456126017716 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 accessed and and others anonymous anon at available at by circa c. cited edition editions ed et al. forthcoming from ibid. in in press internet interview letter no date n.d. online presented at the reference references ref. refs. retrieved scale version AD BC « » th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers line lines note notes opus opera page pages page pages paragraph paragraph part parts section sections sub verbo sub verbis verse verses volume volumes bk chap col fig f no l. n. op p pp p pp para pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors editor editors editor editors illustrator illustrators translator translators editor & translator editors & translators dir. dirs. ed eds ed. eds. ill. ills. tran trans ed. & tran. eds. & trans. by directed by edited by edited by illustrated by interview by to by translated by edited & translated by dir. ed ed. illus. trans ed. & trans. by January February March April May June July August September October November December Jan Feb Mar Apr May Jun Jul Aug Sep Oct Nov Dec Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-nb-NO.xml0000644000000000000000000002401213063456126017676 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2013-03-01T12:20:00+01:00 åpnet og med flere anonym anon. tilgjengelig på av circa ca. sitert utgave utgaver utg. mfl. kommende fra ibid. i i trykk Internett intervju brev ingen dato udatert online presentert på referanse referanser ref. refr. hentet målestokk versjon fvt. evt. « » . første andre tredje fjerde femte sjette sjuende åttende niende tiende bok bøker kapittel kapitler kolonne kolonner figur figurer folio folioer nummer numre linje linjer note noter opus opus side sider side sider avsnitt avsnitt del deler paragraf paragrafer sub verbo sub verbis vers vers bind bind b. kap. kol. fig. fol. nr. l. n. op. s. s. s. s. avsn. d. pargr. s.v. s.vv. v. v. bd. bd. ¶¶ § §§ regissør regissører redaktør redaktører redaktør redaktører illustratør illustratører oversetter oversettere redaktør & oversetter redaktører & oversettere regi regi red. red. red. red. ill. ills. overs. overs. red. & overs. red. & overs. av regissert av redigert av redigert av illustrert av intervjuet av til av oversatt av redigert & oversatt av regi red. red. illus. overs. red. & overs. av januar februar mars april mai juni juli august september oktober november desember jan. feb. mar. apr. mai jun. jul. aug. sep. okt. nov. des. vår sommer høst vinter pandoc-citeproc-0.10.5.1/locales/locales-nl-NL.xml0000644000000000000000000002610213063456126017707 0ustar0000000000000000 Rintze Zelle http://twitter.com/rintzezelle This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 geraadpleegd en en anderen anoniem anon. bij beschikbaar op door circa c. geciteerd editie edities ed. e.a. in voorbereiding van ibid. in in druk internet interview brief zonder datum z.d. online gepresenteerd bij referentie referenties ref. refs. geraadpleegd schaal versie AD BC ste de de de de de de de de de de de de de de de de de de eerste tweede derde vierde vijfde zesde zevende achtste negende tiende boek boeken hoofdstuk hoofdstukken column columns figuur figuren folio folio's nummer nummers regel regels aantekening aantekeningen opus opera pagina pagina's pagina pagina's paragraaf paragrafen deel delen sectie secties sub verbo sub verbis vers versen volume volumes bk. hfdst. col. fig. f. nr. l. n. op. p. pp. p. pp. par. deel sec. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ regisseur regisseurs redacteur redacteuren redacteur redacteuren illustrator illustrators vertaler vertalers redacteur & vertaler redacteuren & vertalers reg. reg. red. red. red. red. ill. ill. vert. vert. red. & vert. red. & vert. door geregisseerd door bewerkt door bewerkt door geïllustreerd door geïnterviewd door ontvangen door door vertaald door bewerkt & vertaald door geregisseerd door bewerkt door bewerkt door geïllustreerd door vertaald door bewerkt & vertaald door januari februari maart april mei juni juli augustus september oktober november december jan. feb. mrt. apr. mei jun. jul. aug. sep. okt. nov. dec. lente zomer herst winter pandoc-citeproc-0.10.5.1/locales/locales-nn-NO.xml0000644000000000000000000002376413063456126017727 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2013-03-01T12:20:00+01:00 vitja og med fleire anonym anon. tilgjengeleg på av circa ca. sitert utgåve utgåver utg. mfl. kommande frå ibid. i i trykk Internett intervju brev ingen dato udatert online presentert på referanse referansar ref. refr. henta målestokk versjon fvt. evt. « » . første andre tredje fjerde femte sjette sjuande åttande niande tiande bok bøker kapittel kapittel kolonne kolonner figur figurar folio folioar nummer nummer linje linjer note notar opus opus side sider side sider avsnitt avsnitt del deler paragraf paragrafar sub verbo sub verbis vers vers bind bind b. kap. kol. fig. fol. nr. l. n. op. s. s. s. s. avsn. d. par. s.v. s.vv. v. v. bd. bd. ¶¶ § §§ regissør regissørar redaktør redaktørar redaktør redaktørar illustratør illustratørar omsetjar omsetjarar redaktør & omsetjar redaktørar & omsetjarar regi regi red. red. red. red. ill. ills. oms. oms. red. & oms. red. & oms. av regissert av redigert av redigert av illustrert av intervjua av til av omsett av redigert & omsett av regi red. red. illus. oms. red. & oms. av januar februar mars april mai juni juli august september oktober november desember jan. feb. mar. apr. mai jun. jul. aug. sep. okt. nov. des. vår sommar haust vinter pandoc-citeproc-0.10.5.1/locales/locales-pl-PL.xml0000644000000000000000000002401613063456126017715 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 udostępniono i i inni anonim anon. na dostępne na przez około ok cytowane wydanie wydania wyd. i in. w przygotowaniu z ibid. w w druku internet wywiad list brak daty b.d. online zaprezentowano na referencja referencje ref. ref. pobrano skala wersja n.e. p.n.e. « » . pierwszy drugi trzeci czwarty piąty szósty siódmy ósmy dziewiąty dziesiąty książka książki rozdział rozdziały kolumna kolumny rycina ryciny folio folio numer numery wers wersy notatka notatki opus opera strona strony strona strony akapit akapity część części sekcja sekcje sub verbo sub verbis wers wersy tom tomy książka rozdz. kol. ryc. fol. nr l. n. op. s. ss. s. ss. akap. cz. sekc. s.v. s.vv. w. w. t. t. ¶¶ § §§ reżyser reżyserzy redaktor redaktorzy edytor edytorzy ilustrator ilustratorzy tłumacz tłumacze redaktor & tłumacz redaktorzy & tłumacze dyr. dyr. red. red. red. red. il. il. tłum. tłum. red.tłum. red.tłum. przez directed by zredagowane przez zredagowane przez ilustrowane przez by przeprowadzony przez dla przez przetłumaczone przez zredagowane i przetłumaczone przez dir. red. red. il. tłum. red.tłum. styczeń luty marzec kwiecień maj czerwiec lipiec sierpień wrzesień październik listopad grudzień sty. luty mar. kwi. maj cze. lip. sie. wrz. paź. lis. grudz. wiosna lato jesień zima pandoc-citeproc-0.10.5.1/locales/locales-pt-BR.xml0000644000000000000000000002617513063456126017725 0ustar0000000000000000 2016-05-16T00:00:00+03:00 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License acessado e e outros anônimo anon em disponível em por circa c. citado edição edições ed et al. a ser publicado de ibidem in no prelo internet entrevista carta sem data [s.d.] online apresentado em referência referências ref. refs. recuperado escala versão DC AC º ª º primeiro segundo terceiro quarto quinto sexto sétimo oitavo nono décimo primeira segunda terceira quarta quinta sexta sétima oitava nona décima livro livros capítulo capítulos coluna colunas figura figuras folio folios número números linha linhas nota notas opus opera página páginas página páginas parágrafo parágrafos parte partes seção seções sub verbo sub verbis verso versos volume volumes liv. cap. col. fig. f. l. n. op. p. p. p. p. parag. pt. seç. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ diretor diretores organizador organizadores editor editores ilustrador ilustradores tradutor tradutores editor e tradutor editores e tradutores dir. dirs. org. orgs. ed. eds. il. ils. trad. trads. ed. e trad. eds. e trads. por dirigido por organizado por editado por ilustrado por entrevista de para por traduzido por editado e traduzido por dir. org. ed. ilus. trad. ed. e trad. por janeiro fevereiro março abril maio junho julho agosto setembro outubro novembro dezembro jan. fev. mar. abr. maio jun. jul. ago. set. out. nov. dez. Primavera Verão Outono Inverno pandoc-citeproc-0.10.5.1/locales/locales-pt-PT.xml0000644000000000000000000002620313063456126017735 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2013-09-20T23:31:02+00:00 Jonadabe PT acedido e e outros anónimo anón. em disponível em por circa c. citado edição edições ed. et al. a publicar de ibid. em no prelo internet entrevista carta sem data sem data em linha apresentado na referência referências ref. refs. obtido scale versão AD BC « » primeiro primeira segundo segunda terceiro terceira quarto quarta quinto quinta sexto sexta sétimo sétima oitavo oitava nono nona décimo décima livro livros capítulo capítulos coluna colunas figura figuras fólio fólios número números linha linhas nota notas opus opera página páginas página páginas parágrafo parágrafos parte partes secção secções sub verbo sub verbis versículo versículos volume volumes liv. cap. col. fig. f. n. l. n. op. p. pp. p. pp. par. pt. sec. s.v. s.vv. v vv vol. vols. ¶¶ § §§ director directores editor editores editor editores ilustrador ilustradores tradutor tradutores editor & tradutor editores & tradutores dir. dirs. ed. eds. ed. eds. il. ils. trad. trads. ed. & trad. eds. & trads. por dirigido por editado por editorial de ilustrado por entrevistado por para revisto por traduzido por editado & traduzido por dir. ed. ed. ilus. trad. ed. & trad. por Janeiro Fevereiro Março Abril Maio Junho Julho Agosto Setembro Outubro Novembro Dezembro Jan. Fev. Mar. Abr. Mai. Jun. Jul. Ago. Set. Out. Nov. Dez. Primavera Verão Outono Inverno pandoc-citeproc-0.10.5.1/locales/locales-ro-RO.xml0000644000000000000000000002432013063456126017725 0ustar0000000000000000 Nicolae Turcan nturcan@gmail.com This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 data accesării și și alții anonim anon. la valabil la de circa cca. citat ediția edițiile ed et al. în curs de apariție din ibidem în sub tipar internet interviu scrisoare fără dată f.a. online prezentat la referință referințe ref. ref. preluat în scală versiunea d.Hr. î.Hr. « » - -lea primul al doilea al treilea al patrulea al cincilea al șaselea al șaptelea al optulea al nouălea al zecelea cartea cărțile capitolul capitolele coloana coloanele figura figurile folio folio numărul numerele linia liniile nota notele opusul opusurile pagina paginile pagina paginile paragraful paragrafele partea părțile secțiunea secțiunile sub verbo sub verbis versetul versetele volumul volumele cart. cap. col. fig. fol. nr. l. n. op. p. pp. p. pp. par. part. sec. s.v. s.vv. v. vv. vol. vol. ¶¶ § §§ director directori editor editori editor editori ilustrator ilustratori traducător traducători editor & traducător editori & traducători dir. dir. ed. ed. ed. ed. ilustr. ilustr. trad. trad. ed. & trad. ed. & trad. de coordonat de ediție de ediție de ilustrații de interviu de în de traducere de ediție & traducere de dir. ed. ed. ilustr. trad. ed. & trad. de ianuarie februarie martie aprilie mai iunie iulie august septembrie octombrie noiembrie decembrie ian. feb. mar. apr. mai iun. iul. aug. sep. oct. nov. dec. primăvara vara toamna iarna pandoc-citeproc-0.10.5.1/locales/locales-ru-RU.xml0000644000000000000000000003454613063456126017754 0ustar0000000000000000 Alexei Kouprianov alexei.kouprianov@gmail.com This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 просмотрено и и др. аноним анон. на доступно на около ок. цитируется по цит. по издание издания изд. и др. ожидается от там же в в печати Интернет интервью письмо без даты б. д. онлайн представлено на ссылка ссылки ссылка ссылки извлечено масштаб версия н. э. до н. э. « » первое второе третье четвертое пятое шестое седьмое восьмое девятое десятое первый второй третий четвертый пятый шестой седьмой восьмой девятый десятый первая вторая третья четвертая пятая шестая седьмая восьмая девятая десятая книга книги глава главы столбец столбцы рисунок рисунки лист листы выпуск выпуски строка строки примечание примечания сочинение сочинения страница страницы страница страницы параграф параграфы часть части раздел разделы смотри стих стихи том тома кн. гл. стб. рис. л. лл. вып. стр. прим. соч. с. сс. с. сс. п. пп. ч. чч. разд. см. ст. т. тт. ¶¶ § §§ режиссер режиссеры редактор редакторы ответственный редактор ответственные редакторы иллюстратор иллюстраторы переводчик переводчики редактор и переводчик редакторы и переводчики реж. ред. отв. ред. ил. пер. ред. и пер. режиссировано под редакцией под ответственной редакцией иллюстрировано интервью проведено к переведено под редакцией и переведено реж. под ред. под отв. ред. ил. пер. под ред. и пер. январь февраль март апрель май июнь июль август сентябрь октябрь ноябрь декабрь янв. фев. мар. апр. май июн. июл. авг. сен. окт. ноя. дек. весна лето осень зима pandoc-citeproc-0.10.5.1/locales/locales-sk-SK.xml0000644000000000000000000002431313063456126017721 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-03-09T22:23:31+00:00 cit a a ďalší anonym anon. v available at by circa cca. cit vydanie vydania vyd. et al. nadchádzajúci z ibid. v v tlači internet osobná komunikácia list no date n.d. online prezentované na reference references ref. refs. cit scale version po Kr. pred Kr. th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth kniha knihy kapitola kapitoly stĺpec stĺpce obrázok obrázky list listy číslo čísla riadok riadky poznámka poznámky opus opera strana strany strana strany odstavec odstavce časť časti sekcia sekcie sub verbo sub verbis verš verše ročník ročníky k. kap. stĺp. obr. l. č. l. n. op. s. s. s. s. par. č. sek. s.v. s.vv. v. v. roč. roč. § § director directors editor editori zostavovateľ zostavovatelia illustrator illustrators prekladateľ prekladatelia zostavovateľ & prekladateľ zostavovatelia & prekladatelia dir. dirs. ed. ed. zost. zost. ill. ills. prel. prel. ed. & tran. eds. & trans. by directed by zostavil zostavil illustrated by rozhovor urobil adresát by preložil zostavil & preložil dir. ed. ed. illus. prel. zost. & prel. január február marec apríl máj jún júl august september október november december jan. feb. mar. apr. máj. jún. júl. aug. sep. okt. nov. dec. Jar Leto Jeseň Zima pandoc-citeproc-0.10.5.1/locales/locales-sl-SI.xml0000644000000000000000000002372513063456126017726 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-11-06T09:41:02+00:00 dostopano in in drugi anonimni anon. pri dostopno circa ca. citirano izdaja izdaje izd. idr. pred izidom od isto v v tisku internet intervju pismo brez datuma b. d. na spletu predstavljeno na referenca reference ref. ref. pridobljeno merilo različica n. št. pr. n. št. . prva druga tretja četrta peta šesta sedma osma deveta deseta knjiga knjige poglavje poglavja stolpec stolpci slika slike folio folii številka številke vrstica vrstice opomba opombe opus opusi stran strani stran strani odstavek odstavki del deli odsek odseki sub verbo sub verbis verz verzi letnik letniki knj. pogl. sto. sl. fol. št. vrst. op. opus str. str. str. str. odst. del odsek s.v. s.v. v. v. let. let. ¶¶ § §§ režiser režiser urednik uredniki glavni urednik glavni uredniki ilustrator ilustratorji prevajalec prevajalci urednik & prevajalec uredniki & prevajalci rež. rež. ur. ur. gl. ur. gl. ur. ilus. ilus. prev. prev. ur. & prev. ur. & prev. režiral uredil uredil ilustriral intervjuval za prevedel uredil & prevedel rež. ured. ured. ilus. prev. ured. & prev. by januar februar marec april maj junij julij avgust september oktober november december jan. feb. mar. apr. maj jun. jul. avg. sep. okt. nov. dec. pomlad poletje jesen zima pandoc-citeproc-0.10.5.1/locales/locales-sr-RS.xml0000644000000000000000000002552513063456126017745 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 приступљено и и остали анонимна анон. на available at by circa c. цитирано издање издања изд. и остали долазећи од ibid. у у штампи Интернет интервју писмо no date без датума на Интернету представљено на reference references ref. refs. преузето scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth књига књиге поглавље поглавља колона колоне цртеж цртежи фолио фолији број бројеви линија линије белешка белешке опус опера страница странице страница странице параграф параграфи део делова одељак одељака sub verbo sub verbis строфа строфе том томова књига Пог. кол. црт. фолио изд. l. n. оп. стр. стр. стр. стр. пар. део од. s.v. s.vv. стр. стр. том томови ¶¶ § §§ director directors уредник урединици editor editors illustrator illustrators преводилац преводиоци editor & translator editors & translators dir. dirs. ур. ур. ed. eds. ill. ills. прев. прев. ed. & tran. eds. & trans. by directed by уредио edited by illustrated by интервјуисао прима by превео edited & translated by dir. ур. ed. illus. прев. ed. & trans. by Јануар Фебруар Март Април Мај Јуни Јули Август Септембар Октобар Новембар Децембар Јан. Феб. Март Апр. Мај Јуни Јули Авг. Сеп. Окт. Нов. Дец. Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-sv-SE.xml0000755000000000000000000002430613063456126017733 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 åtkomstdatum och och andra anonym anon. vid tillgänglig vid av cirka ca citerad upplaga upplagor uppl. m.fl. kommande från ibid. i i tryck internet intervju brev utan årtal u.å. online presenterad vid referens referenser ref. ref. hämtad scale version e.Kr. f.Kr. :e :a :a :e :e första andra tredje fjärde femte sjätte sjunde åttonde nionde tionde bok böcker kapitel kapitel kolumn kolumner figur figurer folio folios nummer nummer rad rader not noter opus opera sida sidor sida sidor stycke stycken del delar avsnitt avsnitt sub verbo sub verbis vers verser volym volymer bok kap. kol. fig. f. nr l. n. op. s. s. s. s. st. del avs. s.v. s.vv. vers verser vol. vol. ¶¶ § §§ director directors redaktör redaktörer editor editors illustratör illustratörer översättare översättare redaktör & översättare redaktörer & översättare dir. dirs. red. red. ed. eds. ill. ill. övers. övers. red. & övers. red. & övers. av directed by redigerad av edited by illustrerad av intervjuad av till by översatt av redigerad & översatt av dir. red. ed. illus. övers. red. & övers. av januari februari mars april maj juni juli augusti september oktober november december jan. feb. mar. apr. maj juni juli aug. sep. okt. nov. dec. vår sommar höst vinter pandoc-citeproc-0.10.5.1/locales/locales-th-TH.xml0000644000000000000000000003004213063456126017711 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 สืบค้น และ และคณะ นิรนาม นิรนาม ที่ available at โดย โดยประมาณ ประมาณ อ้างถึง พิมพ์ครั้งที่ พิมพ์ครั้งที่ พิมพ์ครั้งที่ และคณะ เต็มใจให้ข้อมูล จาก ในที่เดียวกัน ใน กำลังรอตีพิมพ์ อินเทอร์เน็ต การสัมภาษณ์ จดหมาย ไม่ปรากฏปีที่พิมพ์ ม.ป.ป. ออนไลน์ นำเสนอที่ เอกสารอ้างอิง เอกสารอ้างอิง อ้างอิง อ้างอิง สืบค้น scale version ค.ศ. พ.ศ. หนึ่ง สอง สาม สี่ ห้า หก เจ็ด แปด เก้า สิบ หนังสือ หนังสือ บทที่ บทที่ สดมภ์ สดมภ์ รูปภาพ รูปภาพ หน้า หน้า ฉบับที่ ฉบับที่ บรรทัดที่ บรรทัดที่ บันทึก บันทึก บทประพันธ์ บทประพันธ์ หน้า หน้า หน้า หน้า ย่อหน้า ย่อหน้า ส่วนย่อย ส่วนย่อย หมวด หมวด ใต้คำ ใต้คำ ร้อยกรอง ร้อยกรอง ปีที่ ปีที่ หนังสือ บทที่ สดมภ์ รูปภาพ หน้า ฉบับที่ l. n. บทประพันธ์ น. น. น. น. ย่อหน้า ส่วนย่อย หมวด ใต้คำ ใต้คำ ร้อยกรอง ร้อยกรอง ปี ปี ¶¶ § §§ director directors บรรณาธิการ บรรณาธิการ ผู้อำนวยการบทบรรณาธิการ ผู้อำนวยการบทบรรณาธิการ illustrator illustrators ผู้แปล ผู้แปล บรรณาธิการและผู้แปล บรรณาธิการและผู้แปล dir. dirs. บ.ก. บ.ก. ผอ.บทบรรณาธิการ ผอ.บทบรรณาธิการ ill. ills. ผู้แปล ผู้แปล บ.ก. บ.ก. โดย directed by เรียบเรียงโดย เรียบเรียงโดย illustrated by สัมภาษณ์โดย ถึง by แปลโดย แปลและเรียบเรียงโดย dir. โดย โดย illus. แปล แปลและเรียบเรียงโดย มกราคม กุมภาพันธ์ มีนาคม เมษายน พฤษภาคม มิถุนายน กรกฎาคม สิงหาคม กันยายน ตุลาคาม พฤศจิกายน ธันวาคม ม.ค. ก.พ. มี.ค. เม.ย. พ.ค. มิ.ย. ก.ค. ส.ค. ก.ย. ต.ค. พ.ย. ธ.ค. ฤดูใบไม้ผลิ ฤดูร้อน ฤดูใบไม้ร่วง ฤดูหนาว pandoc-citeproc-0.10.5.1/locales/locales-tr-TR.xml0000644000000000000000000002405513063456126017744 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 erişim ve ve diğerleri anonim anonim de available at by circa c. kaynak baskı baskı baskı vd. gelecek adresinden erişildi a.g.e. içinde basımda internet kişisel iletişim mektup tarih yok y.y. çevrimiçi sunulan kaynak kaynaklar kay. kay. tarihinde scale versiyon M.S. M.Ö. . birinci ikinci üçüncü dördüncü beşinci altıncı yedinci sekizinci dokuzuncu onuncu kitap kitaplar bölüm bölümler sütun sütunlar şekil şekiller folyo folyo sayı sayılar satır satırlar not notlar opus opera sayfa sayfalar sayfa sayfalar paragraf paragraflar kısım kısımlar bölüm bölümler sub verbo sub verbis dize dizeler cilt ciltler kit. böl. süt. şek. f. sayı satır n. op. s. ss. s. ss. par. kıs. böl. s.v. s.vv. v. vv. c. c. ¶¶ § §§ direktör direktörler editör editörler editör editörler illüstrasyon illüstrasyon çeviren çevirenler editör & çeviren editörler & çevirenler dir. dir. ed. ed. ed. ed. ill. ill. çev. çev. ed. & çev. ed. & çev. direktör editör düzenleyen illustrated by Röportaj yapan to by çeviren düzenleyen & çeviren by dir. ed. ed. illüs. çev. ed. & çev. Ocak Şubat Mart Nisan Mayıs Haziran Temmuz Ağustos Eylül Ekim Kasım Aralık Oca. Şub. Mar. Nis. May. Haz. Tem. Ağu. Eyl. Eki. Kas. Ara. Bahar Yaz Sonbahar Kış pandoc-citeproc-0.10.5.1/locales/locales-uk-UA.xml0000644000000000000000000002450413063456126017715 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 accessed і та інші анонімний анон. на available at by circa c. cited edition editions ed et al. forthcoming із ibid. в у пресі інтернет інтервю лист no date n.d. online presented at the reference references ref. refs. retrieved scale version AD BC « » th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth book books chapter chapters column columns figure figures folio folios number numbers line lines note notes opus opera page pages page pages paragraph paragraph part parts section sections sub verbo sub verbis verse verses volume volumes bk chap col fig f no l. n. op p pp p pp para pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors editor editors editor editors illustrator illustrators translator translators editor & translator editors & translators dir. dirs. ed eds ed. eds. ill. ills. tran trans ed. & tran. eds. & trans. by directed by edited by edited by illustrated by interview by to by translated by edited & translated by dir. ed ed. illus. trans ed. & trans. by Січень Лютий Березень Квітень Травень Червень Липень Серпень Вересень Жовтень Листопад Грудень Січ Лют Бер Квіт Трав Чер Лип Сер Вер Жов Лис Груд Spring Summer Autumn Winter pandoc-citeproc-0.10.5.1/locales/locales-vi-VN.xml0000755000000000000000000002477613063456126017750 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 truy cập and others vô danh v.d tại available at bởi circa c. cited ấn bản ấn bản a.b và c.s. sắp tới từ n.t. trong in press internet interview letter không ngày không ngày online được trình bày tại reference references ref. refs. truy vấn scale version AD BC th st nd rd th th th thứ nhất thứ hai thứ ba thứ tư thứ năm thứ sáu thứ bảy thứ tám thứ chính thứ mười sách sách chương chương column columns figure figures folio folios số số dòng dòng ghi chú ghi chú opus opera trang trang trang trang đoạn văn đoạn văn phần phần section sections sub verbo sub verbis câu câu tập tập sách ch col fig f số p.h d. gc. op tr tr tr tr para ph sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors biên tập viên biên tập viên biên tập viên biên tập viên họa sĩ họa sĩ biên dịch viên biên dịch viên biên tập viên & biên dịch viên biên tập viên & biên dịch viên dir. dirs. b.t.v b.t.v b.t.v b.t.v h.s h.s b.d.v b.d.v b.t.v & b.d.v b.t.v & b.d.v bởi directed by biên tập bởi biên tập bởi illustrated by interview by to bởi biên dịch bởi biên tập & biên dịch bởi dir. b.t b.t h.s b.d b.t & b.d bởi Tháng Giêng Tháng Hai Tháng Ba Tháng Tư Tháng Năm Tháng Sáu Tháng Bảy Tháng Tám Tháng Chín Tháng Mười Tháng Mười-Một Tháng Chạp tháng 1 tháng 2 tháng 3 tháng 4 tháng 5 tháng 6 tháng 7 tháng 8 tháng 9 tháng 10 tháng 11 tháng 12 Mùa Xuân Mùa Hè Mùa Thu Mùa Đông pandoc-citeproc-0.10.5.1/locales/locales-zh-CN.xml0000644000000000000000000001730613063456126017714 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-05-15T23:31:02+00:00 见於 及其他 作者不详 无名氏 载於 介于 见引於 版本 即将出版 同上 收入 送印中 网际网络 访谈 信函 日期不详 不详 在线 发表於 参考 取读于 比例 公元 公元前 图表 注脚 作品 总页数 段落 部分 另见 op. 另见 ¶¶ § §§ 导演 编辑 主编 绘图 翻译 编译 导演 主编 编译 指导 编辑 主编 绘图 采访 受函 校订 翻译 编译 主编 编译 一月 二月 三月 四月 五月 六月 七月 八月 九月 十月 十一月 十二月 1月 2月 3月 4月 5月 6月 7月 8月 9月 10月 11月 12月 pandoc-citeproc-0.10.5.1/locales/locales-zh-TW.xml0000644000000000000000000002026713063456126017746 0ustar0000000000000000 This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2014-05-15T23:31:02+00:00 引見於 及其他 作者不詳 無名氏 載於 介於 見引於 版本 即將出版 同上 收入 印行中 互聯網 訪談 信函 日期不詳 不詳 線上 發表於 參考 讀取於 比例 西元 西元前 圖表 註腳 作品 總頁數 段落 部分 另見 op. 另見 ¶¶ § §§ 作者 導演 編輯 主編 繪圖師 採訪員 收信人 翻譯員 編譯員 評論人 作者 導演 編輯 主編 繪圖師 採訪員 收信人 翻譯員 編譯員 評論人 指導 編輯 點校 主編 繪圖 採訪 受函 點評 翻譯 編譯 一月 二月 三月 四月 五月 六月 七月 八月 九月 十月 十一月 十二月 1月 2月 3月 4月 5月 6月 7月 8月 9月 10月 11月 12月 pandoc-citeproc-0.10.5.1/README.md0000644000000000000000000000263012743760365014471 0ustar0000000000000000pandoc-citeproc =============== This package provides a library and executable to facilitate the use of citeproc with pandoc 1.12 and greater. (Earlier versions of pandoc have integrated citeproc support.) `pandoc-citeproc` ----------------- The `pandoc-citeproc` executable can be used as a filter with pandoc to resolve and format citations using a bibliography file and a CSL stylesheet. It can also be used (with `--bib2yaml` or `--bib2json` options) to convert a bibliography to a YAML format that can be put directly into a pandoc markdown document or to CSL JSON. Bibliographies can be in any of several formats, but bibtex and biblatex are the best supported. For usage and further details, see the [pandoc-citeproc man page](https://github.com/jgm/pandoc-citeproc/blob/master/man/pandoc-citeproc.1.md). The current version of the package includes code from citeproc-hs, which has not been updated for some time. When citeproc-hs is brought up to date, this code can be removed and this package will depend on citeproc-hs. `Text.CSL.Pandoc` ----------------- Those who use pandoc as a library (e.g. in a web application) will need to use this module to process citations. The module exports two functions, `processCites`, which is pure and accepts a style and a list of references as arguments, and `processCites'`, which lives in the IO monad and derives the style and references from the document's metadata. pandoc-citeproc-0.10.5.1/LICENSE0000644000000000000000000000300013063457044014200 0ustar0000000000000000Copyright (c) 2008-2013, Andrea Rossato Copyright (c) 2013-2017, John MacFarlane All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. Neither the name of the {organization} nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. pandoc-citeproc-0.10.5.1/man/man1/pandoc-citeproc.10000644000000000000000000002721113114777545017760 0ustar0000000000000000.\"t .\" Automatically generated by Pandoc 2.0 .\" .TH "pandoc\-citeproc" "1" "2017-06-04" "pandoc-citeproc 0.10.5" "" .hy .SH NAME .PP pandoc\-citeproc \- filter to resolve citations in a pandoc document. .SH SYNOPSIS .PP pandoc\-citeproc options (#options) [file..] .SH DESCRIPTION .PP The \f[C]pandoc\-citeproc\f[] executable has two modes, filter mode and convert mode. .SS Filter mode .PP Run without options, it acts as a filter that takes a JSON\-encoded Pandoc document, formats citations and adds a bibliography, and returns a JSON\-encoded pandoc document. Citations will be resolved, and, assuming there are bibliography entries, a bibliography will be inserted into a Div element with id \f[C]refs\f[]. If no such Div exists, one will be created and appended to the end of the document (unless the \f[C]suppress\-bibliography\f[] metadata field is set to a true value). If you wish the bibliography to have a section header, put the section header at the end of your document. (See the \f[C]pandoc_markdown\f[] (5) man page under \[lq]Citations\[rq] for details on how to encode citations in pandoc's markdown.) .PP To process citations with pandoc, call pandoc\-citeproc as a filter: .IP .nf \f[C] pandoc\ \-\-filter\ pandoc\-citeproc\ input.md\ \-s\ \-o\ output.html \f[] .fi .PP pandoc\-citeproc will look for the following metadata fields in the input: .TP .B \f[C]bibliography\f[] A path, or YAML list of paths, of bibliography files to use. These may be in any of the formats supported by bibutils. .RS .PP .TS tab(@); l l. T{ Format T}@T{ File extension T} _ T{ BibLaTeX T}@T{ \&.bib T} T{ BibTeX T}@T{ \&.bibtex T} T{ Copac T}@T{ \&.copac T} T{ CSL JSON T}@T{ \&.json T} T{ CSL YAML T}@T{ \&.yaml T} T{ EndNote T}@T{ \&.enl T} T{ EndNote XML T}@T{ \&.xml T} T{ ISI T}@T{ \&.wos T} T{ MEDLINE T}@T{ \&.medline T} T{ MODS T}@T{ \&.mods T} T{ RIS T}@T{ \&.ris T} .TE .PP Note that \f[C]\&.bib\f[] can generally be used with both BibTeX and BibLaTeX files, but you can use \f[C]\&.bibtex\f[] to force BibTeX. .RE .TP .B \f[C]references\f[] A YAML list of references. Each reference is a YAML object. The format is essentially CSL JSON format. Here is an example: .RS .IP .nf \f[C] \-\ id:\ doe2006 \ \ author: \ \ \ \ family:\ Doe \ \ \ \ given:\ [John,\ F.] \ \ title:\ Article \ \ page:\ 33\-34 \ \ issued: \ \ \ \ year:\ 2006 \ \ type:\ article\-journal \ \ volume:\ 6 \ \ container\-title:\ Journal\ of\ Generic\ Studies \f[] .fi .PP The contents of fields will be interpreted as markdown when appropriate: so, for example, emphasis and strong emphasis can be used in title fields. Simple tex math will also be parsed and rendered appropriately. .RE .TP .B \f[C]csl\f[] or \f[C]citation\-style\f[] Path or URL of a CSL style file. If the file is not found relative to the working directory, pandoc\-citeproc will look in the \f[C]$HOME/.csl\f[] directory (or \f[C]C:\\Users\\USERNAME\\AppData\\Roaming\\csl\f[] in Windows 7). If this is left off, pandoc\-citeproc will look for \f[C]$HOME/.pandoc/default.csl\f[], and if this is not present, it will use \f[C]chicago\-author\-date.csl\f[], looking first in \f[C]$HOME/.csl\f[] and then in its own data files. .RS .RE .TP .B \f[C]link\-citations\f[] If this has a true value, citations in author\-date and numerical styles will be hyperlinked to their corresponding bibliography entries. The default is not to add hyperlinks. .RS .RE .TP .B \f[C]citation\-abbreviations\f[] Path to a CSL abbreviations JSON file. If the file is not found relative to the working directory, pandoc\-citeproc will look in the \f[C]$HOME/.csl\f[] directory (or \f[C]C:\\Users\\USERNAME\\AppData\\Roaming\\csl\f[] in Windows 7). The format is described here (http://citationstylist.org/2011/10/19/abbreviations-for-zotero-test-release). Abbreviations are only output if, in the \f[C]\&.csl\f[] file, \f[C]form="short"\f[] is set on the element that renders the variable. .RS .PP Here is a short example: .IP .nf \f[C] {\ "default":\ { \ \ \ \ "container\-title":\ { \ \ \ \ \ \ \ \ \ \ \ \ "Lloyd\[aq]s\ Law\ Reports":\ "Lloyd\[aq]s\ Rep", \ \ \ \ \ \ \ \ \ \ \ \ "Estates\ Gazette":\ "EG", \ \ \ \ \ \ \ \ \ \ \ \ "Scots\ Law\ Times":\ "SLT" \ \ \ \ } \ \ } } \f[] .fi .RE .TP .B \f[C]lang\f[] Locale to use in formatting citations. If this is not set, the locale is taken from the \f[C]default\-locale\f[] attribute of the CSL file. \f[C]en\-US\f[] is used if a locale is not specified in either the metadata or the CSL file. (For backwards compatibility, the field \f[C]locale\f[] can be used instead of \f[C]lang\f[], but this \f[C]lang\f[] should be used going forward.) .RS .RE .TP .B \f[C]suppress\-bibliography\f[] If this has a true value, the bibliography will be left off. Otherwise a bibliography will be inserted into each Div element with id \f[C]refs\f[]. If there is no such Div, one will be created at the end of the document. .RS .RE .TP .B \f[C]reference\-section\-title\f[] If this has a value, a section header with this title will be added before the bibliography. If \f[C]reference\-section\-title\f[] is not specified and the document ends with a section header, this final header will be treated as the bibliography header. .RS .RE .TP .B \f[C]notes\-after\-punctuation\f[] If true (the default), pandoc will put footnote citations after following punctuation. For example, if the source contains \f[C]blah\ blah\ [\@jones99].\f[], the result will look like \f[C]blah\ blah.[^1]\f[], with the note moved after the period and the space collapsed. If false, the space will still be collapsed, but the footnote will not be moved after the punctuation. .RS .RE .PP The metadata must contain either \f[C]references\f[] or \f[C]bibliography\f[] or both as a source of references. \f[C]csl\f[] and \f[C]citation\-abbreviations\f[] are optional. If \f[C]csl\f[] is not provided, a default stylesheet will be used (either \f[C]~/.pandoc/default.csl\f[] or a version of \f[C]chicago\-author\-date.csl\f[]). .SS Convert mode .PP If the option \f[C]\-\-bib2yaml\f[] or \f[C]\-\-bib2json\f[] is used, \f[C]pandoc\-citeproc\f[] will not process citations; instead, it will treat its input (from stdin or files) as a bibliography and convert it either to a pandoc YAML metadata section, suitable for inclusion in a pandoc document (\f[C]\-\-bib2yaml\f[]), or as a CSL JSON bibliography, suitable for import to zotero (\f[C]\-\-bib2json\f[]). .PP The \f[C]\-\-format\f[] option can be used to specify the bibliography format, though when files are used, \f[C]pandoc\-citeproc\f[] can generally guess this from the extension. .PP This mode supersedes the old \f[C]biblio2yaml\f[] program. .SS Raw content (pandoc\-citeproc only) .PP To include raw content in a prefix, suffix, delimiter, or term, surround it with these tags indicating the format: .IP .nf \f[C] {{jats}}<ref>{{/jats}} \f[] .fi .PP Without the tags, the string will be interpreted as a string and escaped in the output, rather than being passed through raw. .PP This feature allows stylesheets to be customized to give different output for different output formats. However, stylesheets customized in this way will not be useable by other CSL implementations. .SH OPTIONS .TP .B \f[C]\-y,\ \-\-bib2yaml\f[] Convert bibliography to YAML suitable for inclusion in pandoc metadata. .RS .RE .TP .B \f[C]\-j,\ \-\-bib2json\f[] Convert bibliography to CSL JSON suitable for import into Zotero. .RS .RE .TP .B \f[C]\-f\f[] \f[I]FORMAT\f[], \f[C]\-\-format=\f[]\f[I]FORMAT\f[] Specify format of bibliography to be converted. Legal values are \f[C]biblatex\f[], \f[C]bibtex\f[], \f[C]ris\f[], \f[C]endnote\f[], \f[C]endnotexml\f[], \f[C]isi\f[], \f[C]medline\f[], \f[C]copac\f[], \f[C]mods\f[], and \f[C]json\f[]. .RS .RE .TP .B \f[C]\-h,\ \-\-help\f[] Print usage information. .RS .RE .TP .B \f[C]\-\-man\f[] Print the man page in groff man format. To get a plain text version, \f[C]pandoc\-citeproc\ \-\-man\ |\ groff\ \-mman\ \-Tutf8\f[]. To \f[C]pandoc\-citeproc\ \-\-man\ |\ groff\ \-mman\ \-Thtml\f[]. .RS .RE .TP .B \f[C]\-\-license\f[] Print the license. .RS .RE .TP .B \f[C]\-V,\ \-\-version\f[] Print version. .RS .RE .SH NOTES .SS General .PP If you use a biblatex database, closely follow the specifications in the \[lq]Database Guide\[rq] section of the biblatex manual (currently 2.8a). .PP If you use a CSL\-YAML or CSL\-JSON database, or a CSL\-YAML metadata section in your markdown document, follow the \[lq]Citation Style Language 1.0.1 Language Specification\[rq] (). Particularly relevant are (which neither comments on usage nor specifies required and optional fields) and (which does contain comments). .SS Titles: Title vs.\ Sentence Case .PP If you are using a bibtex or biblatex bibliography, then observe the following rules: .IP \[bu] 2 English titles should be in title case. Non\-English titles should be in sentence case, and the \f[C]langid\f[] field in biblatex should be set to the relevant language. (The following values are treated as English: \f[C]american\f[], \f[C]british\f[], \f[C]canadian\f[], \f[C]english\f[], \f[C]australian\f[], \f[C]newzealand\f[], \f[C]USenglish\f[], or \f[C]UKenglish\f[].) .IP \[bu] 2 As is standard with bibtex/biblatex, proper names should be protected with curly braces so that they won't be lowercased in styles that call for sentence case. For example: .RS 2 .IP .nf \f[C] title\ =\ {My\ Dinner\ with\ {Andre}} \f[] .fi .RE .IP \[bu] 2 In addition, words that should remain lowercase (or camelCase) should be protected: .RS 2 .IP .nf \f[C] title\ =\ {Spin\ Wave\ Dispersion\ on\ the\ {nm}\ Scale} \f[] .fi .PP Though this is not necessary in bibtex/biblatex, it is necessary with citeproc, which stores titles internally in sentence case, and converts to title case in styles that require it. Here we protect \[lq]nm\[rq] so that it doesn't get converted to \[lq]Nm\[rq] at this stage. .RE .PP If you are using a CSL bibliography (either JSON or YAML), then observe the following rules: .IP \[bu] 2 All titles should be in sentence case. .IP \[bu] 2 Use the \f[C]language\f[] field for non\-English titles to prevent their conversion to title case in styles that call for this. (Conversion happens only if \f[C]language\f[] begins with \f[C]en\f[] or is left empty.) .IP \[bu] 2 Protect words that should not be converted to title case using this syntax: .RS 2 .IP .nf \f[C] Spin\ wave\ dispersion\ on\ the\ nm\ scale \f[] .fi .RE .SS Conference Papers, Published vs.\ Unpublished .PP For a formally published conference paper, use the biblatex entry type \f[C]inproceedings\f[] (which will be mapped to CSL \f[C]paper\-conference\f[]). .PP For an unpublished manuscript, use the biblatex entry type \f[C]unpublished\f[] without an \f[C]eventtitle\f[] field (this entry type will be mapped to CSL \f[C]manuscript\f[]). .PP For a talk, an unpublished conference paper, or a poster presentation, use the biblatex entry type \f[C]unpublished\f[] with an \f[C]eventtitle\f[] field (this entry type will be mapped to CSL \f[C]speech\f[]). Use the biblatex \f[C]type\f[] field to indicate the type, e.g. \[lq]Paper\[rq], or \[lq]Poster\[rq]. \f[C]venue\f[] and \f[C]eventdate\f[] may be useful too, though \f[C]eventdate\f[] will not be rendered by most CSL styles. Note that \f[C]venue\f[] is for the event's venue, unlike \f[C]location\f[] which describes the publisher's location; do not use the latter for an unpublished conference paper. .SH AUTHORS .PP Andrea Rossato and John MacFarlane. .SH SEE ALSO .PP \f[C]pandoc\f[] (1), \f[C]pandoc_markdown\f[] (5). .PP The pandoc\-citeproc source code and all documentation may be downloaded from . pandoc-citeproc-0.10.5.1/changelog0000644000000000000000000010072613115051616015053 0ustar0000000000000000pandoc-citeproc (0.10.5.1) * Minor tweaks for clean CI builds. * Require recent yaml for uniform test output. pandoc-citeproc (0.10.5) * Use file-embed instead of hsb2hs for embed_data_files flag (#285). * Allow `&` in bibtex keys (#289). They are discouraged because of problems in tables, but technically they are allowed. * Allow + in bibtex field name (#290). BibLaTeX now allows things like `author+an` for annotations. See "Data Annotations" in the bibtex manual. Note that we don't actually parse the annotations, we just don't crash on bibtex files that include them. * caseTransform: fix corner case where last word has internal periods (#288). E.g. in `www.example.com`, previously `com` was capitalized as the last word. * If there's a list of csl, locale, or abbrev files, use the last one. * Don't catch exceptions in reading CSL file. Previously some exceptions were silently caught, leading to unexpected use of the default. * Util.findFile: return right away if absolute path. * Added mechanism for inserting raw content into delimiters, prefixes, suffixes. So, for example, in your CSL file you can have prefix="{{html}}<i>{{/html}}" and this will turn into RawInline (Format "html") "" rather than, as before Str "", which would get escaped in the output. See jgm/pandoc#3536 for the motivation. * Text.CSL.Pandoc: Simplified code for looking up default CSL. * Fix titlecase bug involving em/en dashes (#284). * Export license from Text.CSL.Data.Embedded. * Added `--license` to CLI and `getLicense` to Text.CSL.Data (API change). * Updated chicago-author-date.csl and locales xml. * Add `getManPage` to Text.CSL.Data and `--man` option to CLI (API change). `pandoc-citeproc --man` now simply spits out the man page in groff format. For a plain text version, use `pandoc-citeproc --man | groff -mman -Tutf8`. For an HTML version, `pandoc-citeproc --man | groff -mman -Thtml`. * Updates to be able to compile and test with current pandoc HEAD. * Automatically link ISBN references to Worldcat (#279). This is similar to existing support for DOIs. Thanks to Eric Marsden. * Text.CSL.Input.Bibtex: export `Lang`, `langToLocale`, `getLangFromEnv` (#281, API change). * Adjusted treatment of `\hyphen` now that pandoc includes trailing space... in RawInline. See jgm/pandoc#1773 and commit f4a452f89174828fea77614a4b6a067fc4675ba5. * Support citation-label variable (#160, Lukas Atkinson). The `citation-label` was not rendered, even when this label was explicitly set in the bibliography. This is now fixed. Citation labels are modelled after citation numbers. In particular, citation labels can also be hyperlinked. API changes: In `Text.CSL,Reference`: The exported type `CLabel` describes a label name in the CSL variables. This allows us to distinguish labels from ordinary strings. This type is analogous to `CNum`. In `Text.CSL.Style`: In `Output` the `OCitLabel` case describes a label in the rendered output. This case is analogous to `OCitNum`. * Allow aeson 1.2. * Fixed overlapping instance problem in test-citeproc w/ recent aeson. pandoc-citeproc (0.10.4.1) * Raise version bounds for xml-conduit. * Use cpphs if embed_data_files on darwin. * Fixed Compat module so it compiles with pandoc 1.9.x and 2.0. * Allow colon to belong to locator numbers (#275). This at least allows 1:22-23 to be interpreted as a page number, though this won't really be useful until we modify the number collapsing code to be sensitive to the colon. pandoc-citeproc (0.10.4) * Fixed 'et al' in certain styles (#274). The `et al` phrase was not being appended in the bibliography in ieee.csl and some others. * Leave ALLCAPS words alone in titlecase transformation. See #273. There is some confusion about the citeproc rules here, but this follows citeproc-js behavior. * Improved title case rules to conform better to CSL spec (#273). We now correctly retain case on mixed-case words and don't decapitalize "small words" when they're the last word. * Use readerSmart in parsing yaml bibliographies (#272). * Bumped some dependency version bounds. * Improved .travis.yml. * Added Text.CSL.Compat.Pandoc module to work around version differences. This allows building with the typeclass branch of pandoc. pandoc-citeproc (0.10.3) * Update to work with pandoc 1.19 (including writerStandalone API change). * Updated test case to use bracketed_spans. Note: this means that tests will fail unless pandoc 1.19 is used. * Fixed pluralization with label for issue (#267). * Factored out `comb` in Text.CSL.Pandoc. * Make it clearer when errors concern CSL parsing (#219). Errors in CSL parsing now point to the CSL file specifically. We convert any error thrown in CSL parsing into an XMLException (from xml-conduit), so the file path will be shown. * Handle EDTF dates in bibtex bibliographies (#240). pandoc-citeproc (0.10.2.2) * Fix overlapping instances with aeson-1.0.2.1 (#263). pandoc-citeproc (0.10.2.1) * Allow pandoc 1.18.x. pandoc-citeproc (0.10.2) * Use linebreaks to simulate display="block" (#85, #261). pandoc-citeproc (0.10.1.4) * Use finer grained Pandoc import statements (Albert Krewinkel). A full import of the Pandoc library leads to name collisions with Pandoc v1.18, so only required functions and datatypes are imported. * Remove unused import. pandoc-citeproc (0.10.1.3) * Fixed compiler warnings. * Setup.hs - removed unnecessary imports. * Travis improvements. Run on stack lts-7, not earlier. Disable optimizations for faster build. Turn on warnings. * Bump pandoc-types to 1.17.0.3 in stack.yaml. pandoc-citeproc (0.10.1.2) * Implemented notes-after-punctuation metadata field (#256). If this is true (the default), citations rendered as footnotes are automatically moved after punctuation. If it is false, footnote citations remain before punctuation, but space is still collapsed before the notes. * Don't require http-client 0.5. This mirrors recent changes to pandoc, which allow 0.4.30.x. * Allow pandoc-types 1.17.*. * Allow xml-conduit 1.4.x (Felix Yan). pandoc-citeproc (0.10.1.1) * Clarify that abbreviations require `form="short"` (Nick Bart). * Allow aeson 1.0.*. * Input.Bibtex: better parsing for month. Don't convert to lowercase if it's not one of the official abbreviations and isn't protected. pandoc-citeproc (0.10.1) * pandoc-citeproc: allow .yaml and .json input files, even without the `bibutils` flag, for conversion to JSON and YAML, resp. * Pluralize locator term when comma-separated series of numbers given (#245). * Don't insert bibliography if there are no entries (#249). * Fixed note field with YAMl bibliographies (#224). Supplementary fields in `note` are parsed only in CSL JSON. * Support latest aeson-pretty (Felix Yan). pandoc-citeproc (0.10) * Allow colons in bibtex field names (John MacFarlane, #220). * Set LANG as well as LC_ALL before translating bibtex (John MacFarlane). This ensures that bibtex will use the locale specified in the document, even if the system locale is different. * Data: Raise CSLLocaleException if locale not found (John MacFarlane). Minor API change: Export CSLLocaleException. * Added DeriveDataTypeable pragma to Data (John MacFarlane). * Bibtex reader: case-insensitive parsing of month names (John MacFarlane). * Bibtex: Export readBibtexInputString', a pure version of readBibtexInputString (John MacFarlane). * Rename readBibtexInput* -> readBibtex* (John MacFarlane, API change). * unTitleCase now lowercases whole word (#234, John MacFarlane). So, for example, unprotected TeV becomes tev, instead of teV. This mimics bibtex's own behavior. * Added caseTransform parameter on readBibtex* functions (#231, John MacFarlane). When set to false, the bibtex reader doesn't do the 'untitlecase' transformation. This is used in Text.CSL.Input.Bibutils, when using bibtex as an intermediate format for conversion from mods, ris, or other formats. Otherwise we get the 'untitlecase' transform when it isn't wanted. * Allow numbers with decimal points to count as "numeric." (#208, John MacFarlane) Thus, we should have "Series 2.2", not "Series, 2.2" with Chicago author-date style. * Fixed capitalization for words following slash (#236, John MacFarlane). * Updated locales. * Fix build failure for --flags=-bibutils mode (Sergei Trofimovich). Reported-by Thomas Beutin https://bugs.gentoo.org/516640. * Add missing -DUSE_BIBUTILS to Cabal build (Vaclav Haisman). pandoc-citeproc (0.9.1.1) * Only changed version number (work around for hackage upload error). pandoc-citeproc (0.9.1) * Fixed YAML/CSL reference type for motion_picture, etc. (#214). Several CSL reference types (`motion_picture`, `legal_case`, ...) use an underscore instead of a hyphen, and these had been incorrectly rendered by pandoc when translating to YAML/CSL. * Fixed handling of dimension and other 'literal' variables (#213). This also affects call-number, scale, language. * Fixed test-citeproc. * Fixed travis builds to use stack. * Only use -rtsopts for executable. * Allow aeson 0.11. * Allow compilation with pandoc 1.17. * Updated locales and chicago-author-date.csl. pandoc-citeproc (0.9) * Allow spaces around CSL note fields. Closes #191. * Add homepage field to .cabal file (Jens Petersen). * Use pandoc 1.16. * Turn on smart quote parsing in reading bib(la)tex. We didn't need this previously, but now we do thanks to changes in pandoc. * Specialize `mkRefMap` to `Reference`, and return empty map for `emptyReference`. * Improved behavior with missing references (API change, #195, #165). Previously in some cases where a citation id wasn't found in the bibliography, a "reference with no printed form" warning was printed instead of "not found." This change fixes that. It also changes some types in ways that make more sense. `processCites` now produces `[[(Cite, Maybe Reference)]]` instead of `[[(Cite, Reference)]]`, and other types are adjusted accordingly. For example, `evalLayout` now has a `Maybe Reference` parameter rather than `Reference`. * Added `hackage-docs.sh` to upload haddocks when Hackage can't build them. * Improved handling of `nocite` (#197). Previously if you had something in `nocite`, then cited it again in the document, pandoc-citeproc would use `ibid`, thinking that the item had already been cited. * Fix for pandoc API change to `writerWrapOptions`. * Allow `SoftBreak` to count as space in some contexts (e.g. splitting). * Fixed path to `chicago-fullnote-bibliography.csl` in test. * Improved error message with illegal 'type' field in YAML bibliographies (#2611). pandoc-citeproc (0.8.1.3) * test-pandoc-citeproc: Better fix for Windows. Use UTF8 strings instead of bytestrings; this helps get line endings right in tests. pandoc-citeproc (0.8.1.2) * Use UTF8 versions of readFile in test program. pandoc-citeproc (0.8.1.1) * Use pandoc's UTF8 versions of getContents, putStrLn, etc. Otherwise we get locale-dependent encodings. pandoc-citeproc (0.8.1) * Improved performance in bibtex cross-reference resolution (#190). * Take 'form' for date-part elements from date if not specified (#116). Previously if the 'form' were unspecified in a date-part element, it would go to the default 'long', even if the date as a whole was 'numeric'. * Transform only uppercase ASCII letters in titlecase transform. This helps us pass one more citeproc test case. * Cleaned up locator parsing code. * Allow roman numeral locators (#173. * Fixed missing dash between months in date ranges (#175). * Fixed `strip-periods` (#185). * Parse supplementary fields in CSL JSON "note" fields (#94). * Support more biblatex markup in converting biblatex bibliographies: `mkbibemph`, `mkbibitalic`, `mkbibbold`, `mkbibparens`, `mkbibbrackets`, `autocap` (Nick Bart, #26). Treat reviews as articles. * Add biblatex keys for additional languages (Nick Bart). * Use HTTPS for DOI resolver (Andrew Dunning). * Add biblatex keys for additional languages (Nick Bart): ca-AD, da-DK, es-ES, fi-FI, it-IT, nl-NL, pl-PL, pt-PT, pt-BR, sv-SE pandoc-citeproc (0.8.0.1) * Allow aeson 0.10.x (Felix Yan). * Add custom Prelude: -Wall clean on ghc 7.10. pandoc-citeproc (0.8) * Use `lang` metadata field to specify locale. `locale` can still be used as before, for backwards compatibility, but `lang` is now preferred. * Put the references section header outside the Div, instead of inside as before.. This interacts better with pandoc's `--section-divs` feature (#176). * Use `refs`, not `references`, for the identifier of the bibliography Div. Unlike `references`, `refs` is not likely to conflict with an autogenerated header identifier (#176). NOTE: workflows designed to work with 0.7.4, with a `
` where the bibliography is to go, will need modification (`s/references/refs/`). * Changed local override for default CSL file (#161). Previously you could override the default CSL file by modifying `~/.csl/chicago-author-date.csl`. Now you do it by modifying `~/.csl/default.csl`. To minimize the effect of this change on existing workflows, we will use the version of `chicago-author-date.csl` in `~/.csl`, if there is one, if `~/.csl/default.csl` is not found. * Implemented fallbacks for CSL terms, as per CSL spec. E.g. `verb` is used if `verb-short` is not defined (#72). * Update CSL style, locales (Andrew Dunning). * Setup.hs: got hsb2hs registered as a build-tool. * Setup.hs: avoid depending on non-base modules (esp. process). This can cause problems with older versions of cabal. * Don't raise error if `HOME` isn't defined (#35). * Add more biblatex localization keys (Nick Bart). * Simplified and improved page range collapsing (#168). * Allow multiword locator labels like "sub verbo" (#168). * Remove `parse-names: true` in a Reference after parsing names (#169). * Don't superscript author-in-text numerical citations (#133). This change also removes `unsetAffixes` from `Text.CSL.Style`'s exported functions. This function was only used in one places and is very simple. (API change) * Fixed `embed_data_files` build on OS X (Chris Knox) * Remove brackets from author-in-text numerical citations (#133). * Removed `compressName` transform on JSON output (#169). This transformation prevented the JSON produced from using a fully broken-out specification of the author, instead pushing suffixes and prefixes into the names themselves. * Fixed regression introduced by #163 (#170). pandoc-citeproc (0.7.4) * Bibliography Div has id `references`, in addition to class. * Make sure a link with a year range encompasses the whole range. Previously you'd get [LINK 1996]--[LINK 2003], where both links went to the same citation. Now you get [LINK 1996-2003]. (#146) * Fix linking of DOIs (#163). Now only a part of a prefix that begins a url (`http...`) will be part of the linked text for a DOI. (This part will also be used for the URL, in place of the default `http://doi.org/`, if present.) Other parts of the prefix and suffix will remain outside the linked text. * Use "literal" instead of "other" in producing CSL YAML (#167). * Test suite: better technique to find right executable to test. We now find the test program and locate pandoc-citeproc relative to it. * Change default for parse-names to False. * Add `Paths_pandoc_citeproc` to other-modules. * Allow flexible insertion of bibliography. + If the document contains a Div element with id `references`, the bibliography will be inserted in it (after any other content in the Div). + Otherwise, a Div with id `references` will be created at the end of the document as before. * Fix parsing of particles with hyphens on family names (#130). * Handle `#+LINK_CITATIONS` metadata in org-mode. The values `true`, `yes`, and `on` are recognized as true values (case-insensitive) (#159). pandoc-citeproc (0.7.3.1) * Moved tests from data-files to extra-source-files. * List biblatex conversion tests in cabal extra-source-files. * Updated tests for changes in yaml library (which now puts quotes arounds strings that could be read as numbers, #158). pandoc-citeproc (0.7.3) * Add Walkable instances for Formatted (Sean Leather). * Allow empty end year in Zotero workaround, e.g. `2005_` (Nick Bart). * man/Makefile - removed unnecessary dependency. * Fixed test-citeproc.hs for change in `ProcOpts`. * Cleaned up Setup.hs. Now takes into account destdir in copying man page. * Don’t add space after particles ending with "-" (Nick Bart). * Names.hs: Add Unicode “Latin Extended Additional” to isByzantine (Nick Bart). * Allow vector 0.11. pandoc-citeproc (0.7.2) * Added `link-citations` metadata field (#141). If this has a true value, citations in author-date and numerical styles are linked to their corresponding bibliography entries. Otherwise not. (In previous versions of 0.7.x, this linking was the default. Now it must be enabled explicitly by setting this field.) * Fixed locale lookup with two-letter codes (#140). * Updated locales and chicago-author-date.csl. * Text.CSL.Data: Remove spurious reference to ar-AR. * Updated tests to escape literal `[` and `]` (to match new pandoc markdown writer's behavior). * Fixed `make update` to grab chicago-author-date.csl from correct URL. * Bumped upper bound to allow aeson 0.9.*. pandoc-citeproc (0.7.1.1) * Fixed regression in numerical citation collapsing (#131). pandoc-citeproc (0.7.1) * Improvements to numerical styles: + Space is now inserted after the reference number in the bibliography when `second-field-align` is `margin` or `flush`. + Author-in-text citations are now treated just like other citations in numerical styles. So, brackets are used, and the term "Reference" is not added: instead of `Reference 1 says...` we have `[1] says...`. This seems to accord better with e.g. IEEE practice. + Improved citation collapsing. Now both the new and the old versions of `ieee.csl` work properly. Previously brackets were dropped with the new version (#55). + Use new `ieee.csl` for testing. pandoc-citeproc (0.7.0.2) * Bump version bound for xml-conduit. pandoc-citeproc (0.7.0.1) * In YAML use pandoc markdown syntax for super, subscript (#128). Added test case for rich text formatting. * Change default for first-reference-note-number to 0 on reading (#128). pandoc-citeproc (0.7) * Improved YAML output: + Fields are now in a deterministic and rational order, id at top. + Blank lines between entries for readability. + Use human-friendlier year, month, etc. rather than date-part. + The test suite no longer normalizes YAML output before comparing, since we now control the order of fields. * Use `locale` in metadata in converting bibtex (#98). * Use `locale` in metadata for unicode collation, when compiled with the `unicode_collation` flag (#122). * Made pandoc-citeproc sensitive to metadata fields `reference-section-title` and `suppress-bibliography` (Jesse Rosenthal). The former specifies a title for a new reference section. The second suppresses the bibliography altogether. Existing documents should behave as before if these fields are not used. * Strip empty span elements from output (#126). * Allow conversion FROM yaml to other formats (#124). * Improved CSL JSON output. Use the rich markup syntax described at http://docs.citationstyles.org/en/1.0/release-notes.html#rich-text-markup-within-fields * Fixed extraction of language from LANG env variable in Bibtex (#98). * Fixed `ghc-prof-options` so we don't get warning with recent cabal. Added French, German localizations to Bibtex converter (#98). * Bibtex: Use type field to further specify mastersthesis or phdthesis (#98). * Ensure that "et al" has a space before it, if no delimiter defined (#93). * Allow "et al" to be formatted (#91). * Depend on `setenv` package for the `setEnv` function, which is found only in base 4.7+. * Fixed problem with droppped final punctuation in some footnotes (#82). * `Text.CSL.Util`: Removed unused `readable`. Renamed `toShow` to `uncamelize`. Use `ppShow` in `tr'`. * Use `doi.org` instead of `dx.doi.org` (#107). * Fixed treatment of `motion_picture` title (#118). * Include preface and suffix of DOI in linked text (#107). * Added `--regenerate` flag to `test-pandoc-citeproc`. * Added `hyperlink` field to `Formatting` (API change). * Made hyperlinked citations work with numerical and author-year styles. * Bibtex: improved short title logic. * Map biblatex title/maintitle to CSL volume-title/title (Nick Bart). * Fix CSL dependent style support (Tim Lin, #105). * Added support for PMCID and PMID fields in bibtex (jgm/pandoc#1923). * Map biblatex `inreference` to `EntryEncyclopedia` rather than `NoType` (#88). * Wrap bibliography entries in Div with id=ref-citationId * Updated `chicago-author-date.csl`. * Allow compilation against pandoc 1.14 (the next release). * Removed obsolete `small_base` cabal flag. * Added `debug` cabal flag which turns on tracing. pandoc-citeproc (0.6.0.1) * Added pandoc-types upper bound. * Removed `auto-all` from profiling options. * Fixed CSL dependent style support (#105, Tim Lin). * Updates to build with GHC 7.10.1 (Mark Wright). pandoc-citeproc (0.6) * The CSL parser has been replaced with a new, xml-conduit based module, which does not rely on C libraries and should be easier to repair and extend. The module has been checked against the old module with all CSL files in the citeproc repository. The only differences are with attribute values beginning or ending with a nonbreaking space (e.g. with French guillemets), and the new parser's behavior (preserving the spaces) is clearly correct. Parsing was measured as about twice as fast in a benchmark. * The `hexpat` cabal flag has been removed. * The old `Text.CSL.Pickle` and `Text.CSL.Pickle.*` modules have been removed. * Plural locator labels (e.g. 'pp.') are now used for page ranges containing en-dashes (#84). * `Elements` has been removed from `Element`. It was entirely unnecessary, used only once (and dispensibly) in `Text.CSL.Eval`. This change results in cleaner code. * Improved man page generation. * Updated `chicago-author-date.csl` default style. pandoc-citeproc (0.5) * Revised locator parsing: + parseLocator now looks for the "short" forms of terms in the style's locale(s). So, in English you'd use "p." or "ch."; in German, "S." or "Kap." + Note that the locator label must match what is in the locale file, including the period. Before this change, you could omit the period: "p 12" or "p. 12" would both give you a "page." Also, previously, the locators were case-insensitive; now they must be in the same case as in the locale. (English "p.", German "S.".) + "no." no longer gets parsed as a "note": closes #74. + Text.CSL.Reference no longer exports parseLocator. parseLocator is now used only locally, in Text.CSL.Pandoc. * Data.getLocale: Try 2-letter locale lookup if longer locale not found. This should fix an error that occured with less common locales (jgm/pandoc#1548). * Added parseNames field to Agent. Set parse-names=true when writing CSL JSON and collapsing suffix or particles into first or last names. * Properly handle agents with 'parse-names' set to 'true' (#77). Note that parse-names defaults to true if not set, as in Zotero. * Reference: added explicit exports. * Styles: Added explicit export list. * Eval: Fixed isNumericString to recognize en dash (#74). * Allow bibtex double quotes to be escaped inside {} (jgm/pandoc#1568). * Titlecase transform improvements (#76). * Added two csl files missing from tests/. * Performance improvements: Avoid unnecessary Output groupings. Eliminated some unnecessary generic traversals. (#71) * Makefile: Use cpphs. Text.CSL.Data seems to break on OSX 10.9 without it. * Added prof target to Makefile * Test suite: don't exit with success if there were errors! pandoc-citeproc (0.4.0.1) * Interpret date literals with underscores (e.g. "2004_2006") as ranges. This covers a common workaround for a deficiency in Zotero (#65). * Correctly handle "literal" in CSL date (#65). * Fixed erroneous capitalization of the first ibid. in a citation, even in the middle of a sentence (#68). Removed "ibid-c", "ibid-locator-c" classifications. * Pandoc: Capitalize first word of citation note, unless span=nocase. Previously we only capitalized citations. This captures ibid and the like. * Text.CSL.Util.toCapital: respect ``. * Turn small caps into SmallCaps element in reading CSL JSON (#67). Either the or the variant may be used. * Added "ca", "c", "et" to list of short words in titlecase transforms (#66). * Fixed some errors in the no-author test case. * test-pandoc-citeproc: Avoid running tests twice! * Check for en dash in checking for page ranges (#70). * Removed unused texmath build-depend. pandoc-citeproc (0.4) * Fixed #58 - previously not all substitute alternatives were tried. * Made first parameter of OName an Agent, not a String (API change). Also moved Agent from Reference to Style. * test-pandoc-citeproc: run tests on all matching files in the directory. This removes the need to recompile when new tests are added. * Style: Fixed appendWithPunct (mappend for Formatted). One definition was wrong, causing commas to be lost in certain places (#57). * Support \nocite{*}. If the `nocite` metadata filed contains a citation with identifier `*`, all entries in the bibliography are included in the references (#64). * Bump upper bound for aeson. * Removed span nodecor around 'ser.' (#60). * Print series as "3rd ser." (using locale's ordinal) (#60). * Added scaffolding for 'ordinalize' and infrastructure for accessing locale information to Bibtex. * Export new parseLocale from Text.CSL.Parser. * Move punctuation before fn in in-text citation before punctuation (#59). * Updated locales and chicago-author-date.csl. * Use collection-title for series, even for articles (#60). * Fixed locator parsing so capital roman numerals are legal numbers (#61). * Map bookinbook -> chapter (#62). * Better error message from parseString. * Remove space before superscript citation (pandoc #1327). * Fixed spurious "et al" problem (#27). * Match biblatex's method for separating von from last name, for biblatex. For bibtex, we match the documented bibtex algorithm as before (#50). Test case: Drummond de Andrade, Carlos. bibtex makes "Drummond de" a dropping particle. biblatex takes "Drummond de Andrade" to be the last name. * Leave off bibliography if `suppress-bibliography` has a true value in the document metadata (#40, with thanks to Jesse Rosenthal). * Try empty (null) 'csl' as if no 'csl' was specified. (The default chicago-author-date.csl is then used.) * Fixed #51: empty braces with date range. * Set pageFirst automatically from page range (#31). * Bibtex input: set page-first automatically. * Fixed capitalization of first word in sentence (#25). E.g. "foo bar baz: bazbaz foo" should turn into "Foo Bar Baz: Bazbaz Foo" in titlecase, but was turning into "foo Bar Baz: bazbaz Foo." * pandoc-citeproc: Allow conversion of mods bibliographies (#28). * readCSLFile now supports dependent styles (#30). * Removed network flag. We now use pandoc's fetchItem. * Changed type of findFile, so it returns a Maybe. * Documented fact that you can specify a URL under 'csl:'. * Added locale parameter to readCSLFile (API change). readCSLFile also now looks in ~/.csl for the file, if it isn't found locally. * Moved findFile to Util. * Bibtex/biblatex: map "unpublished" to "speech" if the record contains "eventtitle", "eventdate", or "venue". Otherwise map it to "manuscript" as before (#44). * Look for chicago-author-date.csl in ~/.csl if no csl specified. If not found there, use the chicago-author-date.csl that comes with the distribution (#48). * Improved case transform behavior with punctuation. Previously capitalization might change after a word-internal period or apostrophe. Now internal punctuation only signals a word boundary if it is a dash or single quote character. pandoc-citeproc (0.3.1) * Marked final heading (if present) as "unnumbered" (pandoc #1277). * Treat empty 'references' (empty string) as empty list. * Fixed titlecase transformation of words containing '. * Fixed punctuation in notes. * Improved test suite. * FromJSON for Formatted: handle block lists as well as inline. * Require yaml >= 0.8.8.2. * Fixed spacing problem with citations in notes in footnote styles (pandoc #1036). * Updated chicago-author-date.csl and locales (#34). * Move punctuation inside quotes, depending on style. This is activated by the `punctuation-in-quote` locale option, which has a default per locale but can be overridden in the style. This gives more flexibility. (Thanks to Jesse Rosenthal.) * Moved `isPunctuationInQuote` to `Text.CSL.Style` and rewrote. Previously it was in `Text.CSL.Output.Pandoc`. It doesn't need to use generics and no longer does. * Fixed recognition of "byzantine" names. Names with curly apostrophes were being counted as non-byzantine, and printed given-first with no space (#39). * Fixed representation of reference types to conform to CSL (#24): `motion_picture`, `legal_case`, `musical_score`, `personal_communication`. pandoc-citeproc (0.3.0.1) * Require ghc-prim if ghc < 7.6 (needed for generics). pandoc-citeproc (0.3) * Removed biblio2yaml. Instead, use pandoc-citeproc with the --bib2yaml or --bib2json option. (#20) * pandoc-citeproc --bib2json will convert bibtex/biblatex to CSL compatible JSON bibliographies. * Updated locale files for correct textual date ranges in e.g. the da-DK locale. Use form="ordinal" instead of a period as suffix. (#16, #18) * Support new langid and langidopts biblatex fields. (#11) * Made test-pandoc-citeproc work in all locales. (#19) It now tests the executable rather than the library function. * Fixed disambiguation with multivolume works (#14). * Improved titlecase/unTitlecase to be sensitive to colons, question marks, and exclamation marks, after which the next character sohuld be capitalized even in sentence case (pandoc #1102). * The "locale" filed in metadata will now override a style's default locale. This can also be set by the command line: --metadata locale=fr-FR (#10). * Use CSL-compatible date-parts for dates in YAML/JSON bibliographies. * Made FromJSON for Reference more forgiving. Suitable strings are coerced into integer values. (pandoc #1094) * Fixed extra punctuation at end of footnote (#13). * Reference: Always use array in JSON for dates, agents. * Bibtex parser: Don't fail on entry with no title. * Bibliography output: 'given' is now a string, not an array. The string will be split on spaces into a list of given names. Note that an array can also be used. But we write a plain string, to match the citeproc json schema. * Fixed spacing bug in date ranges (#7). * Names: Fixed formatLabel so it works for editortranslator. This fixes a bug for cases where editor = translator (#9). * Text.CSL.Eval.Date: Fixed bugs with date ranges. Ranges within the same year were raising an error "Prelude.init: empty list" (#7). * Util: Export tr' and init'. * Text.CSL.Proc.Disamb: Correct definition of allTheSame. * Improved disambiguation. Now we correctly handle the case with no author but title. * Consider names too when determining date disambiguations. Previously if you had two distinct names needing disambiguation for the same date, the letters would not start over with 'a' for the second name. * Added Generic instances for the types in Style and Reference. pandoc-citeproc-0.10.5.1/LICENSE0000644000000000000000000000300013063457044014200 0ustar0000000000000000Copyright (c) 2008-2013, Andrea Rossato Copyright (c) 2013-2017, John MacFarlane All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. Neither the name of the {organization} nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. pandoc-citeproc-0.10.5.1/Setup.hs0000644000000000000000000000342513003500055014623 0ustar0000000000000000{-# LANGUAGE CPP #-} import Distribution.Simple import Distribution.Simple.PreProcess import Distribution.PackageDescription (PackageDescription(..)) import Distribution.Simple.Program (simpleProgram, Program(..)) import Distribution.Simple.Utils ( rawSystemExitCode, findProgramVersion ) import System.Exit import Distribution.Simple.Utils (info, notice, installOrdinaryFiles) import Distribution.Simple.Setup import Distribution.Simple.LocalBuildInfo main :: IO () main = defaultMainWithHooks $ simpleUserHooks { -- enable hsb2hs preprocessor for .hsb files hookedPreProcessors = [ppBlobSuffixHandler] , hookedPrograms = [(simpleProgram "hsb2hs"){ programFindVersion = \verbosity fp -> findProgramVersion "--version" id verbosity fp }] , postCopy = installManPage } installManPage :: Args -> CopyFlags -> PackageDescription -> LocalBuildInfo -> IO () installManPage _ flags pkg lbi = do let verbosity = fromFlag (copyVerbosity flags) let copydest = fromFlag (copyDest flags) let mandest = mandir (absoluteInstallDirs pkg lbi copydest) ++ "/man1" notice verbosity $ "Copying man page to " ++ mandest installOrdinaryFiles verbosity mandest [("man/man1", "pandoc-citeproc.1")] ppBlobSuffixHandler :: PPSuffixHandler ppBlobSuffixHandler = ("hsb", \_ _ -> PreProcessor { platformIndependent = True, runPreProcessor = mkSimplePreProcessor $ \infile outfile verbosity -> do info verbosity $ "Preprocessing " ++ infile ++ " to " ++ outfile ec <- rawSystemExitCode verbosity "hsb2hs" [infile, infile, outfile] case ec of ExitSuccess -> return () ExitFailure _ -> error "hsb2hs is needed to build this program" }) pandoc-citeproc-0.10.5.1/pandoc-citeproc.cabal0000644000000000000000000001610513115051625017234 0ustar0000000000000000name: pandoc-citeproc version: 0.10.5.1 cabal-version: >= 1.12 synopsis: Supports using pandoc with citeproc description: The pandoc-citeproc library exports functions for using the citeproc system with pandoc. It relies on citeproc-hs, a library for rendering bibliographic reference citations into a variety of styles using a macro language called Citation Style Language (CSL). More details on CSL can be found here: . . Currently this package includes a heavily revised copy of the citeproc-hs code. When citeproc-hs is updated to be compatible, this package will simply depend on citeproc-hs. . This package also contains an executable: pandoc-citeproc, which works as a pandoc filter, and also has a mode for converting bibliographic databases a YAML format suitable for inclusion in pandoc YAML metadata. homepage: https://github.com/jgm/pandoc-citeproc category: Text tested-with: GHC == 7.8.4, GHC == 7.10.3, GHC == 8.0.1 license: BSD3 license-file: LICENSE author: John MacFarlane, Andrea Rossato maintainer: jgm@berkeley.edu build-type: Custom data-files: chicago-author-date.csl locales/*.xml -- documentation README.md LICENSE man/man1/pandoc-citeproc.1 changelog extra-source-files: stack.yaml -- tests tests/*.in.native tests/*.expected.native tests/*.csl tests/biblio.bib tests/biblio2yaml/*.bibtex tests/biblio2yaml/*.biblatex tests/biblio2yaml/pandoc-2/*.biblatex source-repository head type: git location: git://github.com/jgm/pandoc-citeproc.git flag bibutils description: Use Chris Putnam's Bibutils. default: True flag embed_data_files description: Embed locale files into the library (needed for windows packaging) default: False flag unicode_collation description: Use Haskell bindings to the International Components for Unicode (ICU) libraries default: False flag test_citeproc description: Build the test-citeproc program default: False flag debug description: Turn on debug tracing. default: False library hs-source-dirs: src, prelude, compat exposed-modules: Text.CSL.Pandoc Text.CSL Text.CSL.Reference Text.CSL.Style Text.CSL.Eval Text.CSL.Eval.Common Text.CSL.Eval.Date Text.CSL.Eval.Names Text.CSL.Eval.Output Text.CSL.Parser Text.CSL.Proc Text.CSL.Proc.Collapse Text.CSL.Proc.Disamb Text.CSL.Input.Bibutils Text.CSL.Input.Bibtex Text.CSL.Output.Pandoc Text.CSL.Output.Plain Text.CSL.Data other-modules: Text.CSL.Util Prelude Paths_pandoc_citeproc Text.CSL.Compat.Pandoc ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind ghc-prof-options: -fprof-auto-exported build-depends: containers, directory, mtl, bytestring, filepath, pandoc-types >= 1.16 && < 1.18, pandoc >= 1.16 && < 2.1, tagsoup, aeson >= 0.7 && < 1.3, text, vector, xml-conduit >= 1.2 && < 1.6, unordered-containers >= 0.2 && < 0.3, data-default, setenv >= 0.1 && < 0.2, split, yaml >= 0.8.8.7 default-language: Haskell2010 default-extensions: CPP if impl(ghc < 7.6) build-depends: ghc-prim if flag(debug) build-depends: pretty-show cpp-options: -DTRACE if flag(bibutils) build-depends: hs-bibutils >= 0.3 cpp-options: -DUSE_BIBUTILS if flag(embed_data_files) build-depends: file-embed >= 0.0 && < 0.1 cpp-options: -DEMBED_DATA_FILES other-modules: Text.CSL.Data.Embedded if flag(unicode_collation) build-depends: text, text-icu cpp-options: -DUNICODE_COLLATION else build-depends: rfc5051 if impl(ghc >= 6.10) build-depends: base >= 4, syb, parsec, old-locale, time else build-depends: base >= 3 && < 4 executable pandoc-citeproc main-is: pandoc-citeproc.hs hs-source-dirs: ., prelude ghc-options: -funbox-strict-fields -Wall ghc-prof-options: -fprof-auto-exported -rtsopts build-depends: base >= 4, pandoc-citeproc, pandoc-types >= 1.16 && < 1.18, pandoc >= 1.16 && < 2.1, aeson, aeson-pretty >= 0.8, yaml, bytestring, syb, attoparsec, text, filepath other-modules: Paths_pandoc_citeproc Prelude default-language: Haskell2010 ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind if flag(bibutils) default-extensions: CPP cpp-options: -DUSE_BIBUTILS executable test-citeproc Main-Is: test-citeproc.hs Other-Modules: JSON Prelude Hs-Source-Dirs: tests, prelude, compat if flag(test_citeproc) Buildable: True else Buildable: False build-depends: base >= 4, aeson, directory, text, mtl, pandoc-types >= 1.16 && < 1.18, pandoc >= 1.16 && < 2.1, filepath, bytestring, pandoc-citeproc, process, temporary >= 1.1, yaml >= 0.8.8.7, containers >= 0.4, vector >= 0.10 ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind default-language: Haskell2010 other-modules: Text.CSL.Compat.Pandoc test-suite test-pandoc-citeproc Type: exitcode-stdio-1.0 Main-Is: test-pandoc-citeproc.hs Other-Modules: JSON Prelude Hs-Source-Dirs: tests, prelude, compat build-depends: base >= 4, aeson, directory, text, pandoc-types >= 1.16 && < 1.18, mtl, pandoc >= 1.16 && < 2.1, filepath, bytestring, pandoc-citeproc, process, temporary >= 1.1, yaml >= 0.8.8.7 ghc-options: -funbox-strict-fields -Wall -fno-warn-unused-do-bind default-language: Haskell2010 other-modules: Text.CSL.Compat.Pandoc pandoc-citeproc-0.10.5.1/stack.yaml0000644000000000000000000000054513115024440015163 0ustar0000000000000000flags: pandoc-citeproc: bibutils: true embed_data_files: false unicode_collation: false test_citeproc: false debug: false packages: - '.' - location: git: https://github.com/jgm/pandoc.git commit: 55d679e382954dd458acd6233609851748522d99 extra-dep: true extra-deps: - xml-conduit-1.5.0 - skylighting-0.3.3 resolver: lts-8.16 pandoc-citeproc-0.10.5.1/tests/chicago-author-date.in.native0000644000000000000000000001265612743760365022012 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("link-citations",MetaBool True),("bibliography",MetaInlines [Str "tests/biblio.bib"]),("csl",MetaInlines [Str "chicago-author-date.csl"])]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/ieee.in.native0000644000000000000000000001264512743760365017107 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("link-citations",MetaBool True),("bibliography",MetaInlines [Str "tests/biblio.bib"]),("csl",MetaInlines [Str "tests/ieee.csl"])]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue118.in.native0000644000000000000000000000143212743760365017552 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("director",MetaMap (fromList [("family",MetaInlines [Str "Hitchcock"]),("given",MetaInlines [Str "Alfred"])])),("id",MetaInlines [Str "nbn"]),("issued",MetaMap (fromList [("year",MetaString "1959")])),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "Metro-Goldwyn-Mayer"]),("publisher-place",MetaInlines [Str "USA"]),("title",MetaInlines [Str "North",Space,Str "by",Space,Str "Northwest"]),("type",MetaInlines [Str "motion_picture"])])])]}) [Para [Cite [Citation {citationId = "nbn", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "@nbn"],Space,Str "is",Space,Str "a",Space,Str "spy",Space,Str "thriller",Space,Str "film."]] pandoc-citeproc-0.10.5.1/tests/issue13.in.native0000644000000000000000000000127112743760365017465 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-note-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Ann"]])])),("container-title",MetaInlines [Str "Journal"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "2011")])]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "article-newspaper"])])])]}) [Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1]"],Str "."]] pandoc-citeproc-0.10.5.1/tests/issue14.in.native0000644000000000000000000000641412743760365017472 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "chicago-author-date.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("container-title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("id",MetaInlines [Str "CTv1c2"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("page",MetaInlines [Str "34-56"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "Chapter",Space,Str "two"]),("type",MetaInlines [Str "chapter"]),("volume",MetaString "1"),("volume-title",MetaInlines [Str "The",Space,Str "emergence",Space,Str "of",Space,Str "the",Space,Str "Catholic",Space,Str "tradition",Space,Str "(100\8211\&600)"])]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("container-title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("id",MetaInlines [Str "CTv1"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "The",Space,Str "emergence",Space,Str "of",Space,Str "the",Space,Str "Catholic",Space,Str "tradition",Space,Str "(100\8211\&600)"]),("type",MetaInlines [Str "book"]),("volume",MetaString "1")]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("id",MetaInlines [Str "CT"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "Foo",Space,Cite [Citation {citationId = "CT", citationPrefix = [], citationSuffix = [Str ",",Space,Str "1:12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@CT,",Space,Str "1:12]"],Str ".",Space,Str "Bar",Space,Cite [Citation {citationId = "CTv1", citationPrefix = [], citationSuffix = [Str ",",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@CTv1,",Space,Str "12]"],Str ".",Space,Str "Baz",Space,Cite [Citation {citationId = "CTv1c2", citationPrefix = [], citationSuffix = [Str ",",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@CTv1c2,",Space,Str "12]"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue160.in.native0000644000000000000000000000166513053647342017551 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/issue160.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "Jane"])])]),("citation-label",MetaInlines [Str "Jane11"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2011")])),("title",MetaInlines [Str "A",Space,Str "book"]),("type",MetaInlines [Str "book"])])])]}) [Header 2 ("no-citation-label",[],[]) [Str "No",Space,Str "citation-label"] ,Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1]"],Str "."] ,Header 2 ("expected",[],[]) [Str "Expected"] ,BlockQuote [Para [Str "Foo",Space,Str "[Jane11]."] ,Para [Str "[Jane11]",Space,Str "Jane",Space,Str "Doe.",Space,Str "A",Space,Str "book.",Space,Str "2011."]]] pandoc-citeproc-0.10.5.1/tests/issue175.in.native0000644000000000000000000000221012743760365017550 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "Jane"])])]),("container-title",MetaInlines [Str "A",Space,Str "magazine"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("month",MetaString "1"),("year",MetaString "2011")]),MetaMap (fromList [("month",MetaString "2"),("year",MetaString "2011")])]),("page",MetaInlines [Str "33-44"]),("title",MetaInlines [Str "A",Space,Str "title"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Header 2 ("missing-en-dash-between-months",[],[]) [Str "Missing",Space,Str "en-dash",Space,Str "between",Space,Str "months"] ,Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1]"],Str "."] ,Header 2 ("expected",[],[]) [Str "Expected"] ,BlockQuote [Para [Str "Doe,",Space,Str "Jane.",Space,Str "2011.",Space,Str "\8220A",Space,Str "Title.\8221",Space,Emph [Str "A",Space,Str "Magazine"],Str ",",Space,Str "January\8211February."]]] pandoc-citeproc-0.10.5.1/tests/issue197.in.native0000644000000000000000000000174712743760365017572 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("nocite",MetaInlines [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@test"]]),("references",MetaList [MetaMap (fromList [("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Abelard"]),("given",MetaInlines [Str "Peter"])])]),("id",MetaInlines [Str "test"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1989"]])])),("publisher",MetaInlines [Str "Clarendon",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Oxford"]),("title",MetaInlines [Str "Test"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Space,Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test]"],Str "."]] pandoc-citeproc-0.10.5.1/tests/issue25.in.native0000644000000000000000000000132712743760365017472 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "bazbaz",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])])])]}) [Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1]"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue27.in.native0000644000000000000000000000217712743760365017500 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/science.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "AuthorOne"]),("given",MetaInlines [Str "Joe"])]),MetaMap (fromList [("family",MetaInlines [Str "AuthorTwo"]),("given",MetaInlines [Str "Jill"])])]),("container-title",MetaInlines [Str "Some",Space,Str "Journal"]),("id",MetaInlines [Str "AuthorOne2014"]),("issue",MetaInlines [Str "X"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2014"]])])),("page",MetaInlines [Str "XXXX-YYYY"]),("title",MetaInlines [Str "Sample",Space,Str "Title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "XX"])])])]}) [Header 1 ("minimal-example",[],[]) [Str "Minimal",Space,Str "example"] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text",Space,Str "that",Space,Str "needs",Space,Str "a",Space,Str "citation",Space,Cite [Citation {citationId = "AuthorOne2014", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@AuthorOne2014]"],Str "."]] pandoc-citeproc-0.10.5.1/tests/issue51.in.native0000644000000000000000000000263312743760365017472 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Something"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1987"],MetaList [MetaString "1988"]])])),("page",MetaInlines [Str "12-34"]),("title",MetaInlines [Str "The",Space,Str "title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "3")]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaInlines [Str "Ron"])])]),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Something"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1987"]])])),("page",MetaInlines [Str "12-34"]),("title",MetaInlines [Str "The",Space,Str "title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "4")])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"],Str ";",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item2"]]] pandoc-citeproc-0.10.5.1/tests/issue57.in.native0000644000000000000000000000215012743760365017472 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-author-date-with-original-date-and-status.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Faraday"]),("given",MetaInlines [Str "Carry"])])]),("container-title",MetaInlines [Str "Seven",Space,Str "Trips",Space,Str "beyond",Space,Str "the",Space,Str "Asteroid",Space,Str "Belt"]),("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Oring"]),("given",MetaInlines [Str "James"])])]),("id",MetaInlines [Str "Faraday-forthcoming"]),("publisher",MetaInlines [Str "Launch",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Cape",Space,Str "Canaveral,",Space,Str "FL"]),("status",MetaInlines [Str "forthcoming"]),("title",MetaInlines [Str "Protean",Space,Str "photography"]),("type",MetaInlines [Str "chapter"])])])]}) [Para [Cite [Citation {citationId = "Faraday-forthcoming", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@Faraday-forthcoming]"]] ,Header 1 ("references",[],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue58.in.native0000644000000000000000000000174712743760365017506 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/issue58.csl"]),("references",MetaList [MetaMap (fromList [("id",MetaInlines [Str "stanze"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1547"]])])),("language",MetaInlines [Str "it-IT"]),("publisher-place",MetaInlines [Str "Florence"]),("title",MetaInlines [Str "Stanze",Space,Str "in",Space,Str "lode",Space,Str "della",Space,Str "donna",Space,Str "brutta"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "In",Space,Str "this",Space,Str "item,",Space,Str "the",Space,Str "title",Space,Str "replaces",Space,Str "the",Space,Str "(unknown)",Space,Str "author",Space,Str "(see",Space,Str "14.79)",Space,Cite [Citation {citationId = "stanze", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@stanze,",Space,Str "p.",Space,Str "12]"],Str "."] ,Header 1 ("references",[],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue61.in.native0000644000000000000000000000433312743760365017472 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/modern-humanities-research-association.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("id",MetaInlines [Str "doe"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1985"]])])),("publisher",MetaInlines [Str "Publisher"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaInlines [Str "Rob"])])]),("id",MetaInlines [Str "roe"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1985"]])])),("publisher",MetaInlines [Str "Publisher"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])])])]}) [Header 1 ("text",[],[]) [Str "Text"] ,Para [Str "Foo",Space,Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "VIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@doe,",Space,Str "VIII,",Space,Str "89]"]] ,Para [Str "Foo",Space,Cite [Citation {citationId = "roe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "III,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@roe,",Space,Str "III,",Space,Str "89]"]] ,Para [Str "Foo",Space,Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "LVIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@doe,",Space,Str "LVIII,",Space,Str "89]"]] ,Para [Str "Foo",Space,Cite [Citation {citationId = "roe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "MVIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@roe,",Space,Str "MVIII,",Space,Str "89]"]] ,Para [Str "Foo",Space,Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "CL,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@doe,",Space,Str "CL,",Space,Str "89]"]] ,Header 1 ("references",[],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/issue64.in.native0000644000000000000000000000047712743760365017502 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("bibliography",MetaList [MetaInlines [Str "tests/biblio.bib"]]),("nocite",MetaInlines [Cite [Citation {citationId = "*", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\nocite{*}"]])]}) [] pandoc-citeproc-0.10.5.1/tests/issue65.in.native0000644000000000000000000000267212743760365017502 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "3406493556"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Stotz"]),("given",MetaInlines [Str "Peter"])])]),("call-number",MetaInlines [Str "PA25",Space,Str "PA2616",Space,Str ".H24",Space,Str "Abt.",Space,Str "2,",Space,Str "T.",Space,Str "5,",Space,Str "Bd.",Space,Str "2,",Space,Str "etc"]),("collection-number",MetaInlines [Str "2.5"]),("collection-title",MetaInlines [Str "Handbuch",Space,Str "der",Space,Str "Altertumswissenschaft"]),("event-place",MetaInlines [Str "Munich"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "stotz:1996handbuch"]),("issued",MetaMap (fromList [("literal",MetaInlines [Str "1996_2004"])])),("language",MetaInlines [Str "German"]),("number-of-volumes",MetaInlines [Str "5"]),("publisher",MetaInlines [Str "Beck"]),("publisher-place",MetaInlines [Str "Munich"]),("source",MetaInlines [Str "Library",Space,Str "of",Space,Str "Congress",Space,Str "ISBN"]),("title",MetaInlines [Str "Handbuch",Space,Str "zur",Space,Str "lateinischen",Space,Str "Sprache",Space,Str "des",Space,Str "Mittelalters"]),("title-short",MetaInlines [Str "Handbuch"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "stotz:1996handbuch", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@stotz:1996handbuch]"]]] pandoc-citeproc-0.10.5.1/tests/issue68.in.native0000644000000000000000000000716412743760365017506 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "0888441088"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Goering"]),("given",MetaInlines [Str "Joseph"])])]),("call-number",MetaInlines [Str "BV4009",Space,Str ".W55",Space,Str "1992"]),("collection-number",MetaInlines [Str "108"]),("collection-title",MetaInlines [Str "Studies",Space,Str "and",Space,Str "Texts"]),("event-place",MetaInlines [Str "Toronto"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "goering:1992william"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1992"]])])),("publisher",MetaInlines [Str "Pontifical",Space,Str "Institute",Space,Str "of",Space,Str "Mediaeval",Space,Str "Studies"]),("publisher-place",MetaInlines [Str "Toronto"]),("source",MetaInlines [Str "toroprod.library.utoronto.ca",Space,Str "Library",Space,Str "Catalog"]),("title",MetaInlines [Str "William",Space,Str "de",Space,Str "Montibus",Space,Str "(c.",Space,Str "1140\8211\&1213):",Space,Str "The",Space,Str "Schools",Space,Str "and",Space,Str "the",Space,Str "Literature",Space,Str "of",Space,Str "Pastoral",Space,Str "Care"]),("title-short",MetaInlines [Str "William",Space,Str "de",Space,Str "Montibus"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "...",Space,Str "a",Space,Str "prose",Space,Str "commentary",Space,Cite [Citation {citationId = "goering:1992william", citationPrefix = [Str "the",Space,Str "text",Space,Str "of",Space,Str "fol.",Space,Str "9r",Space,Str "is",Space,Str "printed",Space,Str "in"], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "501\8211\&3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[the",Space,Str "text",Space,Str "of",Space,Str "fol.",Space,Str "9r",Space,Str "is",Space,Str "printed",Space,Str "in",Space,Str "@goering:1992william,",Space,Str "pp.",Space,Str "501\8211\&3]"],Str ".",Space,Str "...",Space,Str "a",Space,Str "collection",Space,Str "of",Space,Str "verses",Space,Str "with",Space,Str "a",Space,Str "formal",Space,Str "prose",Space,Str "commentary",Space,Cite [Citation {citationId = "goering:1992william", citationPrefix = [Str "excerpts",Space,Str "from",Space,Str "this",Space,Str "text",Space,Str "were",Space,Str "previously",Space,Str "printed",Space,Str "in"], citationSuffix = [Str ",",Space,Str "p.",Space,Str "508\8211\&14"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "goering:1992william", citationPrefix = [Str "it",Space,Str "was",Space,Str "also",Space,Str "briefly",Space,Str "described",Space,Str "in"], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "141\8211\&42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[excerpts",Space,Str "from",Space,Str "this",Space,Str "text",Space,Str "were",Space,Str "previously",Space,Str "printed",Space,Str "in",Space,Str "@goering:1992william,",Space,Str "p.",Space,Str "508\8211\&14;",Space,Str "it",Space,Str "was",Space,Str "also",Space,Str "briefly",Space,Str "described",Space,Str "in",Space,Str "@goering:1992william,",Space,Str "pp.",Space,Str "141\8211\&42]"],Space,Str "...",Space,Str "and",Space,Str "finally",Space,Str "a",Space,Str "note",Space,Str "starting",Space,Str "with",Space,Str "a",Space,Str "citation",Space,Cite [Citation {citationId = "goering:1992william", citationPrefix = [], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "141-42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@goering:1992william,",Space,Str "pp.",Space,Str "141-42]"],Str "."]] pandoc-citeproc-0.10.5.1/tests/issue7.in.native0000644000000000000000000000135612743760365017414 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Ann"]])])),("container-title",MetaInlines [Str "Journal"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("day",MetaString "24"),("month",MetaString "9"),("year",MetaString "2011")]),MetaMap (fromList [("day",MetaString "26"),("month",MetaString "9"),("year",MetaString "2011")])]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"]]] pandoc-citeproc-0.10.5.1/tests/issue70.in.native0000644000000000000000000000645012743760365017474 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "9782503531465"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Dinkova-Bruun"]),("given",MetaInlines [Str "Greti"])])]),("call-number",MetaInlines [Str "CB351",Space,Str ".F564",Space,Str "2009"]),("collection-number",MetaInlines [Str "50"]),("collection-title",MetaInlines [Str "Textes",Space,Str "et",Space,Str "\233tudes",Space,Str "du",Space,Str "moyen",Space,Str "\226ge"]),("container-title",MetaInlines [Str "Florilegium",Space,Str "mediaevale:",Space,Str "\201tudes",Space,Str "offertes",Space,Str "\224",Space,Str "Jacqueline",Space,Str "Hamesse",Space,Str "\224",Space,Str "l\8217occasion",Space,Str "de",Space,Str "son",Space,Str "\233m\233ritat"]),("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Meirinhos"]),("given",MetaInlines [Str "Jos\233",Space,Str "Francisco"])]),MetaMap (fromList [("family",MetaInlines [Str "Weijers"]),("given",MetaInlines [Str "Olga"])])]),("event-place",MetaInlines [Str "Louvain-la-Neuve"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "bruun:2009samuel"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2009"]])])),("language",MetaInlines [Str "French"]),("page",MetaInlines [Str "155\8211\&174"]),("publisher",MetaInlines [Str "F\233d\233ration",Space,Str "Internationale",Space,Str "des",Space,Str "Instituts",Space,Str "d\8217\201tudes",Space,Str "M\233di\233vales"]),("publisher-place",MetaInlines [Str "Louvain-la-Neuve"]),("source",MetaInlines [Str "Library",Space,Str "of",Space,Str "Congress",Space,Str "ISBN"]),("title",MetaInlines [Str "Samuel",Space,Str "Presbyter",Space,Str "and",Space,Str "the",Space,Str "Glosses",Space,Str "to",Space,Str "His",Space,Str "Versification",Space,Str "of",Space,Str "Psalm",Space,Str "1:",Space,Str "An",Space,Str "Anti-Church",Space,Str "Invective?"]),("title-short",MetaInlines [Str "Samuel",Space,Str "Presbyter"]),("type",MetaInlines [Str "chapter"])]),MetaMap (fromList [("ISSN",MetaInlines [Str "0362-1529"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Thorndike"]),("given",MetaInlines [Str "Lynn"])])]),("container-title",MetaInlines [Str "Traditio"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "thorndike:1955unde"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1955"]])])),("language",MetaInlines [Str "Latin"]),("note",MetaInlines [Str "ArticleType:",Space,Str "research-article",Space,Str "/",Space,Str "Full",Space,Str "publication",Space,Str "date:",Space,Str "1955",Space,Str "/",Space,Str "Copyright",Space,Str "\169",Space,Str "1955",Space,Str "Fordham",Space,Str "University"]),("page",MetaInlines [Str "163\8211\&193"]),("source",MetaInlines [Str "JSTOR"]),("title",MetaInlines [Str "Unde",Space,Str "versus"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "11"])])])]}) [Para [Cite [Citation {citationId = "thorndike:1955unde", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "bruun:2009samuel", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@thorndike:1955unde;",Space,Str "@bruun:2009samuel]"]]] pandoc-citeproc-0.10.5.1/tests/issue75.in.native0000644000000000000000000000617112743760365017501 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/apa.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("id",MetaInlines [Str "test"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2006"]])])),("title",MetaInlines [Str "Test"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "81"])])])]}) [Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "p.",Space,Str "6]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "chap.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "chap.",Space,Str "6]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "n.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "n.",Space,Str "6]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "34-36,",Space,Str "38-39"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "pp.",Space,Str "34-36,",Space,Str "38-39]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "sec.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "sec.",Space,Str "3]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "p.3]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "33-35,",Space,Str "38-39"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "33-35,",Space,Str "38-39]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "14"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "14]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Space,Str "bk.",Space,Str "VI"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test",Space,Str "bk.",Space,Str "VI]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "no.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "no.",Space,Str "6]"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "nos.",Space,Str "6",Space,Str "and",Space,Str "7"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@test,",Space,Str "nos.",Space,Str "6",Space,Str "and",Space,Str "7]"]]] pandoc-citeproc-0.10.5.1/tests/issue76.in.native0000644000000000000000000000466712743760365017512 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "the",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item3"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "a",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "an",Space,Str "abazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"],Str ",",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item2"],Str ",",Space,Cite [Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item3"],Str ",",Space,Cite [Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item4"]]] pandoc-citeproc-0.10.5.1/tests/issue77.in.native0000644000000000000000000000430412743760365017477 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John,",Space,Str "III"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item1"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "van",Space,Str "Gogh"]),("given",MetaInlines [Str "Vincent"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item2"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Humboldt"]),("given",MetaInlines [Str "Alexander",Space,Str "von"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item3"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Bennett"]),("given",MetaInlines [Str "Frank",Space,Str "G.,!",Space,Str "Jr."]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item4"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Dumboldt"]),("given",MetaInlines [Str "Ezekiel,",Space,Str "III"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item5"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item5", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@item1;",Space,Str "@item2;",Space,Str "@item3;",Space,Str "@item4;",Space,Str "@item5]"]]] pandoc-citeproc-0.10.5.1/tests/issue82.in.native0000644000000000000000000000167312743760365017501 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-annotated-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("URL",MetaInlines [Str "https://www.worldcat.org/"]),("accessed",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2014",MetaString "9",MetaString "19"]])])),("author",MetaList [MetaMap (fromList [("literal",MetaInlines [Str "OCLC"])])]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "OCLC_i1099"]),("title",MetaInlines [Str "WorldCat"]),("type",MetaInlines [Str "webpage"])])])]}) [Header 1 ("title",[],[]) [Str "Title"] ,Para [Str "Some",Space,Str "text.",Note [Para [Str "Comment",Space,Str "regarding",Space,Str "text,",Space,Str "supported",Space,Str "by",Space,Str "citation",Space,Cite [Citation {citationId = "OCLC_i1099", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@OCLC_i1099]"]]]]] pandoc-citeproc-0.10.5.1/tests/mhra.in.native0000644000000000000000000001603412743760365017123 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("link-citations",MetaBool True),("csl",MetaInlines [Str "tests/mhra.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])])),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2005")])),("publisher",MetaInlines [Str "Cambridge",Space,Str "University",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Cambridge"]),("title",MetaInlines [Str "First",Space,Str "Book"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])])),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("year",MetaString "2006")])),("page",MetaInlines [Str "33-34"]),("title",MetaInlines [Str "Article"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "6")]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])]),MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaList [MetaInlines [Str "Jenny"]])])]),("container-title",MetaInlines [Str "Third",Space,Str "Book"]),("editor",MetaMap (fromList [("family",MetaInlines [Str "Smith"]),("given",MetaList [MetaInlines [Str "Sam"]])])),("id",MetaInlines [Str "\1087\1091\1085\1082\1090\&3"]),("issued",MetaMap (fromList [("year",MetaString "2007")])),("publisher",MetaInlines [Str "Oxford",Space,Str "University",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Oxford"]),("title",MetaInlines [Str "Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet"]),("type",MetaInlines [Str "chapter"])])])]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "???"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "???"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"]] pandoc-citeproc-0.10.5.1/tests/no-author.in.native0000644000000000000000000000625412743760365020113 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "A"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "B"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item3"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "C"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "D"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item5"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "E"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "D"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Newspaper"]),("id",MetaInlines [Str "item5"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "E"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Newspaper"]),("id",MetaInlines [Str "item6"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "F"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "3"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1",Space,Str "[p.",Space,Str "3]"],Str ",",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item2"],Str ",",Space,Cite [Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item3"],Str ",",Space,Cite [Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item4"],Str ",",Space,Cite [Citation {citationId = "item5", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item5"],Str ",",Space,Cite [Citation {citationId = "item6", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item6"]]] pandoc-citeproc-0.10.5.1/tests/number-of-volumes.in.native0000644000000000000000000000127512743760365021557 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Al"]])])),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2013")])),("language",MetaInlines [Str "en-US"]),("number-of-volumes",MetaString "2"),("publisher",MetaInlines [Str "Publisher"]),("publisher-place",MetaInlines [Str "Location"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@item1"]]] pandoc-citeproc-0.10.5.1/tests/chicago-author-date.expected.native0000644000000000000000000002103012743760365023167 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("bibliography",MetaInlines [Str "tests/biblio.bib"]),("csl",MetaInlines [Str "chicago-author-date.csl"]),("link-citations",MetaBool True)]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(",Span ("",["citeproc-not-found"],[("data-reference-id","nonexistent")]) [Strong [Str "???"]],Str ")"]] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 2}] [Str "(",Span ("",["citeproc-not-found"],[("data-reference-id","nonexistent")]) [Strong [Str "???"]],Str ")"]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 3}] [Str "Doe",Space,Str "(",Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ")"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 4}] [Str "Doe",Space,Str "(",Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "30)"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 5}] [Str "Doe",Space,Str "(",Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "30,",Space,Str "with",Space,Str "suffix)"],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 6},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 7},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 8}] [Str "Doe",Space,Str "(",Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ";",Space,Link ("",[],[]) [Str "2006"] ("#ref-item2",""),Str ",",Space,Str "30;",Space,Str "see",Space,Str "also",Space,Str "Doe",Space,Str "and",Space,Str "Roe",Space,Link ("",[],[]) [Str "2007"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ")"],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 9}] [Str "Doe",Space,Str "and",Space,Str "Roe",Space,Str "(",Link ("",[],[]) [Str "2007"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ",",Space,Str "12)"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 10}] [Str "(Doe",Space,Str "and",Space,Str "Roe",Space,Link ("",[],[]) [Str "2007"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ")"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 11},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 12}] [Str "(see",Space,Str "Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "Doe",Space,Str "and",Space,Str "Roe",Space,Link ("",[],[]) [Str "2007"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ",",Space,Str "34\8211\&35)"],Str "."] ,Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 13}] [Str "(see",Space,Str "Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "34\8211\&35)"],Str "."] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 14},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 15},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 16}] [Str "(see",Space,Str "Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "chap.",Space,Str "3;",Space,Str "Doe",Space,Str "and",Space,Str "Roe",Space,Link ("",[],[]) [Str "2007"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ";",Space,Str "Doe",Space,Link ("",[],[]) [Str "2006"] ("#ref-item2",""),Str ")"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 17}] [Str "(Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space,Str "else)"],Str "."] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 18}] [Str "(Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Space,Str "and",Space,Str "nowhere",Space,Str "else)"],Str "."] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 19}] [Str "(",Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ")"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 20}] [Str "(",Link ("",[],[]) [Str "2006"] ("#ref-item2",""),Str ",",Space,Str "44)"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 21}] [Str "(",Emph [Str "see"],Space,Str "Doe",Space,Link ("",[],[]) [Str "2005"] ("#ref-item1",""),Str ",",Space,Str "32)"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Doe,",Space,Str "John.",Space,Str "2005.",Space,Emph [Str "First",Space,Str "Book"],Str ".",Space,Str "Cambridge:",Space,Str "Cambridge",Space,Str "University",Space,Str "Press."]],Div ("ref-item2",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "2006.",Space,Str "\8220Article.\8221",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"],Space,Str "6:",Space,Str "33\8211\&34."]],Div ("ref-\1087\1091\1085\1082\1090\&3",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Str "and",Space,Str "Jenny",Space,Str "Roe.",Space,Str "2007.",Space,Str "\8220Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet.\8221",Space,Str "In",Space,Emph [Str "Third",Space,Str "Book"],Str ",",Space,Str "edited",Space,Str "by",Space,Str "Sam",Space,Str "Smith.",Space,Str "Oxford:",Space,Str "Oxford",Space,Str "University",Space,Str "Press."]]]] pandoc-citeproc-0.10.5.1/tests/ieee.expected.native0000644000000000000000000001703212743760365020275 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("bibliography",MetaInlines [Str "tests/biblio.bib"]),("csl",MetaInlines [Str "tests/ieee.csl"]),("link-citations",MetaBool True)]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Span ("",["citeproc-not-found"],[("data-reference-id","nonexistent")]) [Strong [Str "???"]]]] ,Para [Strong [Str "???"]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 3}] [Link ("",[],[]) [Str "1"] ("#ref-item1","")],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 4}] [Link ("",[],[]) [Str "1"] ("#ref-item1","")],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 5}] [Link ("",[],[]) [Str "1"] ("#ref-item1","")],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 6},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 7},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 8}] [Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str ",",Space,Str "[",Link ("",[],[]) [Str "2"] ("#ref-item2",""),Str ",",Space,Str "p.",Space,Str "30],",Space,Str "[",Link ("",[],[]) [Str "3"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str "]"],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 9}] [Link ("",[],[]) [Str "3"] ("#ref-\1087\1091\1085\1082\1090\&3","")],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 10}] [Str "[",Link ("",[],[]) [Str "3"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str "]"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 11},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 12}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str "],",Space,Str "[",Link ("",[],[]) [Str "3"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str ",",Space,Str "pp.",Space,Str "34\8211\&35]"],Str "."] ,Para [Str "Another",Space,Str "one",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 13}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str ",",Space,Str "pp.",Space,Str "34\8211\&35]"],Str "."] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 14},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 15},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 16}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str "]\8211[",Link ("",[],[]) [Str "3"] ("#ref-\1087\1091\1085\1082\1090\&3",""),Str "]"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 17}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str ",",Space,Str "pp.",Space,Str "33,",Space,Str "35\8211\&37]"],Str "."] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 18}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str "]"],Str "."] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 19}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str "]"],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 20}] [Str "[",Link ("",[],[]) [Str "2"] ("#ref-item2",""),Str ",",Space,Str "p.",Space,Str "44]"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Space,Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 21}] [Str "[",Link ("",[],[]) [Str "1"] ("#ref-item1",""),Str ",",Space,Str "p.",Space,Str "32]"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "[1]",Space,Str "J.",Space,Str "Doe,",Space,Emph [Str "First",Space,Str "book"],Str ".",Space,Str "Cambridge:",Space,Str "Cambridge",Space,Str "University",Space,Str "Press,",Space,Str "2005."]],Div ("ref-item2",[],[]) [Para [Str "[2]",Space,Str "J.",Space,Str "Doe,",Space,Str "\8220Article,\8221",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"],Str ",",Space,Str "vol.",Space,Str "6,",Space,Str "pp.",Space,Str "33\8211\&34,",Space,Str "2006."]],Div ("ref-\1087\1091\1085\1082\1090\&3",[],[]) [Para [Str "[3]",Space,Str "J.",Space,Str "Doe",Space,Str "and",Space,Str "J.",Space,Str "Roe,",Space,Str "\8220Why",Space,Str "water",Space,Str "is",Space,Str "wet,\8221",Space,Str "in",Space,Emph [Str "Third",Space,Str "book"],Str ",",Space,Str "S.",Space,Str "Smith,",Space,Str "Ed.",Space,Str "Oxford:",Space,Str "Oxford",Space,Str "University",Space,Str "Press,",Space,Str "2007."]]]] pandoc-citeproc-0.10.5.1/tests/issue118.expected.native0000644000000000000000000000206312743760365020746 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("director",MetaMap (fromList [("family",MetaInlines [Str "Hitchcock"]),("given",MetaInlines [Str "Alfred"])])),("id",MetaInlines [Str "nbn"]),("issued",MetaMap (fromList [("year",MetaString "1959")])),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "Metro-Goldwyn-Mayer"]),("publisher-place",MetaInlines [Str "USA"]),("title",MetaInlines [Str "North",Space,Str "by",Space,Str "Northwest"]),("type",MetaInlines [Str "motion_picture"])])])]}) [Para [Cite [Citation {citationId = "nbn", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Hitchcock",Space,Str "1959)"],Space,Str "is",Space,Str "a",Space,Str "spy",Space,Str "thriller",Space,Str "film."] ,Div ("refs",["references"],[]) [Div ("ref-nbn",[],[]) [Para [Str "Hitchcock,",Space,Str "Alfred,",Space,Str "dir.",Space,Str "1959.",Space,Emph [Str "North",Space,Str "by",Space,Str "Northwest"],Str ".",Space,Str "USA:",Space,Str "Metro-Goldwyn-Mayer."]]]] pandoc-citeproc-0.10.5.1/tests/issue13.expected.native0000644000000000000000000000162413032532307020643 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-note-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Ann"]])])),("container-title",MetaInlines [Str "Journal"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "2011")])]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "article-newspaper"])])])]}) [Para [Str "Foo",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Note [Para [Str "Author,",Space,Str "\8220Title.\8221"]]]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Author,",Space,Str "Ann.",Space,Str "\8220Title.\8221",Space,Emph [Str "Journal"],Str ",",Space,Str "2011."]]]] pandoc-citeproc-0.10.5.1/tests/issue14.expected.native0000644000000000000000000001135512743760365020665 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "chicago-author-date.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("container-title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("id",MetaInlines [Str "CTv1c2"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("page",MetaInlines [Str "34-56"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "Chapter",Space,Str "two"]),("type",MetaInlines [Str "chapter"]),("volume",MetaString "1"),("volume-title",MetaInlines [Str "The",Space,Str "emergence",Space,Str "of",Space,Str "the",Space,Str "Catholic",Space,Str "tradition",Space,Str "(100\8211\&600)"])]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("container-title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("id",MetaInlines [Str "CTv1"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "The",Space,Str "emergence",Space,Str "of",Space,Str "the",Space,Str "Catholic",Space,Str "tradition",Space,Str "(100\8211\&600)"]),("type",MetaInlines [Str "book"]),("volume",MetaString "1")]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Pelikan"]),("given",MetaInlines [Str "Jaroslav"])])),("id",MetaInlines [Str "CT"]),("issued",MetaList [MetaMap (fromList [("year",MetaString "1971")])]),("language",MetaInlines [Str "en-US"]),("publisher",MetaInlines [Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Chicago"]),("title",MetaInlines [Str "The",Space,Str "Christian",Space,Str "tradition:",Space,Str "A",Space,Str "history",Space,Str "of",Space,Str "the",Space,Str "development",Space,Str "of",Space,Str "doctrine"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "Foo",Space,Cite [Citation {citationId = "CT", citationPrefix = [], citationSuffix = [Str ",",Space,Str "1:12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Pelikan",Space,Str "1971b,",Space,Str "1:12)"],Str ".",Space,Str "Bar",Space,Cite [Citation {citationId = "CTv1", citationPrefix = [], citationSuffix = [Str ",",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2}] [Str "(Pelikan",Space,Str "1971c,",Space,Str "1:12)"],Str ".",Space,Str "Baz",Space,Cite [Citation {citationId = "CTv1c2", citationPrefix = [], citationSuffix = [Str ",",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 3}] [Str "(Pelikan",Space,Str "1971a,",Space,Str "12)"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-CTv1c2",[],[]) [Para [Str "Pelikan,",Space,Str "Jaroslav.",Space,Str "1971a.",Space,Str "\8220Chapter",Space,Str "Two.\8221",Space,Str "In",Space,Emph [Str "The",Space,Str "Christian",Space,Str "Tradition:",Space,Str "A",Space,Str "History",Space,Str "of",Space,Str "the",Space,Str "Development",Space,Str "of",Space,Str "Doctrine"],Str ",",Space,Str "1:34\8211\&56.",Space,Str "Chicago:",Space,Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press."]],Div ("ref-CT",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "1971b.",Space,Emph [Str "The",Space,Str "Christian",Space,Str "Tradition:",Space,Str "A",Space,Str "History",Space,Str "of",Space,Str "the",Space,Str "Development",Space,Str "of",Space,Str "Doctrine"],Str ".",Space,Str "Chicago:",Space,Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press."]],Div ("ref-CTv1",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "1971c.",Space,Emph [Str "The",Space,Str "Emergence",Space,Str "of",Space,Str "the",Space,Str "Catholic",Space,Str "Tradition",Space,Str "(100\8211\&600)"],Str ".",Space,Emph [Str "The",Space,Str "Christian",Space,Str "Tradition:",Space,Str "A",Space,Str "History",Space,Str "of",Space,Str "the",Space,Str "Development",Space,Str "of",Space,Str "Doctrine"],Str ".",Space,Str "Vol.",Space,Str "1.",Space,Str "Chicago:",Space,Str "University",Space,Str "of",Space,Str "Chicago",Space,Str "Press."]]]] pandoc-citeproc-0.10.5.1/tests/issue160.expected.native0000644000000000000000000000213613053647342020736 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/issue160.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "Jane"])])]),("citation-label",MetaInlines [Str "Jane11"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2011")])),("title",MetaInlines [Str "A",Space,Str "book"]),("type",MetaInlines [Str "book"])])])]}) [Header 2 ("no-citation-label",[],[]) [Str "No",Space,Str "citation-label"] ,Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "[Jane11]"],Str "."] ,Header 2 ("expected",[],[]) [Str "Expected"] ,BlockQuote [Para [Str "Foo",Space,Str "[Jane11]."] ,Para [Str "[Jane11]",Space,Str "Jane",Space,Str "Doe.",Space,Str "A",Space,Str "book.",Space,Str "2011."]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "[Jane11]",Space,Str "Jane",Space,Str "Doe.",Space,Str "A",Space,Str "book.",Space,Str "2011."]]]] pandoc-citeproc-0.10.5.1/tests/issue175.expected.native0000644000000000000000000000261213032532307020732 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "Jane"])])]),("container-title",MetaInlines [Str "A",Space,Str "magazine"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("month",MetaString "1"),("year",MetaString "2011")]),MetaMap (fromList [("month",MetaString "2"),("year",MetaString "2011")])]),("page",MetaInlines [Str "33-44"]),("title",MetaInlines [Str "A",Space,Str "title"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Header 2 ("missing-en-dash-between-months",[],[]) [Str "Missing",Space,Str "en-dash",Space,Str "between",Space,Str "months"] ,Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Doe",Space,Str "2011)"],Str "."] ,Header 2 ("expected",[],[]) [Str "Expected"] ,BlockQuote [Para [Str "Doe,",Space,Str "Jane.",Space,Str "2011.",Space,Str "\8220A",Space,Str "Title.\8221",Space,Emph [Str "A",Space,Str "Magazine"],Str ",",Space,Str "January\8211February."]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Doe,",Space,Str "Jane.",Space,Str "2011.",Space,Str "\8220A",Space,Str "Title.\8221",Space,Emph [Str "A",Space,Str "Magazine"],Str ",",Space,Str "January\8211February."]]]] pandoc-citeproc-0.10.5.1/tests/issue197.expected.native0000644000000000000000000000254213032532307020740 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("nocite",MetaInlines [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 0}] [Str "@test"]]),("references",MetaList [MetaMap (fromList [("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Abelard"]),("given",MetaInlines [Str "Peter"])])]),("id",MetaInlines [Str "test"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1989"]])])),("publisher",MetaInlines [Str "Clarendon",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Oxford"]),("title",MetaInlines [Str "Test"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Str ".",Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Note [Para [Str "Peter",Space,Str "Abelard,",Space,Str "ed.,",Space,Emph [Str "Test"],Space,Str "(Oxford:",Space,Str "Clarendon",Space,Str "Press,",Space,Str "1989)."]]]] ,Div ("refs",["references"],[]) [Div ("ref-test",[],[]) [Para [Str "Abelard,",Space,Str "Peter,",Space,Str "ed.",Space,Emph [Str "Test"],Str ".",Space,Str "Oxford:",Space,Str "Clarendon",Space,Str "Press,",Space,Str "1989."]]]] pandoc-citeproc-0.10.5.1/tests/issue25.expected.native0000644000000000000000000000167212743760365020670 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "bazbaz",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])])])]}) [Para [Str "Foo",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Author",Space,Str "1998)"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Author,",Space,Str "Al.",Space,Str "1998.",Space,Str "\8220Foo",Space,Str "Bar",Space,Str "Baz:",Space,Str "Bazbaz",Space,Str "Foo.\8221"]]]] pandoc-citeproc-0.10.5.1/tests/issue27.expected.native0000644000000000000000000000257512743760365020675 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/science.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "AuthorOne"]),("given",MetaInlines [Str "Joe"])]),MetaMap (fromList [("family",MetaInlines [Str "AuthorTwo"]),("given",MetaInlines [Str "Jill"])])]),("container-title",MetaInlines [Str "Some",Space,Str "Journal"]),("id",MetaInlines [Str "AuthorOne2014"]),("issue",MetaInlines [Str "X"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2014"]])])),("page",MetaInlines [Str "XXXX-YYYY"]),("title",MetaInlines [Str "Sample",Space,Str "Title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "XX"])])])]}) [Header 1 ("minimal-example",[],[]) [Str "Minimal",Space,Str "example"] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "text",Space,Str "that",Space,Str "needs",Space,Str "a",Space,Str "citation",Space,Cite [Citation {citationId = "AuthorOne2014", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(",Emph [Str "1"],Str ")"],Str "."] ,Div ("refs",["references"],[]) [Div ("ref-AuthorOne2014",[],[]) [Para [Str "1.",Space,Str "J.",Space,Str "AuthorOne,",Space,Str "J.",Space,Str "AuthorTwo,",Space,Emph [Str "Some",Space,Str "Journal"],Str ",",Space,Str "in",Space,Str "press."]]]] pandoc-citeproc-0.10.5.1/tests/issue51.expected.native0000644000000000000000000000367412743760365020673 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Something"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1987"],MetaList [MetaString "1988"]])])),("page",MetaInlines [Str "12-34"]),("title",MetaInlines [Str "The",Space,Str "title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "3")]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaInlines [Str "Ron"])])]),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Something"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1987"]])])),("page",MetaInlines [Str "12-34"]),("title",MetaInlines [Str "The",Space,Str "title"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "4")])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 1}] [Str "Doe",Space,Str "(1987\8211\&1988)"],Str ";",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 2}] [Str "Roe",Space,Str "(1987)"]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Doe,",Space,Str "John.",Space,Str "1987\8211\&1988.",Space,Str "\8220The",Space,Str "Title.\8221",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Something"],Space,Str "3:",Space,Str "12\8211\&34."]],Div ("ref-item2",[],[]) [Para [Str "Roe,",Space,Str "Ron.",Space,Str "1987.",Space,Str "\8220The",Space,Str "Title.\8221",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Something"],Space,Str "4:",Space,Str "12\8211\&34."]]]] pandoc-citeproc-0.10.5.1/tests/issue57.expected.native0000644000000000000000000000316312743760365020672 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-author-date-with-original-date-and-status.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Faraday"]),("given",MetaInlines [Str "Carry"])])]),("container-title",MetaInlines [Str "Seven",Space,Str "Trips",Space,Str "beyond",Space,Str "the",Space,Str "Asteroid",Space,Str "Belt"]),("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Oring"]),("given",MetaInlines [Str "James"])])]),("id",MetaInlines [Str "Faraday-forthcoming"]),("publisher",MetaInlines [Str "Launch",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Cape",Space,Str "Canaveral,",Space,Str "FL"]),("status",MetaInlines [Str "forthcoming"]),("title",MetaInlines [Str "Protean",Space,Str "photography"]),("type",MetaInlines [Str "chapter"])])])]}) [Para [Cite [Citation {citationId = "Faraday-forthcoming", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Faraday,",Space,Str "forthcoming)"]] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-Faraday-forthcoming",[],[]) [Para [Str "Faraday,",Space,Str "Carry.",Space,Str "Forthcoming.",Space,Str "\8220Protean",Space,Str "Photography.\8221",Space,Str "In",Space,Emph [Str "Seven",Space,Str "Trips",Space,Str "Beyond",Space,Str "the",Space,Str "Asteroid",Space,Str "Belt"],Str ",",Space,Str "edited",Space,Str "by",Space,Str "James",Space,Str "Oring.",Space,Str "Cape",Space,Str "Canaveral,",Space,Str "FL:",Space,Str "Launch",Space,Str "Press."]]]] pandoc-citeproc-0.10.5.1/tests/issue58.expected.native0000644000000000000000000000247012743760365020673 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/issue58.csl"]),("references",MetaList [MetaMap (fromList [("id",MetaInlines [Str "stanze"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1547"]])])),("language",MetaInlines [Str "it-IT"]),("publisher-place",MetaInlines [Str "Florence"]),("title",MetaInlines [Str "Stanze",Space,Str "in",Space,Str "lode",Space,Str "della",Space,Str "donna",Space,Str "brutta"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "In",Space,Str "this",Space,Str "item,",Space,Str "the",Space,Str "title",Space,Str "replaces",Space,Str "the",Space,Str "(unknown)",Space,Str "author",Space,Str "(see",Space,Str "14.79)",Space,Cite [Citation {citationId = "stanze", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.",Space,Str "12"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(",Emph [Str "Stanze",Space,Str "in",Space,Str "lode",Space,Str "della",Space,Str "donna",Space,Str "brutta"],Space,Str "1547,",Space,Str "12)"],Str "."] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-stanze",[],[]) [Para [Emph [Str "Stanze",Space,Str "in",Space,Str "lode",Space,Str "della",Space,Str "donna",Space,Str "brutta"],Str ".",Space,Str "1547.",Space,Str "Florence."]]]] pandoc-citeproc-0.10.5.1/tests/issue61.expected.native0000644000000000000000000000536713032532307020656 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/modern-humanities-research-association.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("id",MetaInlines [Str "doe"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1985"]])])),("publisher",MetaInlines [Str "Publisher"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaInlines [Str "Rob"])])]),("id",MetaInlines [Str "roe"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1985"]])])),("publisher",MetaInlines [Str "Publisher"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])])])]}) [Header 1 ("text",[],[]) [Str "Text"] ,Para [Str "Foo",Str "",Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "VIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Note [Para [Str "John",Space,Str "Doe,",Space,Emph [Str "Title"],Space,Str "(Publisher,",Space,Str "1985),",Space,Str "VIII,",Space,Str "89."]]]] ,Para [Str "Foo",Str "",Cite [Citation {citationId = "roe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "III,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2}] [Note [Para [Str "Rob",Space,Str "Roe,",Space,Emph [Str "Title"],Space,Str "(Publisher,",Space,Str "1985),",Space,Str "III,",Space,Str "89."]]]] ,Para [Str "Foo",Str "",Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "LVIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 3}] [Note [Para [Str "Doe,",Space,Str "LVIII,",Space,Str "89."]]]] ,Para [Str "Foo",Str "",Cite [Citation {citationId = "roe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "MVIII,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 4}] [Note [Para [Str "Roe,",Space,Str "MVIII,",Space,Str "89."]]]] ,Para [Str "Foo",Str "",Cite [Citation {citationId = "doe", citationPrefix = [], citationSuffix = [Str ",",Space,Str "CL,",Space,Str "89"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 5}] [Note [Para [Str "Doe,",Space,Str "CL,",Space,Str "89."]]]] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-doe",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Emph [Str "Title"],Space,Str "(Publisher,",Space,Str "1985)"]] ,Div ("ref-roe",[],[]) [Para [Str "Roe,",Space,Str "Rob,",Space,Emph [Str "Title"],Space,Str "(Publisher,",Space,Str "1985)"]]]] pandoc-citeproc-0.10.5.1/tests/issue64.expected.native0000644000000000000000000000234313032532307020650 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("bibliography",MetaList [MetaInlines [Str "tests/biblio.bib"]]),("nocite",MetaInlines [Cite [Citation {citationId = "*", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\nocite{*}"]])]}) [Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Doe,",Space,Str "John.",Space,Str "2005.",Space,Emph [Str "First",Space,Str "Book"],Str ".",Space,Str "Cambridge:",Space,Str "Cambridge",Space,Str "University",Space,Str "Press."]] ,Div ("ref-item2",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "2006.",Space,Str "\8220Article.\8221",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"],Space,Str "6:",Space,Str "33\8211\&34."]] ,Div ("ref-\1087\1091\1085\1082\1090\&3",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Str "and",Space,Str "Jenny",Space,Str "Roe.",Space,Str "2007.",Space,Str "\8220Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet.\8221",Space,Str "In",Space,Emph [Str "Third",Space,Str "Book"],Str ",",Space,Str "edited",Space,Str "by",Space,Str "Sam",Space,Str "Smith.",Space,Str "Oxford:",Space,Str "Oxford",Space,Str "University",Space,Str "Press."]]]] pandoc-citeproc-0.10.5.1/tests/issue65.expected.native0000644000000000000000000000357512743760365020700 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "3406493556"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Stotz"]),("given",MetaInlines [Str "Peter"])])]),("call-number",MetaInlines [Str "PA25",Space,Str "PA2616",Space,Str ".H24",Space,Str "Abt.",Space,Str "2,",Space,Str "T.",Space,Str "5,",Space,Str "Bd.",Space,Str "2,",Space,Str "etc"]),("collection-number",MetaInlines [Str "2.5"]),("collection-title",MetaInlines [Str "Handbuch",Space,Str "der",Space,Str "Altertumswissenschaft"]),("event-place",MetaInlines [Str "Munich"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "stotz:1996handbuch"]),("issued",MetaMap (fromList [("literal",MetaInlines [Str "1996_2004"])])),("language",MetaInlines [Str "German"]),("number-of-volumes",MetaInlines [Str "5"]),("publisher",MetaInlines [Str "Beck"]),("publisher-place",MetaInlines [Str "Munich"]),("source",MetaInlines [Str "Library",Space,Str "of",Space,Str "Congress",Space,Str "ISBN"]),("title",MetaInlines [Str "Handbuch",Space,Str "zur",Space,Str "lateinischen",Space,Str "Sprache",Space,Str "des",Space,Str "Mittelalters"]),("title-short",MetaInlines [Str "Handbuch"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "stotz:1996handbuch", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Stotz",Space,Str "1996\8211\&2004)"]] ,Div ("refs",["references"],[]) [Div ("ref-stotz:1996handbuch",[],[]) [Para [Str "Stotz,",Space,Str "Peter.",Space,Str "1996\8211\&2004.",Space,Emph [Str "Handbuch",Space,Str "zur",Space,Str "lateinischen",Space,Str "Sprache",Space,Str "des",Space,Str "Mittelalters"],Str ".",Space,Str "5",Space,Str "vols.",Space,Str "Handbuch",Space,Str "der",Space,Str "Altertumswissenschaft",Space,Str "2.5.",Space,Str "Munich:",Space,Str "Beck."]]]] pandoc-citeproc-0.10.5.1/tests/issue68.expected.native0000644000000000000000000001112513032532307020652 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "0888441088"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Goering"]),("given",MetaInlines [Str "Joseph"])])]),("call-number",MetaInlines [Str "BV4009",Space,Str ".W55",Space,Str "1992"]),("collection-number",MetaInlines [Str "108"]),("collection-title",MetaInlines [Str "Studies",Space,Str "and",Space,Str "Texts"]),("event-place",MetaInlines [Str "Toronto"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "goering:1992william"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1992"]])])),("publisher",MetaInlines [Str "Pontifical",Space,Str "Institute",Space,Str "of",Space,Str "Mediaeval",Space,Str "Studies"]),("publisher-place",MetaInlines [Str "Toronto"]),("source",MetaInlines [Str "toroprod.library.utoronto.ca",Space,Str "Library",Space,Str "Catalog"]),("title",MetaInlines [Str "William",Space,Str "de",Space,Str "Montibus",Space,Str "(c.",Space,Str "1140\8211\&1213):",Space,Str "The",Space,Str "Schools",Space,Str "and",Space,Str "the",Space,Str "Literature",Space,Str "of",Space,Str "Pastoral",Space,Str "Care"]),("title-short",MetaInlines [Str "William",Space,Str "de",Space,Str "Montibus"]),("type",MetaInlines [Str "book"])])])]}) [Para [Str "...",Space,Str "a",Space,Str "prose",Space,Str "commentary",Str ".",Cite [Citation {citationId = "goering:1992william", citationPrefix = [Str "the",Space,Str "text",Space,Str "of",Space,Str "fol.",Space,Str "9r",Space,Str "is",Space,Str "printed",Space,Str "in"], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "501\8211\&3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Note [Para [Str "The",Space,Str "text",Space,Str "of",Space,Str "fol.",Space,Str "9r",Space,Str "is",Space,Str "printed",Space,Str "in",Space,Str "Joseph",Space,Str "Goering,",Space,Emph [Str "William",Space,Str "de",Space,Str "Montibus",Space,Str "(c.",Space,Str "1140\8211\&1213):",Space,Str "The",Space,Str "Schools",Space,Str "and",Space,Str "the",Space,Str "Literature",Space,Str "of",Space,Str "Pastoral",Space,Str "Care"],Str ",",Space,Str "Studies",Space,Str "and",Space,Str "Texts",Space,Str "108",Space,Str "(Toronto:",Space,Str "Pontifical",Space,Str "Institute",Space,Str "of",Space,Str "Mediaeval",Space,Str "Studies,",Space,Str "1992),",Space,Str "501\8211\&3."]]],Space,Str "...",Space,Str "a",Space,Str "collection",Space,Str "of",Space,Str "verses",Space,Str "with",Space,Str "a",Space,Str "formal",Space,Str "prose",Space,Str "commentary",Cite [Citation {citationId = "goering:1992william", citationPrefix = [Str "excerpts",Space,Str "from",Space,Str "this",Space,Str "text",Space,Str "were",Space,Str "previously",Space,Str "printed",Space,Str "in"], citationSuffix = [Str ",",Space,Str "p.",Space,Str "508\8211\&14"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2},Citation {citationId = "goering:1992william", citationPrefix = [Str "it",Space,Str "was",Space,Str "also",Space,Str "briefly",Space,Str "described",Space,Str "in"], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "141\8211\&42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 3}] [Note [Para [Str "Excerpts",Space,Str "from",Space,Str "this",Space,Str "text",Space,Str "were",Space,Str "previously",Space,Str "printed",Space,Str "in",Space,Str "ibid.,",Space,Str "508\8211\&14;",Space,Str "it",Space,Str "was",Space,Str "also",Space,Str "briefly",Space,Str "described",Space,Str "in",Space,Str "ibid.,",Space,Str "141\8211\&42."]]],Space,Str "...",Space,Str "and",Space,Str "finally",Space,Str "a",Space,Str "note",Space,Str "starting",Space,Str "with",Space,Str "a",Space,Str "citation",Str ".",Cite [Citation {citationId = "goering:1992william", citationPrefix = [], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "141-42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 4}] [Note [Para [Str "Ibid.,",Space,Str "141\8211\&42."]]]] ,Div ("refs",["references"],[]) [Div ("ref-goering:1992william",[],[]) [Para [Str "Goering,",Space,Str "Joseph.",Space,Emph [Str "William",Space,Str "de",Space,Str "Montibus",Space,Str "(c.",Space,Str "1140\8211\&1213):",Space,Str "The",Space,Str "Schools",Space,Str "and",Space,Str "the",Space,Str "Literature",Space,Str "of",Space,Str "Pastoral",Space,Str "Care"],Str ".",Space,Str "Studies",Space,Str "and",Space,Str "Texts",Space,Str "108.",Space,Str "Toronto:",Space,Str "Pontifical",Space,Str "Institute",Space,Str "of",Space,Str "Mediaeval",Space,Str "Studies,",Space,Str "1992."]]]] pandoc-citeproc-0.10.5.1/tests/issue7.expected.native0000644000000000000000000000174412743760365020610 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Ann"]])])),("container-title",MetaInlines [Str "Journal"]),("id",MetaInlines [Str "item1"]),("issued",MetaList [MetaMap (fromList [("day",MetaString "24"),("month",MetaString "9"),("year",MetaString "2011")]),MetaMap (fromList [("day",MetaString "26"),("month",MetaString "9"),("year",MetaString "2011")])]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 1}] [Str "Author",Space,Str "(2011)"]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Author,",Space,Str "Ann.",Space,Str "2011.",Space,Str "\8220Title.\8221",Space,Emph [Str "Journal"],Str ",",Space,Str "September",Space,Str "24\8211\&26."]]]] pandoc-citeproc-0.10.5.1/tests/issue70.expected.native0000644000000000000000000001125112743760365020662 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("ISBN",MetaInlines [Str "9782503531465"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Dinkova-Bruun"]),("given",MetaInlines [Str "Greti"])])]),("call-number",MetaInlines [Str "CB351",Space,Str ".F564",Space,Str "2009"]),("collection-number",MetaInlines [Str "50"]),("collection-title",MetaInlines [Str "Textes",Space,Str "et",Space,Str "\233tudes",Space,Str "du",Space,Str "moyen",Space,Str "\226ge"]),("container-title",MetaInlines [Str "Florilegium",Space,Str "mediaevale:",Space,Str "\201tudes",Space,Str "offertes",Space,Str "\224",Space,Str "Jacqueline",Space,Str "Hamesse",Space,Str "\224",Space,Str "l\8217occasion",Space,Str "de",Space,Str "son",Space,Str "\233m\233ritat"]),("editor",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Meirinhos"]),("given",MetaInlines [Str "Jos\233",Space,Str "Francisco"])]),MetaMap (fromList [("family",MetaInlines [Str "Weijers"]),("given",MetaInlines [Str "Olga"])])]),("event-place",MetaInlines [Str "Louvain-la-Neuve"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "bruun:2009samuel"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2009"]])])),("language",MetaInlines [Str "French"]),("page",MetaInlines [Str "155\8211\&174"]),("publisher",MetaInlines [Str "F\233d\233ration",Space,Str "Internationale",Space,Str "des",Space,Str "Instituts",Space,Str "d\8217\201tudes",Space,Str "M\233di\233vales"]),("publisher-place",MetaInlines [Str "Louvain-la-Neuve"]),("source",MetaInlines [Str "Library",Space,Str "of",Space,Str "Congress",Space,Str "ISBN"]),("title",MetaInlines [Str "Samuel",Space,Str "Presbyter",Space,Str "and",Space,Str "the",Space,Str "Glosses",Space,Str "to",Space,Str "His",Space,Str "Versification",Space,Str "of",Space,Str "Psalm",Space,Str "1:",Space,Str "An",Space,Str "Anti-Church",Space,Str "Invective?"]),("title-short",MetaInlines [Str "Samuel",Space,Str "Presbyter"]),("type",MetaInlines [Str "chapter"])]),MetaMap (fromList [("ISSN",MetaInlines [Str "0362-1529"]),("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Thorndike"]),("given",MetaInlines [Str "Lynn"])])]),("container-title",MetaInlines [Str "Traditio"]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "thorndike:1955unde"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1955"]])])),("language",MetaInlines [Str "Latin"]),("note",MetaInlines [Str "ArticleType:",Space,Str "research-article",Space,Str "/",Space,Str "Full",Space,Str "publication",Space,Str "date:",Space,Str "1955",Space,Str "/",Space,Str "Copyright",Space,Str "\169",Space,Str "1955",Space,Str "Fordham",Space,Str "University"]),("page",MetaInlines [Str "163\8211\&193"]),("source",MetaInlines [Str "JSTOR"]),("title",MetaInlines [Str "Unde",Space,Str "versus"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "11"])])])]}) [Para [Cite [Citation {citationId = "thorndike:1955unde", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1},Citation {citationId = "bruun:2009samuel", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2}] [Str "(Thorndike",Space,Str "1955;",Space,Str "Dinkova-Bruun",Space,Str "2009)"]] ,Div ("refs",["references"],[]) [Div ("ref-bruun:2009samuel",[],[]) [Para [Str "Dinkova-Bruun,",Space,Str "Greti.",Space,Str "2009.",Space,Str "\8220Samuel",Space,Str "Presbyter",Space,Str "and",Space,Str "the",Space,Str "Glosses",Space,Str "to",Space,Str "His",Space,Str "Versification",Space,Str "of",Space,Str "Psalm",Space,Str "1:",Space,Str "An",Space,Str "Anti-Church",Space,Str "Invective?\8221",Space,Str "In",Space,Emph [Str "Florilegium",Space,Str "mediaevale:",Space,Str "\201tudes",Space,Str "offertes",Space,Str "\224",Space,Str "Jacqueline",Space,Str "Hamesse",Space,Str "\224",Space,Str "l\8217occasion",Space,Str "de",Space,Str "son",Space,Str "\233m\233ritat"],Str ",",Space,Str "edited",Space,Str "by",Space,Str "Jos\233",Space,Str "Francisco",Space,Str "Meirinhos",Space,Str "and",Space,Str "Olga",Space,Str "Weijers,",Space,Str "155\8211\&74.",Space,Str "Textes",Space,Str "et",Space,Str "\233tudes",Space,Str "du",Space,Str "moyen",Space,Str "\226ge",Space,Str "50.",Space,Str "Louvain-la-Neuve:",Space,Str "F\233d\233ration",Space,Str "Internationale",Space,Str "des",Space,Str "Instituts",Space,Str "d\8217\201tudes",Space,Str "M\233di\233vales."]],Div ("ref-thorndike:1955unde",[],[]) [Para [Str "Thorndike,",Space,Str "Lynn.",Space,Str "1955.",Space,Str "\8220Unde",Space,Str "versus.\8221",Space,Emph [Str "Traditio"],Space,Str "11:",Space,Str "163\8211\&93."]]]] pandoc-citeproc-0.10.5.1/tests/issue75.expected.native0000644000000000000000000000702112743760365020667 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/apa.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John"])])]),("id",MetaInlines [Str "test"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2006"]])])),("title",MetaInlines [Str "Test"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaInlines [Str "81"])])])]}) [Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "(Doe,",Space,Str "2006,",Space,Str "p.",Space,Str "6)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "chap.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2}] [Str "(Doe,",Space,Str "2006,",Space,Str "Chapter",Space,Str "6)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "n.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 3}] [Str "(Doe,",Space,Str "2006,",Space,Str "n.",Space,Str "6)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "pp.",Space,Str "34-36,",Space,Str "38-39"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 4}] [Str "(Doe,",Space,Str "2006,",Space,Str "pp.",Space,Str "34\8211\&36,",Space,Str "38\8211\&39)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "sec.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 5}] [Str "(Doe,",Space,Str "2006,",Space,Str "sec.",Space,Str "3)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "p.3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 6}] [Str "(Doe,",Space,Str "2006,",Space,Str "p.",Space,Str "3)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "33-35,",Space,Str "38-39"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 7}] [Str "(Doe,",Space,Str "2006,",Space,Str "pp.",Space,Str "33\8211\&35,",Space,Str "38\8211\&39)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "14"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 8}] [Str "(Doe,",Space,Str "2006,",Space,Str "p.",Space,Str "14)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Space,Str "bk.",Space,Str "VI"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 9}] [Str "(Doe,",Space,Str "2006,",Space,Str "bk.",Space,Str "VI)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "no.",Space,Str "6"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 10}] [Str "(Doe,",Space,Str "2006,",Space,Str "no.",Space,Str "6)"]] ,Para [Cite [Citation {citationId = "test", citationPrefix = [], citationSuffix = [Str ",",Space,Str "nos.",Space,Str "6",Space,Str "and",Space,Str "7"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 11}] [Str "(Doe,",Space,Str "2006,",Space,Str "no.",Space,Str "6",Space,Str "and",Space,Str "7)"]] ,Div ("refs",["references"],[]) [Div ("ref-test",[],[]) [Para [Str "Doe,",Space,Str "J.",Space,Str "(2006).",Space,Str "Test,",Space,Emph [Str "81"],Str "."]]]] pandoc-citeproc-0.10.5.1/tests/issue76.expected.native0000644000000000000000000000650612743760365020677 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "the",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item3"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "a",Space,Str "bazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaInlines [Str "Al"])])]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "1998"]])])),("title",MetaInlines [Str "foo",Space,Str "bar",Space,Str "baz:",Space,Str "an",Space,Str "abazbaz",Space,Str "bar",Space,Str "foo"]),("type",MetaInlines [Str "article-journal"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 1}] [Str "Author",Space,Str "(1998c)"],Str ",",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 2}] [Str "Author",Space,Str "(1998d)"],Str ",",Space,Cite [Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 3}] [Str "Author",Space,Str "(1998a)"],Str ",",Space,Cite [Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 4}] [Str "Author",Space,Str "(1998b)"]] ,Div ("refs",["references"],[]) [Div ("ref-item3",[],[]) [Para [Str "Author,",Space,Str "Al.",Space,Str "1998a.",Space,Str "\8220Foo",Space,Str "Bar",Space,Str "Baz:",Space,Str "A",Space,Str "Bazbaz",Space,Str "Bar",Space,Str "Foo.\8221"]],Div ("ref-item4",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "1998b.",Space,Str "\8220Foo",Space,Str "Bar",Space,Str "Baz:",Space,Str "An",Space,Str "Abazbaz",Space,Str "Bar",Space,Str "Foo.\8221"]],Div ("ref-item1",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "1998c.",Space,Str "\8220Foo",Space,Str "Bar",Space,Str "Baz:",Space,Str "Bazbaz",Space,Str "Bar",Space,Str "Foo.\8221"]],Div ("ref-item2",[],[]) [Para [Str "\8212\8212\8212.",Space,Str "1998d.",Space,Str "\8220Foo",Space,Str "Bar",Space,Str "Baz:",Space,Str "The",Space,Str "Bazbaz",Space,Str "Bar",Space,Str "Foo.\8221"]]]] pandoc-citeproc-0.10.5.1/tests/issue77.expected.native0000644000000000000000000000605013032532307020653 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-fullnote-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaInlines [Str "John,",Space,Str "III"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item1"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "van",Space,Str "Gogh"]),("given",MetaInlines [Str "Vincent"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item2"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Humboldt"]),("given",MetaInlines [Str "Alexander",Space,Str "von"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item3"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Bennett"]),("given",MetaInlines [Str "Frank",Space,Str "G.,!",Space,Str "Jr."]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item4"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Dumboldt"]),("given",MetaInlines [Str "Ezekiel,",Space,Str "III"]),("parse-names",MetaBool True)])]),("id",MetaInlines [Str "item5"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 2},Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 3},Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 4},Citation {citationId = "item5", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 5}] [Note [Para [Str "John",Space,Str "Doe",Space,Str "III,",Space,Str "n.d.;",Space,Str "Vincent",Space,Str "van",Space,Str "Gogh,",Space,Str "n.d.;",Space,Str "Alexander",Space,Str "von",Space,Str "Humboldt,",Space,Str "n.d.;",Space,Str "Frank",Space,Str "G.",Space,Str "Bennett,",Space,Str "Jr.,",Space,Str "n.d.;",Space,Str "Ezekiel",Space,Str "Dumboldt",Space,Str "III,",Space,Str "n.d."]]]] ,Div ("refs",["references"],[]) [Div ("ref-item4",[],[]) [Para [Str "Bennett,",Space,Str "Frank",Space,Str "G.,",Space,Str "Jr.,",Space,Str "n.d."]] ,Div ("ref-item1",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Str "III,",Space,Str "n.d."]] ,Div ("ref-item5",[],[]) [Para [Str "Dumboldt,",Space,Str "Ezekiel,",Space,Str "III,",Space,Str "n.d."]] ,Div ("ref-item3",[],[]) [Para [Str "Humboldt,",Space,Str "Alexander",Space,Str "von,",Space,Str "n.d."]] ,Div ("ref-item2",[],[]) [Para [Str "van",Space,Str "Gogh,",Space,Str "Vincent,",Space,Str "n.d."]]]] pandoc-citeproc-0.10.5.1/tests/issue82.expected.native0000644000000000000000000000237013032532307020650 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/chicago-annotated-bibliography.csl"]),("references",MetaList [MetaMap (fromList [("URL",MetaInlines [Str "https://www.worldcat.org/"]),("accessed",MetaMap (fromList [("date-parts",MetaList [MetaList [MetaString "2014",MetaString "9",MetaString "19"]])])),("author",MetaList [MetaMap (fromList [("literal",MetaInlines [Str "OCLC"])])]),("first-reference-note-number",MetaString "1"),("id",MetaInlines [Str "OCLC_i1099"]),("title",MetaInlines [Str "WorldCat"]),("type",MetaInlines [Str "webpage"])])])]}) [Header 1 ("title",[],[]) [Str "Title"] ,Para [Str "Some",Space,Str "text.",Note [Para [Str "Comment",Space,Str "regarding",Space,Str "text,",Space,Str "supported",Space,Str "by",Space,Str "citation",Space,Cite [Citation {citationId = "OCLC_i1099", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Str "OCLC,",Space,Str "\8220WorldCat.\8221"]]]] ,Div ("refs",["references"],[]) [Div ("ref-OCLC_i1099",[],[]) [Para [Str "OCLC.",Space,Str "\8220WorldCat.\8221",Space,Str "Accessed",Space,Str "September",Space,Str "19,",Space,Str "2014.",Space,Link ("",[],[]) [Str "https://www.worldcat.org/"] ("https://www.worldcat.org/",""),Str "."]]]] pandoc-citeproc-0.10.5.1/tests/mhra.expected.native0000644000000000000000000002447013032532307020302 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("csl",MetaInlines [Str "tests/mhra.csl"]),("link-citations",MetaBool True),("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])])),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2005")])),("publisher",MetaInlines [Str "Cambridge",Space,Str "University",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Cambridge"]),("title",MetaInlines [Str "First",Space,Str "Book"]),("type",MetaInlines [Str "book"])]),MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])])),("container-title",MetaInlines [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("year",MetaString "2006")])),("page",MetaInlines [Str "33-34"]),("title",MetaInlines [Str "Article"]),("type",MetaInlines [Str "article-journal"]),("volume",MetaString "6")]),MetaMap (fromList [("author",MetaList [MetaMap (fromList [("family",MetaInlines [Str "Doe"]),("given",MetaList [MetaInlines [Str "John"]])]),MetaMap (fromList [("family",MetaInlines [Str "Roe"]),("given",MetaList [MetaInlines [Str "Jenny"]])])]),("container-title",MetaInlines [Str "Third",Space,Str "Book"]),("editor",MetaMap (fromList [("family",MetaInlines [Str "Smith"]),("given",MetaList [MetaInlines [Str "Sam"]])])),("id",MetaInlines [Str "\1087\1091\1085\1082\1090\&3"]),("issued",MetaMap (fromList [("year",MetaString "2007")])),("publisher",MetaInlines [Str "Oxford",Space,Str "University",Space,Str "Press"]),("publisher-place",MetaInlines [Str "Oxford"]),("title",MetaInlines [Str "Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet"]),("type",MetaInlines [Str "chapter"])])])]}) [Header 1 ("pandoc-with-citeproc-hs",[],[]) [Str "Pandoc",Space,Str "with",Space,Str "citeproc-hs"] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 1}] [Note [Para [Span ("",["citeproc-not-found"],[("data-reference-id","nonexistent")]) [Strong [Str "???"]]]]]] ,Para [Cite [Citation {citationId = "nonexistent", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 2}] [Note [Para [Span ("",["citeproc-not-found"],[("data-reference-id","nonexistent")]) [Strong [Str "???"]]]]]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 3}] [Str "John",Space,Str "Doe",Str ".",Note [Para [Emph [Str "First",Space,Str "Book"],Space,Str "(Cambridge:",Space,Str "Cambridge",Space,Str "University",Space,Str "Press,",Space,Str "2005)."]]]] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 4}] [Str "Doe",Note [Para [Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "p.",Space,Str "30."]]],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 5}] [Str "Doe",Note [Para [Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "p.",Space,Str "30,",Space,Str "with",Space,Str "suffix."]]],Space,Str "says",Space,Str "blah."] ,Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 6},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "30"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 7},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "see",Space,Str "also"], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 8}] [Str "Doe",Note [Para [Emph [Str "First",Space,Str "Book"],Str ";",Space,Str "\8216Article\8217,",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"],Str ",",Space,Str "6",Space,Str "(2006),",Space,Str "33\8211\&34",Space,Str "(p.",Space,Str "30);",Space,Str "see",Space,Str "also",Space,Str "John",Space,Str "Doe",Space,Str "and",Space,Str "Jenny",Space,Str "Roe,",Space,Str "\8216Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet\8217,",Space,Str "in",Space,Emph [Str "Third",Space,Str "Book"],Str ",",Space,Str "ed.",Space,Str "by",Space,Str "Sam",Space,Str "Smith",Space,Str "(Oxford:",Space,Str "Oxford",Space,Str "University",Space,Str "Press,",Space,Str "2007)."]]],Space,Str "says",Space,Str "blah."] ,Para [Str "In",Space,Str "a",Space,Str "note.",Note [Para [Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "12"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 9}] [Str "Doe",Space,Str "and",Space,Str "Roe",Str ",",Space,Str "p.",Space,Str "12"],Space,Str "and",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "locators",Space,Cite [Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 10}] [Str "Doe",Space,Str "and",Space,Str "Roe"],Str "."]]] ,Para [Str "A",Space,Str "citation",Space,Str "group",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 11},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [Str "also"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 12}] [Note [Para [Str "See",Space,Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "chap.",Space,Str "3;",Space,Str "also",Space,Str "Doe",Space,Str "and",Space,Str "Roe,",Space,Str "pp.",Space,Str "34\8211\&35."]]]] ,Para [Str "Another",Space,Str "one",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "p.",Space,Str "34-35"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 13}] [Note [Para [Str "See",Space,Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "pp.",Space,Str "34\8211\&35."]]]] ,Para [Str "And",Space,Str "another",Space,Str "one",Space,Str "in",Space,Str "a",Space,Str "note.",Note [Para [Str "Some",Space,Str "citations",Space,Cite [Citation {citationId = "item1", citationPrefix = [Str "see"], citationSuffix = [Space,Str "chap.",Space,Str "3"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 14},Citation {citationId = "\1087\1091\1085\1082\1090\&3", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 15},Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 16}] [Str "see",Space,Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "chap.",Space,Str "3;",Space,Str "Doe",Space,Str "and",Space,Str "Roe;",Space,Str "Doe,",Space,Str "\8216Article\8217,",Space,Str "33\8211\&34"],Str "."]]] ,Para [Str "Citation",Space,Str "with",Space,Str "a",Space,Str "suffix",Space,Str "and",Space,Str "locator",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "pp.",Space,Str "33,",Space,Str "35-37,",Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 17}] [Note [Para [Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "pp.",Space,Str "33,",Space,Str "35\8211\&37,",Space,Str "and",Space,Str "nowhere",Space,Str "else."]]]] ,Para [Str "Citation",Space,Str "with",Space,Str "suffix",Space,Str "only",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Space,Str "and",Space,Str "nowhere",Space,Str "else"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 18}] [Note [Para [Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Space,Str "and",Space,Str "nowhere",Space,Str "else."]]]] ,Para [Str "Now",Space,Str "some",Space,Str "modifiers.",Note [Para [Str "Like",Space,Str "a",Space,Str "citation",Space,Str "without",Space,Str "author:",Space,Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 19}] [Emph [Str "First",Space,Str "Book"],Str ""],Str ",",Space,Str "and",Space,Str "now",Space,Str "Doe",Space,Str "with",Space,Str "a",Space,Str "locator",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [Space,Str "p.",Space,Str "44"], citationMode = SuppressAuthor, citationNoteNum = 0, citationHash = 20}] [Str "\8216Article\8217,",Space,Str "33\8211\&34",Space,Str "(p.",Space,Str "44)"],Str "."]]] ,Para [Str "With",Space,Str "some",Space,Str "markup",Str ".",Cite [Citation {citationId = "item1", citationPrefix = [Emph [Str "see"]], citationSuffix = [Space,Str "p.",Space,Strong [Str "32"]], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 21}] [Note [Para [Emph [Str "See"],Space,Str "Doe,",Space,Emph [Str "First",Space,Str "Book"],Str ",",Space,Str "p.",Space,Str "32."]]]] ,Header 1 ("references",["unnumbered"],[]) [Str "References"] ,Div ("refs",["references"],[]) [Div ("ref-item2",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Str "\8216Article\8217,",Space,Emph [Str "Journal",Space,Str "of",Space,Str "Generic",Space,Str "Studies"],Str ",",Space,Str "6",Space,Str "(2006),",Space,Str "33\8211\&34."]] ,Div ("ref-item1",[],[]) [Para [Str "---,",Space,Emph [Str "First",Space,Str "Book"],Space,Str "(Cambridge:",Space,Str "Cambridge",Space,Str "University",Space,Str "Press,",Space,Str "2005)."]] ,Div ("ref-\1087\1091\1085\1082\1090\&3",[],[]) [Para [Str "Doe,",Space,Str "John,",Space,Str "and",Space,Str "Jenny",Space,Str "Roe,",Space,Str "\8216Why",Space,Str "Water",Space,Str "Is",Space,Str "Wet\8217,",Space,Str "in",Space,Emph [Str "Third",Space,Str "Book"],Str ",",Space,Str "ed.",Space,Str "by",Space,Str "Sam",Space,Str "Smith",Space,Str "(Oxford:",Space,Str "Oxford",Space,Str "University",Space,Str "Press,",Space,Str "2007)."]]]] pandoc-citeproc-0.10.5.1/tests/no-author.expected.native0000644000000000000000000001020412743760365021274 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "A"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item2"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "B"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item3"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "C"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "D"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item5"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "E"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Magazine"]),("id",MetaInlines [Str "item4"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "D"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Newspaper"]),("id",MetaInlines [Str "item5"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "E"]),("type",MetaInlines [Str "article-magazine"])]),MetaMap (fromList [("container-title",MetaInlines [Str "Newspaper"]),("id",MetaInlines [Str "item6"]),("issued",MetaMap (fromList [("year",MetaString "2012")])),("title",MetaInlines [Str "Title",Space,Str "F"]),("type",MetaInlines [Str "article-magazine"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [Str "p.",Space,Str "3"], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 1}] [Str "(",Emph [Str "Magazine"],Space,Str "2012a,",Space,Str "3)"],Str ",",Space,Cite [Citation {citationId = "item2", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 2}] [Str "(",Emph [Str "Magazine"],Space,Str "2012b)"],Str ",",Space,Cite [Citation {citationId = "item3", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 3}] [Str "(",Emph [Str "Magazine"],Space,Str "2012c)"],Str ",",Space,Cite [Citation {citationId = "item4", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 4}] [Str "(",Emph [Str "Magazine"],Space,Str "2012d)"],Str ",",Space,Cite [Citation {citationId = "item5", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 5}] [Str "(",Emph [Str "Magazine"],Space,Str "2012e)"],Str ",",Space,Cite [Citation {citationId = "item6", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 6}] [Str "(",Emph [Str "Newspaper"],Space,Str "2012)"]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Emph [Str "Magazine"],Str ".",Space,Str "2012a.",Space,Str "\8220Title",Space,Str "A.\8221"]],Div ("ref-item2",[],[]) [Para [Emph [Str "Magazine"],Str ".",Space,Str "2012b.",Space,Str "\8220Title",Space,Str "B.\8221"]],Div ("ref-item3",[],[]) [Para [Emph [Str "Magazine"],Str ".",Space,Str "2012c.",Space,Str "\8220Title",Space,Str "C.\8221"]],Div ("ref-item4",[],[]) [Para [Emph [Str "Magazine"],Str ".",Space,Str "2012d.",Space,Str "\8220Title",Space,Str "D.\8221"]],Div ("ref-item5",[],[]) [Para [Emph [Str "Magazine"],Str ".",Space,Str "2012e.",Space,Str "\8220Title",Space,Str "E.\8221"]],Div ("ref-item6",[],[]) [Para [Emph [Str "Newspaper"],Str ".",Space,Str "2012.",Space,Str "\8220Title",Space,Str "F.\8221"]]]] pandoc-citeproc-0.10.5.1/tests/number-of-volumes.expected.native0000644000000000000000000000166112743760365022751 0ustar0000000000000000Pandoc (Meta {unMeta = fromList [("references",MetaList [MetaMap (fromList [("author",MetaMap (fromList [("family",MetaInlines [Str "Author"]),("given",MetaList [MetaInlines [Str "Al"]])])),("id",MetaInlines [Str "item1"]),("issued",MetaMap (fromList [("year",MetaString "2013")])),("language",MetaInlines [Str "en-US"]),("number-of-volumes",MetaString "2"),("publisher",MetaInlines [Str "Publisher"]),("publisher-place",MetaInlines [Str "Location"]),("title",MetaInlines [Str "Title"]),("type",MetaInlines [Str "book"])])])]}) [Para [Cite [Citation {citationId = "item1", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 0, citationHash = 1}] [Str "Author",Space,Str "(2013)"]] ,Div ("refs",["references"],[]) [Div ("ref-item1",[],[]) [Para [Str "Author,",Space,Str "Al.",Space,Str "2013.",Space,Emph [Str "Title"],Str ".",Space,Str "2",Space,Str "vols.",Space,Str "Location:",Space,Str "Publisher."]]]] pandoc-citeproc-0.10.5.1/tests/apa.csl0000644000000000000000000003721012743760365015622 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/chicago-annotated-bibliography.csl0000644000000000000000000011277612743760365023115 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/chicago-author-date-with-original-date-and-status.csl0000644000000000000000000004475212743760365026451 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/chicago-fullnote-bibliography.csl0000644000000000000000000011215412743760365022756 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/chicago-note-bibliography.csl0000644000000000000000000007656212743760365022107 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/ieee.csl0000644000000000000000000002626512743760365016000 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/issue160.csl0000644000000000000000000000154413053647342016433 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/issue58.csl0000644000000000000000000004346212743760365016374 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/jats.csl0000644000000000000000000002332513067446125016017 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/mhra.csl0000644000000000000000000002775512743760365016025 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/modern-humanities-research-association.csl0000644000000000000000000003465612743760365024630 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/science.csl0000644000000000000000000002022612743760365016471 0ustar0000000000000000 pandoc-citeproc-0.10.5.1/tests/biblio.bib0000644000000000000000000000071312743760365016272 0ustar0000000000000000@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{пункт3, 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" } pandoc-citeproc-0.10.5.1/tests/biblio2yaml/basic.bibtex0000644000000000000000000000221112743760365021034 0ustar0000000000000000@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{пункт3, 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" } --- references: - id: item1 type: book author: - family: Doe given: John issued: - year: '2005' title: First book publisher: Cambridge University Press publisher-place: Cambridge - id: item2 type: article-journal author: - family: Doe given: John issued: - year: '2006' title: Article container-title: Journal of Generic Studies page: '33-34' volume: '6' - id: пункт3 type: chapter author: - family: Doe given: John - family: Roe given: Jenny editor: - family: Smith given: Sam issued: - year: '2007' title: Why water is wet container-title: Third book publisher: Oxford University Press publisher-place: Oxford ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/aksin.biblatex0000644000000000000000000000374412743760365021411 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Aksin et al. 2006) Aksin, Özge, Hayati Türkmen, Levent Artok, Bekir Çetinkaya, Chaoying Ni, Orhan Büyükgüngör, and Erhan Özkal. 2006. “Effect of Immobilization on Catalytic Characteristics of Saturated Pd-N-heterocyclic Carbenes in Mizoroki-Heck Reactions.” *J. Organomet. Chem.* 691 (13): 3027–3036. Formatted with pandoc and apa.csl, 2013-10-23: (Aksin et al., 2006) Aksin, Ö., Türkmen, H., Artok, L., Çetinkaya, B., Ni, C., Büyükgüngör, O., & Özkal, E. (2006). Effect of immobilization on catalytic characteristics of saturated Pd-N-heterocyclic carbenes in Mizoroki-Heck reactions. *J. Organomet. Chem.*, *691*(13), 3027–3036. } @string{ jomch = {J.~Organomet. Chem.} } @Article{aksin, author = {Aks{\i}n, {\"O}zge and T{\"u}rkmen, Hayati and Artok, Levent and {\c{C}}etinkaya, Bekir and Ni, Chaoying and B{\"u}y{\"u}kg{\"u}ng{\"o}r, Orhan and {\"O}zkal, Erhan}, title = {Effect of immobilization on catalytic characteristics of saturated {Pd-N}-heterocyclic carbenes in {Mizoroki-Heck} reactions}, journaltitle = jomch, date = 2006, volume = 691, number = 13, pages = {3027-3036}, indextitle = {Effect of immobilization on catalytic characteristics}, } --- references: - id: aksin type: article-journal author: - family: Aksin given: Özge - family: Türkmen given: Hayati - family: Artok given: Levent - family: Çetinkaya given: Bekir - family: Ni given: Chaoying - family: Büyükgüngör given: Orhan - family: Özkal given: Erhan issued: - year: '2006' title: Effect of immobilization on catalytic characteristics of saturated Pd-N-heterocyclic carbenes in Mizoroki-Heck reactions container-title: J. Organomet. Chem. page: '3027-3036' volume: '691' issue: '13' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/almendro.biblatex0000644000000000000000000000327212743760365022101 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Almendro et al. 1998) Almendro, José L., Jacinto Martín, Alberto Sánchez, and Fernando Nozal. 1998. “Elektromagnetisches Signalhorn.” Formatted with pandoc and apa.csl, 2013-10-23: (Almendro, Martín, Sánchez, & Nozal, 1998) Almendro, J. L., Martín, J., Sánchez, A., & Nozal, F. (1998). Elektromagnetisches Signalhorn. NOTES: - CSL styles’ handling of patent items needs to be improved } @Patent{almendro, author = {Almendro, Jos{\'e} L. and Mart{\'i}n, Jacinto and S{\'a}nchez, Alberto and Nozal, Fernando}, title = {Elektromagnetisches Signalhorn}, number = {EU-29702195U}, date = 1998, location = {countryfr and countryuk and countryde}, hyphenation = {german}, annotation = {This is a patent entry with a location field. The number is given in the number field. Note the format of the location field in the database file. Compare laufenberg, sorace, and kowalik}, } --- references: - id: almendro type: patent author: - family: Almendro given: José L. - family: Martín given: Jacinto - family: Sánchez given: Alberto - family: Nozal given: Fernando issued: - year: '1998' title: Elektromagnetisches Signalhorn jurisdiction: France; United Kingdom; Germany annote: This is a patent entry with a location field. The number is given in the number field. Note the format of the location field in the database file. Compare laufenberg, sorace, and kowalik number: EU-29702195U language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/angenendt.biblatex0000644000000000000000000000304612743760365022242 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Angenendt 2002) Angenendt, Arnold. 2002. “In Honore Salvatoris – Vom Sinn und Unsinn der Patrozinienkunde.” *Revue d’Histoire Ecclésiastique* 97: 431–456, 791–823. Formatted with pandoc and apa.csl, 2013-10-23: (Angenendt, 2002) Angenendt, A. (2002). In Honore Salvatoris – Vom Sinn und Unsinn der Patrozinienkunde. *Revue d’Histoire Ecclésiastique*, *97*, 431–456, 791–823. } @Article{angenendt, author = {Angenendt, Arnold}, title = {In Honore Salvatoris~-- Vom Sinn und Unsinn der Patrozinienkunde}, journaltitle = {Revue d'Histoire Eccl{\'e}siastique}, date = 2002, volume = 97, pages = {431--456, 791--823}, hyphenation = {german}, indextitle = {In Honore Salvatoris}, shorttitle = {In Honore Salvatoris}, annotation = {A German article in a French journal. Apart from that, a typical article entry. Note the indextitle field}, } --- references: - id: angenendt type: article-journal author: - family: Angenendt given: Arnold issued: - year: '2002' title: In Honore Salvatoris – Vom Sinn und Unsinn der Patrozinienkunde title-short: In Honore Salvatoris container-title: Revue d’Histoire Ecclésiastique page: 431-456, 791-823 volume: '97' annote: A German article in a French journal. Apart from that, a typical article entry. Note the indextitle field language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/aristotle-anima.biblatex0000644000000000000000000000213512743760365023366 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Aristotle 1907) Aristotle. 1907. *De Anima*. Edited by Robert Drew Hicks. Cambridge: Cambridge University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Aristotle, 1907) Aristotle. (1907). *De anima*. (R. D. Hicks, Ed.). Cambridge: Cambridge University Press. } @string{ cup = {Cambridge University Press} } @Book{aristotle:anima, author = {Aristotle}, title = {De Anima}, date = 1907, editor = {Hicks, Robert Drew}, publisher = cup, location = {Cambridge}, keywords = {primary}, hyphenation = {british}, annotation = {A book entry with an author and an editor}, } --- references: - id: aristotle:anima type: book author: - family: Aristotle editor: - family: Hicks given: Robert Drew issued: - year: '1907' title: De anima publisher: Cambridge University Press publisher-place: Cambridge annote: A book entry with an author and an editor keyword: primary language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/aristotle-physics.biblatex0000644000000000000000000000220612743760365023762 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Aristotle 1929) Aristotle. 1929. *Physics*. Translated by P. H. Wicksteed and F. M. Cornford. New York: G. P. Putnam. Formatted with pandoc and apa.csl, 2013-10-23: (Aristotle, 1929) Aristotle. (1929). *Physics*. (P. H. Wicksteed & F. M. Cornford, Trans.). New York: G. P. Putnam. } @Book{aristotle:physics, author = {Aristotle}, title = {Physics}, date = 1929, translator = {Wicksteed, P. H. and Cornford, F. M.}, publisher = {G. P. Putnam}, location = {New York}, keywords = {primary}, hyphenation = {american}, shorttitle = {Physics}, annotation = {A book entry with a translator field}, } --- references: - id: aristotle:physics type: book author: - family: Aristotle translator: - family: Wicksteed given: P. H. - family: Cornford given: F. M. issued: - year: '1929' title: Physics title-short: Physics publisher: G. P. Putnam publisher-place: New York annote: A book entry with a translator field keyword: primary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/aristotle-poetics.biblatex0000644000000000000000000000230712743760365023750 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Aristotle 1968) Aristotle. 1968. *Poetics*. Edited by D. W. Lucas. Clarendon Aristotle. Oxford: Clarendon Press. Formatted with pandoc and apa.csl, 2013-10-23: (Aristotle, 1968) Aristotle. (1968). *Poetics*. (D. W. Lucas, Ed.). Oxford: Clarendon Press. } @Book{aristotle:poetics, author = {Aristotle}, title = {Poetics}, date = 1968, editor = {Lucas, D. W.}, series = {Clarendon {Aristotle}}, publisher = {Clarendon Press}, location = {Oxford}, keywords = {primary}, hyphenation = {british}, shorttitle = {Poetics}, annotation = {A book entry with an author and an editor as well as a series field}, } --- references: - id: aristotle:poetics type: book author: - family: Aristotle editor: - family: Lucas given: D. W. issued: - year: '1968' title: Poetics title-short: Poetics collection-title: Clarendon Aristotle publisher: Clarendon Press publisher-place: Oxford annote: A book entry with an author and an editor as well as a series field keyword: primary language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/aristotle-rhetoric.biblatex0000644000000000000000000000353012743760365024120 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Aristotle 1877) Aristotle. 1877. *The Rhetoric of Aristotle with a Commentary by the Late Edward Meredith Cope*. Edited by Edward Meredith Cope. 3. Cambridge University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Aristotle, 1877) Aristotle. (1877). *The rhetoric of Aristotle with a commentary by the late Edward Meredith Cope*. (E. M. Cope, Ed.) (1-3). Cambridge University Press. NOTES: - biblio2yaml - commentator has no counterpart in CSL } @string{ cup = {Cambridge University Press} } @Book{aristotle:rhetoric, author = {Aristotle}, title = {The Rhetoric of {Aristotle} with a commentary by the late {Edward Meredith Cope}}, date = 1877, editor = {Cope, Edward Meredith}, commentator = {Cope, Edward Meredith}, volumes = 3, publisher = cup, keywords = {primary}, hyphenation = {british}, sorttitle = {Rhetoric of Aristotle}, indextitle = {Rhetoric of {Aristotle}, The}, shorttitle = {Rhetoric}, annotation = {A commented edition. Note the concatenation of the editor and commentator fields as well as the volumes, sorttitle, and indextitle fields}, } --- references: - id: aristotle:rhetoric type: book author: - family: Aristotle editor: - family: Cope given: Edward Meredith issued: - year: '1877' title: The rhetoric of Aristotle with a commentary by the late Edward Meredith Cope title-short: Rhetoric publisher: Cambridge University Press number-of-volumes: '3' annote: A commented edition. Note the concatenation of the editor and commentator fields as well as the volumes, sorttitle, and indextitle fields keyword: primary language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/article.biblatex0000644000000000000000000000736512743760365021732 0ustar0000000000000000@comment{ - contains: - an article entry with just the required fields - an article entry with required and all optional fields - notes: - year, month to be ignored if date is present - journal to be ignored if journaltitle is present - editortype, editoratype, editorbtype, editorctype, pubstate, series contain keys which, unless corresponding CSL terms exist, require locale-specific expansion - limitations: - annotator, commentator, eid, eprint, eprintclass, eprinttype, issuetitle, issuesubtitle, language, origlanguage have no matching counterparts in CSL - for editor, editora, editorb, editorc (plus editortype, editoratype, editorbtype, editorctype) only a subset, editor and director, has matching counterparts in CSL - kludges: - note + addendum -> CSL note - number + issue -> CSL issue - handling of titleaddon - handling of (journal) series - done properly, this should be mapped to some CSL variable (version? edition? collection-number?), CSL styles would have to be adapted - slightly better kludge would map integer to ordinal + "ser." ("3" -> "3rd ser."); localization keys "newseries" -> "new ser.", "oldseries" -> "old ser."; and print all other values as is -- but still wouldn't fit all styles or locales. } @article{article-req, Author = {Author, Ann}, Date = {2013-07-29}, Hyphenation = {english}, Journaltitle = {The Journaltitle}, Title = {An Article Entry with Just the Required Fields}} @article{article-opt, Addendum = {The Addendum}, Annotator = {Annotator, A.}, Author = {Author, Jr., Ann A.}, Commentator = {Commentator, C.}, Date = {2008-12-31}, Doi = {10.1086/520976}, Editor = {Editor, Edward}, Editora = {Editor, A.}, Editorb = {Editor, B.}, Editorc = {Editor, C.}, Eid = {eid}, Eprint = {eprint}, Eprintclass = {eprintclass}, Eprinttype = {eprinttype}, Hyphenation = {english}, Issn = {issn}, Issue = {issue}, Issuesubtitle = {The Issuesubtitle}, Issuetitle = {The Issuetitle}, Journalsubtitle = {The Journalsubtitle}, Journaltitle = {The Journaltitle}, Journal = {The Journal}, Language = {language}, Month = {08}, Year = {2007}, Note = {The Note}, Number = {number}, Origlanguage = {origlanguage}, Pages = {pages}, Pubstate = {inpress}, Series = {newseries}, Subtitle = {The Subtitle}, Title = {An Article Entry with the Required and All Optional Fields}, Titleaddon = {The Titleaddon}, Translator = {Translator, Ted}, Url = {http://foo.bar.baz/}, Urldate = {2013-07-29}, Version = {version}, Volume = {volume}, } --- references: - id: article-req type: article-journal author: - family: Author given: Ann issued: - year: '2013' month: '7' day: '29' title: An article entry with just the required fields container-title: The Journaltitle language: en-US - id: article-opt type: article-journal author: - family: Author given: Ann A. suffix: Jr. editor: - family: Editor given: Edward translator: - family: Translator given: Ted issued: - year: '2008' month: '12' day: '31' accessed: - year: '2013' month: '7' day: '29' title: 'An article entry with the required and all optional fields: The subtitle. The titleaddon' title-short: An article entry with the required and all optional fields container-title: 'The Journaltitle: The Journalsubtitle' collection-title: new series page: pages version: version volume: volume issue: number, issue status: in press note: The Note. The Addendum URL: http://foo.bar.baz/ DOI: 10.1086/520976 ISSN: issn language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/augustine.biblatex0000644000000000000000000000205512743760365022302 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Augustine 1995) Augustine, Robert L. 1995. *Heterogeneous Catalysis for the Synthetic Chemist*. New York: Marcel Dekker. Formatted with pandoc and apa.csl, 2013-10-23: (Augustine, 1995) Augustine, R. L. (1995). *Heterogeneous catalysis for the synthetic chemist*. New York: Marcel Dekker. } @Book{augustine, author = {Augustine, Robert L.}, title = {Heterogeneous catalysis for the synthetic chemist}, date = 1995, publisher = {Marcel Dekker}, location = {New York}, hyphenation = {american}, shorttitle = {Heterogeneous catalysis}, annotation = {A plain book entry}, } --- references: - id: augustine type: book author: - family: Augustine given: Robert L. issued: - year: '1995' title: Heterogeneous catalysis for the synthetic chemist title-short: Heterogeneous catalysis publisher: Marcel Dekker publisher-place: New York annote: A plain book entry language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/averroes-bland.biblatex0000644000000000000000000000452312743760365023204 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Averroes 1982) Averroes. 1982. *The Epistle on the Possibility of Conjunction with the Active Intellect by Ibn Rushd with the Commentary of Moses Narboni*. Kalman P. Bland. Moreshet: Studies in Jewish History, Literature and Thought 7. New York: Jewish Theological Seminary of America. Formatted with pandoc and apa.csl, 2013-10-23: (Averroes, 1982) Averroes. (1982). *The epistle on the possibility of conjunction with the active intellect by Ibn Rushd with the commentary of Moses Narboni*. (K. P. Bland). New York: Jewish Theological Seminary of America. NOTES: - citeproc - term "edited and translated by" missing } @Book{averroes-bland, author = {Averroes}, title = {The Epistle on the Possibility of Conjunction with the Active Intellect by {Ibn Rushd} with the Commentary of {Moses Narboni}}, date = 1982, editor = {Bland, Kalman P.}, translator = {Bland, Kalman P.}, series = {Moreshet: {Studies} in {Jewish} History, Literature and Thought}, number = 7, publisher = {Jewish Theological Seminary of America}, location = {New York}, keywords = {primary}, hyphenation = {american}, indextitle = {Epistle on the Possibility of Conjunction, The}, shorttitle = {Possibility of Conjunction}, annotation = {A book entry with a series and a number. Note the concatenation of the editor and translator fields as well as the indextitle field}, } --- references: - id: averroes-bland type: book author: - family: Averroes editor: - family: Bland given: Kalman P. translator: - family: Bland given: Kalman P. issued: - year: '1982' title: The epistle on the possibility of conjunction with the active intellect by Ibn Rushd with the commentary of Moses Narboni title-short: Possibility of conjunction collection-title: 'Moreshet: Studies in Jewish history, literature and thought' collection-number: '7' publisher: Jewish Theological Seminary of America publisher-place: New York annote: A book entry with a series and a number. Note the concatenation of the editor and translator fields as well as the indextitle field keyword: primary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/averroes-hannes.biblatex0000644000000000000000000000444012743760365023376 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Averroes 1892) Averroes. 1892. *Des Averroës Abhandlung: “Über die Möglichkeit der Conjunktion” oder “Über den materiellen Intellekt”*. Ludwig Hannes. Halle an der Saale: C. A. Kaemmerer. Formatted with pandoc and apa.csl, 2013-10-23: (Averroes, 1892) Averroes. (1892). *Des Averroës Abhandlung: “Über die Möglichkeit der Conjunktion” oder “Über den materiellen Intellekt”*. (L. Hannes). Halle an der Saale: C. A. Kaemmerer. NOTES: - citeproc - term "edited and translated by" missing } @Book{averroes-hannes, author = {Averroes}, title = {Des Averro{\"e}s Abhandlung: \mkbibquote{{\"U}ber die M{\"o}glichkeit der Conjunktion} oder \mkbibquote{{\"U}ber den materiellen Intellekt}}, date = 1892, editor = {Hannes, Ludwig}, translator = {Hannes, Ludwig}, annotator = {Hannes, Ludwig}, publisher = {C.~A. Kaemmerer}, location = {Halle an der Saale}, keywords = {primary}, hyphenation = {german}, sorttitle = {Uber die Moglichkeit der Conjunktion}, indexsorttitle= {Uber die Moglichkeit der Conjunktion}, indextitle = {{\"U}ber die M{\"o}glichkeit der Conjunktion}, shorttitle = {{\"U}ber die M{\"o}glichkeit der Conjunktion}, annotation = {An annotated edition. Note the concatenation of the editor, translator, and annotator fields. Also note the shorttitle, indextitle, sorttitle, and indexsorttitle fields}, } --- references: - id: averroes-hannes type: book author: - family: Averroes editor: - family: Hannes given: Ludwig translator: - family: Hannes given: Ludwig issued: - year: '1892' title: 'Des Averroës Abhandlung: “Über die Möglichkeit der Conjunktion” oder “Über den materiellen Intellekt”' title-short: Über die Möglichkeit der Conjunktion publisher: C. A. Kaemmerer publisher-place: Halle an der Saale annote: An annotated edition. Note the concatenation of the editor, translator, and annotator fields. Also note the shorttitle, indextitle, sorttitle, and indexsorttitle fields keyword: primary language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/averroes-hercz.biblatex0000644000000000000000000000421012743760365023230 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Averroes 1869) Averroes. 1869. *Drei Abhandlungen über die Conjunction des separaten Intellects mit dem Menschen: Von Averroes (Vater und Sohn), aus dem Arabischen übersetzt von Samuel Ibn Tibbon*. J. Hercz. Berlin: S. Hermann. Formatted with pandoc and apa.csl, 2013-10-23: (Averroes, 1869) Averroes. (1869). *Drei Abhandlungen über die Conjunction des separaten Intellects mit dem Menschen: Von Averroes (Vater und Sohn), aus dem Arabischen übersetzt von Samuel Ibn Tibbon*. (J. Hercz). Berlin: S. Hermann. NOTES: - citeproc - term "edited and translated by" missing } @Book{averroes-hercz, author = {Averroes}, title = {Drei Abhandlungen {\"u}ber die Conjunction des separaten Intellects mit dem Menschen}, date = 1869, editor = {Hercz, J.}, translator = {Hercz, J.}, publisher = {S.~Hermann}, location = {Berlin}, keywords = {primary}, hyphenation = {german}, indexsorttitle= {Drei Abhandlungen uber die Conjunction}, indextitle = {Drei Abhandlungen {\"u}ber die Conjunction}, subtitle = {Von Averroes (Vater und Sohn), aus dem Arabischen {\"u}bersetzt von Samuel Ibn Tibbon}, shorttitle = {Drei Abhandlungen}, annotation = {A book entry. Note the concatenation of the editor and translator fields as well as the indextitle and indexsorttitle fields}, } --- references: - id: averroes-hercz type: book author: - family: Averroes editor: - family: Hercz given: J. translator: - family: Hercz given: J. issued: - year: '1869' title: 'Drei Abhandlungen über die Conjunction des separaten Intellects mit dem Menschen: Von Averroes (Vater und Sohn), aus dem Arabischen übersetzt von Samuel Ibn Tibbon' title-short: Drei Abhandlungen publisher: S. Hermann publisher-place: Berlin annote: A book entry. Note the concatenation of the editor and translator fields as well as the indextitle and indexsorttitle fields keyword: primary language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/baez-article.biblatex0000644000000000000000000000360012743760365022635 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Baez and Lauda 2004) Baez, John C., and Aaron D. Lauda. 2004. “Higher-dimensional Algebra V: 2-groups” (version 3). *Theory and Applications of Categories* 12: 423–491. Formatted with pandoc and apa.csl, 2013-10-23: (Baez & Lauda, 2004) Baez, J. C., & Lauda, A. D. (2004). Higher-dimensional algebra V: 2-groups. *Theory and Applications of Categories*, *12*, 423–491. NOTES: - biblio2yaml - eprint: see baez-online } @Article{baez-article, author = {Baez, John C. and Lauda, Aaron D.}, title = {Higher-Dimensional Algebra {V}: 2-Groups}, journaltitle = {Theory and Applications of Categories}, date = 2004, volume = 12, pages = {423-491}, version = 3, eprint = {math/0307200v3}, eprinttype = {arxiv}, hyphenation = {american}, annotation = {An article with eprint and eprinttype fields. Note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled. Compare baez\slash online, which is the same item given as an online entry}, } --- references: - id: baez-article type: article-journal author: - family: Baez given: John C. - family: Lauda given: Aaron D. issued: - year: '2004' title: 'Higher-dimensional algebra V: 2-groups' title-short: Higher-dimensional algebra V container-title: Theory and Applications of Categories page: '423-491' version: '3' volume: '12' annote: An article with eprint and eprinttype fields. Note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled. Compare baez/online, which is the same item given as an online entry URL: http://arxiv.org/abs/math/0307200v3 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/baez-online.biblatex0000644000000000000000000000323712743760365022504 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Baez and Lauda 2004) Baez, John C., and Aaron D. Lauda. 2004. “Higher-dimensional Algebra V: 2-groups” (version 3). October 27. Formatted with pandoc and apa.csl, 2013-10-23: (Baez & Lauda, 2004) Baez, J. C., & Lauda, A. D. (2004, October 27). Higher-dimensional algebra V: 2-groups. NOTES: - biblio2yaml: - eprinttype = {arxiv}, eprint = {math/0307200v3}, should be converted to a url: http://arxiv.org/abs/math/0307200v3 (prefix http://arxiv.org/abs/ seems to work for all arxiv material) } @Online{baez-online, author = {Baez, John C. and Lauda, Aaron D.}, title = {Higher-Dimensional Algebra {V}: 2-Groups}, date = {2004-10-27}, version = 3, hyphenation = {american}, eprinttype = {arxiv}, eprint = {math/0307200v3}, annotation = {An online reference from arXiv. Note the eprint and eprinttype fields. Compare baez\slash article which is the same item given as an article entry with eprint information}, } --- references: - id: baez-online type: webpage author: - family: Baez given: John C. - family: Lauda given: Aaron D. issued: - year: '2004' month: '10' day: '27' title: 'Higher-dimensional algebra V: 2-groups' title-short: Higher-dimensional algebra V version: '3' annote: An online reference from arXiv. Note the eprint and eprinttype fields. Compare baez/article which is the same item given as an article entry with eprint information URL: http://arxiv.org/abs/math/0307200v3 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/bertram.biblatex0000644000000000000000000000262212743760365021732 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Bertram and Wentworth 1996) Bertram, Aaron, and Richard Wentworth. 1996. “Gromov Invariants for Holomorphic Maps on Riemann Surfaces.” *J. Amer. Math. Soc.* 9 (2): 529–571. Formatted with pandoc and apa.csl, 2013-10-23: (Bertram & Wentworth, 1996) Bertram, A., & Wentworth, R. (1996). Gromov invariants for holomorphic maps on Riemann surfaces. *J. Amer. Math. Soc.*, *9*(2), 529–571. } @string{ jams = {J.~Amer. Math. Soc.} } @Article{bertram, author = {Bertram, Aaron and Wentworth, Richard}, title = {Gromov invariants for holomorphic maps on {Riemann} surfaces}, journaltitle = jams, date = 1996, volume = 9, number = 2, pages = {529-571}, hyphenation = {american}, shorttitle = {Gromov invariants}, annotation = {An article entry with a volume and a number field}, } --- references: - id: bertram type: article-journal author: - family: Bertram given: Aaron - family: Wentworth given: Richard issued: - year: '1996' title: Gromov invariants for holomorphic maps on Riemann surfaces title-short: Gromov invariants container-title: J. Amer. Math. Soc. page: '529-571' volume: '9' issue: '2' annote: An article entry with a volume and a number field language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/bibstring-resolution.biblatex0000644000000000000000000000032612743760365024461 0ustar0000000000000000@book{item1, Title = {The Title: \bibstring{newseries}}, Hyphenation = {english} } --- references: - id: item1 type: book title: 'The title: new series' title-short: The title language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/book-averroes.biblatex0000644000000000000000000001050213013615770023036 0ustar0000000000000000@comment{ adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib @book{averroes/bland, Annotation = {A book entry with a series and a number. Note the concatenation of the editor and translator fields as well as the indextitle field}, Author = {Averroes}, Date = 1982, Editor = {Bland, Kalman P.}, Hyphenation = {american}, Indextitle = {Epistle on the Possibility of Conjunction, The}, Keywords = {primary}, Location = {New York}, Number = 7, Publisher = {Jewish Theological Seminary of America}, Series = {{Moreshet: Studies in Jewish History, Literature and Thought}}, Shorttitle = {Possibility of Conjunction}, Title = {The Epistle on the Possibility of Conjunction with the Active Intellect by {Ibn Rushd} with the Commentary of {Moses Narboni}}, Translator = {Bland, Kalman P.}} @book{averroes/hannes, Annotation = {An annotated edition. Note the concatenation of the editor, translator, and annotator fields. Also note the shorttitle, indextitle, sorttitle, and indexsorttitle fields}, Annotator = {Hannes, Ludwig}, Author = {Averroes}, Date = 1892, Editor = {Hannes, Ludwig}, Hyphenation = {german}, Indexsorttitle = {Uber die Moglichkeit der Conjunktion}, Indextitle = {Über die Möglichkeit der Conjunktion}, Keywords = {primary}, Location = {Halle an der Saale}, Publisher = {C.~A. Kaemmerer}, Shorttitle = {Über die Möglichkeit der Conjunktion}, Sorttitle = {Uber die Moglichkeit der Conjunktion}, Title = {Des Averroës Abhandlung: \mkbibquote{Über die Möglichkeit der Conjunktion} oder \mkbibquote{Über den materiellen Intellekt}}, Translator = {Hannes, Ludwig}} @book{averroes/hercz, Annotation = {A book entry. Note the concatenation of the editor and translator fields as well as the indextitle and indexsorttitle fields}, Author = {Averroes}, Date = 1869, Editor = {Hercz, J.}, Hyphenation = {german}, Indexsorttitle = {Drei Abhandlungen uber die Conjunction}, Indextitle = {Drei Abhandlungen über die Conjunction}, Keywords = {primary}, Location = {Berlin}, Publisher = {S.~Hermann}, Shorttitle = {Drei Abhandlungen}, Subtitle = {Von Averroes (Vater und Sohn), aus dem Arabischen übersetzt von Samuel Ibn Tibbon}, Title = {Drei Abhandlungen über die Conjunction des separaten Intellects mit dem Menschen}, Translator = {Hercz, J.}} --- references: - id: averroes/bland type: book author: - family: Averroes editor: - family: Bland given: Kalman P. translator: - family: Bland given: Kalman P. issued: - year: '1982' title: The epistle on the possibility of conjunction with the active intellect by Ibn Rushd with the commentary of Moses Narboni title-short: Possibility of conjunction collection-title: '[Moreshet: Studies in Jewish History, Literature and Thought]{.nocase}' collection-number: '7' publisher: Jewish Theological Seminary of America publisher-place: New York annote: A book entry with a series and a number. Note the concatenation of the editor and translator fields as well as the indextitle field keyword: primary language: en-US - id: averroes/hannes type: book author: - family: Averroes editor: - family: Hannes given: Ludwig translator: - family: Hannes given: Ludwig issued: - year: '1892' title: 'Des Averroës Abhandlung: “Über die Möglichkeit der Conjunktion” oder “Über den materiellen Intellekt”' title-short: Über die Möglichkeit der Conjunktion publisher: C. A. Kaemmerer publisher-place: Halle an der Saale annote: An annotated edition. Note the concatenation of the editor, translator, and annotator fields. Also note the shorttitle, indextitle, sorttitle, and indexsorttitle fields keyword: primary language: de-DE - id: averroes/hercz type: book author: - family: Averroes editor: - family: Hercz given: J. translator: - family: Hercz given: J. issued: - year: '1869' title: 'Drei Abhandlungen über die Conjunction des separaten Intellects mit dem Menschen: Von Averroes (Vater und Sohn), aus dem Arabischen übersetzt von Samuel Ibn Tibbon' title-short: Drei Abhandlungen publisher: S. Hermann publisher-place: Berlin annote: A book entry. Note the concatenation of the editor and translator fields as well as the indextitle and indexsorttitle fields keyword: primary language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/book-coleridge.biblatex0000644000000000000000000000341012743760365023157 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib TODO (as a stopgap): Combine biblatex “volume = 7” and “part = 2” to CSL “volume: 7.2” } @book{coleridge, Annotation = {One (partial) volume of a multivolume book. This is a book entry with a volume and a part field which explicitly refers to the second (physical) part of the seventh (logical) volume. Also note the series and number fields}, Author = {Coleridge, Samuel Taylor}, Date = 1983, Editor = {Coburn, Kathleen and Engell, James and Bate, W. Jackson}, Hyphenation = {british}, Indextitle = {Biographia literaria}, Location = {London}, Maintitle = {The collected works of {Samuel Taylor Coleridge}}, Number = 75, Part = 2, Publisher = {Routledge {and} Kegan Paul}, Series = {Bollingen Series}, Shorttitle = {Biographia literaria}, Title = {Biographia literaria, or {Biographical} sketches of my literary life and opinions}, Volume = 7} --- references: - id: coleridge type: book author: - family: Coleridge given: Samuel Taylor editor: - family: Coburn given: Kathleen - family: Engell given: James - family: Bate given: W. Jackson issued: - year: '1983' title: The collected works of Samuel Taylor Coleridge volume-title: Biographia literaria, or Biographical sketches of my literary life and opinions collection-title: Bollingen series collection-number: '75' publisher: Routledge and Kegan Paul publisher-place: London volume: '7.2' annote: One (partial) volume of a multivolume book. This is a book entry with a volume and a part field which explicitly refers to the second (physical) part of the seventh (logical) volume. Also note the series and number fields language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/book-title-maintitle-series.biblatex0000644000000000000000000000125712743760365025626 0ustar0000000000000000@book{item1, Author = {Author, Al}, Date = {2013}, Hyphenation = {french}, Location = {Location}, Mainsubtitle = {Mainsubtitle}, Maintitle = {Maintitle}, Maintitleaddon = {Maintitleaddon}, Number = {3}, Publisher = {Publisher}, Series = {Series}, Subtitle = {Subtitle}, Title = {Title of the Book}, Titleaddon = {Titleaddon}, } --- references: - id: item1 type: book author: - family: Author given: Al issued: - year: '2013' title: 'Maintitle: Mainsubtitle. Maintitleaddon' volume-title: 'Title of the Book: Subtitle. Titleaddon' collection-title: Series collection-number: '3' publisher: Publisher publisher-place: Location language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/book-vazques-de-parga.biblatex0000644000000000000000000000250212743760365024377 0ustar0000000000000000@comment{excerpted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib Note handling of Author = {Vázques{ de }Parga, Luis} } @book{vazques-de-parga, Annotation = {A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields}, Author = {Vázques{ de }Parga, Luis and Lacarra, José María and Uría Ríu, Juan}, Date = 1993, Hyphenation = {spanish}, Indextitle = {Peregrinaciones a Santiago de Compostela, Las}, Location = {Pamplona}, Note = {Ed. facs. de la realizada en 1948--49}, Publisher = {Iberdrola}, Shorttitle = {Peregrinaciones}, Sorttitle = {Peregrinaciones a Santiago de Compostela}, Title = {Las Peregrinaciones a Santiago de Compostela}, Volumes = 3} --- references: - id: vazques-de-parga type: book author: - family: Vázques de Parga given: Luis - family: Lacarra given: José María - family: Uría Ríu given: Juan issued: - year: '1993' title: Las Peregrinaciones a Santiago de Compostela title-short: Peregrinaciones publisher: Iberdrola publisher-place: Pamplona number-of-volumes: '3' note: Ed. facs. de la realizada en 1948–49 annote: A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields language: es-ES ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/brandt.biblatex0000644000000000000000000000506712743760365021556 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Brandt and Hoffmann 1987) Brandt, Ahasver von, and Erich Hoffmann. 1987. “Die nordischen Länder von der Mitte des 11. Jahrhunderts bis 1448.” In *Europa im Hoch- und Spätmittelalter*, edited by Ferdinand Seibt, 884–917. Handbuch der europäischen Geschichte 2. Stuttgart: Klett-Cotta. Formatted with pandoc and apa.csl, 2013-10-23: (Brandt & Hoffmann, 1987) Brandt, A. von, & Hoffmann, E. (1987). Die nordischen Länder von der Mitte des 11. Jahrhunderts bis 1448. In F. Seibt (ed.), *Europa im Hoch- und Spätmittelalter* (pp. 884–917). Stuttgart: Klett-Cotta. } @InCollection{brandt, author = {von Brandt, Ahasver and Erich Hoffmann}, editor = {Ferdinand Seibt}, title = {Die nordischen L{\"a}nder von der Mitte des 11.~Jahrhunderts bis 1448}, date = 1987, booktitle = {Europa im Hoch- und Sp{\"a}tmittelalter}, series = {Handbuch der europ{\"a}ischen Geschichte}, number = 2, publisher = {Klett-Cotta}, location = {Stuttgart}, pages = {884-917}, options = {useprefix=false}, hyphenation = {german}, indexsorttitle= {Nordischen Lander von der Mitte des 11. Jahrhunderts bis 1448}, indextitle = {Nordischen L{\"a}nder von der Mitte des 11.~Jahrhunderts bis 1448, Die}, shorttitle = {Die nordischen L{\"a}nder}, annotation = {An incollection entry with a series and a number. Note the format of the printed name and compare the useprefix option in the options field as well as vangennep. Also note the indextitle, and indexsorttitle fields}, } --- references: - id: brandt type: chapter author: - family: Brandt given: Ahasver dropping-particle: von - family: Hoffmann given: Erich editor: - family: Seibt given: Ferdinand issued: - year: '1987' title: Die nordischen Länder von der Mitte des 11. Jahrhunderts bis 1448 title-short: Die nordischen Länder container-title: Europa im Hoch- und Spätmittelalter collection-title: Handbuch der europäischen Geschichte collection-number: '2' publisher: Klett-Cotta publisher-place: Stuttgart page: '884-917' annote: An incollection entry with a series and a number. Note the format of the printed name and compare the useprefix option in the options field as well as vangennep. Also note the indextitle, and indexsorttitle fields language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/britannica.biblatex0000644000000000000000000000474412743760365022417 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Preece 2003) Preece, Warren E., ed. 2003. *The New EncyclopæDia Britannica*. 15th ed. 32. Chicago, Ill.: Encyclopædia Britannica. Formatted with pandoc and apa.csl, 2013-10-23: (Preece, 2003) Preece, W. E. (Ed.). (2003). *The new encyclopædia Britannica* (15th ed., 1-32). Chicago, Ill.: Encyclopædia Britannica. NOTES: - biblio2yaml - spurious in Encyclopædia - options = {useeditor=false} has no equivalent in CSL, so citing and alphabetizing by title even though there is an editor does not seem to be possible - citeproc - incorrect camel case: "EncyclopæDia" - term "vols." missing } @Collection{britannica, editor = {Preece, Warren E.}, title = {The New Encyclop{\ae}dia {Britannica}}, date = 2003, edition = 15, volumes = 32, publisher = {Encyclop{\ae}dia Britannica}, location = {Chicago, Ill.}, options = {useeditor=false}, label = {EB}, hyphenation = {british}, sorttitle = {Encyclop{\ae}dia Britannica}, indextitle = {Encyclop{\ae}dia Britannica, The New}, shorttitle = {Encyclop{\ae}dia {Britannica}}, annotation = {This is a collection entry for an encyclopedia. Note the useeditor option in the options field as well as the sorttitle field. We want this entry to be cited and alphabetized by title even though there is an editor. In addition to that, we want the title to be alphabetized under \enquote*{E} rather than \enquote*{T}. Also note the label field which is provided for author-year citation styles}, } --- references: - id: britannica type: book editor: - family: Preece given: Warren E. issued: - year: '2003' title: The new encyclopædia Britannica title-short: Encyclopædia Britannica publisher: Encyclopædia Britannica publisher-place: Chicago, Ill. number-of-volumes: '32' edition: '15' annote: This is a collection entry for an encyclopedia. Note the useeditor option in the options field as well as the sorttitle field. We want this entry to be cited and alphabetized by title even though there is an editor. In addition to that, we want the title to be alphabetized under “E” rather than “T”. Also note the label field which is provided for author-year citation styles language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/chiu.biblatex0000644000000000000000000000407012743760365021225 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Chiu and Chow 1978) Chiu, Willy W., and We Min Chow. 1978. “A Hybrid Hierarchical Model of a Multiple Virtual Storage (MVS) Operating System.” Research report RC-6947. IBM. Formatted with pandoc and apa.csl, 2013-10-23: (Chiu & Chow, 1978) Chiu, W. W., & Chow, W. M. (1978). *A hybrid hierarchical model of a multiple virtual storage (MVS) operating system* (research report No. RC-6947). IBM. NOTES: - biblio2yaml - "MVS", when not wrapped in {}, gives "mVS", which is probably never intended, or useful (latex converts the whole word to lowercase if unprotected ("MVS" -> "mvs")) } @Report{chiu, author = {Chiu, Willy W. and Chow, We Min}, title = {A Hybrid Hierarchical Model of a Multiple Virtual Storage ({MVS}) Operating System}, type = {resreport}, institution = {IBM}, date = 1978, number = {RC-6947}, hyphenation = {american}, sorttitle = {Hybrid Hierarchical Model of a Multiple Virtual Storage (MVS) Operating System}, indextitle = {Hybrid Hierarchical Model, A}, annotation = {This is a report entry for a research report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields}, } --- references: - id: chiu type: report author: - family: Chiu given: Willy W. - family: Chow given: We Min issued: - year: '1978' title: A hybrid hierarchical model of a multiple virtual storage (MVS) operating system publisher: IBM genre: research report annote: This is a report entry for a research report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields number: RC-6947 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/cicero.biblatex0000644000000000000000000000374312743760365021547 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Cicero 1995) Cicero, Marcus Tullius. 1995. *De natura deorum. Über das Wesen der Götter*. Ursula Blank-Sangmeister. Stuttgart: Reclam. Formatted with pandoc and apa.csl, 2013-10-23: (Cicero, 1995) Cicero, M. T. (1995). *De natura deorum. Über das Wesen der Götter*. (U. Blank-Sangmeister). Stuttgart: Reclam. NOTES: - biblio2yaml - afterword, language: no CSL variables available - citeproc: - term such as "edited and translated by" should appear } @Book{cicero, author = {Cicero, Marcus Tullius}, title = {De natura deorum. {\"U}ber das Wesen der G{\"o}tter}, date = 1995, editor = {Blank-Sangmeister, Ursula}, translator = {Blank-Sangmeister, Ursula}, afterword = {Thraede, Klaus}, language = {langlatin and langgerman}, publisher = {Reclam}, location = {Stuttgart}, hyphenation = {german}, indextitle = {De natura deorum}, shorttitle = {De natura deorum}, annotation = {A bilingual edition of Cicero's \emph{De natura deorum}, with a German translation. Note the format of the language field in the database file, the concatenation of the editor and translator fields, and the afterword field}, } --- references: - id: cicero type: book author: - family: Cicero given: Marcus Tullius editor: - family: Blank-Sangmeister given: Ursula translator: - family: Blank-Sangmeister given: Ursula issued: - year: '1995' title: De natura deorum. Über das Wesen der Götter title-short: De natura deorum publisher: Reclam publisher-place: Stuttgart annote: A bilingual edition of Cicero’s *De natura deorum*, with a German translation. Note the format of the language field in the database file, the concatenation of the editor and translator fields, and the afterword field language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/cms.biblatex0000644000000000000000000000474112743760365021064 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (*The Chicago Manual of Style: The Essential Guide for Writers, Editors, and Publishers* 2003) *The Chicago Manual of Style: The Essential Guide for Writers, Editors, and Publishers*. 2003. 15th ed. Chicago, Ill.: University of Chicago Press. Formatted with pandoc and apa.csl, 2013-10-23: (*Chicago manual of style*, 2003) *The Chicago manual of style: The essential guide for writers, editors, and publishers*. (2003) (15th ed.). Chicago, Ill.: University of Chicago Press. NOTES: - chicago-author-date.csl should have as in-text citation: (*Chicago Manual of Style* 2003) Same behaviour in Zotero; most probably a style file issue. } @Manual{cms, title = {The {Chicago} Manual of Style}, date = 2003, subtitle = {The Essential Guide for Writers, Editors, and Publishers}, edition = 15, publisher = {University of Chicago Press}, location = {Chicago, Ill.}, isbn = {0-226-10403-6}, label = {CMS}, hyphenation = {american}, sorttitle = {Chicago Manual of Style}, indextitle = {Chicago Manual of Style, The}, shorttitle = {Chicago Manual of Style}, annotation = {This is a manual entry without an author or editor. Note the label field in the database file which is provided for author-year citation styles. Also note the sorttitle and indextitle fields. By default, all entries without an author or editor are alphabetized by title but we want this entry to be alphabetized under \enquote*{C} rather than \enquote*{T}. There's also an isbn field}, } --- references: - id: cms type: book issued: - year: '2003' title: 'The Chicago manual of style: The essential guide for writers, editors, and publishers' title-short: Chicago manual of style publisher: University of Chicago Press publisher-place: Chicago, Ill. edition: '15' annote: This is a manual entry without an author or editor. Note the label field in the database file which is provided for author-year citation styles. Also note the sorttitle and indextitle fields. By default, all entries without an author or editor are alphabetized by title but we want this entry to be alphabetized under “C” rather than “T”. There’s also an isbn field ISBN: '0-226-10403-6' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/coleridge.biblatex0000644000000000000000000000457312743760365022242 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Coleridge 1983) Coleridge, Samuel Taylor. 1983. *The Collected Works of Samuel Taylor Coleridge*. Edited by Kathleen Coburn, James Engell, and W. Jackson Bate. Vol. 7.2. Bollingen Series 75. London: Routledge and Kegan Paul. Formatted with pandoc and apa.csl, 2015-03-08: (Coleridge, 1983) Coleridge, S. T. (1983). *The collected works of Samuel Taylor Coleridge*. (K. Coburn, J. Engell, & W. J. Bate, Eds.) (Vol. 7.2). London: Routledge and Kegan Paul. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{coleridge, author = {Coleridge, Samuel Taylor}, title = {Biographia literaria, or {Biographical} sketches of my literary life and opinions}, date = 1983, editor = {Coburn, Kathleen and Engell, James and Bate, W. Jackson}, maintitle = {The collected works of {Samuel Taylor Coleridge}}, volume = 7, part = 2, series = {Bollingen Series}, number = 75, publisher = {Routledge {and} Kegan Paul}, location = {London}, hyphenation = {british}, indextitle = {Biographia literaria}, shorttitle = {Biographia literaria}, annotation = {One (partial) volume of a multivolume book. This is a book entry with a volume and a part field which explicitly refers to the second (physical) part of the seventh (logical) volume. Also note the series and number fields}, } --- references: - id: coleridge type: book author: - family: Coleridge given: Samuel Taylor editor: - family: Coburn given: Kathleen - family: Engell given: James - family: Bate given: W. Jackson issued: - year: '1983' title: The collected works of Samuel Taylor Coleridge volume-title: Biographia literaria, or Biographical sketches of my literary life and opinions collection-title: Bollingen series collection-number: '75' publisher: Routledge and Kegan Paul publisher-place: London volume: '7.2' annote: One (partial) volume of a multivolume book. This is a book entry with a volume and a part field which explicitly refers to the second (physical) part of the seventh (logical) volume. Also note the series and number fields language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/companion.biblatex0000644000000000000000000000314112743760365022256 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Goossens, Mittelbach, and Samarin 1994) Goossens, Michel, Frank Mittelbach, and Alexander Samarin. 1994. *The LaTeX Companion*. 1st ed. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2013-10-23: (Goossens, Mittelbach, & Samarin, 1994) Goossens, M., Mittelbach, F., & Samarin, A. (1994). *The LaTeX companion* (1st ed.). Reading, Mass.: Addison-Wesley. } @Book{companion, author = {Goossens, Michel and Mittelbach, Frank and Samarin, Alexander}, title = {The {LaTeX} Companion}, date = 1994, edition = 1, publisher = {Addison-Wesley}, location = {Reading, Mass.}, pagetotal = 528, hyphenation = {american}, sorttitle = {LaTeX Companion}, indextitle = {LaTeX Companion, The}, shorttitle = {LaTeX Companion}, annotation = {A book with three authors. Note the formatting of the author list. By default, only the first name is reversed in the bibliography}, } --- references: - id: companion type: book author: - family: Goossens given: Michel - family: Mittelbach given: Frank - family: Samarin given: Alexander issued: - year: '1994' title: The LaTeX companion title-short: LaTeX companion publisher: Addison-Wesley publisher-place: Reading, Mass. number-of-pages: '528' edition: '1' annote: A book with three authors. Note the formatting of the author list. By default, only the first name is reversed in the bibliography language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/cotton.biblatex0000644000000000000000000000307712743760365021611 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Cotton et al. 1999) Cotton, Frank Albert, Geoffrey Wilkinson, Carlos A. Murillio, and Manfred Bochmann. 1999. *Advanced Inorganic Chemistry*. 6th ed. Chichester: Wiley. Formatted with pandoc and apa.csl, 2013-10-23: (Cotton, Wilkinson, Murillio, & Bochmann, 1999) Cotton, F. A., Wilkinson, G., Murillio, C. A., & Bochmann, M. (1999). *Advanced inorganic chemistry* (6th ed.). Chichester: Wiley. } @Book{cotton, author = {Cotton, Frank Albert and Wilkinson, Geoffrey and Murillio, Carlos A. and Bochmann, Manfred}, title = {Advanced inorganic chemistry}, date = 1999, edition = 6, publisher = {Wiley}, location = {Chichester}, hyphenation = {british}, annotation = {A book entry with \arabic{author} authors and an edition field. By default, long author and editor lists are automatically truncated. This is configurable}, } --- references: - id: cotton type: book author: - family: Cotton given: Frank Albert - family: Wilkinson given: Geoffrey - family: Murillio given: Carlos A. - family: Bochmann given: Manfred issued: - year: '1999' title: Advanced inorganic chemistry publisher: Wiley publisher-place: Chichester edition: '6' annote: A book entry with author authors and an edition field. By default, long author and editor lists are automatically truncated. This is configurable language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/crossref-inbook-mvbook.biblatex0000644000000000000000000000205312743760365024674 0ustar0000000000000000@comment{ crossref, directly from inbook to mvbook } @inbook{inbook-1, Crossref = {mvbook-1}, Title = {Macbeth [title field of inbook-1]}, Date = {1975}, Volume = {3}, Chapter = {7}, Pages = {100-200}, } @mvbook{mvbook-1, Author = {Shakespeare}, Date = {1970/1980}, Title = {Collected Works [title field of mvbook-1]}, Location = {Location}, Publisher = {Publisher}, Volumes = {4}, } --- references: - id: inbook-1 type: chapter author: - family: Shakespeare container-author: - family: Shakespeare issued: - year: '1975' title: Macbeth \[title field of inbook-1\] container-title: Collected works \[title field of mvbook-1\] publisher: Publisher publisher-place: Location page: '100-200' volume: '3' number-of-volumes: '4' chapter-number: '7' - id: mvbook-1 type: book author: - family: Shakespeare issued: - year: '1970' - year: '1980' title: Collected works \[title field of mvbook-1\] publisher: Publisher publisher-place: Location number-of-volumes: '4' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/crossref-nested.biblatex0000644000000000000000000000411612743760365023404 0ustar0000000000000000@comment{ Nested crossreferences (see biber manual v 1.7) } @bookinbook{bookinbook-1, Crossref = {book-1}, Title = {Macbeth [title field of bookinbook-1]}, Chapter = {7}, Pages = {100-200}, } @inbook{inbook-1, Crossref = {book-1}, Title = {Macbeth [title field of inbook-1]}, Chapter = {7}, Pages = {100-200}, } @book{book-1, Crossref = {mvbook-1}, Date = {1975}, Title = {Tragedies [title field of book-1]}, Volume = {3} } @mvbook{mvbook-1, Author = {Shakespeare}, Date = {1970/1980}, Title = {Collected Works [title field of mvbook-1]}, Location = {Location}, Publisher = {Publisher}, Volumes = {4} } --- references: - id: bookinbook-1 type: chapter author: - family: Shakespeare container-author: - family: Shakespeare issued: - year: '1975' title: Macbeth \[title field of bookinbook-1\] container-title: Collected works \[title field of mvbook-1\] volume-title: Tragedies \[title field of book-1\] publisher: Publisher publisher-place: Location page: '100-200' volume: '3' number-of-volumes: '4' chapter-number: '7' - id: inbook-1 type: chapter author: - family: Shakespeare container-author: - family: Shakespeare issued: - year: '1975' title: Macbeth \[title field of inbook-1\] container-title: Collected works \[title field of mvbook-1\] volume-title: Tragedies \[title field of book-1\] publisher: Publisher publisher-place: Location page: '100-200' volume: '3' number-of-volumes: '4' chapter-number: '7' - id: book-1 type: book author: - family: Shakespeare container-author: - family: Shakespeare issued: - year: '1975' title: Collected works \[title field of mvbook-1\] volume-title: Tragedies \[title field of book-1\] publisher: Publisher publisher-place: Location volume: '3' number-of-volumes: '4' - id: mvbook-1 type: book author: - family: Shakespeare issued: - year: '1970' - year: '1980' title: Collected works \[title field of mvbook-1\] publisher: Publisher publisher-place: Location number-of-volumes: '4' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/ctan.biblatex0000644000000000000000000000410312743760365021217 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (“CTAN: The Comprehensive TeX Archive Network” 2006) “CTAN: The Comprehensive TeX Archive Network.” 2006. . Formatted with pandoc and apa.csl, 2013-10-23: (“CTAN: The Comprehensive TeX Archive Network,” 2006) CTAN: The Comprehensive TeX Archive Network. (2006). Retrieved October 01, 2006, from NOTES: - biblio2yaml - if there is no shorttitle, but title and subtitle, the title alone should also be mapped to title-short - citeproc - citeproc should use title-short (if available) instead of title for in-text citations when there is no author } @Online{ctan, title = {{CTAN}}, date = 2006, url = {http://www.ctan.org}, subtitle = {{The Comprehensive TeX Archive Network}}, urldate = {2006-10-01}, label = {CTAN}, hyphenation = {american}, annotation = {This is an online entry. The \textsc{url}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and\slash or a year}, } --- references: - id: ctan type: webpage issued: - year: '2006' accessed: - year: '2006' month: '10' day: '1' title: 'CTAN: The Comprehensive TeX Archive Network' title-short: CTAN annote: This is an online entry. The url, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and/or a year URL: http://www.ctan.org language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/dates.biblatex0000644000000000000000000001235112743760365021376 0ustar0000000000000000@comment{ - Dates - Not included in tests: - malformed dates and date ranges - literal dates ("13th century"; not supported by biblatex) - seasons (would have to come from parsing the issue field) - uncertain dates (use "doubtfuldate" from biblatex-apa?) - dates with single-digit day or month (not supported by biblatex) - negative dates (not supported by biblatex) - Note: biblatex supports years < 1000 but only if padded with leading zeros - TODO: - either biblio2yaml or, probably better, citeproc should strip leading zeros from days and months (CSL can add leading zeros to its output, but not remove them when they are in its input data) } @article{year-month-old, Author = {Author, Al}, Journal = {Journal}, Month = aug, Title = {Year and Month, bibtex style, supported by biblatex for backwards compatibility}, Year = {1999}} @article{year-month-new, Author = {Author, Al}, Journal = {Journal}, Month = {08}, Title = {Year and Month, biblatex style; note that biblatex does not have a "day" field}, Year = {1999}} @article{dates, Author = {Author, Al}, Date = {2012-12-13}, Eventdate = {2011-10-03}, Journal = {Journal}, Month = may, Origdate = {1888-10-01}, Title = {Dates, default biblatex style; year, month to be ignored if date exists}, Urldate = {1999-05-23}, Year = {9999}} @article{date-ranges-different-years, Author = {Author, Al}, Date = {1999-10-14/2010-01-23}, Eventdate = {1999-12/2000-01}, Journal = {Journal}, Origdate = {1888-01-02/1913-12-13}, Title = {Date ranges; different years}, Urldate = {2012-10-12/2013-01-31}} @article{date-ranges-same-year, Author = {Author, Al}, Date = {1999-10-14/1999-10-15}, Eventdate = {1999-10/1999-11}, Journal = {Journal}, Origdate = {1888-01-02/1888-12-13}, Title = {Date ranges; same year}, Urldate = {2012-10-31/2012-11-01}} @article{date-ranges-open, Author = {Author, Al}, Date = {1999-10-14/}, Eventdate = {1999-10/}, Journal = {Journal}, Origdate = {1888-01-02/}, Title = {Date ranges, open-ended}, Urldate = {2012-10-31/}} @article{dates-very-old, Author = {Author, Al}, Date = {0712-12-13}, Eventdate = {0311-10-03}, Journal = {Journal}, Month = may, Origdate = {0088-10-01}, Title = {Dates, year less than 1000}, Urldate = {0999-12-14}} --- references: - id: year-month-old type: article-journal author: - family: Author given: Al issued: - year: '1999' month: '8' title: Year and month, bibtex style, supported by biblatex for backwards compatibility container-title: Journal - id: year-month-new type: article-journal author: - family: Author given: Al issued: - year: '1999' month: '08' title: Year and month, biblatex style; note that biblatex does not have a “day” field container-title: Journal - id: dates type: article-journal author: - family: Author given: Al issued: - year: '2012' month: '12' day: '13' event-date: - year: '2011' month: '10' day: '3' accessed: - year: '1999' month: '5' day: '23' original-date: - year: '1888' month: '10' day: '1' title: Dates, default biblatex style; year, month to be ignored if date exists container-title: Journal - id: date-ranges-different-years type: article-journal author: - family: Author given: Al issued: - year: '1999' month: '10' day: '14' - year: '2010' month: '1' day: '23' event-date: - year: '1999' month: '12' - year: '2000' month: '1' accessed: - year: '2012' month: '10' day: '12' - year: '2013' month: '1' day: '31' original-date: - year: '1888' month: '1' day: '2' - year: '1913' month: '12' day: '13' title: Date ranges; different years container-title: Journal - id: date-ranges-same-year type: article-journal author: - family: Author given: Al issued: - year: '1999' month: '10' day: '14' - year: '1999' month: '10' day: '15' event-date: - year: '1999' month: '10' - year: '1999' month: '11' accessed: - year: '2012' month: '10' day: '31' - year: '2012' month: '11' day: '1' original-date: - year: '1888' month: '1' day: '2' - year: '1888' month: '12' day: '13' title: Date ranges; same year container-title: Journal - id: date-ranges-open type: article-journal author: - family: Author given: Al issued: - year: '1999' month: '10' day: '14' - {} event-date: - year: '1999' month: '10' - {} accessed: - year: '2012' month: '10' day: '31' - {} original-date: - year: '1888' month: '1' day: '2' - {} title: Date ranges, open-ended container-title: Journal - id: dates-very-old type: article-journal author: - family: Author given: Al issued: - year: '712' month: '12' day: '13' event-date: - year: '311' month: '10' day: '3' accessed: - year: '999' month: '12' day: '14' original-date: - year: '88' month: '10' day: '1' title: Dates, year less than 1000 container-title: Journal ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/doody.biblatex0000644000000000000000000000506112743760365021414 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Doody 1974) (Matuz 1990) Doody, Terrence. 1974. “Hemingway’s Style and Jake’s Narration.” *The Journal of Narrative Technique* 4 (3): 212–225. Matuz, Roger, ed. 1990. *Contemporary Literary Criticism*. Vol. 61. Detroit: Gale. Formatted with pandoc and apa.csl, 2013-10-23: (Doody, 1974) (Matuz, 1990) Doody, T. (1974). Hemingway’s style and Jake’s narration. *The Journal of Narrative Technique*, *4*(3), 212–225. Matuz, R. (Ed.). (1990). *Contemporary literary criticism* (Vol. 61, pp. 204–208). Detroit: Gale. NOTES - biblio2yaml - contains fields “related” and “relatedstring”. In principle, these could be appended to CSL "note", if citeproc can handle citations in the bibliography ... } @Article{doody, author = {Doody, Terrence}, title = {Hemingway's Style and {Jake}'s Narration}, year = 1974, volume = 4, number = 3, pages = {212-225}, hyphenation = {american}, related = {matuz:doody}, relatedstring= {\autocap{e}xcerpt in}, journal = {The Journal of Narrative Technique}, annotation = {An article entry cited as an excerpt from a collection entry. Note the format of the related and relatedstring fields}, } @Collection{matuz:doody, editor = {Matuz, Roger}, title = {Contemporary Literary Criticism}, year = 1990, volume = 61, publisher = {Gale}, location = {Detroit}, pages = {204-208}, hyphenation = {american}, annotation = {A collection entry providing the excerpt information for the doody entry. Note the format of the pages field}, } --- references: - id: doody type: article-journal author: - family: Doody given: Terrence issued: - year: '1974' title: Hemingway’s style and Jake’s narration container-title: The Journal of Narrative Technique page: '212-225' volume: '4' issue: '3' annote: An article entry cited as an excerpt from a collection entry. Note the format of the related and relatedstring fields language: en-US - id: matuz:doody type: book editor: - family: Matuz given: Roger issued: - year: '1990' title: Contemporary literary criticism publisher: Gale publisher-place: Detroit page: '204-208' volume: '61' annote: A collection entry providing the excerpt information for the doody entry. Note the format of the pages field language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/edtf-date.biblatex0000644000000000000000000000310413007456644022123 0ustar0000000000000000@article{item3-3, date={1998/unknown}} @article{item3-4, date={1999/open}} @article{item3-10, date={2004-04-05T14:34:00}} @article{item5-1, date={0000}} @article{item5-2, date={-0876}} @article{item5-3, date={-0877/-0866}} @article{item5-5, date={-0343-02}} @article{item5-8, date={1723~}} @article{item5-9, date={1723?}} @article{item5-10, date={1723?~}} @article{item5-11, date={2004-22}} @article{item5-12, date={2004-24}} @article{item5-13, date={20uu}} @article{item5-14, date={y-123456789}} --- references: - id: item3-3 type: article-journal issued: - year: '1998' - {} - id: item3-4 type: article-journal issued: - year: '1999' - {} - id: item3-10 type: article-journal issued: - year: '2004' month: '4' day: '5' - id: item5-1 type: article-journal issued: - year: '-1' - id: item5-2 type: article-journal issued: - year: '-877' - id: item5-3 type: article-journal issued: - year: '-878' - year: '-867' - id: item5-5 type: article-journal issued: - year: '-344' month: '2' - id: item5-8 type: article-journal issued: - year: '1723' circa: '1' - id: item5-9 type: article-journal issued: - year: '1723' - id: item5-10 type: article-journal issued: - year: '1723' circa: '1' - id: item5-11 type: article-journal issued: - year: '2004' season: '2' - id: item5-12 type: article-journal issued: - year: '2004' season: '4' - id: item5-13 type: article-journal issued: - year: '2000' - year: '2099' - id: item5-14 type: article-journal issued: - year: '-123456790' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/escapedquotes.biblatex0000644000000000000000000000246312743760365023146 0ustar0000000000000000@comment{From jgm/pandoc#1568. Double quotes escaped using {"}.} @ARTICLE{Koff2009-gn, title = "Pan-Canadian evaluation of irreversible compression ratios ({"}lossy{"} compression) for development of national guidelines", author = "Koff, David and Bak, Peter and Brownrigg, Paul and Hosseinzadeh, Danoush and Khademi, April and Kiss, Alex and Lepanto, Luigi and Michalak, Tracy and Shulman, Harry and Volkening, Andrew", affiliation = "Sunnybrook Health Sciences Centre, 2075 Bayview Ave., Toronto, ON, M4N 3M5, Canada. dkoffmcmaster.ca", journal = "Journal of digital imaging", } --- references: - id: Koff2009-gn type: article-journal author: - family: Koff given: David - family: Bak given: Peter - family: Brownrigg given: Paul - family: Hosseinzadeh given: Danoush - family: Khademi given: April - family: Kiss given: Alex - family: Lepanto given: Luigi - family: Michalak given: Tracy - family: Shulman given: Harry - family: Volkening given: Andrew title: Pan-canadian evaluation of irreversible compression ratios ("lossy" compression) for development of national guidelines container-title: Journal of digital imaging ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/formatting.biblatex0000644000000000000000000000060412743760365022446 0ustar0000000000000000@article{item1, Title = {The Title: \textit{italics}, \textbf{bold}, \textsubscript{subscript}, \textsuperscript{superscript}, \textsc{small-caps}} } --- references: - id: item1 type: article-journal title: 'The title: *Italics*, **bold**, ~subscript~, ^superscript^, small-caps' title-short: The title ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/gaonkar-in.biblatex0000644000000000000000000000242012743760365022320 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Gaonkar 2001) Gaonkar, Dilip Parameshwar. 2001. “On Alternative Modernities.” In *Alternative Modernities*, edited by Dilip Parameshwar Gaonkar, 1–23. Durham; London: Duke University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Gaonkar, 2001) Gaonkar, D. P. (2001). On alternative modernities. In D. P. Gaonkar (Ed.), *Alternative modernities* (pp. 1–23). Durham; London: Duke University Press. } @InCollection{gaonkar:in, author = {Gaonkar, Dilip Parameshwar}, editor = {Gaonkar, Dilip Parameshwar}, title = {On Alternative Modernities}, date = 2001, booktitle = {Alternative Modernities}, publisher = {Duke University Press}, location = {Durham and London}, isbn = {0-822-32714-7}, pages = {1-23}, } --- references: - id: gaonkar:in type: chapter author: - family: Gaonkar given: Dilip Parameshwar editor: - family: Gaonkar given: Dilip Parameshwar issued: - year: '2001' title: On alternative modernities container-title: Alternative modernities publisher: Duke University Press publisher-place: Durham; London page: '1-23' ISBN: '0-822-32714-7' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/gaonkar.biblatex0000644000000000000000000000234512743760365021722 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Gaonkar 2001) Gaonkar, Dilip Parameshwar, ed. 2001. *Alternative Modernities*. Durham; London: Duke University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Gaonkar, 2001) Gaonkar, D. P. (Ed.). (2001). *Alternative modernities*. Durham; London: Duke University Press. } @Collection{gaonkar, editor = {Gaonkar, Dilip Parameshwar}, title = {Alternative Modernities}, date = 2001, publisher = {Duke University Press}, location = {Durham and London}, isbn = {0-822-32714-7}, hyphenation = {american}, annotation = {This is a collection entry. Note the format of the location field in the database file as well as the isbn field}, } --- references: - id: gaonkar type: book editor: - family: Gaonkar given: Dilip Parameshwar issued: - year: '2001' title: Alternative modernities publisher: Duke University Press publisher-place: Durham; London annote: This is a collection entry. Note the format of the location field in the database file as well as the isbn field ISBN: '0-822-32714-7' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/geer.biblatex0000644000000000000000000000364412743760365021225 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Geer 1985) Geer, Ingrid de. 1985. “Earl, Saint, Bishop, Skald – and Music: The Orkney Earldom of the Twelfth Century. A Musicological Study.” PhD thesis, Uppsala: Uppsala Universitet. Formatted with pandoc and apa.csl, 2013-10-23: (Geer, 1985) Geer, I. de. (1985). *Earl, saint, bishop, skald – and music: The Orkney earldom of the twelfth century. A musicological study* (PhD thesis). Uppsala Universitet, Uppsala. } @Thesis{geer, author = {de Geer, Ingrid}, title = {Earl, Saint, Bishop, Skald~-- and Music}, type = {phdthesis}, institution = {Uppsala Universitet}, date = 1985, subtitle = {The {Orkney} Earldom of the Twelfth Century. {A} Musicological Study}, location = {Uppsala}, options = {useprefix=false}, hyphenation = {british}, annotation = {This is a typical thesis entry for a PhD thesis. Note the type field in the database file which uses a localization key. Also note the format of the printed name and compare the useprefix option in the options field as well as vangennep}, } --- references: - id: geer type: thesis author: - family: Geer given: Ingrid dropping-particle: de issued: - year: '1985' title: 'Earl, saint, bishop, skald – and music: The Orkney earldom of the twelfth century. A musicological study' title-short: Earl, saint, bishop, skald – and music publisher: Uppsala Universitet publisher-place: Uppsala genre: PhD thesis annote: This is a typical thesis entry for a PhD thesis. Note the type field in the database file which uses a localization key. Also note the format of the printed name and compare the useprefix option in the options field as well as vangennep language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/gerhardt.biblatex0000644000000000000000000000304412743760365022075 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Gerhardt 2000) Gerhardt, Michael J. 2000. *The Federal Appointments Process: A Constitutional and Historical Analysis*. Durham; London: Duke University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Gerhardt, 2000) Gerhardt, M. J. (2000). *The federal appointments process: A constitutional and historical analysis*. Durham; London: Duke University Press. } @Book{gerhardt, author = {Gerhardt, Michael J.}, title = {The Federal Appointments Process}, date = 2000, publisher = {Duke University Press}, location = {Durham and London}, hyphenation = {american}, sorttitle = {Federal Appointments Process}, indextitle = {Federal Appointments Process, The}, subtitle = {A Constitutional and Historical Analysis}, shorttitle = {Federal Appointments Process}, annotation = {This is a book entry. Note the format of the location field as well as the sorttitle and indextitle fields}, } --- references: - id: gerhardt type: book author: - family: Gerhardt given: Michael J. issued: - year: '2000' title: 'The federal appointments process: A constitutional and historical analysis' title-short: Federal appointments process publisher: Duke University Press publisher-place: Durham; London annote: This is a book entry. Note the format of the location field as well as the sorttitle and indextitle fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/gillies.biblatex0000644000000000000000000000316112743760365021725 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Gillies 1933) Gillies, Alexander. 1933. “Herder and the Preparation of Goethe’s Idea of World Literature.” *Publications of the English Goethe Society, New Series* 9: 46–67. Formatted with pandoc and apa.csl, 2013-10-23: (Gillies, 1933) Gillies, A. (1933). Herder and the preparation of Goethe’s idea of world literature. *Publications of the English Goethe Society, new series*, *9*, 46–67. NOTES: - biblio2yaml - "new series" is not pretty, but it’s the best we can do at the moment, given the limitations of CSL. } @Article{gillies, author = {Gillies, Alexander}, title = {Herder and the Preparation of {Goethe}'s Idea of World Literature}, journaltitle = {Publications of the English Goethe Society}, date = 1933, series = {newseries}, volume = 9, pages = {46-67}, hyphenation = {british}, annotation = {An article entry with a series and a volume field. Note that format of the series field in the database file}, } --- references: - id: gillies type: article-journal author: - family: Gillies given: Alexander issued: - year: '1933' title: Herder and the preparation of Goethe’s idea of world literature container-title: Publications of the English Goethe Society collection-title: new series page: '46-67' volume: '9' annote: An article entry with a series and a volume field. Note that format of the series field in the database file language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/glashow.biblatex0000644000000000000000000000153612743760365021745 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Glashow 1961) Glashow, Sheldon. 1961. “Partial Symmetries of Weak Interactions.” *Nucl. Phys.* 22: 579–588. Formatted with pandoc and apa.csl, 2013-10-23: (Glashow, 1961) Glashow, S. (1961). Partial symmetries of weak interactions. *Nucl. Phys.*, *22*, 579–588. } @Article{glashow, author = {Glashow, Sheldon}, title = {Partial Symmetries of Weak Interactions}, journaltitle = {Nucl.~Phys.}, date = 1961, volume = 22, pages = {579-588}, } --- references: - id: glashow type: article-journal author: - family: Glashow given: Sheldon issued: - year: '1961' title: Partial symmetries of weak interactions container-title: Nucl. Phys. page: '579-588' volume: '22' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/gonzalez.biblatex0000644000000000000000000000300212743760365022120 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Gonzalez 2001) Gonzalez, Ray. 2001. *The Ghost of John Wayne and Other Stories*. Tucson: The University of Arizona Press. Formatted with pandoc and apa.csl, 2013-10-23: (Gonzalez, 2001) Gonzalez, R. (2001). *The ghost of John Wayne and other stories*. Tucson: The University of Arizona Press. } @Book{gonzalez, author = {Gonzalez, Ray}, title = {The Ghost of {John Wayne} and Other Stories}, date = 2001, publisher = {The University of Arizona Press}, location = {Tucson}, isbn = {0-816-52066-6}, hyphenation = {american}, sorttitle = {Ghost of John Wayne and Other Stories}, indextitle = {Ghost of {John Wayne} and Other Stories, The}, shorttitle = {Ghost of {John Wayne}}, annotation = {A collection of short stories. This is a book entry. Note the sorttitle and indextitle fields in the database file. There's also an isbn field}, } --- references: - id: gonzalez type: book author: - family: Gonzalez given: Ray issued: - year: '2001' title: The ghost of John Wayne and other stories title-short: Ghost of John Wayne publisher: The University of Arizona Press publisher-place: Tucson annote: A collection of short stories. This is a book entry. Note the sorttitle and indextitle fields in the database file. There’s also an isbn field ISBN: '0-816-52066-6' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/hammond.biblatex0000644000000000000000000000307712743760365021726 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Hammond 1997) Hammond, Christopher. 1997. *The Basics of Crystallography and Diffraction*. Oxford: International Union of Crystallography; Oxford University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Hammond, 1997) Hammond, C. (1997). *The basics of crystallography and diffraction*. Oxford: International Union of Crystallography; Oxford University Press. } @Book{hammond, author = {Hammond, Christopher}, title = {The basics of crystallography and diffraction}, date = 1997, publisher = {International Union of Crystallography and Oxford University Press}, location = {Oxford}, hyphenation = {british}, sorttitle = {Basics of crystallography and diffraction}, indextitle = {Basics of crystallography and diffraction, The}, shorttitle = {Crystallography and diffraction}, annotation = {A book entry. Note the sorttitle and indextitle fields as well as the format of the publisher field}, } --- references: - id: hammond type: book author: - family: Hammond given: Christopher issued: - year: '1997' title: The basics of crystallography and diffraction title-short: Crystallography and diffraction publisher: International Union of Crystallography; Oxford University Press publisher-place: Oxford annote: A book entry. Note the sorttitle and indextitle fields as well as the format of the publisher field language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/herrmann.biblatex0000644000000000000000000000331312743760365022106 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Herrmann et al. 2006) Herrmann, Wolfgang A., Karl Öfele, Sabine K. Schneider, Eberhardt Herdtweck, and Stephan D. Hoffmann. 2006. “A Carbocyclic Carbene as an Efficient Catalyst Ligand for C–C Coupling Reactions.” *Angew. Chem. Int. Ed.* 45 (23): 3859–3862. Formatted with pandoc and apa.csl, 2013-10-23: (Herrmann, Öfele, Schneider, Herdtweck, & Hoffmann, 2006) Herrmann, W. A., Öfele, K., Schneider, S. K., Herdtweck, E., & Hoffmann, S. D. (2006). A carbocyclic carbene as an efficient catalyst ligand for C–C coupling reactions. *Angew. Chem. Int. Ed.*, *45*(23), 3859–3862. } @string{ anch-ie = {Angew.~Chem. Int.~Ed.} } @Article{herrmann, author = {Herrmann, Wolfgang A. and {\"O}fele, Karl and Schneider, Sabine K. and Herdtweck, Eberhardt and Hoffmann, Stephan D.}, title = {A carbocyclic carbene as an efficient catalyst ligand for {C--C} coupling reactions}, journaltitle = anch-ie, date = 2006, volume = 45, number = 23, pages = {3859-3862}, indextitle = {Carbocyclic carbene as an efficient catalyst, A}, } --- references: - id: herrmann type: article-journal author: - family: Herrmann given: Wolfgang A. - family: Öfele given: Karl - family: Schneider given: Sabine K. - family: Herdtweck given: Eberhardt - family: Hoffmann given: Stephan D. issued: - year: '2006' title: A carbocyclic carbene as an efficient catalyst ligand for C–C coupling reactions container-title: Angew. Chem. Int. Ed. page: '3859-3862' volume: '45' issue: '23' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/hyman.biblatex0000644000000000000000000000407612743760365021417 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Hyman 1981) Hyman, Arthur. 1981. “Aristotle’s Theory of the Intellect and Its Interpretation by Averroes.” In *Studies in Aristotle*, edited by Dominic J. O’Meara, 161–191. Studies in Philosophy and the History of Philosophy 9. Washington, D.C.: The Catholic University of America Press. Formatted with pandoc and apa.csl, 2013-10-23: (Hyman, 1981) Hyman, A. (1981). Aristotle’s theory of the intellect and its interpretation by Averroes. In D. J. O’Meara (Ed.), *Studies in Aristotle* (pp. 161–191). Washington, D.C.: The Catholic University of America Press. } @InCollection{hyman, author = {Arthur Hyman}, editor = {O'Meara, Dominic J.}, title = {Aristotle's Theory of the Intellect and its Interpretation by {Averroes}}, date = 1981, booktitle = {Studies in {Aristotle}}, series = {Studies in Philosophy and the History of Philosophy}, number = 9, publisher = {The Catholic University of America Press}, location = {Washington, D.C.}, pages = {161-191}, keywords = {secondary}, hyphenation = {american}, indextitle = {Aristotle's Theory of the Intellect}, shorttitle = {Aristotle's Theory of the Intellect}, annotation = {An incollection entry with a series and number field}, } --- references: - id: hyman type: chapter author: - family: Hyman given: Arthur editor: - family: O’Meara given: Dominic J. issued: - year: '1981' title: Aristotle’s theory of the intellect and its interpretation by Averroes title-short: Aristotle’s theory of the intellect container-title: Studies in Aristotle collection-title: Studies in philosophy and the history of philosophy collection-number: '9' publisher: The Catholic University of America Press publisher-place: Washington, D.C. page: '161-191' annote: An incollection entry with a series and number field keyword: secondary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/iliad.biblatex0000644000000000000000000000306612743760365021363 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Homer 2004) Homer. 2004. *Die Ilias*. Translated by Wolfgang Schadewaldt. 3rd ed. Düsseldorf; Zürich: Artemis & Winkler. Formatted with pandoc and apa.csl, 2013-10-23: (Homer, 2004) Homer. (2004). *Die Ilias*. (W. Schadewaldt, trans.) (3rd ed.). Düsseldorf; Zürich: Artemis & Winkler. } @Book{iliad, author = {Homer}, title = {Die Ilias}, date = 2004, translator = {Schadewaldt, Wolfgang}, introduction = {Latacz, Joachim}, edition = 3, publisher = {Artemis \& Winkler}, location = {D{\"u}sseldorf and Z{\"u}rich}, hyphenation = {german}, sorttitle = {Ilias}, indextitle = {Ilias, Die}, shorttitle = {Ilias}, annotation = {A German translation of the \emph{Iliad}. Note the translator and introduction fields and the format of the location field in the database file. Also note the sorttitle and indextitle fields}, } --- references: - id: iliad type: book author: - family: Homer translator: - family: Schadewaldt given: Wolfgang issued: - year: '2004' title: Die Ilias title-short: Ilias publisher: Artemis & Winkler publisher-place: Düsseldorf; Zürich edition: '3' annote: A German translation of the *Iliad*. Note the translator and introduction fields and the format of the location field in the database file. Also note the sorttitle and indextitle fields language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/inbook-title-booktitle-maintitle-series-2.biblatex0000644000000000000000000000173512743760365030307 0ustar0000000000000000@inbook{item1, Author = {Author, Al}, Bookauthor = {Bookauthor, Bob}, Booksubtitle = {Booksubtitle}, Booktitle = {Booktitle}, Booktitleaddon = {Booktitleaddon}, Date = {2011}, Hyphenation = {french}, Location = {Location}, Mainsubtitle = {Mainsubtitle}, Maintitle = {Maintitle}, Maintitleaddon = {Maintitleaddon}, Number = {3}, Publisher = {Publisher}, Series = {Series}, Subtitle = {Subtitle}, Title = {Title of the "inbook" Entry}, Titleaddon = {Titleaddon}, Volume = {4}} --- references: - id: item1 type: chapter author: - family: Author given: Al container-author: - family: Bookauthor given: Bob issued: - year: '2011' title: 'Title of the “inbook” Entry: Subtitle. Titleaddon' container-title: 'Maintitle: Mainsubtitle. Maintitleaddon' volume-title: 'Booktitle: Booksubtitle. Booktitleaddon' collection-title: Series collection-number: '3' publisher: Publisher publisher-place: Location volume: '4' language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/inbook-title-booktitle-maintitle-series.biblatex0000644000000000000000000000160212743760365030141 0ustar0000000000000000@inbook{item1, Author = {Author, Al}, Booksubtitle = {Booksubtitle}, Booktitle = {Booktitle}, Booktitleaddon = {Booktitleaddon}, Date = {2011}, Hyphenation = {french}, Location = {Location}, Mainsubtitle = {Mainsubtitle}, Maintitle = {Maintitle}, Maintitleaddon = {Maintitleaddon}, Number = {3}, Publisher = {Publisher}, Series = {Series}, Subtitle = {Subtitle}, Title = {Title of the "inbook" Entry}, Titleaddon = {Titleaddon}, Volume = {4}} --- references: - id: item1 type: chapter author: - family: Author given: Al issued: - year: '2011' title: 'Title of the “inbook” Entry: Subtitle. Titleaddon' container-title: 'Maintitle: Mainsubtitle. Maintitleaddon' volume-title: 'Booktitle: Booksubtitle. Booktitleaddon' collection-title: Series collection-number: '3' publisher: Publisher publisher-place: Location volume: '4' language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/inbook.biblatex0000644000000000000000000001264612743760365021566 0ustar0000000000000000@comment{ adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib TODO / citeproc: in biblatex "inbook" entries, citeproc should suppress bookauthor = CSL container-author if identical with author. -- See annotation in kant:kpv. } @string{dtv = {Deutscher Taschenbuch-Verlag}} @inbook{kant:kpv, Annotation = {An edition of Kant's \emph{Collected Works}, volume five. This is an inbook entry which explicitly refers to the \emph{Critique of Practical Reason} only, not to the entire fifth volume. Note the author and bookauthor fields in the database file. By default, the bookauthor is omitted if the values of the author and bookauthor fields are identical}, Author = {Kant, Immanuel}, Bookauthor = {Kant, Immanuel}, Booktitle = {Kritik der praktischen Vernunft. Kritik der Urtheilskraft}, Date = 1968, Hyphenation = {german}, Location = {Berlin}, Maintitle = {Kants Werke. Akademie Textausgabe}, Pages = {1-163}, Publisher = {Walter de Gruyter}, Shorthand = {KpV}, Shorttitle = {Kritik der praktischen Vernunft}, Title = {Kritik der praktischen Vernunft}, Volume = 5} @inbook{kant:ku, Annotation = {An edition of Kant's \emph{Collected Works}, volume five. This is an inbook entry which explicitly refers to the \emph{Critique of Judgment} only, not to the entire fifth volume}, Author = {Kant, Immanuel}, Bookauthor = {Kant, Immanuel}, Booktitle = {Kritik der praktischen Vernunft. Kritik der Urtheilskraft}, Date = 1968, Hyphenation = {german}, Location = {Berlin}, Maintitle = {Kants Werke. Akademie Textausgabe}, Pages = {165-485}, Publisher = {Walter de Gruyter}, Shorthand = {KU}, Title = {Kritik der Urtheilskraft}, Volume = 5} @inbook{nietzsche:historie, Annotation = {A single essay from the critical edition of Nietzsche's works. This inbook entry explicitly refers to an essay found in the first volume. Note the title, booktitle, and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire first volume}, Author = {Nietzsche, Friedrich}, Bookauthor = {Nietzsche, Friedrich}, Booktitle = {Die Geburt der Tragödie. Unzeitgemäße Betrachtungen I--IV. Nachgelassene Schriften 1870--1973}, Date = 1988, Editor = {Colli, Giorgio and Montinari, Mazzino}, Hyphenation = {german}, Indexsorttitle = {Vom Nutzen und Nachtheil der Historie fur das Leben}, Indextitle = {Vom Nutzen und Nachtheil der Historie für das Leben}, Location = {München and Berlin and New York}, Mainsubtitle = {Kritische Studienausgabe}, Maintitle = {Sämtliche Werke}, Pages = {243-334}, Publisher = dtv # { and Walter de Gruyter}, Shorttitle = {Vom Nutzen und Nachtheil der Historie}, Sorttitle = {Werke-01-243}, Sortyear = {1988-2}, Subtitle = {Vom Nutzen und Nachtheil der Historie für das Leben}, Title = {Unzeitgemässe Betrachtungen. Zweites Stück}, Volume = 1} --- references: - id: kant:kpv type: chapter author: - family: Kant given: Immanuel container-author: - family: Kant given: Immanuel issued: - year: '1968' title: Kritik der praktischen Vernunft title-short: Kritik der praktischen Vernunft container-title: Kants Werke. Akademie Textausgabe volume-title: Kritik der praktischen Vernunft. Kritik der Urtheilskraft publisher: Walter de Gruyter publisher-place: Berlin page: '1-163' volume: '5' annote: An edition of Kant’s *Collected Works*, volume five. This is an inbook entry which explicitly refers to the *Critique of Practical Reason* only, not to the entire fifth volume. Note the author and bookauthor fields in the database file. By default, the bookauthor is omitted if the values of the author and bookauthor fields are identical language: de-DE - id: kant:ku type: chapter author: - family: Kant given: Immanuel container-author: - family: Kant given: Immanuel issued: - year: '1968' title: Kritik der Urtheilskraft container-title: Kants Werke. Akademie Textausgabe volume-title: Kritik der praktischen Vernunft. Kritik der Urtheilskraft publisher: Walter de Gruyter publisher-place: Berlin page: '165-485' volume: '5' annote: An edition of Kant’s *Collected Works*, volume five. This is an inbook entry which explicitly refers to the *Critique of Judgment* only, not to the entire fifth volume language: de-DE - id: nietzsche:historie type: chapter author: - family: Nietzsche given: Friedrich editor: - family: Colli given: Giorgio - family: Montinari given: Mazzino container-author: - family: Nietzsche given: Friedrich issued: - year: '1988' title: 'Unzeitgemässe Betrachtungen. Zweites Stück: Vom Nutzen und Nachtheil der Historie für das Leben' title-short: Vom Nutzen und Nachtheil der Historie container-title: 'Sämtliche Werke: Kritische Studienausgabe' volume-title: Die Geburt der Tragödie. Unzeitgemäße Betrachtungen I–IV. Nachgelassene Schriften 1870–1973 publisher: Deutscher Taschenbuch-Verlag; Walter de Gruyter publisher-place: München; Berlin; New York page: '243-334' volume: '1' annote: A single essay from the critical edition of Nietzsche’s works. This inbook entry explicitly refers to an essay found in the first volume. Note the title, booktitle, and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire first volume language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/incollection-2.biblatex0000644000000000000000000000543712743760365023126 0ustar0000000000000000 @comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @string{hup = {Harvard University Press}} @incollection{westfahl:space, Annotation = {A cross-referenced article from a collection. This is an incollection entry with a crossref field. Note the subtitle and indextitle fields}, Author = {Westfahl, Gary}, Crossref = {westfahl:frontier}, Hyphenation = {american}, Indextitle = {True Frontier, The}, Pages = {55-65}, Subtitle = {Confronting and Avoiding the Realities of Space in {American} Science Fiction Films}, Title = {The True Frontier}} @incollection{gaonkar:in, Author = {Gaonkar, Dilip Parameshwar}, Booktitle = {Alternative Modernities}, Date = 2001, Editor = {Gaonkar, Dilip Parameshwar}, Isbn = {0-822-32714-7}, Location = {Durham and London}, Pages = {1-23}, Publisher = {Duke University Press}, Title = {On Alternative Modernities}} @collection{westfahl:frontier, Annotation = {This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields}, Booksubtitle = {The Frontier Theme in Science Fiction}, Booktitle = {Space and Beyond}, Date = 2000, Editor = {Westfahl, Gary}, Hyphenation = {american}, Location = {Westport, Conn. and London}, Publisher = {Greenwood}, Subtitle = {The Frontier Theme in Science Fiction}, Title = {Space and Beyond}} --- references: - id: westfahl:space type: chapter author: - family: Westfahl given: Gary editor: - family: Westfahl given: Gary issued: - year: '2000' title: 'The true frontier: Confronting and avoiding the realities of space in American science fiction films' title-short: The true frontier container-title: 'Space and beyond: The frontier theme in science fiction' publisher: Greenwood publisher-place: Westport, Conn.; London page: '55-65' annote: A cross-referenced article from a collection. This is an incollection entry with a crossref field. Note the subtitle and indextitle fields language: en-US - id: gaonkar:in type: chapter author: - family: Gaonkar given: Dilip Parameshwar editor: - family: Gaonkar given: Dilip Parameshwar issued: - year: '2001' title: On alternative modernities container-title: Alternative modernities publisher: Duke University Press publisher-place: Durham; London page: '1-23' ISBN: '0-822-32714-7' - id: westfahl:frontier type: book editor: - family: Westfahl given: Gary issued: - year: '2000' title: 'Space and beyond: The frontier theme in science fiction' title-short: Space and beyond publisher: Greenwood publisher-place: Westport, Conn.; London annote: This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/incollection.biblatex0000644000000000000000000001032213013615770022742 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @string{hup = {Harvard University Press}} @incollection{brandt, Annotation = {An incollection entry with a series and a number. Note the format of the printed name and compare the useprefix option in the options field as well as vangennep. Also note the indextitle, and indexsorttitle fields}, Author = {von Brandt, Ahasver and Hoffmann, Erich}, Booktitle = {Europa im Hoch- und Spätmittelalter}, Date = 1987, Editor = {Seibt, Ferdinand}, Hyphenation = {german}, Indexsorttitle = {Nordischen Lander von der Mitte des 11. Jahrhunderts bis 1448}, Indextitle = {Nordischen Länder von der Mitte des 11.~Jahrhunderts bis 1448, Die}, Location = {Stuttgart}, Number = 2, Options = {useprefix=false}, Pages = {884-917}, Publisher = {Klett-Cotta}, Series = {Handbuch der europäischen Geschichte}, Shorttitle = {Die nordischen Länder}, Title = {Die nordischen Länder von der Mitte des 11.~Jahrhunderts bis 1448}} @incollection{hyman, Annotation = {An incollection entry with a series and number field}, Author = {Hyman, Arthur}, Booktitle = {Studies in {Aristotle}}, Date = 1981, Editor = {O'Meara, Dominic J.}, Hyphenation = {american}, Indextitle = {Aristotle's Theory of the Intellect}, Keywords = {secondary}, Location = {Washington, D.C.}, Number = 9, Pages = {161-191}, Publisher = {The Catholic University of America Press}, Series = {Studies in Philosophy and the History of Philosophy}, Shorttitle = {Aristotle's Theory of the Intellect}, Title = {Aristotle's Theory of the Intellect and its Interpretation by {Averroes}}} @incollection{pines, Annotation = {A typical incollection entry. Note the indextitle field}, Author = {Pines, Shlomo}, Booktitle = {Studies in Medieval {Jewish} History and Literature}, Date = 1979, Editor = {Twersky, Isadore}, Hyphenation = {american}, Indextitle = {Limitations of Human Knowledge According to Al-Farabi, ibn Bajja, and Maimonides, The}, Keywords = {secondary}, Location = {Cambridge, Mass.}, Pages = {82-109}, Publisher = hup, Shorttitle = {Limitations of Human Knowledge}, Title = {The Limitations of Human Knowledge According to {Al-Farabi}, {ibn Bajja}, and {Maimonides}}} --- references: - id: brandt type: chapter author: - family: Brandt given: Ahasver dropping-particle: von - family: Hoffmann given: Erich editor: - family: Seibt given: Ferdinand issued: - year: '1987' title: Die nordischen Länder von der Mitte des 11. Jahrhunderts bis 1448 title-short: Die nordischen Länder container-title: Europa im Hoch- und Spätmittelalter collection-title: Handbuch der europäischen Geschichte collection-number: '2' publisher: Klett-Cotta publisher-place: Stuttgart page: '884-917' annote: An incollection entry with a series and a number. Note the format of the printed name and compare the useprefix option in the options field as well as vangennep. Also note the indextitle, and indexsorttitle fields language: de-DE - id: hyman type: chapter author: - family: Hyman given: Arthur editor: - family: O’Meara given: Dominic J. issued: - year: '1981' title: Aristotle’s theory of the intellect and its interpretation by Averroes title-short: Aristotle’s theory of the intellect container-title: Studies in Aristotle collection-title: Studies in philosophy and the history of philosophy collection-number: '9' publisher: The Catholic University of America Press publisher-place: Washington, D.C. page: '161-191' annote: An incollection entry with a series and number field keyword: secondary language: en-US - id: pines type: chapter author: - family: Pines given: Shlomo editor: - family: Twersky given: Isadore issued: - year: '1979' title: The limitations of human knowledge according to Al-Farabi, [ibn Bajja]{.nocase}, and Maimonides title-short: Limitations of human knowledge container-title: Studies in medieval Jewish history and literature publisher: Harvard University Press publisher-place: Cambridge, Mass. page: '82-109' annote: A typical incollection entry. Note the indextitle field keyword: secondary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/inproceedings.biblatex0000644000000000000000000000545512743760365023136 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @string{cup = {Cambridge University Press}} @inproceedings{moraux, Annotation = {This is a typical inproceedings entry. Note the booksubtitle, shorttitle, indextitle, and indexsorttitle fields. Also note the eventdate field.}, Author = {Moraux, Paul}, Booktitle = {Aristotle on Mind and the Senses}, Booktitleaddon = {Proceedings of the Seventh Symposium Aristotelicum}, Date = 1979, Editor = {Lloyd, G. E. R. and Owen, G. E. L.}, Eventdate = 1975, Hyphenation = {french}, Indexsorttitle = {De Anima dans la tradition grecque}, Indextitle = {\emph{De Anima} dans la tradition grècque, Le}, Keywords = {secondary}, Location = {Cambridge}, Pages = {281-324}, Publisher = cup, Shorttitle = {\emph{De Anima} dans la tradition grècque}, Subtitle = {Quelques aspects de l'interpretation du traité, de Theophraste à Themistius}, Title = {Le \emph{De Anima} dans la tradition grècque}} @inproceedings{salam, Author = {Salam, Abdus}, Booksubtitle = {Relativistic groups and analyticity}, Booktitle = {Elementary particle theory}, Booktitleaddon = {Proceedings of the Eighth {Nobel} Symposium}, Date = 1968, Editor = {Svartholm, Nils}, Eventdate = {1968-05-19/1968-05-25}, Location = {Stockholm}, Pages = {367-377}, Publisher = {Almquist \& Wiksell}, Title = {Weak and Electromagnetic Interactions}, Venue = {Aspenäsgarden, Lerum}} --- references: - id: moraux type: paper-conference author: - family: Moraux given: Paul editor: - family: Lloyd given: G. E. R. - family: Owen given: G. E. L. issued: - year: '1979' event-date: - year: '1975' title: 'Le *De Anima* dans la tradition grècque: Quelques aspects de l’interpretation du traité, de Theophraste à Themistius' title-short: '*De Anima* dans la tradition grècque' container-title: Aristotle on Mind and the Senses. Proceedings of the Seventh Symposium Aristotelicum publisher: Cambridge University Press publisher-place: Cambridge page: '281-324' annote: This is a typical inproceedings entry. Note the booksubtitle, shorttitle, indextitle, and indexsorttitle fields. Also note the eventdate field. keyword: secondary language: fr-FR - id: salam type: paper-conference author: - family: Salam given: Abdus editor: - family: Svartholm given: Nils issued: - year: '1968' event-date: - year: '1968' month: '5' day: '19' - year: '1968' month: '5' day: '25' title: Weak and electromagnetic interactions container-title: 'Elementary particle theory: Relativistic groups and analyticity. Proceedings of the eighth Nobel symposium' publisher: Almquist & Wiksell publisher-place: Stockholm event-place: Aspenäsgarden, Lerum page: '367-377' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/issue288.biblatex0000644000000000000000000000142013076677105021662 0ustar0000000000000000@thesis{Leavitt_2016, location = {{Los Angeles, CA}}, title = {Upvoting the News: {{Breaking}} News Aggregation, Crowd Collaboration, and Algorithm-Driven Attention on Reddit.Com}, timestamp = {2017-04-06T14:13:22Z}, langid = {english}, institution = {{University of Southern California}}, type = {Dissertation}, author = {Leavitt, Alex}, date = {2016-08}, } --- references: - id: Leavitt_2016 type: thesis author: - family: Leavitt given: Alex issued: - year: '2016' month: '8' title: 'Upvoting the news: Breaking news aggregation, crowd collaboration, and algorithm-driven attention on reddit.com' title-short: Upvoting the news publisher: University of Southern California publisher-place: Los Angeles, CA genre: Dissertation language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/itzhaki.biblatex0000644000000000000000000000506513013615770021733 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Itzhaki 1996) Itzhaki, Nissan. 1996. “Some Remarks on ’t Hooft’s S-matrix for Black Holes” (version 1). March 11. Formatted with pandoc and apa.csl, 2013-10-23: (Itzhaki, 1996) Itzhaki, N. (1996, March 11). Some remarks on ’t Hooft’s S-matrix for black holes. NOTES: - biblio2yaml: - eprinttype = {arxiv}, eprint = {hep-th/9603067}, should be converted to a url: http://arxiv.org/abs/hep-th/9603067 (prefix http://arxiv.org/abs/ seems to work for all arxiv material) - citeproc: - obtaining correct case of "'t Hooft's" in title is possible but awkward: '{t Hooft's} works; {'t Hooft}'s or '{t Hooft}'s do not } @Online{itzhaki, author = {Itzhaki, Nissan}, title = {Some remarks on '{t Hooft's} {S}-matrix for black holes}, date = {1996-03-11}, version = 1, hyphenation = {american}, eprinttype = {arxiv}, eprint = {hep-th/9603067}, annotation = {An online reference from arXiv. Note the eprint and eprinttype fields. Also note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled}, abstract = {We discuss the limitations of 't Hooft's proposal for the black hole S-matrix. We find that the validity of the S-matrix implies violation of the semi-classical approximation at scales large compared to the Planck scale. We also show that the effect of the centrifugal barrier on the S-matrix is crucial even for large transverse distances.}, } --- references: - id: itzhaki type: webpage author: - family: Itzhaki given: Nissan issued: - year: '1996' month: '3' day: '11' title: Some remarks on ’[t Hooft’s]{.nocase} S-matrix for black holes version: '1' annote: An online reference from arXiv. Note the eprint and eprinttype fields. Also note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled abstract: We discuss the limitations of ’t Hooft’s proposal for the black hole S-matrix. We find that the validity of the S-matrix implies violation of the semi-classical approximation at scales large compared to the Planck scale. We also show that the effect of the centrifugal barrier on the S-matrix is crucial even for large transverse distances. URL: http://arxiv.org/abs/hep-th/9603067 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/jaffe.biblatex0000644000000000000000000000425512743760365021355 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Jaffé 1885–1888) Jaffé, Philipp, ed. 1885–1888. *Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \mcxcviii\
*. 2nd ed. 2. Leipzig. Formatted with pandoc and apa.csl, 2013-10-23: (Jaffé, 1885–1888) Jaffé, P. (Ed.). (1885–1888). *Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \mcxcviii\* (2nd ed., 1-2). Leipzig. NOTES: - biblatex conversion: - hyphenation = {latin} - citeproc: - "vols." is missing - works in Zotero - This does not show up in the tests from the citeproc test suite that currently fail. - "\ needs to be fixed. - maybe add markdown syntax ^^small caps^^ ? - in pandoc "plain" output, small caps could be converted to uppercase chars: "MCXCVIII" would definitely look better here. } @Collection{jaffe, editor = {Jaff{\'e}, Philipp}, title = {Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \textsc{mcxcviii}}, date = {1885/1888}, editora = {Loewenfeld, Samuel and Kaltenbrunner, Ferdinand and Ewald, Paul}, edition = 2, volumes = 2, location = {Leipzig}, editoratype = {redactor}, indextitle = {Regesta Pontificum Romanorum}, shorttitle = {Regesta Pontificum Romanorum}, annotation = {A collection entry with edition and volumes fields. Note the editora and editoratype fields}, hyphenation = {latin}, } --- references: - id: jaffe type: book editor: - family: Jaffé given: Philipp issued: - year: '1885' - year: '1888' title: Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum mcxcviii title-short: Regesta Pontificum Romanorum publisher-place: Leipzig number-of-volumes: '2' edition: '2' annote: A collection entry with edition and volumes fields. Note the editora and editoratype fields language: la ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/jcg.biblatex0000644000000000000000000000203412743760365021036 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (“Semantic 3D Media and Content” 2011) “Semantic 3D Media and Content.” 2011. *Computers and Graphics* 35 (4). Formatted with pandoc and apa.csl, 2013-10-23: (“Semantic 3D media and content,” 2011) Semantic 3D media and content. (2011). *Computers and Graphics*, *35*(4). NOTES: - output looks OK even if indistinguishable from article without page numbers } @Periodical{jcg, title = {Computers and Graphics}, year = 2011, issuetitle = {Semantic {3D} Media and Content}, volume = 35, number = 4, issn = {0097-8493}, annotation = {This is a periodical entry with an issn field.}, } --- references: - id: jcg type: article-journal issued: - year: '2011' title: Semantic 3D media and content container-title: Computers and Graphics volume: '35' issue: '4' annote: This is a periodical entry with an issn field. ISSN: '0097-8493' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kant-kpv.biblatex0000644000000000000000000000504512743760365022033 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kant 1968) Kant, Immanuel. 1968. “Kritik der praktischen Vernunft.” In *Kants Werke. Akademie Textausgabe*, by Immanuel Kant, 5:1–163. Berlin: Walter de Gruyter. Formatted with pandoc and apa.csl, 2013-10-23: (Kant, 1968) Kant, I. (1968). Kritik der praktischen Vernunft. In *Kants Werke. Akademie Textausgabe* (Vol. 5, pp. 1–163). Berlin: Walter de Gruyter. NOTES: - citeproc - support for the not yet official "volume-title" is missing - csl style file - if author and container-author are identical, container-author should be suppressed (apparently csl style file issue; zotero shows same behaviour) } @InBook{kant:kpv, title = {Kritik der praktischen Vernunft}, date = 1968, author = {Kant, Immanuel}, booktitle = {Kritik der praktischen Vernunft. Kritik der Urtheilskraft}, bookauthor = {Kant, Immanuel}, maintitle = {Kants Werke. Akademie Textausgabe}, volume = 5, publisher = {Walter de Gruyter}, location = {Berlin}, pages = {1-163}, shorthand = {KpV}, hyphenation = {german}, shorttitle = {Kritik der praktischen Vernunft}, annotation = {An edition of Kant's \emph{Collected Works}, volume five. This is an inbook entry which explicitly refers to the \emph{Critique of Practical Reason} only, not to the entire fifth volume. Note the author and bookauthor fields in the database file. By default, the bookauthor is omitted if the values of the author and bookauthor fields are identical}, } --- references: - id: kant:kpv type: chapter author: - family: Kant given: Immanuel container-author: - family: Kant given: Immanuel issued: - year: '1968' title: Kritik der praktischen Vernunft title-short: Kritik der praktischen Vernunft container-title: Kants Werke. Akademie Textausgabe volume-title: Kritik der praktischen Vernunft. Kritik der Urtheilskraft publisher: Walter de Gruyter publisher-place: Berlin page: '1-163' volume: '5' annote: An edition of Kant’s *Collected Works*, volume five. This is an inbook entry which explicitly refers to the *Critique of Practical Reason* only, not to the entire fifth volume. Note the author and bookauthor fields in the database file. By default, the bookauthor is omitted if the values of the author and bookauthor fields are identical language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kant-ku.biblatex0000644000000000000000000000403012743760365021643 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kant 1968) Kant, Immanuel. 1968. “Kritik der Urtheilskraft.” In *Kants Werke. Akademie Textausgabe*, by Immanuel Kant, 5:165–485. Berlin: Walter de Gruyter. Formatted with pandoc and apa.csl, 2013-10-23: (Kant, 1968) Kant, I. (1968). Kritik der Urtheilskraft. In *Kants Werke. Akademie Textausgabe* (Vol. 5, pp. 165–485). Berlin: Walter de Gruyter. NOTES: - citeproc - support for the not yet official "volume-title" is missing - CSL style file - if author and container-author are identical, container-author should be suppressed (apparently csl style file issue; zotero shows same behaviour) } @InBook{kant:ku, title = {Kritik der Urtheilskraft}, date = 1968, author = {Kant, Immanuel}, booktitle = {Kritik der praktischen Vernunft. Kritik der Urtheilskraft}, bookauthor = {Kant, Immanuel}, maintitle = {Kants Werke. Akademie Textausgabe}, volume = 5, publisher = {Walter de Gruyter}, location = {Berlin}, pages = {165-485}, shorthand = {KU}, hyphenation = {german}, annotation = {An edition of Kant's \emph{Collected Works}, volume five. This is an inbook entry which explicitly refers to the \emph{Critique of Judgment} only, not to the entire fifth volume}, } --- references: - id: kant:ku type: chapter author: - family: Kant given: Immanuel container-author: - family: Kant given: Immanuel issued: - year: '1968' title: Kritik der Urtheilskraft container-title: Kants Werke. Akademie Textausgabe volume-title: Kritik der praktischen Vernunft. Kritik der Urtheilskraft publisher: Walter de Gruyter publisher-place: Berlin page: '165-485' volume: '5' annote: An edition of Kant’s *Collected Works*, volume five. This is an inbook entry which explicitly refers to the *Critique of Judgment* only, not to the entire fifth volume language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kastenholz.biblatex0000644000000000000000000001262512743760365022464 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kastenholz and Hünenberger 2006) Kastenholz, M. A., and Philippe H. Hünenberger. 2006. “Computation of Methodologyindependent Ionic Solvation Free Energies from Molecular Simulations: I. the Electrostatic Potential in Molecular Liquids.” *J. Chem. Phys.* 124. doi:[10.1063/1.2172593](https://doi.org/10.1063/1.2172593 "10.1063/1.2172593"). Formatted with pandoc and apa.csl, 2013-10-23: (Kastenholz & Hünenberger, 2006) Kastenholz, M. A., & Hünenberger, P. H. (2006). Computation of methodologyindependent ionic solvation free energies from molecular simulations: I. the electrostatic potential in molecular liquids. *J. Chem. Phys.*, *124*. doi:[10.1063/1.2172593](https://doi.org/10.1063/1.2172593 "10.1063/1.2172593") NOTES: - biblio2xaml - fix conversion of "\hyphen” - the string "doi:" should not appear as part of the content of the "doi" field } @string{ jchph = {J.~Chem. Phys.} } @Article{kastenholz, author = {Kastenholz, M. A. and H{\"u}nenberger, Philippe H.}, title = {Computation of methodology\hyphen independent ionic solvation free energies from molecular simulations}, journaltitle = jchph, date = 2006, subtitle = {I. {The} electrostatic potential in molecular liquids}, volume = 124, eid = 124106, doi = {10.1063/1.2172593}, hyphenation = {american}, indextitle = {Computation of ionic solvation free energies}, annotation = {An article entry with an eid and a doi field. Note that the \textsc{doi} is transformed into a clickable link if hyperref support has been enabled}, abstract = {The computation of ionic solvation free energies from atomistic simulations is a surprisingly difficult problem that has found no satisfactory solution for more than 15 years. The reason is that the charging free energies evaluated from such simulations are affected by very large errors. One of these is related to the choice of a specific convention for summing up the contributions of solvent charges to the electrostatic potential in the ionic cavity, namely, on the basis of point charges within entire solvent molecules (M scheme) or on the basis of individual point charges (P scheme). The use of an inappropriate convention may lead to a charge-independent offset in the calculated potential, which depends on the details of the summation scheme, on the quadrupole-moment trace of the solvent molecule, and on the approximate form used to represent electrostatic interactions in the system. However, whether the M or P scheme (if any) represents the appropriate convention is still a matter of on-going debate. The goal of the present article is to settle this long-standing controversy by carefully analyzing (both analytically and numerically) the properties of the electrostatic potential in molecular liquids (and inside cavities within them).}, } --- references: - id: kastenholz type: article-journal author: - family: Kastenholz given: M. A. - family: Hünenberger given: Philippe H. issued: - year: '2006' title: 'Computation of methodology-independent ionic solvation free energies from molecular simulations: I. The electrostatic potential in molecular liquids' title-short: Computation of methodology-independent ionic solvation free energies from molecular simulations container-title: J. Chem. Phys. volume: '124' annote: An article entry with an eid and a doi field. Note that the doi is transformed into a clickable link if hyperref support has been enabled abstract: The computation of ionic solvation free energies from atomistic simulations is a surprisingly difficult problem that has found no satisfactory solution for more than 15 years. The reason is that the charging free energies evaluated from such simulations are affected by very large errors. One of these is related to the choice of a specific convention for summing up the contributions of solvent charges to the electrostatic potential in the ionic cavity, namely, on the basis of point charges within entire solvent molecules (M scheme) or on the basis of individual point charges (P scheme). The use of an inappropriate convention may lead to a charge-independent offset in the calculated potential, which depends on the details of the summation scheme, on the quadrupole-moment trace of the solvent molecule, and on the approximate form used to represent electrostatic interactions in the system. However, whether the M or P scheme (if any) represents the appropriate convention is still a matter of on-going debate. The goal of the present article is to settle this long-standing controversy by carefully analyzing (both analytically and numerically) the properties of the electrostatic potential in molecular liquids (and inside cavities within them). DOI: 10.1063/1.2172593 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-a.biblatex0000644000000000000000000000400012743760365022241 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Knuth 1984) Knuth, Donald E. 1984. *Computers & Typesetting*. Vol. A. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2013-10-23: (Knuth, 1984) Knuth, D. E. (1984). *Computers & typesetting* (Vol. A). Reading, Mass.: Addison-Wesley. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{knuth:ct:a, author = {Knuth, Donald E.}, title = {The {\TeX} book}, date = 1984, maintitle = {Computers \& Typesetting}, volume = {A}, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1984-1}, sorttitle = {Computers & Typesetting A}, indexsorttitle= {The TeXbook}, indextitle = {\protect\TeX book, The}, shorttitle = {\TeX book}, annotation = {The first volume of a five-volume book. Note the sorttitle and sortyear fields. We want this volume to be listed after the entry referring to the entire five-volume set. Also note the indextitle and indexsorttitle fields. Indexing packages that don't generate robust index entries require some control sequences to be protected from expansion}, } --- references: - id: knuth:ct:a type: book author: - family: Knuth given: Donald E. issued: - year: '1984' title: Computers & typesetting volume-title: The TeX book publisher: Addison-Wesley publisher-place: Reading, Mass. volume: A annote: The first volume of a five-volume book. Note the sorttitle and sortyear fields. We want this volume to be listed after the entry referring to the entire five-volume set. Also note the indextitle and indexsorttitle fields. Indexing packages that don’t generate robust index entries require some control sequences to be protected from expansion language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-b.biblatex0000644000000000000000000000272612743760365022257 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Knuth 1986) Knuth, Donald E. 1986. *Computers & Typesetting*. Vol. B. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2015-03-08: (Knuth, 1986) Knuth, D. E. (1986). *Computers & typesetting* (Vol. B). Reading, Mass.: Addison-Wesley. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{knuth:ct:b, author = {Knuth, Donald E.}, title = {\TeX: {T}he Program}, date = 1986, maintitle = {Computers \& Typesetting}, volume = {B}, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1986-1}, sorttitle = {Computers & Typesetting B}, indexsorttitle= {TeX: The Program}, shorttitle = {\TeX}, annotation = {The second volume of a five-volume book. Note the sorttitle and sortyear fields. Also note the indexsorttitle field}, } --- references: - id: knuth:ct:b type: book author: - family: Knuth given: Donald E. issued: - year: '1986' title: Computers & typesetting title-short: TeX volume-title: 'TeX: The program' publisher: Addison-Wesley publisher-place: Reading, Mass. volume: B annote: The second volume of a five-volume book. Note the sorttitle and sortyear fields. Also note the indexsorttitle field language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-c.biblatex0000644000000000000000000000270012743760365022250 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Knuth 1986) Knuth, Donald E. 1986. *Computers & Typesetting*. Vol. C. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2015-03-08: (Knuth, 1986) Knuth, D. E. (1986). *Computers & typesetting* (Vol. C). Reading, Mass.: Addison-Wesley. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{knuth:ct:c, author = {Knuth, Donald E.}, title = {The {METAFONTbook}}, date = 1986, maintitle = {Computers \& Typesetting}, volume = {C}, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1986-2}, sorttitle = {Computers & Typesetting C}, indextitle = {METAFONTbook, The}, shorttitle = {{METAFONTbook}}, annotation = {The third volume of a five-volume book. Note the sorttitle and sortyear fields as well as the indextitle field}, } --- references: - id: knuth:ct:c type: book author: - family: Knuth given: Donald E. issued: - year: '1986' title: Computers & typesetting volume-title: The METAFONTbook publisher: Addison-Wesley publisher-place: Reading, Mass. volume: C annote: The third volume of a five-volume book. Note the sorttitle and sortyear fields as well as the indextitle field language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-d.biblatex0000644000000000000000000000277612743760365022266 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Knuth 1986) Knuth, Donald E. 1986. *Computers & Typesetting*. Vol. D. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2015-03-08: (Knuth, 1986) Knuth, D. E. (1986). *Computers & typesetting* (Vol. D). Reading, Mass.: Addison-Wesley. NOTES: - biblio2yaml - Should letters following a colon, such as the "T" in "{{METAFONT}: {T}he Program}" be protected by default? -- I'm not sure ... - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{knuth:ct:d, author = {Knuth, Donald E.}, title = {{METAFONT}: {T}he Program}, date = 1986, maintitle = {Computers \& Typesetting}, volume = {D}, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1986-3}, sorttitle = {Computers & Typesetting D}, shorttitle = {{METAFONT}}, annotation = {The fourth volume of a five-volume book. Note the sorttitle and sortyear fields}, } --- references: - id: knuth:ct:d type: book author: - family: Knuth given: Donald E. issued: - year: '1986' title: Computers & typesetting title-short: METAFONT volume-title: 'METAFONT: The program' publisher: Addison-Wesley publisher-place: Reading, Mass. volume: D annote: The fourth volume of a five-volume book. Note the sorttitle and sortyear fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-e.biblatex0000644000000000000000000000246513115031301022231 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Knuth 1986) Knuth, Donald E. 1986. *Computers & Typesetting*. Vol. E. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2015-03-08: (Knuth, 1986) Knuth, D. E. (1986). *Computers & typesetting* (Vol. E). Reading, Mass.: Addison-Wesley. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @Book{knuth:ct:e, author = {Knuth, Donald E.}, title = {Computer Modern Typefaces}, date = 1986, maintitle = {Computers \& Typesetting}, volume = {E}, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1986-4}, sorttitle = {Computers & Typesetting E}, annotation = {The fifth volume of a five-volume book. Note the sorttitle and sortyear fields}, } --- references: - id: knuth:ct:e type: book author: - family: Knuth given: Donald E. issued: - year: '1986' title: Computers & typesetting volume-title: Computer modern typefaces publisher: Addison-Wesley publisher-place: Reading, Mass. volume: E annote: The fifth volume of a five-volume book. Note the sorttitle and sortyear fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct-related.biblatex0000644000000000000000000000307512743760365023454 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Knuth 1984–1986) Knuth, Donald E. 1984–1986. *Computers & Typesetting*. 5. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2013-10-23: (Knuth, 1984–1986) Knuth, D. E. (1984–1986). *Computers & typesetting* (1-5). Reading, Mass.: Addison-Wesley. NOTES: - biblio2yaml - related = {...}, relatedtype = {multivolume}, -- no counterpart in CSL - citeproc - term "vols." missing } @Book{knuth:ct:related, author = {Knuth, Donald E.}, title = {Computers \& Typesetting}, date = {1984/1986}, volumes = 5, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1984-0}, sorttitle = {Computers & Typesetting}, indexsorttitle= {Computers & Typesetting}, related = {knuth:ct:a,knuth:ct:b,knuth:ct:c,knuth:ct:d,knuth:ct:e}, relatedtype = {multivolume}, annotation = {A five-volume book cited as a whole and related to its individual volumes. Note the related and relatedtype fields}, } --- references: - id: knuth:ct:related type: book author: - family: Knuth given: Donald E. issued: - year: '1984' - year: '1986' title: Computers & typesetting publisher: Addison-Wesley publisher-place: Reading, Mass. number-of-volumes: '5' annote: A five-volume book cited as a whole and related to its individual volumes. Note the related and relatedtype fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/knuth-ct.biblatex0000644000000000000000000000242612743760365022035 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Knuth 1984–1986) Knuth, Donald E. 1984–1986. *Computers & Typesetting*. 5. Reading, Mass.: Addison-Wesley. Formatted with pandoc and apa.csl, 2013-10-23: (Knuth, 1984–1986) Knuth, D. E. (1984–1986). *Computers & typesetting* (1-5). Reading, Mass.: Addison-Wesley. NOTES: - citeproc - term "vols." is missing } @Book{knuth:ct, author = {Knuth, Donald E.}, title = {Computers \& Typesetting}, date = {1984/1986}, volumes = 5, publisher = {Addison-Wesley}, location = {Reading, Mass.}, hyphenation = {american}, sortyear = {1984-0}, sorttitle = {Computers & Typesetting}, indexsorttitle= {Computers & Typesetting}, annotation = {A five-volume book cited as a whole. This is a book entry, note the volumes field}, } --- references: - id: knuth:ct type: book author: - family: Knuth given: Donald E. issued: - year: '1984' - year: '1986' title: Computers & typesetting publisher: Addison-Wesley publisher-place: Reading, Mass. number-of-volumes: '5' annote: A five-volume book cited as a whole. This is a book entry, note the volumes field language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kowalik.biblatex0000644000000000000000000000354612743760365021745 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kowalik and Isard 1995) Kowalik, F., and M. Isard. 1995. “Estimateur d’un défaut de fonctionnement d’un modulateur en quadrature et étage de modulation l’utilisant.” French patent request. Formatted with pandoc and apa.csl, 2013-10-23: (Kowalik & Isard, 1995) Kowalik, F., & Isard, M. (1995, January 11). Estimateur d’un défaut de fonctionnement d’un modulateur en quadrature et étage de modulation l’utilisant. French patent request. } @Patent{kowalik, author = {Kowalik, F. and Isard, M.}, title = {Estimateur d'un d{\'e}faut de fonctionnement d'un modulateur en quadrature et {\'e}tage de modulation l'utilisant}, number = 9500261, date = {1995-01-11}, type = {patreqfr}, hyphenation = {french}, indextitle = {Estimateur d'un d{\'e}faut de fonctionnement}, annotation = {This is a patent entry for a French patent request with a full date. The number is given in the number field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and sorace}, } --- references: - id: kowalik type: patent author: - family: Kowalik given: F. - family: Isard given: M. issued: - year: '1995' month: '1' day: '11' title: Estimateur d’un défaut de fonctionnement d’un modulateur en quadrature et étage de modulation l’utilisant genre: French patent request annote: This is a patent entry for a French patent request with a full date. The number is given in the number field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and sorace number: '9500261' language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kullback-related.biblatex0000644000000000000000000000233212743760365023502 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kullback 1997) Kullback, Solomon. 1997. *Information Theory and Statistics*. New York: Dover Publications. Formatted with pandoc and apa.csl, 2013-10-23: (Kullback, 1997) Kullback, S. (1997). *Information theory and statistics*. New York: Dover Publications. NOTES: - related = {kullback}, relatedtype = {origpubin}, -- not possible in CSL } @Book{kullback:related, author = {Kullback, Solomon}, title = {Information Theory and Statistics}, year = 1997, publisher = {Dover Publications}, location = {New York}, hyphenation = {american}, related = {kullback}, relatedtype = {origpubin}, annotation = {A reprint of the kullback entry. Note the format of the related and relatedtype fields}, } --- references: - id: kullback:related type: book author: - family: Kullback given: Solomon issued: - year: '1997' title: Information theory and statistics publisher: Dover Publications publisher-place: New York annote: A reprint of the kullback entry. Note the format of the related and relatedtype fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kullback-reprint.biblatex0000644000000000000000000000301712743760365023546 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kullback 1997) Kullback, Solomon. 1997. *Information Theory and Statistics*. New York: Dover Publications. Formatted with pandoc and apa.csl, 2013-10-23: (Kullback, 1997) Kullback, S. (1997). *Information theory and statistics*. New York: Dover Publications. NOTES: Formatted with chicago-author-date-TEST-20131018.csl (Kullback [1959] 1997) Kullback, Solomon. (1959) 1997. *Information Theory and Statistics*. New York: Dover Publications. } @Book{kullback:reprint, author = {Kullback, Solomon}, title = {Information Theory and Statistics}, year = 1997, publisher = {Dover Publications}, location = {New York}, origyear = 1959, origpublisher= {John Wiley \& Sons}, hyphenation = {american}, annotation = {A reprint of the kullback entry. Note the format of origyear and origpublisher. These fields are not used by the standard bibliography styles}, } --- references: - id: kullback:reprint type: book author: - family: Kullback given: Solomon issued: - year: '1997' original-date: - year: '1959' title: Information theory and statistics publisher: Dover Publications original-publisher: John Wiley & Sons publisher-place: New York annote: A reprint of the kullback entry. Note the format of origyear and origpublisher. These fields are not used by the standard bibliography styles language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/kullback.biblatex0000644000000000000000000000152712743760365022071 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kullback 1959) Kullback, Solomon. 1959. *Information Theory and Statistics*. New York: John Wiley & Sons. Formatted with pandoc and apa.csl, 2013-10-23: (Kullback, 1959) Kullback, S. (1959). *Information theory and statistics*. New York: John Wiley & Sons. } @Book{kullback, author = {Kullback, Solomon}, title = {Information Theory and Statistics}, year = 1959, publisher = {John Wiley \& Sons}, location = {New York}, hyphenation = {american}, } --- references: - id: kullback type: book author: - family: Kullback given: Solomon issued: - year: '1959' title: Information theory and statistics publisher: John Wiley & Sons publisher-place: New York language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/laufenberg.biblatex0000644000000000000000000000660212743760365022412 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Laufenberg et al. 2006) Laufenberg, Xaver, Dominique Eynius, Helmut Suelzle, Stephan Usbeck, Matthias Spaeth, Miriam Neuser-Hoffmann, Christian Myrzik, et al. 2006. “Elektrische Einrichtung und Betriebsverfahren.” European patent. Formatted with pandoc and apa.csl, 2013-10-23: (Laufenberg et al., 2006) Laufenberg, X., Eynius, D., Suelzle, H., Usbeck, S., Spaeth, M., Neuser-Hoffmann, M., … Ebner, N. (2006, September 13). Elektrische Einrichtung und Betriebsverfahren. European patent. NOTES: - biblio2yaml - Is there any equivalent of "holder" in CSL? } @Patent{laufenberg, author = {Laufenberg, Xaver and Eynius, Dominique and Suelzle, Helmut and Usbeck, Stephan and Spaeth, Matthias and Neuser-Hoffmann, Miriam and Myrzik, Christian and Schmid, Manfred and Nietfeld, Franz and Thiel, Alexander and Braun, Harald and Ebner, Norbert}, title = {Elektrische Einrichtung und Betriebsverfahren}, number = 1700367, date = {2006-09-13}, holder = {{Robert Bosch GmbH} and {Daimler Chrysler AG} and {Bayerische Motoren Werke AG}}, type = {patenteu}, hyphenation = {german}, annotation = {This is a patent entry with a holder field. Note the format of the type and location fields in the database file. Compare almendro, sorace, and kowalik}, abstract = {The invention relates to an electric device comprising a generator, in particular for use in the vehicle electric system of a motor vehicle and a controller for controlling the generator voltage. The device is equipped with a control zone, in which the voltage is controlled and zones, in which the torque is controlled. The invention also relates to methods for operating a device of this type.}, file = {http://v3.espacenet.com/textdoc?IDX=EP1700367}, } --- references: - id: laufenberg type: patent author: - family: Laufenberg given: Xaver - family: Eynius given: Dominique - family: Suelzle given: Helmut - family: Usbeck given: Stephan - family: Spaeth given: Matthias - family: Neuser-Hoffmann given: Miriam - family: Myrzik given: Christian - family: Schmid given: Manfred - family: Nietfeld given: Franz - family: Thiel given: Alexander - family: Braun given: Harald - family: Ebner given: Norbert issued: - year: '2006' month: '9' day: '13' title: Elektrische Einrichtung und Betriebsverfahren genre: European patent annote: This is a patent entry with a holder field. Note the format of the type and location fields in the database file. Compare almendro, sorace, and kowalik abstract: The invention relates to an electric device comprising a generator, in particular for use in the vehicle electric system of a motor vehicle and a controller for controlling the generator voltage. The device is equipped with a control zone, in which the voltage is controlled and zones, in which the torque is controlled. The invention also relates to methods for operating a device of this type. number: '1700367' language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/loh.biblatex0000644000000000000000000000302012743760365021051 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Loh 1992) Loh, Nin C. 1992. “High-resolution Micromachined Interferometric Accelerometer.” Master’s thesis, Cambridge, Mass.: Massachusetts Institute of Technology. Formatted with pandoc and apa.csl, 2013-10-23: (Loh, 1992) Loh, N. C. (1992). *High-resolution micromachined interferometric accelerometer* (Master’s thesis). Massachusetts Institute of Technology, Cambridge, Mass. NOTES: - biblio2yaml - At some point, actual localization of "localization keys" will have to be implemented } @Thesis{loh, author = {Loh, Nin C.}, title = {High-Resolution Micromachined Interferometric Accelerometer}, type = {mathesis}, institution = {Massachusetts Institute of Technology}, date = 1992, location = {Cambridge, Mass.}, hyphenation = {american}, annotation = {This is a typical thesis entry for an MA thesis. Note the type field in the database file which uses a localization key}, } --- references: - id: loh type: thesis author: - family: Loh given: Nin C. issued: - year: '1992' title: High-resolution micromachined interferometric accelerometer publisher: Massachusetts Institute of Technology publisher-place: Cambridge, Mass. genre: Master’s thesis annote: This is a typical thesis entry for an MA thesis. Note the type field in the database file which uses a localization key language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/malinowski.biblatex0000644000000000000000000000326213013615770022442 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Malinowski 1972) Malinowski, Bronisław. 1972. *Argonauts of the Western Pacific: An Account of Native Enterprise and Adventure in the Archipelagoes of Melanesian New Guinea*. 8th ed. London: Routledge and Kegan Paul. Formatted with pandoc and apa.csl, 2013-10-23: (Malinowski, 1972) Malinowski, B. (1972). *Argonauts of the Western Pacific: An account of native enterprise and adventure in the Archipelagoes of Melanesian New Guinea* (8th ed.). London: Routledge and Kegan Paul. } @Book{malinowski, author = {Malinowski, Bronis{\l}aw}, title = {Argonauts of the {Western Pacific}}, date = 1972, edition = 8, publisher = {Routledge {and} Kegan Paul}, location = {London}, hyphenation = {british}, subtitle = {An account of native enterprise and adventure in the {Archipelagoes of Melanesian New Guinea}}, shorttitle = {Argonauts}, annotation = {This is a book entry. Note the format of the publisher and edition fields as well as the subtitle field}, } --- references: - id: malinowski type: book author: - family: Malinowski given: Bronisław issued: - year: '1972' title: 'Argonauts of the Western Pacific: An account of native enterprise and adventure in the [Archipelagoes of Melanesian New Guinea]{.nocase}' title-short: Argonauts publisher: Routledge and Kegan Paul publisher-place: London edition: '8' annote: This is a book entry. Note the format of the publisher and edition fields as well as the subtitle field language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/manual.biblatex0000644000000000000000000000352712743760365021560 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @Manual{cms, title = {The {Chicago} Manual of Style}, date = 2003, subtitle = {The Essential Guide for Writers, Editors, and Publishers}, edition = 15, publisher = {University of Chicago Press}, location = {Chicago, Ill.}, isbn = {0-226-10403-6}, label = {CMS}, hyphenation = {american}, sorttitle = {Chicago Manual of Style}, indextitle = {Chicago Manual of Style, The}, shorttitle = {Chicago Manual of Style}, annotation = {This is a manual entry without an author or editor. Note the label field in the database file which is provided for author-year citation styles. Also note the sorttitle and indextitle fields. By default, all entries without an author or editor are alphabetized by title but we want this entry to be alphabetized under \enquote*{C} rather than \enquote*{T}. There's also an isbn field}, } --- references: - id: cms type: book issued: - year: '2003' title: 'The Chicago manual of style: The essential guide for writers, editors, and publishers' title-short: Chicago manual of style publisher: University of Chicago Press publisher-place: Chicago, Ill. edition: '15' annote: This is a manual entry without an author or editor. Note the label field in the database file which is provided for author-year citation styles. Also note the sorttitle and indextitle fields. By default, all entries without an author or editor are alphabetized by title but we want this entry to be alphabetized under “C” rather than “T”. There’s also an isbn field ISBN: '0-226-10403-6' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/markey.biblatex0000644000000000000000000000310012743760365021556 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Markey 2005) Markey, Nicolas. 2005. “Tame the BeaST: The B to X of BibTeX” (version 1.3). October 16. . Formatted with pandoc and apa.csl, 2013-10-23: (Markey, 2005) Markey, N. (2005, October 16). Tame the BeaST: The B to X of BibTeX. Retrieved October 01, 2006, from } @Online{markey, author = {Markey, Nicolas}, title = {Tame the {BeaST}}, date = {2005-10-16}, url = {http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf}, subtitle = {The {B} to {X} of {BibTeX}}, version = {1.3}, urldate = {2006-10-01}, hyphenation = {american}, sorttitle = {Tame the Beast}, annotation = {An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file.}, } --- references: - id: markey type: webpage author: - family: Markey given: Nicolas issued: - year: '2005' month: '10' day: '16' accessed: - year: '2006' month: '10' day: '1' title: 'Tame the BeaST: The B to X of BibTeX' title-short: Tame the BeaST version: '1.3' annote: An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file. URL: http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/maron.biblatex0000644000000000000000000000312212743760365021406 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Maron 2000) Maron, Monika. 2000. *Animal Triste*. Translated by Brigitte Goldstein. Lincoln: University of Nebraska Press. Formatted with pandoc and apa.csl, 2013-10-23: (Maron, 2000) Maron, M. (2000). *Animal triste*. (B. Goldstein, Trans.). Lincoln: University of Nebraska Press. NOTES: - origlanguage concatenated with translator, e.g. “translated from the German by …” not possible in CSL } @Book{maron, author = {Maron, Monika}, title = {Animal Triste}, date = 2000, translator = {Brigitte Goldstein}, origlanguage = {german}, publisher = {University of Nebraska Press}, location = {Lincoln}, hyphenation = {american}, shorttitle = {Animal Triste}, annotation = {An English translation of a German novel with a French title. In other words: a book entry with a translator field. Note the origlanguage field which is concatenated with the translator}, } --- references: - id: maron type: book author: - family: Maron given: Monika translator: - family: Goldstein given: Brigitte issued: - year: '2000' title: Animal triste title-short: Animal triste publisher: University of Nebraska Press publisher-place: Lincoln annote: 'An English translation of a German novel with a French title. In other words: a book entry with a translator field. Note the origlanguage field which is concatenated with the translator' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/massa.biblatex0000644000000000000000000000163212743760365021402 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Massa 2004) Massa, Werner. 2004. *Crystal Structure Determination*. 2nd ed. Berlin: Spinger. Formatted with pandoc and apa.csl, 2013-10-23: (Massa, 2004) Massa, W. (2004). *Crystal structure determination* (2nd ed.). Berlin: Spinger. } @Book{massa, author = {Werner Massa}, title = {Crystal structure determination}, date = 2004, edition = 2, publisher = {Spinger}, location = {Berlin}, hyphenation = {british}, annotation = {A book entry with an edition field}, } --- references: - id: massa type: book author: - family: Massa given: Werner issued: - year: '2004' title: Crystal structure determination publisher: Spinger publisher-place: Berlin edition: '2' annote: A book entry with an edition field language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/moore-related.biblatex0000644000000000000000000000254012743760365023034 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Moore 1998) Moore, Gordon E. 1998. “Cramming More Components onto Integrated Circuits.” *Proceedings of the IEEE* 86 (1): 82–85. Formatted with pandoc and apa.csl, 2013-10-23: (Moore, 1998) Moore, G. E. (1998). Cramming more components onto integrated circuits. *Proceedings of the IEEE*, *86*(1), 82–85. NOTES: - "related = {moore}, relatedtype = {reprintfrom}," – no equivalent implemented in CSL } @Article{moore:related, author = {Moore, Gordon E.}, title = {Cramming more components onto integrated circuits}, journaltitle = {Proceedings of the {IEEE}}, year = 1998, volume = 86, number = 1, pages = {82-85}, hyphenation = {american}, related = {moore}, relatedtype = {reprintfrom}, annotation = {A reprint of Moore's law. Note the related and relatedtype fields}, } --- references: - id: moore:related type: article-journal author: - family: Moore given: Gordon E. issued: - year: '1998' title: Cramming more components onto integrated circuits container-title: Proceedings of the IEEE page: '82-85' volume: '86' issue: '1' annote: A reprint of Moore’s law. Note the related and relatedtype fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/moore.biblatex0000644000000000000000000000172412743760365021421 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Moore 1965) Moore, Gordon E. 1965. “Cramming More Components onto Integrated Circuits.” *Electronics* 38 (8): 114–117. Formatted with pandoc and apa.csl, 2013-10-23: (Moore, 1965) Moore, G. E. (1965). Cramming more components onto integrated circuits. *Electronics*, *38*(8), 114–117. } @Article{moore, author = {Moore, Gordon E.}, title = {Cramming more components onto integrated circuits}, journaltitle = {Electronics}, year = 1965, volume = 38, number = 8, pages = {114-117}, hyphenation = {american}, } --- references: - id: moore type: article-journal author: - family: Moore given: Gordon E. issued: - year: '1965' title: Cramming more components onto integrated circuits container-title: Electronics page: '114-117' volume: '38' issue: '8' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/moraux.biblatex0000644000000000000000000000555112743760365021615 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Moraux 1979) Moraux, Paul. 1979. “Le *De Anima* dans la tradition grècque: Quelques aspects de l’interpretation du traité, de Theophraste à Themistius.” In *Aristotle on Mind and the Senses. Proceedings of the Seventh Symposium Aristotelicum*, edited by G. E. R. Lloyd and G. E. L. Owen, 281–324. Cambridge: Cambridge University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Moraux, 1979) Moraux, P. (1979). Le *De Anima* dans la tradition grècque: Quelques aspects de l’interpretation du traité, de Theophraste à Themistius. In G. E. R. Lloyd & G. E. L. Owen (eds.), *Aristotle on Mind and the Senses. Proceedings of the Seventh Symposium Aristotelicum* (pp. 281–324). Cambridge: Cambridge University Press. NOTES: - Since case (conversion) can only be specified per entry, not per field, for apa.csl the case of container-title would have to be adjusted manually. } @string{ cup = {Cambridge University Press} } @InProceedings{moraux, author = {Moraux, Paul}, editor = {Lloyd, G. E. R. and Owen, G. E. L.}, title = {Le \emph{De Anima} dans la tradition gr{\`e}cque}, date = 1979, booktitle = {Aristotle on Mind and the Senses}, subtitle = {Quelques aspects de l'interpretation du trait{\'e}, de Theophraste {\`a} Themistius}, booktitleaddon= {Proceedings of the Seventh Symposium Aristotelicum}, eventdate = 1975, publisher = cup, location = {Cambridge}, pages = {281-324}, keywords = {secondary}, hyphenation = {french}, indexsorttitle= {De Anima dans la tradition grecque}, indextitle = {\emph{De Anima} dans la tradition gr{\`e}cque, Le}, shorttitle = {\emph{De Anima} dans la tradition gr{\`e}cque}, annotation = {This is a typical inproceedings entry. Note the booksubtitle, shorttitle, indextitle, and indexsorttitle fields. Also note the eventdate field.}, } --- references: - id: moraux type: paper-conference author: - family: Moraux given: Paul editor: - family: Lloyd given: G. E. R. - family: Owen given: G. E. L. issued: - year: '1979' event-date: - year: '1975' title: 'Le *De Anima* dans la tradition grècque: Quelques aspects de l’interpretation du traité, de Theophraste à Themistius' title-short: '*De Anima* dans la tradition grècque' container-title: Aristotle on Mind and the Senses. Proceedings of the Seventh Symposium Aristotelicum publisher: Cambridge University Press publisher-place: Cambridge page: '281-324' annote: This is a typical inproceedings entry. Note the booksubtitle, shorttitle, indextitle, and indexsorttitle fields. Also note the eventdate field. keyword: secondary language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/murray.biblatex0000644000000000000000000000566413013615770021614 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Hostetler et al. 1998) Hostetler, Michael J., Julia E. Wingate, Chuan-Jian Zhong, Jay E. Harris, Richard W. Vachet, Michael R. Clark, J. David Londono, et al. 1998. “Alkanethiolate Gold Cluster Molecules with Core Diameters from 1.5 to 5.2 nm: Core and Monolayer Properties as a Function of Core Size.” *Langmuir* 14 (1): 17–30. Formatted with pandoc and apa.csl, 2013-10-23: (Hostetler et al., 1998) Hostetler, M. J., Wingate, J. E., Zhong, C.-J., Harris, J. E., Vachet, R. W., Clark, M. R., … Murray, R. W. (1998). Alkanethiolate gold cluster molecules with core diameters from 1.5 to 5.2 nm: Core and monolayer properties as a function of core size. *Langmuir*, *14*(1), 17–30. } @Article{murray, author = {Hostetler, Michael J. and Wingate, Julia E. and Zhong, Chuan-Jian and Harris, Jay E. and Vachet, Richard W. and Clark, Michael R. and Londono, J. David and Green, Stephen J. and Stokes, Jennifer J. and Wignall, George D. and Glish, Gary L. and Porter, Marc D. and Evans, Neal D. and Murray, Royce W.}, title = {Alkanethiolate gold cluster molecules with core diameters from 1.5 to 5.2~{nm}}, journaltitle = {Langmuir}, date = 1998, subtitle = {Core and monolayer properties as a function of core size}, volume = 14, number = 1, pages = {17-30}, hyphenation = {american}, indextitle = {Alkanethiolate gold cluster molecules}, shorttitle = {Alkanethiolate gold cluster molecules}, annotation = {An article entry with \arabic{author} authors. By default, long author and editor lists are automatically truncated. This is configurable}, } --- references: - id: murray type: article-journal author: - family: Hostetler given: Michael J. - family: Wingate given: Julia E. - family: Zhong given: Chuan-Jian - family: Harris given: Jay E. - family: Vachet given: Richard W. - family: Clark given: Michael R. - family: Londono given: J. David - family: Green given: Stephen J. - family: Stokes given: Jennifer J. - family: Wignall given: George D. - family: Glish given: Gary L. - family: Porter given: Marc D. - family: Evans given: Neal D. - family: Murray given: Royce W. issued: - year: '1998' title: 'Alkanethiolate gold cluster molecules with core diameters from 1.5 to 5.2 [nm]{.nocase}: Core and monolayer properties as a function of core size' title-short: Alkanethiolate gold cluster molecules container-title: Langmuir page: '17-30' volume: '14' issue: '1' annote: An article entry with author authors. By default, long author and editor lists are automatically truncated. This is configurable language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/nietzsche-historie.biblatex0000644000000000000000000000666512743760365024131 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Nietzsche 1988) Nietzsche, Friedrich. 1988. “Unzeitgemässe Betrachtungen. Zweites Stück: Vom Nutzen und Nachtheil der Historie für das Leben.” In *Sämtliche Werke: Kritische Studienausgabe*, by Friedrich Nietzsche, edited by Giorgio Colli and Mazzino Montinari, 1:243–334. München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. Formatted with pandoc and apa.csl, 2013-10-23: (Nietzsche, 1988) Nietzsche, F. (1988). Unzeitgemässe Betrachtungen. Zweites Stück: Vom Nutzen und Nachtheil der Historie für das Leben. In G. Colli & M. Montinari (eds.), *Sämtliche Werke: Kritische Studienausgabe* (Vol. 1, pp. 243–334). München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. } @string{ dtv = {Deutscher Taschenbuch-Verlag} } @InBook{nietzsche:historie, title = {Unzeitgem{\"a}sse Betrachtungen. Zweites St{\"u}ck}, date = 1988, author = {Nietzsche, Friedrich}, booktitle = {Die Geburt der Trag{\"o}die. Unzeitgem{\"a}{\ss}e Betrachtungen I--IV. Nachgelassene Schriften 1870--1973}, bookauthor = {Nietzsche, Friedrich}, editor = {Colli, Giorgio and Montinari, Mazzino}, subtitle = {Vom Nutzen und Nachtheil der Historie f{\"u}r das Leben}, maintitle = {S{\"a}mtliche Werke}, mainsubtitle = {Kritische Studienausgabe}, volume = 1, publisher = dtv # { and Walter de Gruyter}, location = {M{\"u}nchen and Berlin and New York}, pages = {243-334}, hyphenation = {german}, sortyear = {1988-2}, sorttitle = {Werke-01-243}, indexsorttitle= {Vom Nutzen und Nachtheil der Historie fur das Leben}, indextitle = {Vom Nutzen und Nachtheil der Historie f{\"u}r das Leben}, shorttitle = {Vom Nutzen und Nachtheil der Historie}, annotation = {A single essay from the critical edition of Nietzsche's works. This inbook entry explicitly refers to an essay found in the first volume. Note the title, booktitle, and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire first volume}, } --- references: - id: nietzsche:historie type: chapter author: - family: Nietzsche given: Friedrich editor: - family: Colli given: Giorgio - family: Montinari given: Mazzino container-author: - family: Nietzsche given: Friedrich issued: - year: '1988' title: 'Unzeitgemässe Betrachtungen. Zweites Stück: Vom Nutzen und Nachtheil der Historie für das Leben' title-short: Vom Nutzen und Nachtheil der Historie container-title: 'Sämtliche Werke: Kritische Studienausgabe' volume-title: Die Geburt der Tragödie. Unzeitgemäße Betrachtungen I–IV. Nachgelassene Schriften 1870–1973 publisher: Deutscher Taschenbuch-Verlag; Walter de Gruyter publisher-place: München; Berlin; New York page: '243-334' volume: '1' annote: A single essay from the critical edition of Nietzsche’s works. This inbook entry explicitly refers to an essay found in the first volume. Note the title, booktitle, and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire first volume language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/nietzsche-ksa.biblatex0000644000000000000000000000503012743760365023042 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Nietzsche 1988) Nietzsche, Friedrich. 1988. *Sämtliche Werke: Kritische Studienausgabe*. Edited by Giorgio Colli and Mazzino Montinari. 2nd ed. 15. München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. Formatted with pandoc and apa.csl, 2013-10-23: (Nietzsche, 1988) Nietzsche, F. (1988). *Sämtliche Werke: Kritische Studienausgabe*. (G. Colli & M. Montinari, eds.) (2nd ed., 1-15). München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. NOTES: - biblio2yaml - term "vols." missing } @string{ dtv = {Deutscher Taschenbuch-Verlag} } @Book{nietzsche:ksa, author = {Nietzsche, Friedrich}, title = {S{\"a}mtliche Werke}, date = 1988, editor = {Colli, Giorgio and Montinari, Mazzino}, edition = 2, volumes = 15, publisher = dtv # { and Walter de Gruyter}, location = {M{\"u}nchen and Berlin and New York}, hyphenation = {german}, sortyear = {1988-0}, sorttitle = {Werke-00-000}, indexsorttitle= {Samtliche Werke}, subtitle = {Kritische Studienausgabe}, annotation = {The critical edition of Nietzsche's works. This is a book entry referring to a 15-volume work as a whole. Note the volumes field and the format of the publisher and location fields in the database file. Also note the sorttitle and sortyear fields which are used to fine-tune the sorting order of the bibliography. We want this item listed first in the bibliography}, } --- references: - id: nietzsche:ksa type: book author: - family: Nietzsche given: Friedrich editor: - family: Colli given: Giorgio - family: Montinari given: Mazzino issued: - year: '1988' title: 'Sämtliche Werke: Kritische Studienausgabe' title-short: Sämtliche Werke publisher: Deutscher Taschenbuch-Verlag; Walter de Gruyter publisher-place: München; Berlin; New York number-of-volumes: '15' edition: '2' annote: The critical edition of Nietzsche’s works. This is a book entry referring to a 15-volume work as a whole. Note the volumes field and the format of the publisher and location fields in the database file. Also note the sorttitle and sortyear fields which are used to fine-tune the sorting order of the bibliography. We want this item listed first in the bibliography language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/nietzsche-ksa1.biblatex0000644000000000000000000000545412743760365023135 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2015-03-08: (Nietzsche 1988) Nietzsche, Friedrich. 1988. *Sämtliche Werke: Kritische Studienausgabe*. Edited by Giorgio Colli and Mazzino Montinari. 2nd ed. Vol. 1. München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. Formatted with pandoc and apa.csl, 2015-03-08: (Nietzsche, 1988) Nietzsche, F. (1988). *Sämtliche Werke: Kritische Studienausgabe*. (G. Colli & M. Montinari, eds., F. Nietzsche) (2nd ed., Vol. 1). München; Berlin; New York: Deutscher Taschenbuch-Verlag; Walter de Gruyter. NOTES: - volume-title currently not implemented by chicago-author-date.csl and apa.csl. } @string{ dtv = {Deutscher Taschenbuch-Verlag} } @Book{nietzsche:ksa1, author = {Nietzsche, Friedrich}, title = {Die Geburt der Trag{\"o}die. Unzeitgem{\"a}{\ss}e Betrachtungen I--IV. Nachgelassene Schriften 1870--1973}, date = 1988, editor = {Colli, Giorgio and Montinari, Mazzino}, maintitle = {S{\"a}mtliche Werke}, mainsubtitle = {Kritische Studienausgabe}, volume = 1, edition = 2, publisher = dtv # { and Walter de Gruyter}, location = {M{\"u}nchen and Berlin and New York}, hyphenation = {german}, sortyear = {1988-1}, sorttitle = {Werke-01-000}, indexsorttitle= {Samtliche Werke I}, bookauthor = {Nietzsche, Friedrich}, indextitle = {S{\"a}mtliche Werke I}, shorttitle = {S{\"a}mtliche Werke I}, annotation = {A single volume from the critical edition of Nietzsche's works. This book entry explicitly refers to the first volume only. Note the title and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire edition}, } --- references: - id: nietzsche:ksa1 type: book author: - family: Nietzsche given: Friedrich editor: - family: Colli given: Giorgio - family: Montinari given: Mazzino container-author: - family: Nietzsche given: Friedrich issued: - year: '1988' title: 'Sämtliche Werke: Kritische Studienausgabe' volume-title: Die Geburt der Tragödie. Unzeitgemäße Betrachtungen I–IV. Nachgelassene Schriften 1870–1973 publisher: Deutscher Taschenbuch-Verlag; Walter de Gruyter publisher-place: München; Berlin; New York volume: '1' edition: '2' annote: A single volume from the critical edition of Nietzsche’s works. This book entry explicitly refers to the first volume only. Note the title and maintitle fields. Also note the sorttitle and sortyear fields. We want this entry to be listed after the entry referring to the entire edition language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/nussbaum.biblatex0000644000000000000000000000254212743760365022134 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Nussbaum 1978) Nussbaum, Martha. 1978. *Aristotle’s “De Motu Animalium”*. Princeton: Princeton University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Nussbaum, 1978) Nussbaum, M. (1978). *Aristotle’s “De Motu Animalium”*. Princeton: Princeton University Press. } @string{ pup = {Princeton University Press} } @Book{nussbaum, author = {Nussbaum, Martha}, title = {Aristotle's \mkbibquote{De Motu Animalium}}, date = 1978, publisher = pup, location = {Princeton}, keywords = {secondary}, hyphenation = {american}, sorttitle = {Aristotle's De Motu Animalium}, indexsorttitle= {Aristotle's De Motu Animalium}, annotation = {A book entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file}, } --- references: - id: nussbaum type: book author: - family: Nussbaum given: Martha issued: - year: '1978' title: Aristotle’s “De Motu Animalium” publisher: Princeton University Press publisher-place: Princeton annote: A book entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file keyword: secondary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/online.biblatex0000644000000000000000000000432312743760365021562 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @online{markey, Annotation = {An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file.}, Author = {Markey, Nicolas}, Date = {2005-10-16}, Hyphenation = {american}, Sorttitle = {Tame the Beast}, Subtitle = {The {B} to {X} of {BibTeX}}, Title = {Tame the {BeaST}}, Url = {http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf}, Urldate = {2006-10-01}, Version = {1.3}, } @online{CTAN, Annotation = {This is an online entry. The \textsc{url}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and\slash or a year}, Date = 2006, Hyphenation = {american}, Label = {CTAN}, Subtitle = {The {Comprehensive TeX Archive Network}}, Title = {{CTAN}}, Url = {http://www.ctan.org}, Urldate = {2006-10-01}, } --- references: - id: markey type: webpage author: - family: Markey given: Nicolas issued: - year: '2005' month: '10' day: '16' accessed: - year: '2006' month: '10' day: '1' title: 'Tame the BeaST: The B to X of BibTeX' title-short: Tame the BeaST version: '1.3' annote: An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file. URL: http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf language: en-US - id: CTAN type: webpage issued: - year: '2006' accessed: - year: '2006' month: '10' day: '1' title: 'CTAN: The Comprehensive TeX Archive Network' title-short: CTAN annote: This is an online entry. The url, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and/or a year URL: http://www.ctan.org language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/options-url-false-doi-false.biblatex0000644000000000000000000000210612743760365025517 0ustar0000000000000000@comment{ Entry contains url and doi fields; these should be discarded since the options field specifies url=false, doi=false. Exception: As in standard biblatex, in online entries url should never be discarded, even if options contains url=false. } @article{item1, Author = {Author, Andy}, Date = {2012}, Doi = {1234/5678.90}, Journal = {Journal}, Options = {url=false, doi=false}, Title = {Title, Any Entry Type Except online}, Url = {http://foo.bar} } @online{item2, Author = {Author, Andy}, Date = {2012}, Doi = {1234/5678.90}, Journal = {Journal}, Options = {url=false, doi=false}, Title = {Title, Entry Type online}, Url = {http://foo.bar} } --- references: - id: item1 type: article-journal author: - family: Author given: Andy issued: - year: '2012' title: Title, any entry type except online container-title: Journal - id: item2 type: webpage author: - family: Author given: Andy issued: - year: '2012' title: Title, entry type online container-title: Journal URL: http://foo.bar ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/padhye.biblatex0000644000000000000000000001210512743760365021545 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Padhye, Firoiu, and Towsley 1999) Padhye, Jitendra, Victor Firoiu, and Don Towsley. 1999. “A Stochastic Model of TCP Reno Congestion Avoidance and Control.” Technical report 99-02. Amherst, Mass.: University of Massachusetts. Formatted with pandoc and apa.csl, 2013-10-23: (Padhye, Firoiu, & Towsley, 1999) Padhye, J., Firoiu, V., & Towsley, D. (1999). *A stochastic model of TCP Reno congestion avoidance and control* (technical report No. 99-02). Amherst, Mass.: University of Massachusetts. } @Report{padhye, author = {Padhye, Jitendra and Firoiu, Victor and Towsley, Don}, title = {A Stochastic Model of {TCP Reno} Congestion Avoidance and Control}, type = {techreport}, institution = {University of Massachusetts}, date = 1999, number = {99-02}, location = {Amherst, Mass.}, hyphenation = {american}, sorttitle = {A Stochastic Model of TCP Reno Congestion Avoidance and Control}, indextitle = {Stochastic Model of {TCP Reno} Congestion Avoidance and Control, A}, annotation = {This is a report entry for a technical report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields}, abstract = {The steady state performance of a bulk transfer TCP flow (i.e. a flow with a large amount of data to send, such as FTP transfers) may be characterized by three quantities. The first is the send rate, which is the amount of data sent by the sender in unit time. The second is the throughput, which is the amount of data received by the receiver in unit time. Note that the throughput will always be less than or equal to the send rate due to losses. Finally, the number of non-duplicate packets received by the receiver in unit time gives us the goodput of the connection. The goodput is always less than or equal to the throughput, since the receiver may receive two copies of the same packet due to retransmissions by the sender. In a previous paper, we presented a simple model for predicting the steady state send rate of a bulk transfer TCP flow as a function of loss rate and round trip time. In this paper, we extend that work in two ways. First, we analyze the performance of bulk transfer TCP flows using more precise, stochastic analysis. Second, we build upon the previous analysis to provide both an approximate formula as well as a more accurate stochastic model for the steady state throughput of a bulk transfer TCP flow.}, file = {ftp://gaia.cs.umass.edu/pub/Padhey99-markov.ps}, } --- references: - id: padhye type: report author: - family: Padhye given: Jitendra - family: Firoiu given: Victor - family: Towsley given: Don issued: - year: '1999' title: A stochastic model of TCP Reno congestion avoidance and control publisher: University of Massachusetts publisher-place: Amherst, Mass. genre: technical report annote: This is a report entry for a technical report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields abstract: The steady state performance of a bulk transfer TCP flow (i.e. a flow with a large amount of data to send, such as FTP transfers) may be characterized by three quantities. The first is the send rate, which is the amount of data sent by the sender in unit time. The second is the throughput, which is the amount of data received by the receiver in unit time. Note that the throughput will always be less than or equal to the send rate due to losses. Finally, the number of non-duplicate packets received by the receiver in unit time gives us the goodput of the connection. The goodput is always less than or equal to the throughput, since the receiver may receive two copies of the same packet due to retransmissions by the sender. In a previous paper, we presented a simple model for predicting the steady state send rate of a bulk transfer TCP flow as a function of loss rate and round trip time. In this paper, we extend that work in two ways. First, we analyze the performance of bulk transfer TCP flows using more precise, stochastic analysis. Second, we build upon the previous analysis to provide both an approximate formula as well as a more accurate stochastic model for the steady state throughput of a bulk transfer TCP flow. number: '99-02' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/patent.biblatex0000644000000000000000000001341612743760365021574 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib TODO: Is there a CSL counterpart for the biblatex field "holder"?} @patent{almendro, Annotation = {This is a patent entry with a location field. The number is given in the number field. Note the format of the location field in the database file. Compare laufenberg, sorace, and kowalik}, Author = {Almendro, José L. and Martín, Jacinto and Sánchez, Alberto and Nozal, Fernando}, Date = 1998, Hyphenation = {german}, Location = {countryfr and countryuk and countryde}, Number = {EU-29702195U}, Title = {Elektromagnetisches Signalhorn}} @patent{kowalik, Annotation = {This is a patent entry for a French patent request with a full date. The number is given in the number field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and sorace}, Author = {Kowalik, F. and Isard, M.}, Date = {1995-01-11}, Hyphenation = {french}, Indextitle = {Estimateur d'un défaut de fonctionnement}, Number = 9500261, Title = {Estimateur d'un défaut de fonctionnement d'un modulateur en quadrature et étage de modulation l'utilisant}, Type = {patreqfr}} @patent{laufenberg, Annotation = {This is a patent entry with a holder field. Note the format of the type and location fields in the database file. Compare almendro, sorace, and kowalik}, Author = {Laufenberg, Xaver and Eynius, Dominique and Suelzle, Helmut and Usbeck, Stephan and Spaeth, Matthias and Neuser-Hoffmann, Miriam and Myrzik, Christian and Schmid, Manfred and Nietfeld, Franz and Thiel, Alexander and Braun, Harald and Ebner, Norbert}, Date = {2006-09-13}, File = {http://v3.espacenet.com/textdoc?IDX=EP1700367}, Holder = {{Robert Bosch GmbH} and {Daimler Chrysler AG} and {Bayerische Motoren Werke AG}}, Hyphenation = {german}, Number = 1700367, Title = {Elektrische Einrichtung und Betriebsverfahren}, Type = {patenteu}, Abstract = {The invention relates to an electric device comprising a generator, in particular for use in the vehicle electric system of a motor vehicle and a controller for controlling the generator voltage. The device is equipped with a control zone, in which the voltage is controlled and zones, in which the torque is controlled. The invention also relates to methods for operating a device of this type.}} @patent{sorace, Annotation = {This is a patent entry with a holder field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and kowalik}, Author = {Sorace, Ronald E. and Reinhardt, Victor S. and Vaughn, Steven A.}, Date = {1997-09-16}, Date-Modified = {2013-10-16 13:44:15 +0000}, Holder = {{Hughes Aircraft Company}}, Hyphenation = {american}, Number = 5668842, Title = {High-Speed Digital-to-{RF} Converter}, Type = {patentus}} --- references: - id: almendro type: patent author: - family: Almendro given: José L. - family: Martín given: Jacinto - family: Sánchez given: Alberto - family: Nozal given: Fernando issued: - year: '1998' title: Elektromagnetisches Signalhorn jurisdiction: France; United Kingdom; Germany annote: This is a patent entry with a location field. The number is given in the number field. Note the format of the location field in the database file. Compare laufenberg, sorace, and kowalik number: EU-29702195U language: de-DE - id: kowalik type: patent author: - family: Kowalik given: F. - family: Isard given: M. issued: - year: '1995' month: '1' day: '11' title: Estimateur d’un défaut de fonctionnement d’un modulateur en quadrature et étage de modulation l’utilisant genre: French patent request annote: This is a patent entry for a French patent request with a full date. The number is given in the number field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and sorace number: '9500261' language: fr-FR - id: laufenberg type: patent author: - family: Laufenberg given: Xaver - family: Eynius given: Dominique - family: Suelzle given: Helmut - family: Usbeck given: Stephan - family: Spaeth given: Matthias - family: Neuser-Hoffmann given: Miriam - family: Myrzik given: Christian - family: Schmid given: Manfred - family: Nietfeld given: Franz - family: Thiel given: Alexander - family: Braun given: Harald - family: Ebner given: Norbert issued: - year: '2006' month: '9' day: '13' title: Elektrische Einrichtung und Betriebsverfahren genre: European patent annote: This is a patent entry with a holder field. Note the format of the type and location fields in the database file. Compare almendro, sorace, and kowalik abstract: The invention relates to an electric device comprising a generator, in particular for use in the vehicle electric system of a motor vehicle and a controller for controlling the generator voltage. The device is equipped with a control zone, in which the voltage is controlled and zones, in which the torque is controlled. The invention also relates to methods for operating a device of this type. number: '1700367' language: de-DE - id: sorace type: patent author: - family: Sorace given: Ronald E. - family: Reinhardt given: Victor S. - family: Vaughn given: Steven A. issued: - year: '1997' month: '9' day: '16' title: High-speed digital-to-RF converter genre: U.S. patent annote: This is a patent entry with a holder field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and kowalik number: '5668842' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/periodical.biblatex0000644000000000000000000000113712743760365022411 0ustar0000000000000000@comment{excerpt from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib @periodical{jcg, Annotation = {This is a periodical entry with an issn field.}, Issn = {0097-8493}, Issuetitle = {Semantic {3D} Media and Content}, Number = 4, Title = {Computers and Graphics}, Volume = 35, Year = 2011} --- references: - id: jcg type: article-journal issued: - year: '2011' title: Semantic 3D media and content container-title: Computers and Graphics volume: '35' issue: '4' annote: This is a periodical entry with an issn field. ISSN: '0097-8493' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/piccato.biblatex0000644000000000000000000000235412743760365021722 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Piccato 2001) Piccato, Pablo. 2001. *City of Suspects: Crime in Mexico City, 1900–1931*. Durham; London: Duke University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Piccato, 2001) Piccato, P. (2001). *City of suspects: Crime in Mexico City, 1900–1931*. Durham; London: Duke University Press. } @Book{piccato, author = {Piccato, Pablo}, title = {City of Suspects}, date = 2001, publisher = {Duke University Press}, location = {Durham and London}, hyphenation = {american}, subtitle = {Crime in {Mexico City}, 1900--1931}, shorttitle = {City of Suspects}, annotation = {This is a book entry. Note the format of the location field in the database file}, } --- references: - id: piccato type: book author: - family: Piccato given: Pablo issued: - year: '2001' title: 'City of suspects: Crime in Mexico City, 1900–1931' title-short: City of suspects publisher: Duke University Press publisher-place: Durham; London annote: This is a book entry. Note the format of the location field in the database file language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pines.biblatex0000644000000000000000000000401413013615770021377 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Pines 1979) Pines, Shlomo. 1979. “The Limitations of Human Knowledge According to Al-Farabi, ibn Bajja, and Maimonides.” In *Studies in Medieval Jewish History and Literature*, edited by Isadore Twersky, 82–109. Cambridge, Mass.: Harvard University Press. Formatted with pandoc and apa.csl, 2013-10-23: (Pines, 1979) Pines, S. (1979). The limitations of human knowledge according to Al-Farabi, ibn Bajja, and Maimonides. In I. Twersky (Ed.), *Studies in medieval Jewish history and literature* (pp. 82–109). Cambridge, Mass.: Harvard University Press. } @string{ hup = {Harvard University Press} } @InCollection{pines, author = {Pines, Shlomo}, editor = {Twersky, Isadore}, title = {The Limitations of Human Knowledge According to {Al-Farabi}, {ibn Bajja}, and {Maimonides}}, date = 1979, booktitle = {Studies in Medieval {Jewish} History and Literature}, publisher = hup, location = {Cambridge, Mass.}, pages = {82-109}, keywords = {secondary}, hyphenation = {american}, indextitle = {Limitations of Human Knowledge According to {Al-Farabi}, {ibn Bajja}, and {Maimonides}, The}, shorttitle = {Limitations of Human Knowledge}, annotation = {A typical incollection entry. Note the indextitle field}, } --- references: - id: pines type: chapter author: - family: Pines given: Shlomo editor: - family: Twersky given: Isadore issued: - year: '1979' title: The limitations of human knowledge according to Al-Farabi, [ibn Bajja]{.nocase}, and Maimonides title-short: Limitations of human knowledge container-title: Studies in medieval Jewish history and literature publisher: Harvard University Press publisher-place: Cambridge, Mass. page: '82-109' annote: A typical incollection entry. Note the indextitle field keyword: secondary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/quotes.biblatex0000644000000000000000000000247212743760365021621 0ustar0000000000000000@comment{excerpt from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib \mkbibquote{} should be replaced by a matching set of quotation marks that can be used by citeproc for quote substitution and flipflopping. English smart double quotation marks seem best, as they cannot be confused with apostrophes. \enquote{}, \enquote*{} should be replaced by a matching set of quotation marks, too: “foo”, ‘bar’. } @string{pup = {Princeton University Press}} @book{nussbaum, Annotation = {A book entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file}, Author = {Nussbaum, Martha}, Date = 1978, Hyphenation = {american}, Indexsorttitle = {Aristotle's De Motu Animalium}, Keywords = {secondary}, Location = {Princeton}, Publisher = pup, Sorttitle = {Aristotle's De Motu Animalium}, Title = {Aristotle's \mkbibquote{De Motu Animalium}}} --- references: - id: nussbaum type: book author: - family: Nussbaum given: Martha issued: - year: '1978' title: Aristotle’s “De Motu Animalium” publisher: Princeton University Press publisher-place: Princeton annote: A book entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file keyword: secondary language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/reese.biblatex0000644000000000000000000000336412743760365021405 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Reese 1958) Reese, Trevor R. 1958. “Georgia in Anglo-Spanish Diplomacy, 1736-1739.” *William and Mary Quarterly, 3* 15: 168–190. Formatted with pandoc and apa.csl, 2013-10-23: (Reese, 1958) Reese, T. R. (1958). Georgia in Anglo-Spanish diplomacy, 1736-1739. *William and Mary Quarterly, 3*, *15*, 168–190. NOTES: - biblio2yaml - series field: still not entirely satisfactory. Could we map this to some existing CSL variable, and have the CSL styles handle this? "edition", maybe ?? } @Article{reese, author = {Reese, Trevor R.}, title = {Georgia in {Anglo-Spanish} Diplomacy, 1736-1739}, journaltitle = {William and Mary Quarterly}, date = 1958, series = 3, volume = 15, pages = {168-190}, hyphenation = {american}, annotation = {An article entry with a series and a volume field. Note the format of the series. If the value of the series field is an integer, this number is printed as an ordinal and the string \enquote*{series} is appended automatically}, } --- references: - id: reese type: article-journal author: - family: Reese given: Trevor R. issued: - year: '1958' title: Georgia in Anglo-Spanish diplomacy, 1736-1739 container-title: William and Mary Quarterly collection-title: 3rd ser. page: '168-190' volume: '15' annote: An article entry with a series and a volume field. Note the format of the series. If the value of the series field is an integer, this number is printed as an ordinal and the string “series” is appended automatically language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/report.biblatex0000644000000000000000000001313612743760365021613 0ustar0000000000000000@comment{excerpt from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib TODO: Where to map "file" field? } @report{chiu, Annotation = {This is a report entry for a research report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields}, Author = {Chiu, Willy W. and Chow, We Min}, Date = 1978, Hyphenation = {american}, Indextitle = {Hybrid Hierarchical Model, A}, Institution = {IBM}, Number = {RC-6947}, Sorttitle = {Hybrid Hierarchical Model of a Multiple Virtual Storage (MVS) Operating System}, Title = {A Hybrid Hierarchical Model of a {Multiple Virtual Storage} ({MVS}) Operating System}, Type = {resreport}} @report{padhye, Annotation = {This is a report entry for a technical report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields}, Author = {Padhye, Jitendra and Firoiu, Victor and Towsley, Don}, Date = 1999, File = {ftp://gaia.cs.umass.edu/pub/Padhey99-markov.ps}, Hyphenation = {american}, Indextitle = {Stochastic Model of TCP Reno Congestion Avoidance and Control, A}, Institution = {University of Massachusetts}, Location = {Amherst, Mass.}, Number = {99-02}, Sorttitle = {A Stochastic Model of TCP Reno Congestion Avoidance and Control}, Title = {A Stochastic Model of {TCP Reno} Congestion Avoidance and Control}, Type = {techreport}, Abstract = {The steady state performance of a bulk transfer TCP flow (i.e. a flow with a large amount of data to send, such as FTP transfers) may be characterized by three quantities. The first is the send rate, which is the amount of data sent by the sender in unit time. The second is the throughput, which is the amount of data received by the receiver in unit time. Note that the throughput will always be less than or equal to the send rate due to losses. Finally, the number of non-duplicate packets received by the receiver in unit time gives us the goodput of the connection. The goodput is always less than or equal to the throughput, since the receiver may receive two copies of the same packet due to retransmissions by the sender. In a previous paper, we presented a simple model for predicting the steady state send rate of a bulk transfer TCP flow as a function of loss rate and round trip time. In this paper, we extend that work in two ways. First, we analyze the performance of bulk transfer TCP flows using more precise, stochastic analysis. Second, we build upon the previous analysis to provide both an approximate formula as well as a more accurate stochastic model for the steady state throughput of a bulk transfer TCP flow.}} --- references: - id: chiu type: report author: - family: Chiu given: Willy W. - family: Chow given: We Min issued: - year: '1978' title: A hybrid hierarchical model of a Multiple Virtual Storage (MVS) operating system publisher: IBM genre: research report annote: This is a report entry for a research report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields number: RC-6947 language: en-US - id: padhye type: report author: - family: Padhye given: Jitendra - family: Firoiu given: Victor - family: Towsley given: Don issued: - year: '1999' title: A stochastic model of TCP Reno congestion avoidance and control publisher: University of Massachusetts publisher-place: Amherst, Mass. genre: technical report annote: This is a report entry for a technical report. Note the format of the type field in the database file which uses a localization key. The number of the report is given in the number field. Also note the sorttitle and indextitle fields abstract: The steady state performance of a bulk transfer TCP flow (i.e. a flow with a large amount of data to send, such as FTP transfers) may be characterized by three quantities. The first is the send rate, which is the amount of data sent by the sender in unit time. The second is the throughput, which is the amount of data received by the receiver in unit time. Note that the throughput will always be less than or equal to the send rate due to losses. Finally, the number of non-duplicate packets received by the receiver in unit time gives us the goodput of the connection. The goodput is always less than or equal to the throughput, since the receiver may receive two copies of the same packet due to retransmissions by the sender. In a previous paper, we presented a simple model for predicting the steady state send rate of a bulk transfer TCP flow as a function of loss rate and round trip time. In this paper, we extend that work in two ways. First, we analyze the performance of bulk transfer TCP flows using more precise, stochastic analysis. Second, we build upon the previous analysis to provide both an approximate formula as well as a more accurate stochastic model for the steady state throughput of a bulk transfer TCP flow. number: '99-02' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/salam.biblatex0000644000000000000000000000337012743760365021374 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Salam 1968) Salam, Abdus. 1968. “Weak and Electromagnetic Interactions.” In *Elementary Particle Theory: Relativistic Groups and Analyticity. Proceedings of the Eighth Nobel Symposium*, edited by Nils Svartholm, 367–377. Stockholm: Almquist & Wiksell. Formatted with pandoc and apa.csl, 2013-10-23: (Salam, 1968) Salam, A. (1968). Weak and electromagnetic interactions. In N. Svartholm (Ed.), *Elementary particle theory: Relativistic groups and analyticity. Proceedings of the eighth Nobel symposium* (pp. 367–377). Stockholm: Almquist & Wiksell. } @InProceedings{salam, author = {Salam, Abdus}, editor = {Svartholm, Nils}, title = {Weak and Electromagnetic Interactions}, date = 1968, booktitle = {Elementary particle theory}, booksubtitle = {Relativistic groups and analyticity}, booktitleaddon= {Proceedings of the Eighth {Nobel} Symposium}, eventdate = {1968-05-19/1968-05-25}, venue = {Aspen{\"a}sgarden, Lerum}, publisher = {Almquist \& Wiksell}, location = {Stockholm}, pages = {367-377}, } --- references: - id: salam type: paper-conference author: - family: Salam given: Abdus editor: - family: Svartholm given: Nils issued: - year: '1968' event-date: - year: '1968' month: '5' day: '19' - year: '1968' month: '5' day: '25' title: Weak and electromagnetic interactions container-title: 'Elementary particle theory: Relativistic groups and analyticity. Proceedings of the eighth Nobel symposium' publisher: Almquist & Wiksell publisher-place: Stockholm event-place: Aspenäsgarden, Lerum page: '367-377' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/sarfraz.biblatex0000644000000000000000000000257412743760365021754 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Sarfraz and Razzak 2002) Sarfraz, M., and M. F. A. Razzak. 2002. “Technical Section: An Algorithm for Automatic Capturing of the Font Outlines.” *Computers and Graphics* 26 (5): 795–804. Formatted with pandoc and apa.csl, 2013-10-23: (Sarfraz & Razzak, 2002) Sarfraz, M., & Razzak, M. F. A. (2002). Technical section: An algorithm for automatic capturing of the font outlines. *Computers and Graphics*, *26*(5), 795–804. } @Article{sarfraz, author = {M. Sarfraz and M. F. A. Razzak}, title = {Technical section: {An} algorithm for automatic capturing of the font outlines}, year = 2002, volume = 26, number = 5, pages = {795-804}, issn = {0097-8493}, journal = {Computers and Graphics}, annotation = {An article entry with an issn field}, } --- references: - id: sarfraz type: article-journal author: - family: Sarfraz given: M. - family: Razzak given: M. F. A. issued: - year: '2002' title: 'Technical section: An algorithm for automatic capturing of the font outlines' title-short: Technical section container-title: Computers and Graphics page: '795-804' volume: '26' issue: '5' annote: An article entry with an issn field ISSN: '0097-8493' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/shore.biblatex0000644000000000000000000000275712743760365021427 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Shore 1991) Shore, Bradd. 1991. “Twice-born, Once Conceived: Meaning Construction and Cultural Cognition.” *American Anthropologist, New Series* 93 (1) (March): 9–27. Formatted with pandoc and apa.csl, 2013-10-23: (Shore, 1991) Shore, B. (1991). Twice-born, once conceived: Meaning construction and cultural cognition. *American Anthropologist, new series*, *93*(1), 9–27. } @Article{shore, author = {Shore, Bradd}, title = {Twice-Born, Once Conceived}, journaltitle = {American Anthropologist}, date = {1991-03}, subtitle = {Meaning Construction and Cultural Cognition}, series = {newseries}, volume = 93, number = 1, pages = {9-27}, annotation = {An article entry with series, volume, and number fields. Note the format of the series which is a localization key}, } --- references: - id: shore type: article-journal author: - family: Shore given: Bradd issued: - year: '1991' month: '3' title: 'Twice-born, once conceived: Meaning construction and cultural cognition' title-short: Twice-born, once conceived container-title: American Anthropologist collection-title: new series page: '9-27' volume: '93' issue: '1' annote: An article entry with series, volume, and number fields. Note the format of the series which is a localization key ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/sigfridsson.biblatex0000644000000000000000000001064612743760365022635 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Sigfridsson and Ryde 1998) Sigfridsson, Emma, and Ulf Ryde. 1998. “Comparison of Methods for Deriving Atomic Charges from the Electrostatic Potential and Moments.” *Journal of Computational Chemistry* 19 (4): 377–395. doi:[10.1002/(SICI)1096-987X(199803)19:4\<377::AID-JCC1\>3.0.CO;2-P](https://doi.org/10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P "10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P"). Formatted with pandoc and apa.csl, 2013-10-23: (Sigfridsson & Ryde, 1998) Sigfridsson, E., & Ryde, U. (1998). Comparison of methods for deriving atomic charges from the electrostatic potential and moments. *Journal of Computational Chemistry*, *19*(4), 377–395. doi:[10.1002/(SICI)1096-987X(199803)19:4\<377::AID-JCC1\>3.0.CO;2-P](https://doi.org/10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P "10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P") NOTES: - biblio2xaml - the string "doi:" should not appear as part of the content of the "doi" field } @Article{sigfridsson, author = {Sigfridsson, Emma and Ryde, Ulf}, title = {Comparison of methods for deriving atomic charges from the electrostatic potential and moments}, journaltitle = {Journal of Computational Chemistry}, date = 1998, volume = 19, number = 4, pages = {377-395}, doi = {10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P}, hyphenation = {american}, indextitle = {Methods for deriving atomic charges}, annotation = {An article entry with volume, number, and doi fields. Note that the \textsc{doi} is transformed into a clickable link if hyperref support has been enabled}, abstract = {Four methods for deriving partial atomic charges from the quantum chemical electrostatic potential (CHELP, CHELPG, Merz-Kollman, and RESP) have been compared and critically evaluated. It is shown that charges strongly depend on how and where the potential points are selected. Two alternative methods are suggested to avoid the arbitrariness in the point-selection schemes and van der Waals exclusion radii: CHELP-BOW, which also estimates the charges from the electrostatic potential, but with potential points that are Boltzmann-weighted after their occurrence in actual simulations using the energy function of the program in which the charges will be used, and CHELMO, which estimates the charges directly from the electrostatic multipole moments. Different criteria for the quality of the charges are discussed.}, } --- references: - id: sigfridsson type: article-journal author: - family: Sigfridsson given: Emma - family: Ryde given: Ulf issued: - year: '1998' title: Comparison of methods for deriving atomic charges from the electrostatic potential and moments container-title: Journal of Computational Chemistry page: '377-395' volume: '19' issue: '4' annote: An article entry with volume, number, and doi fields. Note that the doi is transformed into a clickable link if hyperref support has been enabled abstract: 'Four methods for deriving partial atomic charges from the quantum chemical electrostatic potential (CHELP, CHELPG, Merz-Kollman, and RESP) have been compared and critically evaluated. It is shown that charges strongly depend on how and where the potential points are selected. Two alternative methods are suggested to avoid the arbitrariness in the point-selection schemes and van der Waals exclusion radii: CHELP-BOW, which also estimates the charges from the electrostatic potential, but with potential points that are Boltzmann-weighted after their occurrence in actual simulations using the energy function of the program in which the charges will be used, and CHELMO, which estimates the charges directly from the electrostatic multipole moments. Different criteria for the quality of the charges are discussed.' DOI: 10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/sorace.biblatex0000644000000000000000000000302412743760365021547 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Sorace, Reinhardt, and Vaughn 1997) Sorace, Ronald E., Victor S. Reinhardt, and Steven A. Vaughn. 1997. “High-speed Digital-to-RF Converter.” U.S. patent. Formatted with pandoc and apa.csl, 2013-10-23: (Sorace, Reinhardt, & Vaughn, 1997) Sorace, R. E., Reinhardt, V. S., & Vaughn, S. A. (1997, September 16). High-speed digital-to-RF converter. U.S. patent. } @Patent{sorace, author = {Sorace, Ronald E. and Reinhardt, Victor S. and Vaughn, Steven A.}, title = {High-Speed Digital-to-{RF} Converter}, number = 5668842, date = {1997-09-16}, holder = {{Hughes Aircraft Company}}, type = {patentus}, hyphenation = {american}, annotation = {This is a patent entry with a holder field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and kowalik}, } --- references: - id: sorace type: patent author: - family: Sorace given: Ronald E. - family: Reinhardt given: Victor S. - family: Vaughn given: Steven A. issued: - year: '1997' month: '9' day: '16' title: High-speed digital-to-RF converter genre: U.S. patent annote: This is a patent entry with a holder field. Note the format of the type and date fields in the database file. Compare almendro, laufenberg, and kowalik number: '5668842' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/spiegelberg.biblatex0000644000000000000000000000351612743760365022571 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Spiegelberg 1969) Spiegelberg, Herbert. 1969. ““Intention” und “Intentionalität” in der Scholastik, bei Brentano und Husserl.” *Studia Philosophica* 29: 189–216. Formatted with pandoc and apa.csl, 2013-10-23: (Spiegelberg, 1969) Spiegelberg, H. (1969). “Intention” und “Intentionalität” in der Scholastik, bei Brentano und Husserl. *Studia Philosophica*, *29*, 189–216. NOTES: - citeproc - flipflopping of quotes incorrect } @Article{spiegelberg, author = {Spiegelberg, Herbert}, title = {\mkbibquote{Intention} und \mkbibquote{Intentionalit{\"a}t} in der Scholastik, bei Brentano und Husserl}, journaltitle = {Studia Philosophica}, date = 1969, volume = 29, pages = {189-216}, hyphenation = {german}, sorttitle = {Intention und Intentionalitat in der Scholastik, bei Brentano und Husserl}, indexsorttitle= {Intention und Intentionalitat in der Scholastik, bei Brentano und Husserl}, shorttitle = {Intention und Intentionalit{\"a}t}, annotation = {An article entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file}, } --- references: - id: spiegelberg type: article-journal author: - family: Spiegelberg given: Herbert issued: - year: '1969' title: “Intention” und “Intentionalität” in der Scholastik, bei Brentano und Husserl title-short: Intention und Intentionalität container-title: Studia Philosophica page: '189-216' volume: '29' annote: An article entry. Note the sorttitle and indexsorttitle fields and the markup of the quotes in the database file language: de-DE ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/springer.biblatex0000644000000000000000000000215112743760365022124 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Springer 1950) Springer, Otto. 1950. “Mediaeval Pilgrim Routes from Scandinavia to Rome.” *Mediaeval Studies* 12: 92–122. Formatted with pandoc and apa.csl, 2013-10-23: (Springer, 1950) Springer, O. (1950). Mediaeval pilgrim routes from Scandinavia to Rome. *Mediaeval Studies*, *12*, 92–122. } @Article{springer, author = {Springer, Otto}, title = {Mediaeval Pilgrim Routes from {Scandinavia} to {Rome}}, journaltitle = {Mediaeval Studies}, date = 1950, volume = 12, pages = {92-122}, hyphenation = {british}, shorttitle = {Mediaeval Pilgrim Routes}, annotation = {A plain article entry}, } --- references: - id: springer type: article-journal author: - family: Springer given: Otto issued: - year: '1950' title: Mediaeval pilgrim routes from Scandinavia to Rome title-short: Mediaeval pilgrim routes container-title: Mediaeval Studies page: '92-122' volume: '12' annote: A plain article entry language: en-GB ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/strings.biblatex0000644000000000000000000000207612743760365021772 0ustar0000000000000000@comment{excerpt from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @string{anch-ie = {Angew.~Chem. Int.~Ed.}} @article{herrmann, Author = {Herrmann, Wolfgang A. and Öfele, Karl and Schneider, Sabine K. and Herdtweck, Eberhardt and Hoffmann, Stephan D.}, Date = 2006, Hyphenation = {english}, Indextitle = {Carbocyclic carbene as an efficient catalyst, A}, Journaltitle = anch-ie, Number = 23, Pages = {3859-3862}, Title = {A Carbocyclic Carbene as an Efficient Catalyst Ligand for {C--C} Coupling Reactions}, Volume = 45} --- references: - id: herrmann type: article-journal author: - family: Herrmann given: Wolfgang A. - family: Öfele given: Karl - family: Schneider given: Sabine K. - family: Herdtweck given: Eberhardt - family: Hoffmann given: Stephan D. issued: - year: '2006' title: A carbocyclic carbene as an efficient catalyst ligand for C–C coupling reactions container-title: Angew. Chem. Int. Ed. page: '3859-3862' volume: '45' issue: '23' language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/test-case-conversion.biblatex0000644000000000000000000000544713013615770024347 0ustar0000000000000000@comment{ - bibtex and biblatex - expect titles in title case - styles use titles as is, or convert them to sentence case - strings wrapped {} are not converted - all CSL styles at and - expect titles in sentence case - styles use titles as is, or convert them to title case - except for (hardcoded) list of stop words, see - citeproc-js (MLZ only?) also recognizes a markup syntax for suppressing title-case changes on a range of text (see ): - `lowercase` - Proposal: - When converting to yaml, convert English titles to sentence case, - for all strings wrapped in {} where {} is not part of a latex command, ... - ... when starting with an uppercase letter: suppress conversion, remove the {} - ... when starting with a lowercase letter ("nm", "iPod"): suppress conversion, replace the {} with - Note: Camel case ("iPod") needs to be protected in bibtex/biblatex anyway; the only "extension" (wrt bibtex/biblatex specs) we'd be introducing is wrapping lowercase-only strings in {}, something that is never necessary on the latex side but won't break anything there either. - citeproc-hs/pandoc-citeproc should be modified to honour this new syntax and suppress conversion to title case for strings wrapped in ``. - Expected output, using one of the title-case CSL styles, here chicago-author-date.csl: Author, Ann. 2013. “A Title, in English, with a Proper Name and an ACRONYM and a camelCase Word and Some Units, 400 nm, 3 cm, and a Quote, *Alea iacta est*.” *Journal*. } @article{item1, Author = {Author, Ann}, Date = {2013}, Hyphenation = {english}, Journaltitle = {Journal}, Title = {A Title, in {English}, with a {Proper Name} and an {ACRONYM} and a {camelCase} Word and Some Units, 400~{nm}, 3~{cm}, and a Quote, \textit{{Alea} {iacta est}}} } --- references: - id: item1 type: article-journal author: - family: Author given: Ann issued: - year: '2013' title: A title, in English, with a Proper Name and an ACRONYM and a [camelCase]{.nocase} word and some units, 400 [nm]{.nocase}, 3 [cm]{.nocase}, and a quote, *Alea [iacta est]{.nocase}* container-title: Journal language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/textnormal.biblatex0000644000000000000000000000023113013615770022453 0ustar0000000000000000@book{item1, Title = {The Title \textnormal{of this book}}, } --- references: - id: item1 type: book title: The title [of this book]{.nodecor} ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/thesis.biblatex0000644000000000000000000000451212743760365021575 0ustar0000000000000000@comment{excerpted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib TODO: Uppercase letters follwing hyphens need to be converted to lowercase, too (e.g., "r" in "High-Resolution". -- Same for citeproc when doing title-case conversion!) } @thesis{geer, Annotation = {This is a typical thesis entry for a PhD thesis. Note the type field in the database file which uses a localization key. Also note the format of the printed name and compare the useprefix option in the options field as well as vangennep}, Author = {de Geer, Ingrid}, Date = 1985, Hyphenation = {british}, Institution = {Uppsala Universitet}, Location = {Uppsala}, Options = {useprefix=false}, Subtitle = {The {Orkney} Earldom of the Twelfth Century. {A} Musicological Study}, Title = {Earl, Saint, Bishop, Skald~-- and Music}, Type = {phdthesis}} @thesis{loh, Annotation = {This is a typical thesis entry for an MA thesis. Note the type field in the database file which uses a localization key}, Author = {Loh, Nin C.}, Date = 1992, Hyphenation = {american}, Institution = {Massachusetts Institute of Technology}, Location = {Cambridge, Mass.}, Title = {High-Resolution Micromachined Interferometric Accelerometer}, Type = {mathesis}} --- references: - id: geer type: thesis author: - family: Geer given: Ingrid dropping-particle: de issued: - year: '1985' title: 'Earl, saint, bishop, skald – and music: The Orkney earldom of the twelfth century. A musicological study' title-short: Earl, saint, bishop, skald – and music publisher: Uppsala Universitet publisher-place: Uppsala genre: PhD thesis annote: This is a typical thesis entry for a PhD thesis. Note the type field in the database file which uses a localization key. Also note the format of the printed name and compare the useprefix option in the options field as well as vangennep language: en-GB - id: loh type: thesis author: - family: Loh given: Nin C. issued: - year: '1992' title: High-resolution micromachined interferometric accelerometer publisher: Massachusetts Institute of Technology publisher-place: Cambridge, Mass. genre: Master’s thesis annote: This is a typical thesis entry for an MA thesis. Note the type field in the database file which uses a localization key language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/title-and-shorttitle.biblatex0000644000000000000000000000454312743760365024362 0ustar0000000000000000@comment{ TODO: Slight inconsistency: When a biblatex “title” field contains a colon, the part before the colon is mapped to CSL “title-short”. When there’s a biblatex “title” and a “subtitle” field, CSL “title-short” is not set, though it would make at least as much sense to map “title” (without “subtitle”) to CSL “title-short” in this case. CSL “container-title-short” could also be set - from biblatex “shortjournal” - for inbook, incollection etc. from the “shorttitle” field of the crossreferenced book, collection etc. entry (see item5, item6) ... but it might not really be worth it, “container-title-short” not being used once in my sample of 70+ CSL styles. } @book{item4, Shorttitle = {The Shorttitle}, Subtitle = {And a Subtitle, in Two Separate Fields; plus a Separate “Shorttitle” Field}, Title = {The Title: With a Colon in the “Title” Field}} @book{item3, Subtitle = {And a Subtitle, in two separate fields}, Title = {The Title: With a Colon in the “title” field}} @book{item2, Subtitle = {The Subtitle, In Two Separate fields}, Title = {The Title}} @book{item1, Title = {The Title: And the Subtitle, all in the “title” Field}} @inbook{item5, Title = {The inbook Title: And the Subtitle, all in the “title” Field}, Crossref = {item6}} @book{item6, Title = {The Title: And the Subtitle, all in the “title” Field}, Shorttitle = {The Shorttitle}, } --- references: - id: item4 type: book title: 'The title: With a colon in the “title” field: And a subtitle, in two separate fields; plus a separate “shorttitle” field' title-short: The shorttitle - id: item3 type: book title: 'The title: With a colon in the “title” field: And a subtitle, in two separate fields' title-short: The title - id: item2 type: book title: 'The title: The subtitle, in two separate fields' title-short: The title - id: item1 type: book title: 'The title: And the subtitle, all in the “title” field' title-short: The title - id: item5 type: chapter title: 'The inbook title: And the subtitle, all in the “title” field' title-short: The inbook title container-title: 'The title: And the subtitle, all in the “title” field' - id: item6 type: book title: 'The title: And the subtitle, all in the “title” field' title-short: The shorttitle ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vangennep-related.biblatex0000644000000000000000000000300412743760365023670 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (van Gennep 1909) van Gennep, Arnold. 1909. *Les rites de passage*. Paris: Nourry. Formatted with pandoc and apa.csl, 2013-10-23: (van Gennep, 1909) van Gennep, A. (1909). *Les rites de passage*. Paris: Nourry. NOTES: - biblio2yaml - "related = {vizedom:related}, relatedtype = {bytranslator}": no equivalent implemented in CSL - "options = {useprefix}," is shorthand for "options = {useprefix=true}," } @Book{vangennep:related, author = {van Gennep, Arnold}, title = {Les rites de passage}, date = 1909, publisher = {Nourry}, location = {Paris}, options = {useprefix}, hyphenation = {french}, related = {vizedom:related}, relatedtype = {bytranslator}, sorttitle = {Rites de passage}, indextitle = {Rites de passage, Les}, shorttitle = {Rites de passage}, annotation = {A variant of the vangennep entry related to its translation. Note the format of the related and relatedtype fields}, } --- references: - id: vangennep:related type: book author: - family: Gennep given: Arnold non-dropping-particle: van issued: - year: '1909' title: Les rites de passage title-short: Rites de passage publisher: Nourry publisher-place: Paris annote: A variant of the vangennep entry related to its translation. Note the format of the related and relatedtype fields language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vangennep-trans.biblatex0000644000000000000000000000313312743760365023402 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (van Gennep 1960) van Gennep, Arnold. 1960. *The Rites of Passage*. Translated by Monika B. Vizedom and Gabrielle L. Caffee. University of Chicago Press. Formatted with pandoc and apa.csl, 2013-10-23: (van Gennep, 1960) van Gennep, A. (1960). *The rites of passage*. (M. B. Vizedom & G. L. Caffee, Trans.). University of Chicago Press. } @Book{vangennep:trans, author = {van Gennep, Arnold}, title = {The Rites of Passage}, year = 1960, translator = {Vizedom, Monika B. and Caffee, Gabrielle L.}, language = {english}, origlanguage = {french}, publisher = {University of Chicago Press}, options = {useprefix}, indextitle = {Rites of Passage, The}, sorttitle = {Rites of Passage}, shorttitle = {Rites of Passage}, hyphenation = {american}, annotation = {A translation of the vangennep entry. Note the translator and origlanguage fields. Compare with the vangennep:related entry.}, } --- references: - id: vangennep:trans type: book author: - family: Gennep given: Arnold non-dropping-particle: van translator: - family: Vizedom given: Monika B. - family: Caffee given: Gabrielle L. issued: - year: '1960' title: The rites of passage title-short: Rites of passage publisher: University of Chicago Press annote: A translation of the vangennep entry. Note the translator and origlanguage fields. Compare with the vangennep:related entry. language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vangennep.biblatex0000644000000000000000000000241412743760365022256 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (van Gennep 1909) van Gennep, Arnold. 1909. *Les rites de passage*. Paris: Nourry. Formatted with pandoc and apa.csl, 2013-10-23: (van Gennep, 1909) van Gennep, A. (1909). *Les rites de passage*. Paris: Nourry. } @Book{vangennep, author = {van Gennep, Arnold}, title = {Les rites de passage}, date = 1909, publisher = {Nourry}, location = {Paris}, options = {useprefix}, hyphenation = {french}, sorttitle = {Rites de passage}, indextitle = {Rites de passage, Les}, shorttitle = {Rites de passage}, annotation = {A book entry. Note the format of the printed name and compare the useprefix option in the options field as well as brandt and geer}, } --- references: - id: vangennep type: book author: - family: Gennep given: Arnold non-dropping-particle: van issued: - year: '1909' title: Les rites de passage title-short: Rites de passage publisher: Nourry publisher-place: Paris annote: A book entry. Note the format of the printed name and compare the useprefix option in the options field as well as brandt and geer language: fr-FR ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vazques-de-parga-mvbook.biblatex0000644000000000000000000000356312743760365024752 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Vázques de Parga, Lacarra, and Uría Ríu 1993) Vázques de Parga, Luis, José María Lacarra, and Juan Uría Ríu. 1993. *Las Peregrinaciones a Santiago de Compostela*. 3. Pamplona: Iberdrola. Formatted with pandoc and apa.csl, 2013-10-23: (Vázques de Parga, Lacarra, & Uría Ríu, 1993) Vázques de Parga, L., Lacarra, J. M., & Uría Ríu, J. (1993). *Las Peregrinaciones a Santiago de Compostela* (1-3). Pamplona: Iberdrola. NOTES: - citeproc - term "vols." missing } @mvbook{vazques-de-parga, author = {V{\'a}zques{ de }Parga, Luis and Lacarra, Jos{\'e} Mar{\'i}a and Ur{\'i}a R{\'i}u, Juan}, title = {Las Peregrinaciones a Santiago de Compostela}, date = 1993, volumes = 3, note = {Ed. facs. de la realizada en 1948--49}, publisher = {Iberdrola}, location = {Pamplona}, hyphenation = {spanish}, sorttitle = {Peregrinaciones a Santiago de Compostela}, indextitle = {Peregrinaciones a Santiago de Compostela, Las}, shorttitle = {Peregrinaciones}, annotation = {A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields}, } --- references: - id: vazques-de-parga type: book author: - family: Vázques de Parga given: Luis - family: Lacarra given: José María - family: Uría Ríu given: Juan issued: - year: '1993' title: Las Peregrinaciones a Santiago de Compostela title-short: Peregrinaciones publisher: Iberdrola publisher-place: Pamplona number-of-volumes: '3' note: Ed. facs. de la realizada en 1948–49 annote: A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields language: es-ES ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vazques-de-parga.biblatex0000644000000000000000000000356012743760365023454 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Vázques de Parga, Lacarra, and Uría Ríu 1993) Vázques de Parga, Luis, José María Lacarra, and Juan Uría Ríu. 1993. *Las Peregrinaciones a Santiago de Compostela*. 3. Pamplona: Iberdrola. Formatted with pandoc and apa.csl, 2013-10-23: (Vázques de Parga, Lacarra, & Uría Ríu, 1993) Vázques de Parga, L., Lacarra, J. M., & Uría Ríu, J. (1993). *Las Peregrinaciones a Santiago de Compostela* (1-3). Pamplona: Iberdrola. NOTES: - citeproc - term "vols." missing } @Book{vazques-de-parga, author = {V{\'a}zques{ de }Parga, Luis and Lacarra, Jos{\'e} Mar{\'i}a and Ur{\'i}a R{\'i}u, Juan}, title = {Las Peregrinaciones a Santiago de Compostela}, date = 1993, volumes = 3, note = {Ed. facs. de la realizada en 1948--49}, publisher = {Iberdrola}, location = {Pamplona}, hyphenation = {spanish}, sorttitle = {Peregrinaciones a Santiago de Compostela}, indextitle = {Peregrinaciones a Santiago de Compostela, Las}, shorttitle = {Peregrinaciones}, annotation = {A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields}, } --- references: - id: vazques-de-parga type: book author: - family: Vázques de Parga given: Luis - family: Lacarra given: José María - family: Uría Ríu given: Juan issued: - year: '1993' title: Las Peregrinaciones a Santiago de Compostela title-short: Peregrinaciones publisher: Iberdrola publisher-place: Pamplona number-of-volumes: '3' note: Ed. facs. de la realizada en 1948–49 annote: A multivolume book cited as a whole. This is a book entry with volumes, note, sorttitle, and indextitle fields language: es-ES ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/video.biblatex0000644000000000000000000000024212743760365021400 0ustar0000000000000000@video{x1,title={blah}} @movie{x2,title={blah}} --- references: - id: x1 type: motion_picture title: Blah - id: x2 type: motion_picture title: Blah ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/vizedom-related.biblatex0000644000000000000000000000301512743760365023366 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Vizedom and Caffee 1960) Vizedom, Monika B., and Gabrielle L. Caffee, trans. 1960. *The Rites of Passage*. University of Chicago Press. Formatted with pandoc and apa.csl, 2013-10-23: (Vizedom & Caffee, 1960) Vizedom, M. B., & Caffee, G. L. (Trans.). (1960). *The rites of passage*. University of Chicago Press. NOTES: - biblio2yaml - "related = {vangennep}, relatedtype = {translationof}": no equivalent implemented in CSL } @Book{vizedom:related, title = {The Rites of Passage}, year = 1960, translator = {Vizedom, Monika B. and Caffee, Gabrielle L.}, language = {english}, publisher = {University of Chicago Press}, hyphenation = {american}, options = {usetranslator}, related = {vangennep}, relatedtype = {translationof}, indextitle = {Rites of Passage, The}, sorttitle = {Rites of Passage}, shorttitle = {Rites of Passage}, annotation = {A translated work from vangennep. Note the format of the related and relatedtype fields}, } --- references: - id: vizedom:related type: book translator: - family: Vizedom given: Monika B. - family: Caffee given: Gabrielle L. issued: - year: '1960' title: The rites of passage title-short: Rites of passage publisher: University of Chicago Press annote: A translated work from vangennep. Note the format of the related and relatedtype fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/wassenberg.biblatex0000644000000000000000000000531412743760365022437 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Wassenberg and Sanders 2010) Wassenberg, Jan, and Peter Sanders. 2010. “Faster Radix Sort via Virtual Memory and Write-combining” (version 1). August 17. Formatted with pandoc and apa.csl, 2013-10-23: (Wassenberg & Sanders, 2010) Wassenberg, J., & Sanders, P. (2010, August 17). Faster radix sort via virtual memory and write-combining. NOTES: - biblio2yaml - "eprinttype = {arxiv}, eprintclass = {cs.DS}, eprint = {1008.2849v1}" should be used to reconstruct a Url: http://arxiv.org/abs/1008.2849v1 ("cs.DS" does not seem to be essential) } @Online{wassenberg, author = {Wassenberg, Jan and Sanders, Peter}, title = {Faster Radix Sort via Virtual Memory and Write-Combining}, date = {2010-08-17}, version = 1, hyphenation = {american}, eprinttype = {arxiv}, eprintclass = {cs.DS}, eprint = {1008.2849v1}, annotation = {A recent online reference from arXiv using the new (April 2007 onward) identifier format. Note the eprint, eprinttype, and eprintclass fields. Also note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled}, abstract = {Sorting algorithms are the deciding factor for the performance of common operations such as removal of duplicates or database sort-merge joins. This work focuses on 32-bit integer keys, optionally paired with a 32-bit value. We present a fast radix sorting algorithm that builds upon a microarchitecture-aware variant of counting sort}, } --- references: - id: wassenberg type: webpage author: - family: Wassenberg given: Jan - family: Sanders given: Peter issued: - year: '2010' month: '8' day: '17' title: Faster radix sort via virtual memory and write-combining version: '1' annote: A recent online reference from arXiv using the new (April 2007 onward) identifier format. Note the eprint, eprinttype, and eprintclass fields. Also note that the arXiv reference is transformed into a clickable link if hyperref support has been enabled abstract: Sorting algorithms are the deciding factor for the performance of common operations such as removal of duplicates or database sort-merge joins. This work focuses on 32-bit integer keys, optionally paired with a 32-bit value. We present a fast radix sorting algorithm that builds upon a microarchitecture-aware variant of counting sort URL: http://arxiv.org/abs/1008.2849v1 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/weinberg.biblatex0000644000000000000000000000145612743760365022104 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Weinberg 1967) Weinberg, Steven. 1967. “A Model of Leptons.” *Phys. Rev. Lett.* 19: 1264–1266. Formatted with pandoc and apa.csl, 2013-10-23: (Weinberg, 1967) Weinberg, S. (1967). A model of leptons. *Phys. Rev. Lett.*, *19*, 1264–1266. } @Article{weinberg, author = {Weinberg, Steven}, title = {A Model of Leptons}, journaltitle = {Phys.~Rev.~Lett.}, date = 1967, volume = 19, pages = {1264-1266}, } --- references: - id: weinberg type: article-journal author: - family: Weinberg given: Steven issued: - year: '1967' title: A model of leptons container-title: Phys. Rev. Lett. page: '1264-1266' volume: '19' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/westfahl-frontier.biblatex0000644000000000000000000000264412743760365023745 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Westfahl 2000) Westfahl, Gary, ed. 2000. *Space and Beyond: The Frontier Theme in Science Fiction*. Westport, Conn.; London: Greenwood. Formatted with pandoc and apa.csl, 2013-10-23: (Westfahl, 2000) Westfahl, G. (Ed.). (2000). *Space and beyond: The frontier theme in science fiction*. Westport, Conn.; London: Greenwood. } @Collection{westfahl:frontier, editor = {Westfahl, Gary}, title = {Space and Beyond}, date = 2000, subtitle = {The Frontier Theme in Science Fiction}, publisher = {Greenwood}, location = {Westport, Conn. and London}, hyphenation = {american}, booktitle = {Space and Beyond}, booksubtitle = {The Frontier Theme in Science Fiction}, annotation = {This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields}, } --- references: - id: westfahl:frontier type: book editor: - family: Westfahl given: Gary issued: - year: '2000' title: 'Space and beyond: The frontier theme in science fiction' title-short: Space and beyond publisher: Greenwood publisher-place: Westport, Conn.; London annote: This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/westfahl-space.biblatex0000644000000000000000000000620512743760365023205 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Westfahl 2000a) (Westfahl 2000b) Westfahl, Gary. 2000a. “The True Frontier: Confronting and Avoiding the Realities of Space in American Science Fiction Films.” In *Space and Beyond: The Frontier Theme in Science Fiction*, edited by Gary Westfahl, 55–65. Westport, Conn.; London: Greenwood. ———, ed. 2000b. *Space and Beyond: The Frontier Theme in Science Fiction*. Westport, Conn.; London: Greenwood. Formatted with pandoc and apa.csl, 2013-10-23: (Westfahl, 2000) (Westfahl, 2000) Westfahl, G. (2000). The true frontier: Confronting and avoiding the realities of space in American science fiction films. In G. Westfahl (Ed.), *Space and beyond: The frontier theme in science fiction* (pp. 55–65). Westport, Conn.; London: Greenwood. Westfahl, G. (Ed.). (2000). *Space and beyond: The frontier theme in science fiction*. Westport, Conn.; London: Greenwood. } @InCollection{westfahl:space, author = {Westfahl, Gary}, title = {The True Frontier}, subtitle = {Confronting and Avoiding the Realities of Space in {American} Science Fiction Films}, pages = {55-65}, crossref = {westfahl:frontier}, hyphenation = {american}, indextitle = {True Frontier, The}, annotation = {A cross-referenced article from a collection. This is an incollection entry with a crossref field. Note the subtitle and indextitle fields}, } @Collection{westfahl:frontier, editor = {Westfahl, Gary}, title = {Space and Beyond}, date = 2000, subtitle = {The Frontier Theme in Science Fiction}, publisher = {Greenwood}, location = {Westport, Conn. and London}, hyphenation = {american}, booktitle = {Space and Beyond}, booksubtitle = {The Frontier Theme in Science Fiction}, annotation = {This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields}, } --- references: - id: westfahl:space type: chapter author: - family: Westfahl given: Gary editor: - family: Westfahl given: Gary issued: - year: '2000' title: 'The true frontier: Confronting and avoiding the realities of space in American science fiction films' title-short: The true frontier container-title: 'Space and beyond: The frontier theme in science fiction' publisher: Greenwood publisher-place: Westport, Conn.; London page: '55-65' annote: A cross-referenced article from a collection. This is an incollection entry with a crossref field. Note the subtitle and indextitle fields language: en-US - id: westfahl:frontier type: book editor: - family: Westfahl given: Gary issued: - year: '2000' title: 'Space and beyond: The frontier theme in science fiction' title-short: Space and beyond publisher: Greenwood publisher-place: Westport, Conn.; London annote: This is a collection entry. Note the format of the location field as well as the subtitle and booksubtitle fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/wilde.biblatex0000644000000000000000000000304212743760365021377 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Wilde 1899) Wilde, Oscar. 1899. *The Importance of Being Earnest: A Trivial Comedy for Serious People*. English and American Drama of the Nineteenth Century. Leonard Smithers and Company. Formatted with pandoc and apa.csl, 2013-10-23: (Wilde, 1899) Wilde, O. (1899). *The importance of being earnest: A trivial comedy for serious people*. Leonard Smithers and Company. NOTES: - biblio2yaml - From "eprint = {4HIWAAAAYAAJ}, eprinttype = {googlebooks}", a url could be reconstructed, shortest form: http://books.google.com?id=4HIWAAAAYAAJ } @Book{wilde, author = {Wilde, Oscar}, title = {The Importance of Being Earnest: {A} Trivial Comedy for Serious People}, year = 1899, series = {English and American drama of the Nineteenth Century}, publisher = {Leonard Smithers {and} Company}, eprint = {4HIWAAAAYAAJ}, eprinttype = {googlebooks}, annotation = {A book with eprint and eprinttype fields.}, } --- references: - id: wilde type: book author: - family: Wilde given: Oscar issued: - year: '1899' title: 'The importance of being earnest: A trivial comedy for serious people' title-short: The importance of being earnest collection-title: English and american drama of the nineteenth century publisher: Leonard Smithers and Company annote: A book with eprint and eprinttype fields. URL: http://books.google.com?id=4HIWAAAAYAAJ ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/worman.biblatex0000644000000000000000000000234112743760365021577 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Worman 2002) Worman, Nancy. 2002. *The Cast of Character: Style in Greek Literature*. Austin: University of Texas Press. Formatted with pandoc and apa.csl, 2013-10-23: (Worman, 2002) Worman, N. (2002). *The cast of character: Style in Greek literature*. Austin: University of Texas Press. } @Book{worman, author = {Worman, Nancy}, title = {The Cast of Character}, date = 2002, publisher = {University of Texas Press}, location = {Austin}, hyphenation = {american}, sorttitle = {Cast of Character}, indextitle = {Cast of Character, The}, subtitle = {Style in {Greek} Literature}, shorttitle = {Cast of Character}, annotation = {A book entry. Note the sorttitle and indextitle fields}, } --- references: - id: worman type: book author: - family: Worman given: Nancy issued: - year: '2002' title: 'The cast of character: Style in Greek literature' title-short: Cast of character publisher: University of Texas Press publisher-place: Austin annote: A book entry. Note the sorttitle and indextitle fields language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/yoon.biblatex0000644000000000000000000000305412743760365021262 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Yoon et al. 2006) Yoon, Myeong S., Dowook Ryu, Jeongryul Kim, and Kyo Han Ahn. 2006. “Palladium Pincer Complexes with Reduced Bond Angle Strain: Efficient Catalysts for the Heck Reaction.” *Organometallics* 25 (10): 2409–2411. Formatted with pandoc and apa.csl, 2013-10-23: (Yoon, Ryu, Kim, & Ahn, 2006) Yoon, M. S., Ryu, D., Kim, J., & Ahn, K. H. (2006). Palladium pincer complexes with reduced bond angle strain: Efficient catalysts for the Heck reaction. *Organometallics*, *25*(10), 2409–2411. } @Article{yoon, author = {Yoon, Myeong S. and Ryu, Dowook and Kim, Jeongryul and Ahn, Kyo Han}, title = {Palladium pincer complexes with reduced bond angle strain: efficient catalysts for the {Heck} reaction}, journaltitle = {Organometallics}, date = 2006, volume = 25, number = 10, pages = {2409-2411}, indextitle = {Palladium pincer complexes}, } --- references: - id: yoon type: article-journal author: - family: Yoon given: Myeong S. - family: Ryu given: Dowook - family: Kim given: Jeongryul - family: Ahn given: Kyo Han issued: - year: '2006' title: 'Palladium pincer complexes with reduced bond angle strain: Efficient catalysts for the Heck reaction' title-short: Palladium pincer complexes with reduced bond angle strain container-title: Organometallics page: '2409-2411' volume: '25' issue: '10' ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/ctan.biblatex0000644000000000000000000000404313063452061022610 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (“CTAN: The Comprehensive TeX Archive Network” 2006) “CTAN: The Comprehensive TeX Archive Network.” 2006. . Formatted with pandoc and apa.csl, 2013-10-23: (“CTAN: The Comprehensive TeX Archive Network,” 2006) CTAN: The Comprehensive TeX Archive Network. (2006). Retrieved October 01, 2006, from NOTES: - biblio2yaml - if there is no shorttitle, but title and subtitle, the title alone should also be mapped to title-short - citeproc - citeproc should use title-short (if available) instead of title for in-text citations when there is no author } @Online{ctan, title = {{CTAN}}, date = 2006, url = {http://www.ctan.org}, subtitle = {{The Comprehensive TeX Archive Network}}, urldate = {2006-10-01}, label = {CTAN}, hyphenation = {american}, annotation = {This is an online entry. The \textsc{url}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and\slash or a year}, } --- references: - id: ctan type: webpage issued: - year: '2006' accessed: - year: '2006' month: '10' day: '1' title: 'CTAN: The Comprehensive TeX Archive Network' title-short: CTAN annote: This is an online entry. The [url]{.smallcaps}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and/or a year URL: http://www.ctan.org language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/formatting.biblatex0000644000000000000000000000054413063452061024037 0ustar0000000000000000@article{item1, Title = {The Title: \textit{italics}, \textbf{bold}, \textsubscript{subscript}, \textsuperscript{superscript}, \textsc{small-caps}} } --- references: - id: item1 type: article-journal title: 'The title: *Italics*, **bold**, ~subscript~, ^superscript^, [small-caps]{.smallcaps}' title-short: The title ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/jaffe.biblatex0000644000000000000000000000421513063452061022737 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Jaffé 1885–1888) Jaffé, Philipp, ed. 1885–1888. *Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \mcxcviii\*. 2nd ed. 2. Leipzig. Formatted with pandoc and apa.csl, 2013-10-23: (Jaffé, 1885–1888) Jaffé, P. (Ed.). (1885–1888). *Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \mcxcviii\* (2nd ed., 1-2). Leipzig. NOTES: - biblatex conversion: - hyphenation = {latin} - citeproc: - "vols." is missing - works in Zotero - This does not show up in the tests from the citeproc test suite that currently fail. - "\ needs to be fixed. - maybe add markdown syntax ^^small caps^^ ? - in pandoc "plain" output, small caps could be converted to uppercase chars: "MCXCVIII" would definitely look better here. } @Collection{jaffe, editor = {Jaff{\'e}, Philipp}, title = {Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum \textsc{mcxcviii}}, date = {1885/1888}, editora = {Loewenfeld, Samuel and Kaltenbrunner, Ferdinand and Ewald, Paul}, edition = 2, volumes = 2, location = {Leipzig}, editoratype = {redactor}, indextitle = {Regesta Pontificum Romanorum}, shorttitle = {Regesta Pontificum Romanorum}, annotation = {A collection entry with edition and volumes fields. Note the editora and editoratype fields}, hyphenation = {latin}, } --- references: - id: jaffe type: book editor: - family: Jaffé given: Philipp issued: - year: '1885' - year: '1888' title: Regesta Pontificum Romanorum ab condita ecclesia ad annum post Christum natum [mcxcviii]{.smallcaps} title-short: Regesta Pontificum Romanorum publisher-place: Leipzig number-of-volumes: '2' edition: '2' annote: A collection entry with edition and volumes fields. Note the editora and editoratype fields language: la ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/kastenholz.biblatex0000644000000000000000000001256513063452061024055 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Kastenholz and Hünenberger 2006) Kastenholz, M. A., and Philippe H. Hünenberger. 2006. “Computation of Methodologyindependent Ionic Solvation Free Energies from Molecular Simulations: I. the Electrostatic Potential in Molecular Liquids.” *J. Chem. Phys.* 124. doi:[10.1063/1.2172593](https://doi.org/10.1063/1.2172593 "10.1063/1.2172593"). Formatted with pandoc and apa.csl, 2013-10-23: (Kastenholz & Hünenberger, 2006) Kastenholz, M. A., & Hünenberger, P. H. (2006). Computation of methodologyindependent ionic solvation free energies from molecular simulations: I. the electrostatic potential in molecular liquids. *J. Chem. Phys.*, *124*. doi:[10.1063/1.2172593](https://doi.org/10.1063/1.2172593 "10.1063/1.2172593") NOTES: - biblio2xaml - fix conversion of "\hyphen” - the string "doi:" should not appear as part of the content of the "doi" field } @string{ jchph = {J.~Chem. Phys.} } @Article{kastenholz, author = {Kastenholz, M. A. and H{\"u}nenberger, Philippe H.}, title = {Computation of methodology\hyphen independent ionic solvation free energies from molecular simulations}, journaltitle = jchph, date = 2006, subtitle = {I. {The} electrostatic potential in molecular liquids}, volume = 124, eid = 124106, doi = {10.1063/1.2172593}, hyphenation = {american}, indextitle = {Computation of ionic solvation free energies}, annotation = {An article entry with an eid and a doi field. Note that the \textsc{doi} is transformed into a clickable link if hyperref support has been enabled}, abstract = {The computation of ionic solvation free energies from atomistic simulations is a surprisingly difficult problem that has found no satisfactory solution for more than 15 years. The reason is that the charging free energies evaluated from such simulations are affected by very large errors. One of these is related to the choice of a specific convention for summing up the contributions of solvent charges to the electrostatic potential in the ionic cavity, namely, on the basis of point charges within entire solvent molecules (M scheme) or on the basis of individual point charges (P scheme). The use of an inappropriate convention may lead to a charge-independent offset in the calculated potential, which depends on the details of the summation scheme, on the quadrupole-moment trace of the solvent molecule, and on the approximate form used to represent electrostatic interactions in the system. However, whether the M or P scheme (if any) represents the appropriate convention is still a matter of on-going debate. The goal of the present article is to settle this long-standing controversy by carefully analyzing (both analytically and numerically) the properties of the electrostatic potential in molecular liquids (and inside cavities within them).}, } --- references: - id: kastenholz type: article-journal author: - family: Kastenholz given: M. A. - family: Hünenberger given: Philippe H. issued: - year: '2006' title: 'Computation of methodology-independent ionic solvation free energies from molecular simulations: I. The electrostatic potential in molecular liquids' title-short: Computation of methodology-independent ionic solvation free energies from molecular simulations container-title: J. Chem. Phys. volume: '124' annote: An article entry with an eid and a doi field. Note that the [doi]{.smallcaps} is transformed into a clickable link if hyperref support has been enabled abstract: The computation of ionic solvation free energies from atomistic simulations is a surprisingly difficult problem that has found no satisfactory solution for more than 15 years. The reason is that the charging free energies evaluated from such simulations are affected by very large errors. One of these is related to the choice of a specific convention for summing up the contributions of solvent charges to the electrostatic potential in the ionic cavity, namely, on the basis of point charges within entire solvent molecules (M scheme) or on the basis of individual point charges (P scheme). The use of an inappropriate convention may lead to a charge-independent offset in the calculated potential, which depends on the details of the summation scheme, on the quadrupole-moment trace of the solvent molecule, and on the approximate form used to represent electrostatic interactions in the system. However, whether the M or P scheme (if any) represents the appropriate convention is still a matter of on-going debate. The goal of the present article is to settle this long-standing controversy by carefully analyzing (both analytically and numerically) the properties of the electrostatic potential in molecular liquids (and inside cavities within them). DOI: 10.1063/1.2172593 language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/online.biblatex0000644000000000000000000000426313063452061023153 0ustar0000000000000000@comment{adapted from http://mirrors.ctan.org/macros/latex/contrib/biblatex/doc/examples/biblatex-examples.bib} @online{markey, Annotation = {An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file.}, Author = {Markey, Nicolas}, Date = {2005-10-16}, Hyphenation = {american}, Sorttitle = {Tame the Beast}, Subtitle = {The {B} to {X} of {BibTeX}}, Title = {Tame the {BeaST}}, Url = {http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf}, Urldate = {2006-10-01}, Version = {1.3}, } @online{CTAN, Annotation = {This is an online entry. The \textsc{url}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and\slash or a year}, Date = 2006, Hyphenation = {american}, Label = {CTAN}, Subtitle = {The {Comprehensive TeX Archive Network}}, Title = {{CTAN}}, Url = {http://www.ctan.org}, Urldate = {2006-10-01}, } --- references: - id: markey type: webpage author: - family: Markey given: Nicolas issued: - year: '2005' month: '10' day: '16' accessed: - year: '2006' month: '10' day: '1' title: 'Tame the BeaST: The B to X of BibTeX' title-short: Tame the BeaST version: '1.3' annote: An online entry for a tutorial. Note the format of the date field (yyyy-mm-dd) in the database file. URL: http://tug.ctan.org/tex-archive/info/bibtex/tamethebeast/ttb_en.pdf language: en-US - id: CTAN type: webpage issued: - year: '2006' accessed: - year: '2006' month: '10' day: '1' title: 'CTAN: The Comprehensive TeX Archive Network' title-short: CTAN annote: This is an online entry. The [url]{.smallcaps}, which is given in the url field, is transformed into a clickable link if hyperref support has been enabled. Note the format of the urldate field (yyyy-mm-dd) in the database file. Also note the label field which may be used as a fallback by citation styles which need an author and/or a year URL: http://www.ctan.org language: en-US ... pandoc-citeproc-0.10.5.1/tests/biblio2yaml/pandoc-2/sigfridsson.biblatex0000644000000000000000000001060213063452061024213 0ustar0000000000000000@comment{ Adapted from biblatex-example.bib Formatted with pandoc and chicago-author-date.csl, 2013-10-23: (Sigfridsson and Ryde 1998) Sigfridsson, Emma, and Ulf Ryde. 1998. “Comparison of Methods for Deriving Atomic Charges from the Electrostatic Potential and Moments.” *Journal of Computational Chemistry* 19 (4): 377–395. doi:[10.1002/(SICI)1096-987X(199803)19:4\<377::AID-JCC1\>3.0.CO;2-P](https://doi.org/10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P "10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P"). Formatted with pandoc and apa.csl, 2013-10-23: (Sigfridsson & Ryde, 1998) Sigfridsson, E., & Ryde, U. (1998). Comparison of methods for deriving atomic charges from the electrostatic potential and moments. *Journal of Computational Chemistry*, *19*(4), 377–395. doi:[10.1002/(SICI)1096-987X(199803)19:4\<377::AID-JCC1\>3.0.CO;2-P](https://doi.org/10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P "10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P") NOTES: - biblio2xaml - the string "doi:" should not appear as part of the content of the "doi" field } @Article{sigfridsson, author = {Sigfridsson, Emma and Ryde, Ulf}, title = {Comparison of methods for deriving atomic charges from the electrostatic potential and moments}, journaltitle = {Journal of Computational Chemistry}, date = 1998, volume = 19, number = 4, pages = {377-395}, doi = {10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P}, hyphenation = {american}, indextitle = {Methods for deriving atomic charges}, annotation = {An article entry with volume, number, and doi fields. Note that the \textsc{doi} is transformed into a clickable link if hyperref support has been enabled}, abstract = {Four methods for deriving partial atomic charges from the quantum chemical electrostatic potential (CHELP, CHELPG, Merz-Kollman, and RESP) have been compared and critically evaluated. It is shown that charges strongly depend on how and where the potential points are selected. Two alternative methods are suggested to avoid the arbitrariness in the point-selection schemes and van der Waals exclusion radii: CHELP-BOW, which also estimates the charges from the electrostatic potential, but with potential points that are Boltzmann-weighted after their occurrence in actual simulations using the energy function of the program in which the charges will be used, and CHELMO, which estimates the charges directly from the electrostatic multipole moments. Different criteria for the quality of the charges are discussed.}, } --- references: - id: sigfridsson type: article-journal author: - family: Sigfridsson given: Emma - family: Ryde given: Ulf issued: - year: '1998' title: Comparison of methods for deriving atomic charges from the electrostatic potential and moments container-title: Journal of Computational Chemistry page: '377-395' volume: '19' issue: '4' annote: An article entry with volume, number, and doi fields. Note that the [doi]{.smallcaps} is transformed into a clickable link if hyperref support has been enabled abstract: 'Four methods for deriving partial atomic charges from the quantum chemical electrostatic potential (CHELP, CHELPG, Merz-Kollman, and RESP) have been compared and critically evaluated. It is shown that charges strongly depend on how and where the potential points are selected. Two alternative methods are suggested to avoid the arbitrariness in the point-selection schemes and van der Waals exclusion radii: CHELP-BOW, which also estimates the charges from the electrostatic potential, but with potential points that are Boltzmann-weighted after their occurrence in actual simulations using the energy function of the program in which the charges will be used, and CHELMO, which estimates the charges directly from the electrostatic multipole moments. Different criteria for the quality of the charges are discussed.' DOI: 10.1002/(SICI)1096-987X(199803)19:4<377::AID-JCC1>3.0.CO;2-P language: en-US ...