citeproc-hs-0.3.9/0000755000175000001440000000000012223317050013107 5ustar andreausersciteproc-hs-0.3.9/README0000644000175000001440000002370712223317046014005 0ustar andreausers% citeproc-hs - A Haskell Implementation of the Citation Style Language % Andrea Rossato About ----- [citeproc-hs] is a [Haskell] implementation of the Citation Style Language ([CSL]). [citeproc-hs] adds to [pandoc], the famous [Haskell] text processing tool, a Bibtex like citation and bibliographic formatting and generation facility. [CSL] is an XML language for specifying citation and bibliographic formatting, similar in principle to BibTeX `.bst` files or the binary style files in commercial products like Endnote or Reference Manager. [CSL] is used by [Zotero] for bibliographic style formatting, and the huge number of [CSL] styles developed by the [Zotero] community can can be downloaded from here: There are plans to use CSL for adding bibliographic support to future releases of [OpenOffice](http://bibliographic.openoffice.org/). [citeproc-hs] can process and format citations according to a [CSL] style, given a collection of references. Natively [citeproc-hs] can read [JSON][^1] and [MODS][^2] XML formatted bibliographic databases. [bibutils] can be used to convert Bibtex and other bibliographic databases to [MODS] collections, which can be thus read by [citeproc-hs]. [bibutils] also exports a library and this library can be used by [citeproc-hs] for reading the most widely used bibliographic databases. This requires the installation of [hs-bibutils], the Haskell bindings to [bibutils]. [citeproc-hs] is a library that exports functions to parse [CSL] styles and [MODS] collections, to process lists of citation groups and to format the processed output. The output is a Haskell data type that can be further processed for conversion to any kind of formats (at the present time plain ASCII and the [pandoc] native format) Download -------- [citeproc-hs] can be downloaded from [Hackage]: To get the darcs source run: darcs get http://gorgias.mine.nu/repos/citeproc-hs/ Installation ------------ [citeproc-hs] depends on a few Haskell packages. Most of them come with the [Haskell Platform] and are usually included in every Haskell tool-chain. In order to install [citeproc-hs] you need to install its dependencies. You can choose to manually download and install everything from [Hackage]: Every package downloaded form [Hackage] can be installed with these simple commands: runhaskell Setup.lhs configure runhaskell Setup.lhs build runhaskell Setup.lhs install This last step requires `root` privileges. If you don't have `root` privileges you can install citeproc-hs and *all* its dependencies locally with these commands: runhaskell Setup.lhs configure --user --prefix=$HOME runhaskell Setup.lhs build runhaskell Setup.lhs install --user Alternatively you can use [cabal-install] to install [citeproc-hs] and all the needed dependencies: cabal update cabal install citeproc-hs ### Installing without bibutils or network support [bibutils] and network support may be suppressed with cabal flags: runhaskell Setup.lhs configure -f'-bibutils' or runhaskell Setup.lhs configure -f'-bibutils -network' and then build and install with: runhaskell Setup.lhs build runhaskell Setup.lhs install It is possible to pass the flags also too [cabal-install]. ### Installing with ICU support Sorting Unicode strings containing non ASCII characters is not supported by the standard Haskell libraries and requires the installation of the ICU libraries, available here: http://site.icu-project.org/ It is then necessary to install the Haskell bindings to these libraries. These bindings are available here: http://hackage.haskell.org/package/text-icu You then need to configure the citeproc-hs package with the appropriate cabal flag: runhaskell Setup.lhs configure -funicode_collation and then build as usual. It is possible to pass the flags also too [cabal-install]. In this case the installation of the ICU libraries is the only prerequisite. Using citeproc-hs with Pandoc ----------------------------- Future releases of [pandoc] will depend on [citeproc-hs] and no specific step will be required to activate citeproc support. Please refer to [pandoc]'s documentation for more information on inserting citations in [pandoc]'s documents. Documentation ------------- [Haddock] documentation for the exported API is available on [Hackage]: ### Name parsing The [MODS] parser has been optimized for bibtex input, especially for parsing names with affixes , dropping and non-dropping particles. Suffixes should come after the family name: Brown, Jr., John W. If a comma is needed before the suffix, an exclamation mark may be used: Brown,! Jr., John W. Non-dropping particles are placed before the family name: von Hicks,! Jr., Michael Dropping particles are placed after the given name: la Martine,! III, Martin B. de See also the [CSL] specification: ### Date parsing The [MODS] parser, which is used to read all bibliograhic databases supported by [bibutils], tries to parse dates, including seasons (expressed in English). An example of supported formats: 2010-01-31 (January 31, 2010) 2004-05 (May, 2004) 2001 (the year only) Summer, 2001 (the season) ### The DOI variable If the DOI variable is prefixed by a `doi:` like: doi = {doi:10.1038/171737a0} the processor will generate a link and produce this pandoc native representation: Link [Str "10.1038/171737a0"] ("http://dx.doi.org/10.1038/171737a0", "10.1038/171737a0") that produces a link like: 10.1038/171737a0 ### Running the test-suite To run the test suite, you first need to grab it with [mercurial] by running, from the root directory of the [citeproc-hs] source tree: hg clone https://bitbucket.org/bdarcus/citeproc-test You then need to grind human-readable test code into machine-readable form by running, in the citeproc-test directory, the following commands: cd citeproc-test ./processor.py -g cd .. Then, from the root directory of citeproc-hs source tree, run: runhaskell test/test.hs You may also specify a test group: runhaskell test/test.hs date or a single test in a group: runhaskell test/test.hs date IgnoreNonexistentSort To increase the debug messages edit *test/test.hs* and increase the *Int* parameter of *runTS*: runTS args 1 testDir Known Issues ------------ The [CSL] implementation is mostly but not entirely complete. Some of the missing features are meaningless in [pandoc], the main target of [citeproc-hs] at the present time. Specifically the [display] attribute has not been implemented yet. The [citeproc-hs]-0.3.9 release passes 586 out of 757 tests of the [citeproc-test] suite. The test-suite has been developed along with [citeproc-js], and the failure of some of those tests is not meaningful for [citeproc-hs]. The [MODS] parser may need some refinement. Bug Reports ----------- To submit bug reports you can use the Google code bug tracking system available at the following address: Credits ------- [Bruce D'Arcus], the man behind [CSL], Rintze Zelle, one of the main [CSL] developer, and [Frank Bennett], the [citeproc-js] author, have been very kind and provided ideas, comments and suggestions that made it easier coding citeproc-hs. [John MacFarlane], the author of [pandoc], has been very supportive of the project and provided a lot of useful feed back, comments and suggestions. Author ------ Andrea Rossato `andrea.rossato at unitn.it` Links to Related Projects ---------------- CSL : citeproc-js : citeproc-test : Zotero : Pandoc : Bibutils : MODS : Legal ----- This software is released under a BSD-style license. See LICENSE for more details. This is an early, "alpha" release. It carries no warranties of any kind. Copyright © 2008--2012 Andrea Rossato [^1]: The [JSON] format is basically documented by citeproc implementations and is derived by the [CSL] scheme. More information can be read in the [citeproc-js] documentation: [^2]: The Metadata Object Description Schema ([MODS]) is an XML format which is used by [bibutils] to interconvert many different bibliographic database formats, like Bibtex, Endnote, and others. [citeproc-hs]: http://code.haskell.org/citeproc-hs [citeproc-js]: https://bitbucket.org/fbennett/citeproc-js/wiki/Home [CSL]: http://citationstyles.org/ [pandoc]: http://johnmacfarlane.net/pandoc/ [Zotero]: http://www.zotero.org [JSON]: http://www.json.org/ [MODS]: http://www.loc.gov/mods/ [bibutils]: http://www.scripps.edu/~cdputnam/software/bibutils/ [hs-bibutils]: http://code.haskell.org/hs-bibutils/ [Haskell Platform]: http://hackage.haskell.org/platform/ [Hackage]: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/citeproc-hs [cabal-install]: http://hackage.haskell.org/trac/hackage/wiki/CabalInstall [Bruce D'Arcus]: http://community.muohio.edu/blogs/darcusb/ [John MacFarlane]: http://johnmacfarlane.net/ [Haddock]: http://www.haskell.org/haddock/ [display]: http://citationstyles.org/downloads/specification.html#display [citeproc-test]: http://bitbucket.org/bdarcus/citeproc-test/ [Frank Bennett]: http://gsl-nagoya-u.net/faculty/cache/gsliF_Bennett.html [mercurial]: http://mercurial.selenic.com/ [Haskell]: http://www.haskell.org citeproc-hs-0.3.9/src/0000755000175000001440000000000012223317047013704 5ustar andreausersciteproc-hs-0.3.9/src/Text/0000755000175000001440000000000012223317050014622 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL.hs0000644000175000001440000001104012223317050015573 0ustar andreausers----------------------------------------------------------------------------- -- | -- 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 , readModsFile , readModsCollectionFile , readJsonInput , readJsonInputString , readJsonAbbrevFile -- ** Reference Representation , Reference (..) , getReference , parseLocator , setNearNote -- * CSL Parser, Representation, and Processing , readCSLFile , parseCSL -- ** The Style Types , Style (..) , Citation (..) , Bibliography (..) , Cite (..) , Affix (..) , emptyCite -- ** High Level Processing , ProcOpts (..) , procOpts , BibOpts (..) , citeproc , processCitations , processBibliography , BiblioData (..) -- * The output and the rendering functions , FormattedOutput (..) , renderPlain , renderPlainStrict , renderPandoc , renderPandoc' , headInline , initInline , tailFirstInlineStr , toCapital , startWithPunct , endWithPunct ) where import Text.CSL.Parser import Text.CSL.Proc import Text.CSL.Reference import Text.CSL.Style import Text.CSL.Input.Bibutils import Text.CSL.Input.Json import Text.CSL.Input.MODS 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, 'FormattedOutput', 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 "apa-x.csl" -- > let result = citeproc procOpts s m $ [cites] -- > putStrLn . unlines . map (renderPlainStrict) . citations $ result -- -- The result would be: -- -- > (Caso, 2007, p. 15; Rossato, 2006, p. 10) citeproc-hs-0.3.9/src/Text/CSL/0000755000175000001440000000000012223317050015243 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Pickle/0000755000175000001440000000000012223317047016460 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Pickle/Xml.hs0000644000175000001440000000440212223317047017554 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Pickle.Xml -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : portable -- ----------------------------------------------------------------------------- module Text.CSL.Pickle.Xml where import Data.ByteString.Lazy.UTF8 ( toString ) import qualified Data.ByteString.Lazy as L import Data.Maybe import Text.XML.Light showXML :: Content -> String showXML = showContent getText :: [Content] -> Maybe String getText [] = Nothing getText (c:_) | Text x <- c = Just (showCData x) | otherwise = Nothing getChildren :: Content -> [Content] getChildren c | Elem el <- c = elContent el | otherwise = [] getElemName :: Content -> Maybe QName getElemName c | Elem el <- c = Just (elName el) | otherwise = Nothing dropFirstElem :: [Content] -> [Content] dropFirstElem [] = [] dropFirstElem (x:xs) | Text {} <- x = dropFirstElem xs | otherwise = xs dropText :: [Content] -> [Content] dropText [] = [] dropText a@(x:xs) | Text {} <- x = dropFirstElem xs | otherwise = a getAttName :: Attr -> String getAttName = qName . attrKey getAttrl :: Content -> [Attr] getAttrl c | Elem el <- c = elAttribs el | otherwise = [] getAttrVal :: [Content] -> String getAttrVal at | Text cd : _ <- at = cdData cd | otherwise = [] mkText :: String -> Content mkText s = Text $ blank_cdata { cdData = s } attrToCont :: Attr -> Content attrToCont a = Text $ blank_cdata { cdData = attrVal a } mkName :: String -> QName mkName n = blank_name {qName = n } mkElement :: String -> [Attr] -> [Content] -> Content mkElement n a c = Elem $ Element (mkName n) a c Nothing mkAttribute :: String -> String -> Attr mkAttribute n c = Attr (mkName n) c qualifiedName :: QName -> String qualifiedName qn = (fromMaybe [] $ qPrefix qn) ++ qName qn onlyElems' :: [Content] -> [Content] onlyElems' = map Elem . onlyElems parseXML' :: L.ByteString -> [Content] parseXML' s = case parseXML (toString s) of [] -> error $ "error while reading the XML string" x -> x citeproc-hs-0.3.9/src/Text/CSL/Pickle/Hexpat.hs0000644000175000001440000000472312223317047020253 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Pickle.Hexpat -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : portable -- ----------------------------------------------------------------------------- module Text.CSL.Pickle.Hexpat where import qualified Data.ByteString.Lazy as L import Data.ByteString.Lazy.UTF8 ( toString ) import Data.Maybe import Text.XML.Expat.Tree hiding ( mkText, getText, getChildren ) import Text.XML.Expat.Format import Text.XML.Expat.Proc type Content = UNode String type Attr = (String, String) showXML :: Content -> String showXML = toString . format getText :: [Content] -> Maybe String getText [] = Nothing getText (c:xs) | Text x <- c = Just (x ++ getAllText xs) | otherwise = Nothing getAllText :: [Content] -> String getAllText [] = [] getAllText (c:xs) | Text cd <- c = cd ++ getAllText xs | otherwise = [] dropFirstElem :: [Content] -> [Content] dropFirstElem [] = [] dropFirstElem (x:xs) | Text {} <- x = dropFirstElem xs | otherwise = xs dropText :: [Content] -> [Content] dropText [] = [] dropText a@(c:cs) | Text _ <- c = dropText cs | otherwise = a getChildren :: Content -> [Content] getChildren c | Element _ _ x <- c = x | otherwise = [] getElemName :: Content -> Maybe String getElemName c | Element x _ _ <- c = Just x | otherwise = Nothing getAttName :: Attr -> String getAttName = reverse . takeWhile (/= ':') . reverse . fst getAttrl :: Content -> [Attr] getAttrl c | Element _ x _ <- c = x | otherwise = [] getAttrVal :: [Content] -> String getAttrVal at | Text cd : _ <- at = cd | otherwise = [] mkText :: String -> Content mkText = Text mkName :: String -> String mkName = id mkElement :: String -> [Attr] -> [Content] -> Content mkElement n a c = Element n a c mkAttribute :: String -> String -> Attr mkAttribute n v = (n, v) attrToCont :: Attr -> Content attrToCont = Text . snd qualifiedName :: String -> String qualifiedName = id onlyElems' :: [Content] -> [Content] onlyElems' = onlyElems parseXML' :: L.ByteString -> [Content] parseXML' s = case parse defaultParseOptions s of (_, Just e) -> error $ "error while reading the XML file: " ++ show e (x, Nothing) -> return x citeproc-hs-0.3.9/src/Text/CSL/Parser.hs0000644000175000001440000005667312223317047017062 0ustar andreausers{-# LANGUAGE PatternGuards, CPP #-} {-# LANGUAGE TemplateHaskell #-} {-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Parser -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CS Language parsers -- ----------------------------------------------------------------------------- module Text.CSL.Parser where import Text.CSL.Reference ( readNum ) import Text.CSL.Style import Text.CSL.Pickle #ifdef EMBED_DATA_FILES import Data.FileEmbed import qualified Data.ByteString as S #else import Paths_citeproc_hs ( getDataFileName ) import System.Directory ( doesFileExist ) #endif import Data.Char ( isUpper, toUpper, toLower ) import Data.Maybe ( catMaybes ) import qualified Data.ByteString.Lazy as L import Data.ByteString.Lazy.UTF8 ( fromString ) #ifdef USE_NETWORK import Network.HTTP ( getResponseBody, mkRequest, RequestMethod(..) ) import Network.Browser ( browse, setAllowRedirects, setUserAgent, request ) import Network.URI ( parseURI, URI(..) ) #endif -- | Read and parse a CSL style file into the internal style -- representation, the 'Style'. readCSLFile :: FilePath -> IO Style readCSLFile src = do #ifdef USE_NETWORK let readURI u = do rsp <- browse $ do setAllowRedirects True setUserAgent "citeproc-hs" request $ mkRequest GET u getResponseBody (Right $ snd rsp) f <- case parseURI src of Just u | uriScheme u `elem` ["http:","https:"] -> readURI u _ -> readFile' src #else f <- readFile' src #endif parseCSL' f -- | Parse a 'String' into a fully localized 'Style' parseCSL :: String -> IO Style parseCSL = parseCSL' . fromString parseCSL' :: L.ByteString -> IO Style parseCSL' f = do let s = readXmlString xpStyle f l <- readLocaleFile (styleDefaultLocale s) return s { styleLocale = mergeLocales (styleDefaultLocale s) l (styleLocale s)} #ifdef EMBED_DATA_FILES localeFiles :: [(FilePath, S.ByteString)] localeFiles = $(embedDir "locales/") #endif readLocaleFile :: String -> IO Locale readLocaleFile s = do #ifdef EMBED_DATA_FILES f <- case s of x | length x == 2 -> let fn = ("locales-" ++ maybe "en-US" id (lookup x langBase) ++ ".xml") in case lookup fn localeFiles of Just x' -> return x' _ -> error "could not load the locale file" | otherwise -> case lookup ("locales-" ++ take 5 x ++ ".xml") localeFiles of Just x' -> return x' _ -> error "could not load the locale file" return $ readXmlString xpLocale $ L.fromChunks [f] #else f <- case s of x | length x == 2 -> getDataFileName ("locales/locales-" ++ maybe "en-US" id (lookup x langBase) ++ ".xml") | otherwise -> getDataFileName ("locales/locales-" ++ take 5 x ++ ".xml") b <- doesFileExist f if b then readXmlFile xpLocale f else readLocaleFile $ take 2 s #endif instance XmlPickler Layout where xpickle = xpWrap (uncurry3 Layout, \(Layout f d e) -> (f,d,e)) $ xpIElem "layout" $ xpTriple xpickle xpDelimiter xpickle instance XmlPickler Element where xpickle = xpAlt tag ps where tag (Choose {}) = 0 tag (Macro {}) = 1 tag (Const {}) = 2 tag (Variable {}) = 4 tag (Term {}) = 5 tag (Label {}) = 6 tag (Names {}) = 7 tag (Substitute {}) = 9 tag (Group {}) = 10 tag (Number {}) = 11 tag (Date {}) = 12 ps = [ xpChoose , xpMacro , xpConst , xpVariable , xpTerm , xpLabel , xpNames , xpSubStitute , xpGroup , xpNumber , xpDate ] instance XmlPickler IfThen where xpickle = xpWrap (uncurry3 IfThen, \(IfThen c m e) -> (c,m,e)) $ xpTriple xpickle xpickle xpickle instance XmlPickler Condition where xpickle = xpWrap ( \ ((t,v,n),(d,p,a,l)) -> Condition (words t) (words v) (words n) (words d) (words p) (words a) (words l), \ (Condition t v n d p a l) -> ((unwords t,unwords v,unwords n) ,(unwords d,unwords p,unwords a,unwords l))) $ xpPair (xpTriple (xpAttrText' "type" ) (xpAttrText' "variable" ) (xpAttrText' "is-numeric" )) (xp4Tuple (xpAttrText' "is-uncertain-date") (xpAttrText' "position" ) (xpAttrText' "disambiguate" ) (xpAttrText' "locator" )) instance XmlPickler Formatting where xpickle = xpWrap ( \(((p,s,ff),(fs,fv,fw)),(td,va,tc,d),(q,sp)) -> Formatting p s ff fs fv fw td va tc d (if q then NativeQuote else NoQuote) sp False False , \(Formatting p s ff fs fv fw td va tc d _ sp _ _) -> (((p,s,ff),(fs,fv,fw)),(td,va,tc,d),(False,sp))) $ xpTriple (xpPair (xpTriple (xpAttrText' "prefix" ) (xpAttrText' "suffix" ) (xpAttrText' "font-family" )) (xpTriple (xpAttrText' "font-style" ) (xpAttrText' "font-variant") (xpAttrText' "font-weight" ))) (xp4Tuple (xpAttrText' "text-decoration") (xpAttrText' "vertical-align" ) (xpAttrText' "text-case" ) (xpAttrText' "display" )) (xpPair (xpAttrWithDefault False "quotes" xpickle) (xpAttrWithDefault False "strip-periods" xpickle)) instance XmlPickler Sort where xpickle = xpAlt tag ps where readSort = read . flip (++) " \"\"" . toRead tag (SortVariable {}) = 0 tag (SortMacro {}) = 1 ps = [ xpWrap ( \(v,s) -> SortVariable v (readSort s) , \(SortVariable v s) -> (v,toShow $ show s)) $ xpElem "key" $ xpPair (xpAttrText "variable") (xpAttrWithDefault "ascending" "sort" xpText) , xpWrap ( \(v,s,a,b,c) -> SortMacro v (readSort s) (readNum a) (readNum b) c , \(SortMacro v s a b c) -> (v,toShow $ show s,show a,show b, c)) $ xpElem "key" $ xp5Tuple (xpAttrText "macro") (xpAttrWithDefault "ascending" "sort" xpText) (xpAttrWithDefault "" "names-min" xpText) (xpAttrWithDefault "" "names-use-first" xpText) (xpAttrWithDefault "" "names-use-last" xpText) ] instance XmlPickler Bool where xpickle = xpWrap readable xpText instance XmlPickler Gender where xpickle = xpWrap readable xpText instance XmlPickler Form where xpickle = xpWrap readable (xpAttrWithDefault "long" "form" xpText) instance XmlPickler NumericForm where xpickle = xpWrap readable (xpAttrWithDefault "numeric" "form" xpText) instance XmlPickler DateForm where xpickle = xpWrap (read . toRead . flip (++) "-date", const []) (xpAttrWithDefault "no-form" "form" xpText) instance XmlPickler Match where xpickle = xpWrap readable (xpAttrWithDefault "all" "match" xpText) instance XmlPickler DatePart where xpickle = xpWrap (uncurry4 DatePart, \(DatePart s f d fm) -> (s,f,d,fm)) $ xpElem "date-part" $ xp4Tuple (xpAttrText "name") (xpAttrWithDefault "long" "form" xpText) (xpAttrWithDefault "-" "range-delimiter" xpText) xpickle instance XmlPickler Name where xpickle = xpAlt tag ps where tag (Name {}) = 0 tag (NameLabel {}) = 1 tag (EtAl {}) = 2 ps = [ xpWrap (uncurry5 Name, \(Name f fm nas d nps) -> (f,fm,nas,d,nps)) $ xpElem "name" $ xp5Tuple xpNameForm xpickle xpNameAttrs xpDelimiter xpickle , xpWrap (uncurry3 NameLabel, \(NameLabel f fm p) -> (f, fm,p)) $ xpElem "label" $ xpTriple xpickle xpickle xpPlural , xpWrap (uncurry EtAl, \(EtAl fm t) -> (fm,t)) $ xpElem "et-al" $ xpPair xpickle $ xpAttrText' "term" ] xpNameForm = xpWrap readable $ xpAttrWithDefault "not-set" "form" xpText instance XmlPickler NamePart where xpickle = xpWrap (uncurry NamePart, \(NamePart s fm) -> (s,fm)) $ xpElem "name-part" $ xpPair (xpAttrText "name") xpickle instance XmlPickler CSInfo where xpickle = xpWrap ( \ ((t,i,u),(a,c)) -> CSInfo t a c i u , \ s -> ((csiTitle s, csiId s, csiUpdated s) ,(csiAuthor s, csiCategories s))) $ xpPair (xpTriple (get "title" ) (get "id" ) (get "updated")) (xpPair (xpIElemWithDefault (CSAuthor "" "" "") "author" xpickle) (xpDefault [] $ xpList $ xpIElem "category" xpickle)) where get = flip xpIElem xpText instance XmlPickler CSAuthor where xpickle = xpWrap (uncurry3 CSAuthor, \(CSAuthor a b c) -> (a, b, c)) $ xpTriple (xpIElemWithDefault [] "name" xpText) (xpIElemWithDefault [] "email" xpText) (xpIElemWithDefault [] "uri" xpText) instance XmlPickler CSCategory where xpickle = xpWrap (uncurry3 CSCategory, \(CSCategory a b c) -> (a, b, c)) $ xpTriple (xpAttrText "term" ) (xpAttrText' "schema") (xpAttrText' "label" ) xpStyle :: PU Style xpStyle = xpWrap ( \ ((v,sc,si,sl,l),(o,m,c,b)) -> Style v sc si sl l [] o m c b , \ (Style v sc si sl l _ o m c b) -> ((v,sc,si,sl,l),(o,m,c,b))) $ xpIElem "style" $ xpPair (xp5Tuple (xpAttrText "version") (xpAttrText "class") xpInfo (xpAttrWithDefault "en-US" "default-locale" xpText) (xpList xpLocale)) (xp4Tuple xpStyleOpts xpMacros xpCitation (xpOption xpBibliography)) xpInfo :: PU (Maybe CSInfo) xpInfo = xpOption . xpIElem "info" $ xpickle xpLocale :: PU Locale xpLocale = xpWrap ( \ ((v,l),(o,t,d)) -> Locale v l o t d , \ (Locale v l o t d) -> ((v,l),(o,t,d))) $ xpIElem "locale" $ xpPair (xpPair (xpAttrText' "version" ) (xpAttrText' "lang")) (xpTriple (xpIElemWithDefault [] "style-options" $ xpOpt "punctuation-in-quote") xpTerms (xpList xpLocaleDate)) xpTerms :: PU [CslTerm] xpTerms = xpWrap (concat,return) $ xpList $ xpIElem "terms" $ xpList $ xpElem "term" $ xpWrap (\((n,f,g,gf,m),(s,p)) -> CT n f g gf s p m, undefined) $ xpPair (xp5Tuple (xpAttrText "name") xpickle (xpAttrWithDefault Neuter "gender" xpickle) (xpAttrWithDefault Neuter "gender-form" xpickle) (xpAttrText' "match")) (xpChoice (xpWrap (\s -> (s,s), fst) xpText0) (xpPair (xpIElem "single" xpText0) (xpIElem "multiple" xpText0)) xpLift) xpMacros :: PU [MacroMap] xpMacros = xpList $ xpIElem "macro" $ xpPair (xpAttrText "name") xpickle xpCitation :: PU Citation xpCitation = xpWrap (uncurry3 Citation, \(Citation o s l) -> (o,s,l)) $ xpIElem "citation" $ xpTriple xpCitOpts xpSort xpickle xpBibliography :: PU Bibliography xpBibliography = xpWrap (uncurry3 Bibliography, \(Bibliography o s l) -> (o,s,l)) $ xpIElem "bibliography" $ xpTriple xpBibOpts xpSort xpickle xpOpt :: String -> PU [Option] xpOpt n = xpWrap (\a -> filter ((/=) [] . snd) $ [(n,a)], const []) $ xpAttrText' n xpNamesOpt :: PU [Option] xpNamesOpt = xpOpt "names-delimiter" xpNameFormat :: PU [Option] xpNameFormat = xpWrap (\(a,b,c,d,e,f) -> catMaybes [ checkOpt "and" a , checkOpt "delimiter-precedes-last" b , checkOpt "sort-separator" c , checkOpt "initialize" d , checkOpt "initialize-with" e , checkOpt "name-as-sort-order" f ] , const (Nothing, Nothing, Nothing, Nothing, Nothing, Nothing)) $ xp6Tuple (getOpt "and") (getOpt "delimiter-precedes-last") (getOpt "sort-separator") (getOpt "initialize") (getOpt "initialize-with") (getOpt "name-as-sort-order") where getOpt n = xpOption $ xpAttr n xpText checkOpt _ Nothing = Nothing checkOpt n (Just s) = Just (n,s) xpNameAttrs :: PU NameAttrs xpNameAttrs = xpWrap (\((a,b,c,d,e),(f,g)) -> filter ((/=) [] . snd) [("et-al-min",a) ,("et-al-use-first",b) ,("et-al-subsequent-min",c) ,("et-al-subsequent-use-first",d) ,("et-al-use-last",e) ,("delimiter-precedes-et-al",f)] ++ g , const (([],[],[],[],[]),([],[]))) $ xpPair (xp5Tuple (xpAttrText' "et-al-min") (xpAttrText' "et-al-use-first") (xpAttrText' "et-al-subsequent-min") (xpAttrText' "et-al-subsequent-use-first") (xpAttrText' "et-al-use-last")) $ xpPair (xpAttrText' "delimiter-precedes-et-al") xpNameFormat xpNameOpt :: PU [Option] xpNameOpt = xpWrap (\(a,b,c) -> filter ((/=) [] . snd) $ a ++ [("name-delimiter",b) ,("name-form",c)], const ([],[],[])) $ xpTriple xpNameAttrs (xpAttrText' "name-delimiter") (xpAttrText' "name-form") xpBibOpts :: PU [Option] xpBibOpts = xpWrap ( \((a,b,c,d,e,f),(g,h)) -> filter ((/=) [] . snd) $ [("hanging-indent",a) ,("second-field-align",b) ,("subsequent-author-substitute",c) ,("subsequent-author-substitute-rule",d) ,("line-spacing",e) ,("entry-spacing",f)] ++ g ++ h , const (([],[],[],[],[],[]),([],[]))) $ xpPair (xp6Tuple (xpAttrText' "hanging-indent") (xpAttrText' "second-field-align") (xpAttrText' "subsequent-author-substitute") (xpAttrText' "subsequent-author-substitute-rule") (xpAttrText' "line-spacing") (xpAttrText' "entry-spacing")) $ xpPair xpNameOpt xpNamesOpt xpCitOpts :: PU [Option] xpCitOpts = xpWrap ( \((a,b,c),(d,e,f,g,h,i),(j,k)) -> filter ((/=) [] . snd) $ [("disambiguate-add-names",a) ,("disambiguate-add-givenname",b) ,("disambiguate-add-year-suffix",c) ,("givenname-disambiguation-rule",d) ,("collapse",e) ,("cite-group-delimiter",f) ,("year-suffix-delimiter",g) ,("after-collapse-delimiter",h) ,("near-note-distance",i)] ++ j ++ k , const (([],[],[]),([],[],[],[],[],[]),([],[]))) $ xpTriple (xpTriple (xpAttrText' "disambiguate-add-names") (xpAttrText' "disambiguate-add-givenname") (xpAttrText' "disambiguate-add-year-suffix")) (xp6Tuple (xpAttrText' "givenname-disambiguation-rule") (xpAttrText' "collapse") (xpAttrText' "cite-group-delimiter") (xpAttrText' "year-suffix-delimiter") (xpAttrText' "after-collapse-delimiter") (xpAttrText' "near-note-distance")) (xpPair xpNameOpt xpNamesOpt) xpStyleOpts :: PU [Option] xpStyleOpts = xpWrap ( \((a,b,c),(d,e)) -> filter ((/=) [] . snd) $ [("page-range-format",a) ,("demote-non-dropping-particle",b) ,("initialize-with-hyphen",c)] ++ d ++ e , const (([],[],[]),([],[]))) $ xpPair (xpTriple (xpAttrText' "page-range-format") (xpAttrText' "demote-non-dropping-particle") (xpAttrText' "initialize-with-hyphen")) $ (xpPair xpNameOpt xpNamesOpt) xpSort :: PU [Sort] xpSort = xpDefault [] $ xpElem "sort" $ xpList xpickle xpChoose :: PU Element xpChoose = xpWrap (uncurry3 Choose, \(Choose b t e) -> (b,t,e)) $ xpElem "choose" $ xpTriple ( xpElem "if" xpickle) (xpDefault [] $ xpList $ xpElem "else-if" xpickle) (xpDefault [] $ xpElem "else" xpickle) xpMacro :: PU Element xpMacro = xpWrap (uncurry Macro, \(Macro s fm) -> (s,fm)) $ xpTextElem $ xpPair (xpAttrText "macro") xpickle xpConst :: PU Element xpConst = xpWrap (uncurry Const, \(Const s fm) -> (s,fm)) $ xpTextElem $ xpPair (xpAttrText "value") xpickle xpVariable :: PU Element xpVariable = xpWrap ( \((v,f,fm),d) -> Variable (words v) f fm d , \(Variable v f fm d) -> ((unwords v,f,fm),d)) $ xpTextElem $ xpPair (xpCommon "variable") xpDelimiter xpTerm :: PU Element xpTerm = xpWrap ( \((t,f,fm),p) -> Term t f fm p , \(Term t f fm p) -> ((t,f,fm),p)) $ xpTextElem $ xpPair (xpCommon "term") $ xpAttrWithDefault True "plural" xpickle xpNames :: PU Element xpNames = xpWrap ( \((a,n,fm),d,sb) -> Names (words a) n fm d sb , \(Names a n fm d sb) -> ((unwords a,n,fm),d,sb)) $ xpElem "names" $ xpTriple names xpDelimiter xpickle where names = xpTriple (xpAttrText "variable") xpName xpickle xpName = xpChoice xpZero xpickle check check [] = xpLift [Name NotSet emptyFormatting [] [] []] check l = if any isName l then xpLift l else xpZero xpLabel :: PU Element xpLabel = xpWrap ( uncurry4 Label , \(Label s f fm p) -> (s,f,fm,p)) $ xpElem "label" $ xp4Tuple (xpAttrText' "variable") xpickle xpickle xpPlural xpSubStitute :: PU Element xpSubStitute = xpWrap (Substitute, \(Substitute es) -> es) $ xpElem "substitute" xpickle xpGroup :: PU Element xpGroup = xpWrap (uncurry3 Group, \(Group fm d e) -> (fm,d,e)) $ xpElem "group" $ xpTriple xpickle xpDelimiter xpickle xpNumber :: PU Element xpNumber = xpWrap (uncurry3 Number, \(Number s f fm) -> (s,f,fm)) $ xpElem "number" $ xpCommon "variable" xpDate :: PU Element xpDate = xpWrap ( \((s,f,fm),(d,dp,dp')) -> Date (words s) f fm d dp dp' , \(Date s f fm d dp dp') -> ((unwords s,f,fm),(d,dp,dp'))) $ xpElem "date" $ xpPair (xpCommon "variable") (xpTriple xpDelimiter xpickle (xpAttrText' "date-parts")) xpLocaleDate :: PU Element xpLocaleDate = xpWrap ( \((s,f,fm),(d,dp,dp')) -> Date (words s) f fm d dp dp' , \(Date s f fm d dp dp') -> ((unwords s,f,fm),(d,dp,dp'))) $ xpIElem "date" $ xpPair (xpTriple (xpLift []) xpickle xpickle) (xpTriple xpDelimiter xpickle (xpLift [])) xpTextElem :: PU a -> PU a xpTextElem = xpElem "text" xpDelimiter :: PU String xpDelimiter = xpAttrText' "delimiter" xpPlural :: PU Plural xpPlural = xpWrap readable $ xpAttrWithDefault "contextual" "plural" xpText xpCommon :: (XmlPickler b, XmlPickler c) => String -> PU (String,b,c) xpCommon s = xpTriple (xpAttrText s) xpickle xpickle -- | For mandatory attributes. xpAttrText :: String -> PU String xpAttrText n = xpAttr n xpText -- | For optional attributes. xpAttrText' :: String -> PU String xpAttrText' n = xpAttrWithDefault [] n xpText xpAttrWithDefault :: Eq a => a -> String -> PU a -> PU a xpAttrWithDefault d n = xpDefault d . xpAttr n xpIElemWithDefault :: Eq a => a -> String -> PU a -> PU a xpIElemWithDefault d n = xpDefault d . xpIElem n readable :: (Read a, Show b) => (String -> a, b -> String) readable = (read . toRead, toShow . show) toShow :: String -> String toShow = foldr g [] . f where g x xs = if isUpper x then '-' : toLower x : xs else x : xs f ( x:xs) = toLower x : xs f [] = [] 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 = [] langBase :: [(String, String)] langBase = [("af", "af-ZA") ,("ar", "ar-AR") ,("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") ] citeproc-hs-0.3.9/src/Text/CSL/Output/0000755000175000001440000000000012223317047016551 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Output/Plain.hs0000644000175000001440000000637012223317047020156 0ustar andreausers{-# 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 , renderPlainStrict , procList , (<+>) , (<>) , capitalize , entityToChar , head' , tail' ) where import Control.Arrow ( (&&&) ) import Data.Char import Text.CSL.Style -- | Render the 'FormattedOutput' into a plain text string. renderPlain :: [FormattedOutput] -> String renderPlain = concatMap $ render False -- | Same as 'renderPlain' , but will not clean up the produced -- output. renderPlainStrict :: [FormattedOutput] -> String renderPlainStrict = concatMap $ render True render :: Bool -> FormattedOutput -> String render _ (FPan i) = show i render _ (FDel s) = s render b fo | (FS str fm ) <- fo = prefix fm <++> format fm (trim str ) <++> suffix fm | (FN str fm ) <- fo = prefix fm <++> format fm (trim str ) <++> suffix fm | (FUrl t fm ) <- fo = prefix fm <++> format fm (trim $ fst t ) <++> suffix fm | (FO fm xs) <- fo = prefix fm <++> format fm (trim $ rest xs) <++> suffix fm | otherwise = [] where rest xs = procList xs $ concatM (render b) trim = if b then id else unwords . words (<++>) = if b then (++) else (<>) concatM f = foldr (<++>) [] . map f quote f s = if s /= [] && quotes f /= NoQuote then "\"" ++ s ++ "\"" else s capital s = toUpper (head s) : (tail s) format f s = quote f . text_case f $ s text_case fm s | "capitalize-first" <- textCase fm = procList s capital | "capitalize-all" <- textCase fm = procList s $ unwords . map capital . words | "lowercase" <- textCase fm = map toLower s | "uppercase" <- textCase fm = map toUpper s | otherwise = s procList :: Eq a => [a] -> ([a] -> [b]) -> [b] procList s f = if s /= [] then f s else [] (<+>) :: String -> String -> String [] <+> ss = ss s <+> [] = s s <+> ss = s ++ " " ++ ss (<>) :: String -> String -> String sa <> sb | sa /= [], (s:xs) <- sb , last sa == s , s `elem` ";:,. " = sa ++ xs | otherwise = sa ++ sb capitalize :: String -> String capitalize s = if s /= [] then toUpper (head s) : tail s else [] entityToChar :: String -> String entityToChar s | '&':'#':xs <- s = uncurry (:) $ parseEntity xs | x :xs <- s = x : entityToChar xs | otherwise = [] where parseEntity = chr . readNum . takeWhile (/= ';') &&& entityToChar . tail' . dropWhile (/= ';') readNum :: String -> Int readNum ('x': n) = readNum $ "0x" ++ n readNum n = case readsPrec 1 n of [(x,[])] -> x _ -> error $ "Invalid character entity:" ++ n head' :: [a] -> [a] head' = foldr (\x _ -> [x]) [] tail' :: Eq a => [a] -> [a] tail' x = if x /= [] then tail x else [] citeproc-hs-0.3.9/src/Text/CSL/Output/Pandoc.hs0000644000175000001440000003461712223317047020324 0ustar andreausers{-# 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' , renderPandoc_ , headInline , initInline , tailFirstInlineStr , toCapital , startWithPunct , endWithPunct ) where import Data.Char ( toUpper, toLower ) import Data.Maybe ( fromMaybe ) import Text.CSL.Style import Text.CSL.Output.Plain import Text.Pandoc.Definition -- | With a 'Style' and the formatted output generate a 'String' in -- the native 'Pandoc' formats (i.e. immediately readable by pandoc). renderPandoc :: Style -> [FormattedOutput] -> [Inline] renderPandoc s = proc (convertQuoted s) . proc' (clean s $ isPunctuationInQuote s) . flipFlop . render s -- | Same as 'renderPandoc', but the output is wrapped in a pandoc -- paragraph block. renderPandoc' :: Style -> [FormattedOutput] -> Block renderPandoc' s = Para . proc (convertQuoted s) . proc' (clean s $ isPunctuationInQuote s) . flipFlop . render s -- | For the testsuite: we use 'Link' and 'Strikeout' to store -- "nocase" and "nodecor" rich text formatting classes. renderPandoc_ :: Style -> [FormattedOutput] -> [Inline] renderPandoc_ s = proc (convertQuoted s) . proc (clean' s $ isPunctuationInQuote s) . flipFlop . render s render :: Style -> [FormattedOutput] -> [Inline] render _ [] = [] render s (x:[]) = renderFo s x render s (x:y:os) = let a = renderFo s x b = renderFo s y isPunct = and . map (flip elem ".!?") in if isPunct (lastInline a) && isPunct (headInline b) then a ++ render s (tailFO [y] ++ os) else a ++ render s (y:os) tailFO :: [FormattedOutput] -> [FormattedOutput] tailFO [] = [] tailFO (f:fs) | FDel s <- f = FDel (tail' s) : fs | FPan is <- f = FPan (tailInline is) : fs | FN s fm <- f = if prefix fm /= [] then FN s (tailFm fm) : fs else FN (tail' s) fm : fs | FS s fm <- f = if prefix fm /= [] then FS s (tailFm fm) : fs else FS (tail' s) fm : fs | FO fm fo <- f = if prefix fm /= [] then FO (tailFm fm) fo : fs else FO fm (tailFO fo) : fs | otherwise = f : tailFO fs where tailFm fm = fm { prefix = tail $ prefix fm } renderFo :: Style -> FormattedOutput -> [Inline] renderFo _ (FPan i) = i renderFo _ (FDel s) = toStr s renderFo sty fo | FS str fm <- fo = toPandoc fm $ toStr str | FN str fm <- fo = toPandoc fm $ toStr $ rmZeros str | FO fm xs <- fo = toPandoc fm $ rest xs | FUrl u fm <- fo = toPandoc fm [Link (toStr $ snd u) u] | otherwise = [] where addSuffix f i | suffix f /= [] , elem (head $ suffix f) ".?!" , lastInline i /= [] , last (lastInline i)`elem` ".?!" = i ++ toStr (tail $ suffix f) | suffix f /= [] = i ++ toStr ( suffix f) | otherwise = i toPandoc f i = addSuffix f $ toStr (prefix f) ++ (quote f . format f . proc cleanStrict $ i) format f = font_variant f . font f . text_case f rest xs = procList xs $ render sty quote f i = if i /= [] && quotes f /= NoQuote then if quotes f == NativeQuote then [escape "inquote" . valign f $ i] else [Quoted DoubleQuote . valign f $ i] else valign f i setCase f i | Str s <- i = Str $ f s | otherwise = i setCase' f i | Link s r <- i = Link (map (setCase f) s) r | otherwise = setCase f i toCap s = if s /= [] then toUpper (head s) : tail s else [] toTitleCap s = if isShortWord s then toUpper (head s) : tail s else s isShortWord s = not $ s `elem` ["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","yet"] text_case _ [] = [] text_case fm a@(i:is) | noCase fm = [escape "nocase" a] | "lowercase" <- textCase fm = map (setCase' $ map toLower) a | "uppercase" <- textCase fm = map (setCase' $ map toUpper) a | "capitalize-all" <- textCase fm = map (setCase $ unwords . map toCap . words) a | "title" <- textCase fm = map (setCase $ unwords . map toTitleCap . words) a | "capitalize-first" <- textCase fm = [setCase capitalize i] ++ is | "sentence" <- textCase fm = [setCase toCap i] ++ map (setCase $ map toLower) is | otherwise = a font_variant fm i | "small-caps" <- fontVariant fm = [SmallCaps i] | otherwise = i font fm | noDecor fm = return . escape "nodecor" | "italic" <- fontStyle fm = return . Emph | "oblique" <- fontStyle fm = return . Emph | "bold" <- fontWeight fm = return . Strong | otherwise = id valign _ [] = [] valign fm i | "sup" <- verticalAlign fm = [Superscript i] | "sub" <- verticalAlign fm = [Subscript i] | "baseline" <- verticalAlign fm = [escape "baseline" i] | otherwise = i rmZeros = dropWhile (== '0') escape s x = Link x (s,s) -- we use a link to store some data toStr :: String -> [Inline] toStr = toStr' . entityToChar where toStr' s |'«':' ':xs <- s = toStr' ("«\8239" ++ xs) |' ':'»':xs <- s = toStr' ("\8239»" ++ xs) |' ':';':xs <- s = toStr' ("\8239;" ++ xs) |' ':':':xs <- s = toStr' ("\8239:" ++ xs) |' ':'!':xs <- s = toStr' ("\8239!" ++ xs) |' ':'?':xs <- s = toStr' ("\8239?" ++ xs) |' ':xs <- s = Space : toStr' xs | x :xs <- s = Str [x] : toStr' xs | otherwise = [] cleanStrict :: [Inline] -> [Inline] cleanStrict [] = [] cleanStrict (i:is) | Str [] <- i = cleanStrict is | Str " " <- i = Space : cleanStrict is | Str sa <- i , Str sb:xs <- is = Str (sa ++ sb) : cleanStrict xs | otherwise = i : cleanStrict is clean :: Style -> Bool -> [Inline] -> [Inline] clean _ _ [] = [] clean s b (i:is) | Superscript x <- i = split (isLink "baseline") (return . Superscript) x ++ clean s b is | Subscript x <- i = split (isLink "baseline") (return . Subscript ) x ++ clean s b is | SmallCaps x <- i = split (isLink "nodecor" ) (return . SmallCaps ) x ++ clean s b is | Emph x <- i = split (isLink' "emph" ) (return . Emph ) x ++ clean s b is | Strong x <- i = split (isLink' "strong" ) (return . Strong ) x ++ clean s b is | Link x t <- i = clean' s b (Link x t : clean s b is) | otherwise = clean' s b (i : clean s b is) where unwrap f ls | Link x _ : _ <- ls = clean' s b x | _ : _ <- ls = f ls | otherwise = [] isLink l il | Link _ (x,y) <- il = x == l && x == y | otherwise = False isLink' l il | Link _ (x,y) <- il = (x == l || x == "nodecor") && x == y | otherwise = False split _ _ [] = [] split f g xs = let (y, r) = break f xs in concatMap (unwrap g) [y, head' r] ++ split f g (tail' r) clean' :: Style -> Bool -> [Inline] -> [Inline] clean' _ _ [] = [] clean' s b (i:is) | Link inls (y,z) <- i, y == "inquote" , y == z = case headInline is of [x] -> if x `elem` ".," && b then if lastInline inls `elem` [".",",",";",":","!","?"] then quote DoubleQuote inls : clean' s b (tailInline is) else quote DoubleQuote (inls ++ [Str [x]]) : clean' s b (tailInline is) else quote DoubleQuote inls : clean' s b is _ -> quote DoubleQuote inls : clean' s b is | Quoted t inls <- i = quote t inls : clean' s b is | otherwise = if lastInline [i] == headInline is && isPunct then i : clean' s b (tailInline is) else i : clean' s b is where quote t x = Quoted t (reverseQuoted t x) isPunct = and . map (flip elem ".,;:!? ") $ headInline is reverseQuoted t = proc reverseQuoted' where reverseQuoted' q | Quoted _ qs <- q , DoubleQuote <- t = Quoted SingleQuote (reverseQuoted SingleQuote qs) | Quoted _ qs <- q , SingleQuote <- t = Quoted DoubleQuote (reverseQuoted DoubleQuote qs) | otherwise = q flipFlop :: [Inline] -> [Inline] flipFlop [] = [] flipFlop (i:is) | Emph inls <- i = Emph (reverseEmph True inls) : flipFlop is | Strong inls <- i = Strong (reverseStrong True inls) : flipFlop is | otherwise = i : flipFlop is where reverseEmph bo = map reverseEmph' where reverseEmph' e | bo, Emph inls <- e = Link (reverseEmph False inls) ("emph","emph") | Emph inls <- e = Emph (reverseEmph True inls) | Link ls (x,y) <- e = if x == "nodecor" && x == y then Link ls ("emph","emph") else e | otherwise = e reverseStrong bo = map reverseStrong' where reverseStrong' e | bo, Strong inls <- e = Link (reverseStrong False inls) ("strong","strong") | Strong inls <- e = Strong (reverseStrong True inls) | Link ls (x,y) <- e = if x == "nodecor" && x == y then Link ls ("strong","strong") else e | otherwise = e isPunctuationInQuote :: Style -> Bool isPunctuationInQuote = or . query punctIn' where punctIn' n | ("punctuation-in-quote","true") <- n = [True] | otherwise = [False] endWithPunct, startWithPunct :: [Inline] -> Bool endWithPunct = and . map (`elem` ".,;:!?") . lastInline startWithPunct = and . map (`elem` ".,;:!?") . headInline convertQuoted :: Style -> [Inline] -> [Inline] convertQuoted s = convertQuoted' where locale = let l = styleLocale s in case l of [x] -> x; _ -> Locale [] [] [] [] [] getQuote x y = entityToChar . 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 = [] headInline :: [Inline] -> String headInline [] = [] headInline (i:_) | Str s <- i = head' s | Space <- i = " " | otherwise = headInline $ getInline i lastInline :: [Inline] -> String lastInline [] = [] lastInline (i:[]) | Str s <- i = last' s | Space <- i = " " | otherwise = lastInline $ getInline i where last' s = if s /= [] then [last s] else [] lastInline (_:xs) = lastInline xs 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 is t <- i = return $ Link (initInline is) t | otherwise = [] where init' s = if s /= [] then init s else [] initInline (i:xs) = i : initInline xs tailInline :: [Inline] -> [Inline] tailInline inls | (i:t) <- inls , Space <- i = t | otherwise = tailFirstInlineStr inls tailFirstInlineStr :: [Inline] -> [Inline] tailFirstInlineStr = mapHeadInline tail' toCapital :: [Inline] -> [Inline] toCapital = mapHeadInline capitalize 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 is t <- i = Link (mapHeadInline f is) t : xs | otherwise = i : xs getInline :: Inline -> [Inline] getInline i | Emph is <- i = is | Strong is <- i = is | Strikeout is <- i = is | Superscript is <- i = is | Subscript is <- i = is | Quoted _ is <- i = is | SmallCaps is <- i = is | Link is _ <- i = is | otherwise = [] citeproc-hs-0.3.9/src/Text/CSL/Eval/0000755000175000001440000000000012223317047016140 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Eval/Names.hs0000644000175000001440000004177212223317047017552 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- 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.Applicative ( (<$>) ) import Control.Monad.State import Data.Char ( toUpper, isLower, isUpper, isSpace ) import Data.List ( nub ) import Data.Maybe ( isJust ) import Text.CSL.Eval.Common import Text.CSL.Eval.Output import Text.CSL.Output.Plain ( (<>) ) import Text.CSL.Parser ( toRead ) import Text.CSL.Reference import Text.CSL.Style import Text.Pandoc.Definition 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 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 res /= [] then let role = if aus == ["author"] then concat aus ++ "sub" else s in return . return . OContrib k role res fb =<< gets etal else return [] 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 etal' == [] then do t <- getTerm False Long "and" return $ delim t o del' $ format m o form fm np x else do 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 } updateEtal [res] return res | EtAl fm t <- n = do o <- gets (options . env) if (getOptionVal "et-al-min" o == []) then return [] else do 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 = if etal st /= [] then map (uncurry (++)) . zip (etal st) $ x' else 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 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 /= [] = return $ OName (show n) institution [] fm | Short <- f = return $ OName (show n) shortName disambdata fm | otherwise = return $ OName (show n) (longName given) disambdata fm where institution = [OStr (literal n) $ form "family"] when_ c o = if c /= [] then o else [] addAffixes s sf ns = [Output ((oStr' s (form sf) { prefix = [], suffix = [] }) ++ ns) $ emptyFormatting { prefix = prefix (form sf) , suffix = suffix (form sf)}] form s = case filter (\(NamePart n' _) -> n' == s) np of NamePart _ fm':_ -> fm' _ -> emptyFormatting hasHyphen = not . null . filter (== '-') hyphen = if getOptionVal "initialize-with-hyphen" ops == "false" then getOptionVal "initialize-with" ops else filter (not . isSpace) $ getOptionVal "initialize-with" ops ++ "-" isInit x = length x == 1 && or (map isUpper x) initial x = if isJust (lookup "initialize-with" ops) && getOptionVal "initialize" ops /= "false" then if not . and . map isLower $ x then addIn x $ getOptionVal "initialize-with" ops else " " ++ case x of _:'\'':[] -> x _ -> x ++ " " else " " ++ if isJust (lookup "initialize-with" ops) && isInit x then addIn x $ getOptionVal "initialize-with" ops else x addIn x i = if hasHyphen x then head ( takeWhile (/= '-') x) : hyphen ++ head (tail $ dropWhile (/= '-') x) : i else head x : i sortSep g s = when_ g $ separator ++ addAffixes (g <+> s) "given" [] separator = if getOptionVal "sort-separator" ops == [] then oStr "," ++ [OSpace] else oStr (getOptionVal "sort-separator" ops) suff = if commaSuffix n && nameSuffix n /= [] then suffCom else suffNoCom suffCom = when_ (nameSuffix n) $ separator ++ [ OStr (nameSuffix n) fm] suffNoCom = when_ (nameSuffix n) $ [OSpace, OStr (nameSuffix n) fm] given = when_ (givenName n) . unwords . words . concatMap initial $ givenName n givenLong = when_ (givenName n) . unwords' $ givenName n family = familyName n shortName = oStr' (nonDroppingPart n <+> family) (form "family") longName g = if isSorting m then let firstPart = case getOptionVal "demote-non-dropping-particle" ops of "never" -> nonDroppingPart n <+> family <+> droppingPart n _ -> family <+> droppingPart n <+> nonDroppingPart n in [OStr firstPart (form "family")] <++> oStr' 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" -> (nonDroppingPart n <+> family, droppingPart n) "sort-only" -> (nonDroppingPart n <+> family, droppingPart n) _ -> (family, droppingPart n <+> nonDroppingPart n) in oStr' fam (form "family") ++ sortSep g par ++ suffCom else oStr' g (form "given") <++> addAffixes (droppingPart n <+> nonDroppingPart n <+> family) "family" suff disWithGiven = getOptionVal "disambiguate-add-givenname" ops == "true" initialize = isJust . lookup "initialize-with" $ ops 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 -> [] unwords' :: [String] -> String unwords' = unwords . words . foldr concatWord [] where concatWord w ws = if w /= [] && last w == '.' then w ++ ws else w ++ ' ':ws 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 ('-' `elem` v) | "page" <- s = checkPlural | "volume" <- s = checkPlural | "ibid" <- s = format' s p | otherwise = if isRole s then form (\fm' x -> [OLabel x fm']) id s p else 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 ('-' `elem` v) format = form output id format' t b = gets (citePosition . cite . env) >>= \po -> if po == "ibid-with-locator-c" || po == "ibid-c" then form output capital t b else format t b form o g t b = return . o fm =<< g . period <$> getTerm (b && p) f t period = if stripPeriods fm then filter (/= '.') else id capital x = toUpper (head x) : (tail x) (<+>) :: String -> String -> String [] <+> ss = ss s <+> [] = s s <+> ss = if last s == '\'' then init s ++ "’" ++ ss else s ++ " " ++ ss citeproc-hs-0.3.9/src/Text/CSL/Eval/Common.hs0000644000175000001440000001462112223317047017730 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- 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.Applicative ( (<$>) ) import Control.Monad.State import Data.Char ( toLower ) import Data.List ( elemIndex ) import qualified Data.Map as M import Data.Maybe import Text.CSL.Reference import Text.CSL.Style 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 :: [Abbrev] } 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 :: [Abbrev] -> String -> String -> String getAbbreviation as s v = case lookup "default" as of Nothing -> [] Just x -> case lookup (if s `elem` numericVars then "number" else s) x of Nothing -> [] Just x' -> case M.lookup v x' of Nothing -> [] Just x'' -> x'' -- | 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 val | Just v <- fromValue val = v | otherwise = [] 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 | Just v <- fromValue val = v | otherwise = [] 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 v <- getStringVar (take (length s - 6) s) a <- gets (abbrevs . env) return $ getAbbreviation a (take (length s - 6) 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 } citeproc-hs-0.3.9/src/Text/CSL/Eval/Date.hs0000644000175000001440000002454512223317047017363 0ustar andreausers{-# 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.Applicative ( (<$>) ) import Control.Monad.State import Data.Char import Data.List import Data.Maybe import Text.CSL.Eval.Common import Text.CSL.Eval.Output import Text.CSL.Parser ( toRead ) import Text.CSL.Reference import Text.CSL.Style 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) (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 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 = return . ODate . concat $ (start a b ++ end a b ++ coda b) | otherwise = [] where start a b = map (formatDatePart False a) . init . diff a b $ dp end a b = map (formatDatePart True a) . return . last . diff a b $ dp coda b = map (formatDatePart False b) dp 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 -> ["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 y m e d _ _) (DatePart n f _ fm) | "year" <- n, y /= [] = return $ OYear (formatYear f y) k fm | "month" <- n, m /= [] = output fm (formatMonth f fm m) | "day" <- n, d /= [] = output fm (formatDay f m d) | "month" <- n, m == [] , e /= [] = output fm $ term f ("season-0" ++ e) formatDatePart True (RefDate y m e d _ _) (DatePart n f rd fm) | "year" <- n, y /= [] = OYear (formatYear f y) k (fm {suffix = []}) : formatDelim | "month" <- n, m /= [] = output (fm {suffix = []}) (formatMonth f fm m) ++ formatDelim | "day" <- n, d /= [] = output (fm {suffix = []}) (formatDay f m d) ++ formatDelim | "month" <- n, m == [] , e /= [] = output (fm {suffix = []}) (term f $ "season-0" ++ e) ++ formatDelim where formatDelim = if rd == "-" then [OPan [Str "\x2013"]] else [OPan [Str rd]] formatDatePart _ (RefDate _ _ _ _ o _) (DatePart n _ _ fm) | "year" <- n, o /= [] = 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 _ _ _ _ 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 y' [] [] [] o c [s',y'] | and (map isDigit y') , and (map isDigit s') -> RefDate y' s' [] [] o c [s',y'] | s' `elem'` seasons -> RefDate y' [] (select s' seasons) [] o [] [s',y'] | s' `elem'` months -> RefDate y' (select s' months) [] [] o c [s',d',y'] | and (map isDigit s') , and (map isDigit y') , and (map isDigit d') -> RefDate y' s' [] d' o c [s',d',y'] | s' `elem'` months , and (map isDigit y') , and (map isDigit d') -> RefDate y' (select s' months) [] d' o c [s',d',y'] | s' `elem'` months , and (map isDigit y') , and (map isDigit d') -> RefDate y' (select s' months) [] d' 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"] citeproc-hs-0.3.9/src/Text/CSL/Eval/Output.hs0000644000175000001440000001331512223317047017777 0ustar andreausers{-# 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.Plain import Text.CSL.Style import Text.ParserCombinators.Parsec hiding ( State (..) ) 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 . map cleanOutput' where cleanOutput' o | Output xs f <- o = Output (cleanOutput xs) 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 xs ++ flatten os | otherwise = rmEmptyOutput o : flatten os rmEmptyOutput :: Output -> Output rmEmptyOutput o | Output [] _ <- o = ONull | OStr [] _ <- o = ONull | OUrl t _ <- o = if null (fst t) then ONull else o | otherwise = o addDelim :: String -> [Output] -> [Output] addDelim d = foldr (\x xs -> if length xs < 1 then x : xs else check x xs) [] where check x xs | ONull <- x = xs | otherwise = let text = renderPlainStrict . formatOutputList in if d /= [] && text [x] /= [] && text xs /= [] then if head d == last (text [x]) && head d `elem` ".,;:!?" then x : ODel (tail d) : xs else x : ODel d : xs else x : xs noOutputError :: Output noOutputError = OStr "[CSL STYLE ERROR: reference with no printed form.]" emptyFormatting noBibDataError :: Cite -> Output noBibDataError c = OStr ("[CSL BIBLIOGRAPHIC DATA ERROR: reference " ++ show (citeId c) ++ " not found.]") emptyFormatting oStr :: String -> [Output] oStr s = oStr' s emptyFormatting oStr' :: String -> Formatting -> [Output] oStr' [] _ = [] oStr' s f = rtfParser f s (<++>) :: [Output] -> [Output] -> [Output] [] <++> o = o o <++> [] = o o1 <++> o2 = o1 ++ [OSpace] ++ o2 rtfTags :: [(String, (String,Formatting))] rtfTags = [("b" , ("b" , ef {fontWeight = "bold" })) ,("i" , ("i" , ef {fontStyle = "italic" })) ,("sc" , ("sc" , ef {fontVariant = "small-caps"})) ,("sup" , ("sup" , ef {verticalAlign = "sup" })) ,("sub" , ("sub" , ef {verticalAlign = "sub" })) ,("span class=\"nocase\"" , ("span", ef {noCase = True })) ,("span class=\"nodecor\"" , ("span", ef {noDecor = True })) ] where ef = emptyFormatting rtfParser :: Formatting -> String -> [Output] rtfParser _ [] = [] rtfParser fm s = either (const [OStr s fm]) (return . flip Output fm . concat) $ parse (manyTill parser eof) "" s where parser = parseText <|> parseMarkup parseText = do let amper = string "&" >> notFollowedBy (char '#') >> return [OStr "&" emptyFormatting] apos = string "'" >> return [OStr "’" emptyFormatting] x <- many $ noneOf "<'\"`“‘&" xs <- parseQuotes <|> parseMarkup <|> amper <|> apos r <- manyTill anyChar eof return (OStr x emptyFormatting : xs ++ [Output (rtfParser emptyFormatting r) emptyFormatting]) parseMarkup = do let tillTag = many $ noneOf "<" m <- string "<" >> manyTill anyChar (try $ string ">") res <- case lookup m rtfTags of Just tf -> do let ot = "<" ++ fst tf ++ ">" ct = "" parseGreedy = do a <- tillTag _ <- string ct return a x <- manyTill anyChar $ try $ string ct y <- try parseGreedy <|> (string ot >> pzero) <|> return [] let r = if null y then x else x ++ ct ++ y return [Output (rtfParser emptyFormatting r) (snd tf)] Nothing -> do r <- tillTag return [OStr ("<" ++ m ++ ">" ++ r) emptyFormatting] return [Output res emptyFormatting] parseQuotes = choice [parseQ "'" "'" ,parseQ "\"" "\"" ,parseQ "``" "''" ,parseQ "`" "'" ,parseQ "“" "”" ,parseQ "‘" "’" ,parseQ "'" "'" ,parseQ """ """ ,parseQ """ """ ,parseQ "'" "'" ] parseQ a b = try $ do q <- string a >> manyTill anyChar (try $ string b >> notFollowedBy letter) return [Output (rtfParser emptyFormatting q) (emptyFormatting {quotes = ParsedQuote})] citeproc-hs-0.3.9/src/Text/CSL/Pickle.hs0000644000175000001440000002400312223317047017013 0ustar andreausers{-# LANGUAGE PatternGuards, CPP #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Pickle -- Copyright : (c) Uwe Schmidt Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : portable -- -- This module is mostly copied from Text.XML.HXT.Arrow.Pickle.Xml -- which is an adaptation of the pickler combinators developed by -- Andrew Kennedy. -- -- See: ----------------------------------------------------------------------------- module Text.CSL.Pickle where import Control.Monad ( unless ) import Data.List ( elemIndex ) import Data.Maybe import System.Directory ( doesFileExist ) import qualified Data.ByteString.Lazy as L #ifdef USE_HEXPAT import Text.CSL.Pickle.Hexpat #else import Text.CSL.Pickle.Xml import Text.XML.Light #endif data St = St { attributes :: [Attr] , contents :: [Content] } data PU a = PU { appPickle :: (a, St) -> St , appUnPickle :: St -> (Maybe a, St) } pickleXML :: PU a -> a -> String pickleXML p v = concatMap showXML $ contents st where st = appPickle p (v, emptySt) unpickleXML :: PU a -> [Content] -> Maybe a unpickleXML p t = fst . appUnPickle p $ St { attributes = [] , contents = t } emptySt :: St emptySt = St { attributes = [] , contents = [] } addAtt :: Attr -> St -> St addAtt x s = s {attributes = x : attributes s} addCont :: Content -> St -> St addCont x s = s {contents = x : contents s} dropCont :: St -> St dropCont s = s { contents = dropFirstElem (contents s)} getAtt :: String -> St -> Maybe Attr getAtt name = listToMaybe . filter ((==) name . getAttName) . attributes getCont :: St -> Maybe Content getCont = listToMaybe . contents class XmlPickler a where xpickle :: PU a instance XmlPickler Int where xpickle = xpPrim instance XmlPickler Integer where xpickle = xpPrim instance XmlPickler () where xpickle = xpUnit instance XmlPickler a => XmlPickler [a] where xpickle = xpList xpickle instance XmlPickler a => XmlPickler (Maybe a) where xpickle = xpOption xpickle xpPrim :: (Read a, Show a) => PU a xpPrim = xpWrapMaybe (readMaybe, show) xpText where readMaybe :: Read a => String -> Maybe a readMaybe str = val (reads str) where val [(x,"")] = Just x val _ = Nothing xpUnit :: PU () xpUnit = xpLift () xpZero :: PU a xpZero = PU { appPickle = snd , appUnPickle = \ s -> (Nothing, s) } xpLift :: a -> PU a xpLift x = PU { appPickle = snd , appUnPickle = \ s -> (Just x, s) } xpCondSeq :: PU b -> (b -> a) -> PU a -> (a -> PU b) -> PU b xpCondSeq pd f pa k = PU { appPickle = ( \ (b, s) -> let a = f b pb = k a in appPickle pa (a, (appPickle pb (b, s))) ) , appUnPickle = ( \ s -> let (a, s') = appUnPickle pa s in case a of Nothing -> appUnPickle pd s Just a' -> appUnPickle (k a') s' ) } xpSeq :: (b -> a) -> PU a -> (a -> PU b) -> PU b xpSeq = xpCondSeq xpZero xpChoice :: PU b -> PU a -> (a -> PU b) -> PU b xpChoice pb = xpCondSeq pb undefined xpWrap :: (a -> b, b -> a) -> PU a -> PU b xpWrap (f, g) pa = xpSeq g pa (xpLift . f) xpDefault :: (Eq a) => a -> PU a -> PU a xpDefault df = xpWrap ( fromMaybe df , \ x -> if x == df then Nothing else Just x ) . xpOption xpOption :: PU a -> PU (Maybe a) xpOption pa = PU { appPickle = ( \ (a, st) -> case a of Nothing -> st Just x -> appPickle pa (x, st) ) , appUnPickle = appUnPickle $ xpChoice (xpLift Nothing) pa (xpLift . Just) } xpAlt :: (a -> Int) -> [PU a] -> PU a xpAlt tag ps = PU { appPickle = ( \ (a, st) -> let pa = ps !! (tag a) in appPickle pa (a, st) ) , appUnPickle = appUnPickle $ ( case ps of [] -> xpZero pa:ps1 -> xpChoice (xpAlt tag ps1) pa xpLift ) } xpList :: PU a -> PU [a] xpList pa = PU { appPickle = ( \ (a, st) -> case a of [] -> st _:_ -> appPickle pc (a, st) ) , appUnPickle = appUnPickle $ xpChoice (xpLift []) pa (\ x -> xpSeq id (xpList pa) (\xs -> xpLift (x:xs))) } where pc = xpSeq head pa (\ x -> xpSeq tail (xpList pa) (\ xs -> xpLift (x:xs))) xpLiftMaybe :: Maybe a -> PU a xpLiftMaybe = maybe xpZero xpLift xpWrapMaybe :: (a -> Maybe b, b -> a) -> PU a -> PU b xpWrapMaybe (i, j) pa = xpSeq j pa (xpLiftMaybe . i) xpPair :: PU a -> PU b -> PU (a, b) xpPair pa pb = ( xpSeq fst pa (\ a -> xpSeq snd pb (\ b -> xpLift (a,b))) ) xpTriple :: PU a -> PU b -> PU c -> PU (a, b, c) xpTriple pa pb pc = xpWrap (toTriple, fromTriple) (xpPair pa (xpPair pb pc)) where toTriple ~(a, ~(b, c)) = (a, b, c ) fromTriple ~(a, b, c ) = (a, (b, c)) xp4Tuple :: PU a -> PU b -> PU c -> PU d -> PU (a, b, c, d) xp4Tuple pa pb pc pd = xpWrap (toQuad, fromQuad) (xpPair pa (xpPair pb (xpPair pc pd))) where toQuad ~(a, ~(b, ~(c, d))) = (a, b, c, d ) fromQuad ~(a, b, c, d ) = (a, (b, (c, d))) xp5Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU (a, b, c, d, e) xp5Tuple pa pb pc pd pe = xpWrap (toQuint, fromQuint) (xpPair pa (xpPair pb (xpPair pc (xpPair pd pe)))) where toQuint ~(a, ~(b, ~(c, ~(d, e)))) = (a, b, c, d, e ) fromQuint ~(a, b, c, d, e ) = (a, (b, (c, (d, e)))) xp6Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU (a, b, c, d, e, f) xp6Tuple pa pb pc pd pe pf = xpWrap (toSix, fromSix) (xpPair pa (xpPair pb (xpPair pc (xpPair pd (xpPair pe pf))))) where toSix ~(a, ~(b, ~(c, ~(d, ~(e, f))))) = (a, b, c, d, e, f ) fromSix ~(a, b, c, d, e, f ) = (a, (b, (c, (d, (e, f))))) -------------------------------------------------------------------------------- xpText :: PU String xpText = PU { appPickle = \ (s, st) -> addCont (mkText s) st , appUnPickle = \ st -> fromMaybe (Nothing, st) (unpickleString st) } where unpickleString st = do s <- getText (contents st) return (Just (unescape s), st {contents = dropText $ contents st}) xpText0 :: PU String xpText0 = xpWrap (fromMaybe "", emptyToNothing) $ xpOption $ xpText where emptyToNothing "" = Nothing emptyToNothing x = Just x xpElem :: String -> PU a -> PU a xpElem name pa = PU { appPickle = ( \ (a, st) -> let st' = appPickle pa (a, emptySt) in addCont (mkElement name (attributes st') (contents st')) st ) , appUnPickle = \ st -> fromMaybe (Nothing, st) (unpickleElement st) } where unpickleElement st = do e <- listToMaybe . onlyElems' . contents $ st n <- getElemName e if qualifiedName n /= name then fail "element name does not match" else do al <- Just $ getAttrl e res <- fst . appUnPickle pa $ St {attributes = al, contents = getChildren e} return (Just res, dropCont st) -- | A pickler for interleaved elements. xpIElem :: String -> PU a -> PU a xpIElem name pa = PU { appPickle = ( \ (a, st) -> let st' = appPickle pa (a, emptySt) in addCont (mkElement name (attributes st') (contents st')) st ) , appUnPickle = \ st -> fromMaybe (Nothing, st) (unpickleElement st) } where unpickleElement st = do let t = onlyElems' . contents $ st ns <- mapM getElemName t case elemIndex name (map qualifiedName ns) of Nothing -> fail "element name does not match" Just i -> do let cs = getChildren (t !! i) al <- Just $ getAttrl (t !! i) res <- fst . appUnPickle pa $ St {attributes = al, contents = cs} return (Just res, st {contents = take i t ++ drop (i + 1) t}) xpAttr :: String -> PU a -> PU a xpAttr name pa = PU { appPickle = ( \ (a, st) -> let st' = appPickle pa (a, emptySt) in addAtt (mkAttribute name $ getAttrVal $ contents st') st ) , appUnPickle = \ st -> fromMaybe (Nothing, st) (unpickleAttr st) } where unpickleAttr st = do a <- getAtt name st res <- fst . appUnPickle pa $ St { attributes = [] , contents = [attrToCont a]} return (Just res, st) xpElemWithAttrValue :: String -> String -> String -> PU a -> PU a xpElemWithAttrValue n a v = xpIElem n . xpAddFixedAttr a v xpAttrFixed :: String -> String -> PU () xpAttrFixed name val = ( xpWrapMaybe ( \ v -> if v == val then Just () else Nothing , const val ) $ xpAttr name xpText ) xpAddFixedAttr :: String -> String -> PU a -> PU a xpAddFixedAttr name val pa = xpWrap ( snd , (,) () ) $ xpPair (xpAttrFixed name val) pa uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d uncurry3 f (a,b,c) = f a b c uncurry4 :: (a -> b -> c -> d -> e) -> (a, b, c, d) -> e uncurry4 f (a,b,c,d) = f a b c d uncurry5 :: (a -> b -> c -> d -> e -> f) -> (a, b, c, d, e) -> f uncurry5 f (a,b,c,d,e) = f a b c d e unescape :: String -> String unescape [] = [] unescape ('&':'l':'t': ';':xs) = "<" ++ unescape xs unescape ('&':'g':'t': ';':xs) = ">" ++ unescape xs unescape ('&':'a':'m':'p':';':xs) = "&" ++ unescape xs unescape (x: xs) = x : unescape xs readXmlString :: Show a => PU a -> L.ByteString -> a readXmlString xp s = case unpickleXML xp $ parseXML' s of Just a -> a _ -> error "error while parsing the XML string" readXmlFile :: Show a => PU a -> FilePath -> IO a readXmlFile xp f = readXmlString xp `fmap` readFile' f readFile' :: FilePath -> IO L.ByteString readFile' f = do flip unless (error $ f ++ " file does not exist") =<< doesFileExist f L.readFile f citeproc-hs-0.3.9/src/Text/CSL/Eval.hs0000644000175000001440000004615512223317047016507 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- 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 , last', split, trim , module Text.CSL.Eval.Common , module Text.CSL.Eval.Output ) where import Control.Arrow import Control.Applicative ( (<$>) ) import Control.Monad.State import Data.Char ( toLower, isDigit, isLetter ) import Data.List import Data.Maybe 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 -- | 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] -> [Abbrev] -> Reference -> [Output] evalLayout (Layout _ _ es) em b l m o a r = cleanOutput evalOut where evalOut = case evalState job initSt of [] -> if (isSorting $ em) then [] else [noOutputError] x | title r == citeId cit ++ " not found!" -> [noBibDataError $ cit] | otherwise -> suppTC x locale = case l of [x] -> x _ -> Locale [] [] [] [] [] job = concatMapM evalElement es cit = case em of EvalCite c -> c EvalSorting c -> c EvalBiblio c -> c initSt = EvalState (mkRefMap r) (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 $ language r) of (_, "en") -> id ("en", []) -> id _ -> proc' rmTitleCase evalSorting :: EvalMode -> [Locale] -> [MacroMap] -> [Option] -> [Sort] -> [Abbrev] -> Reference -> [Sorting] evalSorting m l ms opts ss as r = map (format . sorting) ss where render = renderPlainStrict . formatOutputList format (s,e) = applaySort s . render $ uncurry eval e eval o e = evalLayout (Layout emptyFormatting [] [e]) m False l ms o as r 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 x = concatMapM evalElement x evalElement :: Element -> State EvalState [Output] evalElement el | Choose i ei e <- el = evalIfThen i ei e | Macro s fm <- el = return . appendOutput fm =<< evalElements =<< getMacro s | Const s fm <- el = return $ rtfParser fm s | Number s f fm <- el = 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 = when' ((/=) [] <$> tryGroup l) $ return . outputList fm d =<< evalElements l | Date _ _ _ _ _ _ <- el = evalDate el | Label s f fm _ <- el = formatLabel f fm True s -- FIXME !! | Term s f fm p <- el = formatLabel 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 = ifEmpty (consuming $ substituteWith e) (getFirst els) id | otherwise = return [] where 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' `betterThen` d) [] _ -> evalElement e tryGroup l = if hasVar l then get >>= \s -> evalElements (rmTermConst l) >>= \r -> put s >> return r else return [ONull] hasVar = not . null . query hasVarQ hasVarQ e | Variable {} <- e = [e] | Date {} <- e = [e] | Names {} <- e = [e] | Number {} <- e = [e] | otherwise = [] rmTermConst [] = [] rmTermConst (e:es) | Term {} <- e = rmTermConst es | Const {} <- e = rmTermConst es | otherwise = e : rmTermConst es 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 getFirst [] = return [] getFirst (x:xs) = whenElse ((/=) [] <$> substituteWith x) (consuming $ substituteWith x) (getFirst xs) getMacro s = maybe [] id . lookup s <$> gets (macros . env) getVariable f fm s = if isTitleVar s || isTitleShortVar s then consumeVariable s >> formatTitle s f fm else 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 [OUrl (k,k) fm] "doi" -> getStringVar "doi" >>= \d -> if "doi:" `isPrefixOf` d then let d' = drop 4 d in return [OUrl ("http://dx.doi.org/" ++ d', d') fm] else return [OStr d fm] _ -> gets (env >>> options &&& abbrevs) >>= \(opts,as) -> getVar [] (getFormattedValue opts as f fm s) s >>= \r -> consumeVariable s >> return r evalIfThen :: IfThen -> [IfThen] -> [Element] -> State EvalState [Output] evalIfThen i ei e | IfThen c m el <- i = ifElse c m el | otherwise = evalElements e where ifElse c m el = if ei == [] then whenElse (evalCond m c) (evalElements el) (evalElements e ) else whenElse (evalCond m c) (evalElements el) (evalIfThen (head ei) (tail ei) 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 = if f c /= [] then mapM a (f c) else checkMatch m checkMatch m | All <- m = return [True] | otherwise = return [False] 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 = if s == "first" || s == "subsequent" then False else True compPosition a b | "first" <- a = if b == "first" then True else False | "subsequent" <- a = if b == "first" then False else True | "ibid-with-locator" <- a = if b == "ibid-with-locator" || b == "ibid-with-locator-c" then True else False | otherwise = isIbid b getFormattedValue :: [Option] -> [Abbrev] -> Form -> Formatting -> String -> Value -> [Output] getFormattedValue o as f fm s val | Just v <- fromValue val :: Maybe String = rtfParser fm . getAbbr $ value 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 [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 getAbbr v = if f == Short then let ab = getAbbreviation as s v in if null ab then v else ab else v 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 . rtfParser 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 == '-' 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 = null . filter (not . isNumber &&& not . isSpecialChar >>> uncurry (&&)) $ words s isTransNumber, isSpecialChar,isNumber :: String -> Bool isTransNumber = and . map isDigit isSpecialChar = and . map (flip elem "&-,") isNumber = filter (not . isLetter) >>> filter (not . flip elem "&-,") >>> map isDigit >>> and &&& not . null >>> uncurry (&&) breakNumericString :: [String] -> [String] breakNumericString [] = [] breakNumericString (x:xs) | isTransNumber x = x : breakNumericString xs | otherwise = let (a,b) = break (flip elem "&-,") x (c,d) = if null b then ("","") else (head' b, tail 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:"-":[] ) = return (x,[]) tupleRange (x:"-":y:xs) = (x, y) : tupleRange xs tupleRange (x: xs) = (x,[]) : tupleRange xs joinRange (a, []) = a joinRange (a, b) = a ++ "-" ++ b process = case opt of "expanded" -> checkRange ts . printNumStr . map (joinRange . uncurry expandedRange) "chicago" -> checkRange ts . printNumStr . map (joinRange . uncurry chicagoRange ) "minimal" -> checkRange ts . printNumStr . map (joinRange . uncurry minimalRange ) _ -> checkRange ts . printNumStr . map (joinRange) return [flip OLoc fm $ [OStr (process pages) emptyFormatting]] expandedRange :: String -> String -> (String, String) expandedRange sa [] = (sa,[]) expandedRange sa sb = (p ++ reverse nA', reverse nB') where (nA,pA) = reverse >>> break isLetter >>> reverse *** reverse $ sa (nB,pB) = reverse >>> break isLetter >>> reverse *** reverse $ sb zipNum x y = zipWith (\a b -> if b == '+' then (a,a) else (a,b)) (reverse x ++ take 10 (repeat '*')) >>> unzip >>> filter (/= '*') *** filter (/= '*') $ (reverse y ++ repeat '+') checkNum a b = let a' = take (length b) a in readNum a' > readNum b (p,(nA',nB')) = case () of _ | pA /= [] , checkNum nA nB -> (,) [] $ (reverse $ pA ++ nA, reverse $ pB ++ nB) | pA /= pB , last' pA == last' pB -> (,) pA $ second (flip (++) (last' pA)) $ zipNum nA nB | pA == pB -> (,) pA $ second (flip (++) (last' pA)) $ zipNum nA nB | pB == [] -> (,) pA $ second (flip (++) (last' pA)) $ zipNum nA nB | otherwise -> (,) [] $ (reverse $ pA ++ nA, reverse $ pB ++ nB) minimalRange :: String -> String -> (String, String) minimalRange sa sb = res where (a,b) = expandedRange sa sb res = if length a == length b then second (filter (/= '+')) $ unzip $ doit a b else (a,b) doit (x:xs) (y:ys) = if x == y then (x,'+') : doit xs ys else zip (x:xs) (y:ys) doit _ _ = [] chicagoRange :: String -> String -> (String, String) chicagoRange sa sb = case () of _ | length sa < 3 -> expandedRange sa sb | '0':'0':_ <- sa' -> expandedRange sa sb | _ :'0':_ <- sa' -> minimalRange sa sb | _ :a2:as <- sa' , b1 :b2:bs <- sb' , comp as bs -> if a2 == b2 then (sa, [b2,b1]) else minimalRange sa sb | _:a2:a3:_:[] <- sa' , _:b2:b3:_ <- sb' -> if a3 /= b3 && a2 /= b2 then expandedRange sa sb else minimalRange sa sb | otherwise -> minimalRange sa sb where sa' = reverse sa sb' = reverse sb comp a b = let b' = takeWhile isDigit b in take (length b') a == b' last' :: [a] -> [a] last' = foldl (\_ x -> [x]) [] trim :: String -> String trim = unwords . words split :: (Char -> Bool) -> String -> [String] split _ [] = [] split f s = let (l, s') = break f s in trim l : case s' of [] -> [] (_:s'') -> split f s'' citeproc-hs-0.3.9/src/Text/CSL/Style.hs0000644000175000001440000005052112223317050016702 0ustar andreausers{-# LANGUAGE PatternGuards, DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- 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 where import Control.Arrow import Data.List ( nubBy, isPrefixOf, isInfixOf ) import Data.Generics ( Typeable, Data, everywhere , everywhere', everything, mkT, mkQ ) import Data.Maybe ( listToMaybe ) import qualified Data.Map as M import Text.JSON import Text.Pandoc.Definition ( Inline, Target ) #ifdef UNICODE_COLLATION import qualified Data.Text as T import qualified Data.Text.ICU as T #endif -- | The representation of a parsed CSL style. data Style = Style { styleVersion :: String , styleClass :: String , styleInfo :: Maybe CSInfo , styleDefaultLocale :: String , styleLocale :: [Locale] , styleAbbrevs :: [Abbrev] , csOptions :: [Option] , csMacros :: [MacroMap] , citation :: Citation , biblio :: Maybe Bibliography } deriving ( Show, Read, Typeable, Data ) data Locale = Locale { localeVersion :: String , localeLang :: String , localeOptions :: [Option] , localeTerms :: [CslTerm] , localeDate :: [Element] } deriving ( Show, Read, Eq, Typeable, Data ) -- | 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 ) newTerm :: CslTerm newTerm = CT [] Long Neuter Neuter [] [] [] findTerm :: String -> Form -> [CslTerm] -> Maybe CslTerm findTerm s f = listToMaybe . filter (cslTerm &&& termForm >>> (==) (s, f)) findTerm' :: String -> Form -> Gender -> [CslTerm] -> Maybe CslTerm findTerm' s f g = listToMaybe . filter (cslTerm &&& termForm &&& termGenderForm >>> (==) (s,(f,g))) hasOrdinals :: Data a => a -> Bool hasOrdinals = or . query hasOrd where hasOrd o | CT {cslTerm = t} <- o , "ordinal" `isInfixOf` t = [True] | otherwise = [False] rmOrdinals :: Data a => a -> a rmOrdinals = proc' doRemove where doRemove [] = [] doRemove (o:os) | CT {cslTerm = t} <- o , "ordinal" `isInfixOf` t = doRemove os | otherwise = o:doRemove os type Abbrev = (String, [(String, M.Map String String)]) type MacroMap = (String,[Element]) data Citation = Citation { citOptions :: [Option] , citSort :: [Sort] , citLayout :: Layout } deriving ( Show, Read, Typeable, Data ) data Bibliography = Bibliography { bibOptions :: [Option] , bibSort :: [Sort] , bibLayout :: Layout } deriving ( Show, Read, Typeable, Data ) 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 ) 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 ) data IfThen = IfThen Condition Match [Element] deriving ( Eq, Show, Read, Typeable, Data ) data Condition = Condition { isType :: [String] , isSet :: [String] , isNumeric :: [String] , isUncertainDate :: [String] , isPosition :: [String] , disambiguation :: [String] , isLocator :: [String] } deriving ( Eq, Show, Read, Typeable, Data ) type Delimiter = String data Match = Any | All | None deriving ( Show, Read, Eq, Typeable, Data ) 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 ) 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 ) data Sorting = Ascending String | Descending String deriving ( Read, Show, Eq, Typeable, Data ) 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 (head x, head y) of ('-','-') -> comp y x ('-', _ ) -> LT (_ ,'-') -> GT _ -> comp x y where #ifdef UNICODE_COLLATION comp a b = T.collate (T.collator T.Current) (T.pack a) (T.pack b) #else comp a b = compare a b #endif data Form = Long | Short | Count | Verb | VerbShort | Symbol | NotSet deriving ( Eq, Show, Read, Typeable, Data ) data Gender = Feminine | Masculine | Neuter deriving ( Eq, Show, Read, Typeable, Data ) data NumericForm = Numeric | Ordinal | Roman | LongOrdinal deriving ( Eq, Show, Read, Typeable, Data ) data DateForm = TextDate | NumericDate | NoFormDate deriving ( Eq, Show, Read, Typeable, Data ) data Plural = Contextual | Always | Never deriving ( Eq, Show, Read, Typeable, Data ) data Name = Name Form Formatting NameAttrs Delimiter [NamePart] | NameLabel Form Formatting Plural | EtAl Formatting String deriving ( Eq, Show, Read, Typeable, Data ) type NameAttrs = [(String, String)] data NamePart = NamePart String Formatting deriving ( Show, Read, Eq, Typeable, Data ) 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 = not . null . query getEtAl where getEtAl n | EtAl _ _ <- n = [n] | otherwise = [] 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 } deriving ( Read, Eq, Ord, Typeable, Data ) instance Show Formatting where show _ = "emptyFormatting" rmTitleCase :: Formatting -> Formatting rmTitleCase f | Formatting _ _ _ _ _ _ _ _ "title" _ _ _ _ _ <- f = f {textCase = []} | otherwise = f data Quote = NativeQuote | ParsedQuote | NoQuote deriving ( Read, Eq, Ord, Typeable, Data ) emptyFormatting :: Formatting emptyFormatting = Formatting [] [] [] [] [] [] [] [] [] [] NoQuote False False False unsetAffixes :: Formatting -> Formatting unsetAffixes f = f {prefix = [], suffix = []} mergeFM :: Formatting -> Formatting -> Formatting mergeFM (Formatting aa ab ac ad ae af ag ah ai aj ak al am an) (Formatting ba bb bc bd be bf bg bh bi bj bk bl bm bn) = Formatting (ba `betterThen` aa) (bb `betterThen` ab) (bc `betterThen` ac) (bd `betterThen` ad) (be `betterThen` ae) (bf `betterThen` af) (bg `betterThen` ag) (bh `betterThen` ah) (bi `betterThen` ai) (bj `betterThen` aj) (if bk == NoQuote then ak else bk) (bl || al) (bm || am) (bn || an) data CSInfo = CSInfo { csiTitle :: String , csiAuthor :: CSAuthor , csiCategories :: [CSCategory] , csiId :: String , csiUpdated :: String } deriving ( Show, Read, Typeable, Data ) data CSAuthor = CSAuthor String String String deriving ( Show, Read, Eq, Typeable, Data ) data CSCategory = CSCategory String String String deriving ( Show, Read, Eq, Typeable, Data ) -- | The formatted output, produced after post-processing the -- evaluated citations. data FormattedOutput = FO Formatting [FormattedOutput] -- ^ List of 'FormatOutput' items | FN String Formatting -- ^ Formatted number | FS String Formatting -- ^ Formatted string | FDel String -- ^ Delimeter string | FUrl Target Formatting -- ^ Formatted URL | FPan [Inline] -- ^ Pandoc inline elements | FNull -- ^ Null formatting item deriving ( Eq, Show ) -- | 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' | OLabel String Formatting -- ^ A label used for roles | ONum Int Formatting -- ^ A number (used to count contributors) | OCitNum Int Formatting -- ^ The citation number | 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 String [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. | OUrl Target Formatting -- ^ An URL | OLoc [Output] Formatting -- ^ The citation's locator | Output [Output] Formatting -- ^ Some nested 'Output' deriving ( Eq, Ord, Show, Typeable, Data ) data Affix = PlainText String | PandocText [Inline] deriving ( Show, Read, Eq, Ord, Typeable, Data ) -- | Needed for the test-suite. instance JSON Affix where showJSON (PlainText s) = JSString . toJSString $ s showJSON (PandocText i) = JSString . toJSString $ show i readJSON jv | JSString js <- jv , [(x,"")] <- reads (fromJSString js) = Ok x | otherwise = Ok $ PlainText [] type Citations = [[Cite]] data Cite = Cite { citeId :: String , citePrefix :: Affix , citeSuffix :: Affix , citeLabel :: String , citeLocator :: String , citeNoteNumber :: String , citePosition :: String , nearNote :: Bool , authorInText :: Bool , suppressAuthor :: Bool , citeHash :: Int } deriving ( Show, Eq, Typeable, Data ) emptyAffix :: Affix emptyAffix = PlainText [] emptyCite :: Cite emptyCite = Cite [] emptyAffix emptyAffix [] [] [] [] 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 ) data BiblioData = BD { citations :: [[FormattedOutput]] , bibliography :: [[FormattedOutput]] } deriving ( Show ) -- | A record with all the data to produce the 'FormattedOutput' 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 ) instance Eq CiteData where (==) (CD ka ca _ _ _ _ _) (CD kb cb _ _ _ _ _) = ka == kb && ca == cb data NameData = ND { nameKey :: String , nameCollision :: [Output] , nameDisambData :: [[Output]] , nameDataSolved :: [Output] } deriving ( Show, Typeable, Data ) instance Eq NameData where (==) (ND ka ca _ _) (ND kb cb _ _) = ka == kb && ca == cb formatOutputList :: [Output] -> [FormattedOutput] formatOutputList = filterUseless . map formatOutput where filterUseless [] = [] filterUseless (o:os) | FO _ [] <- o = filterUseless os | FO f xs <- o , isEmpty f = filterUseless xs ++ filterUseless os | FO f xs <- o = case filterUseless xs of [] -> filterUseless os xs' -> FO f xs' : filterUseless os | FNull <- o = filterUseless os | otherwise = o : filterUseless os where isEmpty f = f == emptyFormatting -- | Convert evaluated 'Output' into 'FormattedOutput', ready for the -- output filters. formatOutput :: Output -> FormattedOutput formatOutput o | OSpace <- o = FDel " " | OPan i <- o = FPan i | ODel [] <- o = FNull | ODel s <- o = FDel s | OStr [] _ <- o = FNull | OStr s f <- o = FS s f | OLabel [] _ <- o = FNull | OLabel s f <- o = FS s f | ODate os <- o = FO emptyFormatting (format os) | OYear s _ f <- o = FS s f | OYearSuf s _ _ f <- o = FS s f | ONum i f <- o = FS (show i) f | OCitNum i f <- o = FN (add00 i) f | OUrl s f <- o = FUrl s f | OName _ s _ f <- o = FO f (format s) | OContrib _ _ s _ _ <- o = FO emptyFormatting (format s) | OLoc os f <- o = FO f (format os) | Output os f <- o = FO f (format os) | otherwise = FNull where format = map formatOutput add00 = reverse . take 5 . flip (++) (repeat '0') . reverse . show -- | Map the evaluated output of a citation group. mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a] mapGroupOutput f (CG _ _ _ os) = concatMap f $ map snd os -- | 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 query function. query :: (Typeable a, Data b) => (a -> [c]) -> b -> [c] query f = everything (++) ([] `mkQ` f) -- | Removes all given names form a 'OName' element with 'proc'. rmGivenNames :: Output -> Output rmGivenNames o | OName i s _ f <- o = OName i s [] f | otherwise = o rmNameHash :: Output -> Output rmNameHash o | OName _ s ss f <- o = OName [] s ss f | otherwise = 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 -- | 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 o | OYearSuf _ _ _ _ <- o = ["a"] | otherwise = [] betterThen :: Eq a => [a] -> [a] -> [a] betterThen a b = if a == [] then b else a citeproc-hs-0.3.9/src/Text/CSL/Reference.hs0000644000175000001440000003144512223317050017504 0ustar andreausers{-# LANGUAGE GeneralizedNewtypeDeriving, PatternGuards, DeriveDataTypeable, ExistentialQuantification #-} ----------------------------------------------------------------------------- -- | -- 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 where import Data.Char ( isUpper, toLower ) import Data.List ( elemIndex, isPrefixOf ) import Data.Maybe ( fromMaybe ) import Data.Generics import Text.CSL.Style import Text.CSL.Output.Plain ((<+>)) -- | 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 :: Data a => a -> ReferenceMap mkRefMap a = zip fields (gmapQ Value a) where fields = map formatField . constrFields . toConstr $ a formatField :: String -> String formatField = foldr f [] . g where f x xs = if isUpper x then '-' : toLower x : xs else x : xs g (x:xs) = toLower x : xs g [] = [] fromValue :: Data a => Value -> Maybe a fromValue (Value a) = cast a isValueSet :: Value -> Bool isValueSet val | Just v <- fromValue val :: Maybe String = v /= [] | 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 _ <- fromValue val :: Maybe Empty = True | otherwise = False data Empty = Empty deriving ( Typeable, Data ) data Agent = Agent { givenName :: [String] , droppingPart :: String , nonDroppingPart :: String , familyName :: String , nameSuffix :: String , literal :: String , commaSuffix :: Bool } deriving ( Read, Eq, Typeable, Data ) instance Show Agent where show (Agent g d n f s [] _) = (foldr (<+>) [] g) <+> d <+> n <+> f <+> s show (Agent _ _ _ _ _ l _) = l data RefDate = RefDate { year :: String , month :: String , season :: String , day :: String , other :: String , circa :: String } deriving ( Show, Read, Eq, Typeable, Data ) 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 ) instance Show RefType where show = map toLower . formatField . showConstr . toConstr newtype CNum = CNum { unCNum :: Int } deriving ( Show, Read, Eq, Num, Typeable, Data ) -- | The 'Reference' record. data Reference = Reference { refId :: String , 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 :: String , titleShort :: String , reviewedTitle :: String , containerTitle :: String , volumeTitle :: String , collectionTitle :: String , containerTitleShort :: String , collectionNumber :: String --Int , originalTitle :: String , publisher :: String , originalPublisher :: String , publisherPlace :: String , originalPublisherPlace :: String , authority :: String , jurisdiction :: String , archive :: String , archivePlace :: String , archiveLocation :: String , event :: String , eventPlace :: String , page :: String , pageFirst :: String , numberOfPages :: String , version :: String , volume :: String , numberOfVolumes :: String --Int , issue :: String , chapterNumber :: String , medium :: String , status :: String , edition :: String , section :: String , source :: String , genre :: String , note :: String , annote :: String , abstract :: String , keyword :: String , number :: String , references :: String , url :: String , doi :: String , isbn :: String , issn :: String , pmcid :: String , pmid :: String , callNumber :: String , dimensions :: String , scale :: String , categories :: [String] , language :: String , citationNumber :: CNum , firstReferenceNoteNumber :: Int , citationLabel :: String } deriving ( Eq, Show, Read, Typeable, Data ) emptyReference :: Reference emptyReference = Reference { refId = [] , refType = NoType , author = [] , editor = [] , translator = [] , recipient = [] , interviewer = [] , composer = [] , director = [] , illustrator = [] , originalAuthor = [] , containerAuthor = [] , collectionEditor = [] , editorialDirector = [] , reviewedAuthor = [] , issued = [] , eventDate = [] , accessed = [] , container = [] , originalDate = [] , submitted = [] , title = [] , titleShort = [] , reviewedTitle = [] , containerTitle = [] , volumeTitle = [] , collectionTitle = [] , containerTitleShort = [] , collectionNumber = [] , originalTitle = [] , publisher = [] , originalPublisher = [] , publisherPlace = [] , originalPublisherPlace = [] , authority = [] , jurisdiction = [] , archive = [] , archivePlace = [] , archiveLocation = [] , event = [] , eventPlace = [] , page = [] , pageFirst = [] , numberOfPages = [] , version = [] , volume = [] , numberOfVolumes = [] , issue = [] , chapterNumber = [] , medium = [] , status = [] , edition = [] , section = [] , source = [] , genre = [] , note = [] , annote = [] , abstract = [] , keyword = [] , number = [] , references = [] , url = [] , doi = [] , isbn = [] , issn = [] , pmcid = [] , pmid = [] , callNumber = [] , dimensions = [] , scale = [] , categories = [] , language = [] , citationNumber = CNum 0 , firstReferenceNoteNumber = 0 , citationLabel = [] } numericVars :: [String] numericVars = [ "edition", "volume", "number-of-volumes", "number", "issue", "citation-number" , "chapter-number", "collection-number", "number-of-pages"] parseLocator :: String -> (String, String) parseLocator s | "b" `isPrefixOf` formatField s = mk "book" | "ch" `isPrefixOf` formatField s = mk "chapter" | "co" `isPrefixOf` formatField s = mk "column" | "fi" `isPrefixOf` formatField s = mk "figure" | "fo" `isPrefixOf` formatField s = mk "folio" | "i" `isPrefixOf` formatField s = mk "issue" | "l" `isPrefixOf` formatField s = mk "line" | "n" `isPrefixOf` formatField s = mk "note" | "o" `isPrefixOf` formatField s = mk "opus" | "para" `isPrefixOf` formatField s = mk "paragraph" | "part" `isPrefixOf` formatField s = mk "part" | "p" `isPrefixOf` formatField s = mk "page" | "sec" `isPrefixOf` formatField s = mk "section" | "sub" `isPrefixOf` formatField s = mk "sub verbo" | "ve" `isPrefixOf` formatField s = mk "verse" | "v" `isPrefixOf` formatField s = mk "volume" | otherwise = ([], []) where mk c = if null s then ([], []) else (,) c . unwords . tail . words $ s getReference :: [Reference] -> Cite -> Reference getReference r c = case citeId c `elemIndex` map refId r of Just i -> setPageFirst $ r !! i Nothing -> emptyReference { title = citeId c ++ " not found!" } processCites :: [Reference] -> [[Cite]] -> [[(Cite, Reference)]] processCites rs cs = procGr [[]] cs where procRef r = case filter ((==) (refId r) . citeId) $ concat cs of x:_ -> r { firstReferenceNoteNumber = readNum $ citeNoteNumber x} [] -> r getRef c = case filter ((==) (citeId c) . refId) rs of x:_ -> procRef $ setPageFirst x [] -> emptyReference { title = citeId c ++ " not found!" } procGr _ [] = [] procGr a (x:xs) = let (a',res) = procCs a x in res : procGr (a' ++ [[]]) xs procCs a [] = (a,[]) procCs a (c:xs) | isIbidC, isLocSet = go "ibid-with-locator-c" | isIbid, isLocSet = go "ibid-with-locator" | isIbidC = go "ibid-c" | isIbid = go "ibid" | isElem = go "subsequent" | otherwise = go "first" where go s = let addCite = if last a /= [] then init a ++ [last a ++ [c]] else init a ++ [[c]] (a', rest) = procCs addCite xs in (a', (c { citePosition = s}, getRef c) : rest) isElem = citeId c `elem` map citeId (concat a) -- Ibid in same citation isIbid = last a /= [] && citeId c == citeId (last $ last a) -- Ibid in different citations (must be capitalized) isIbidC = init a /= [] && length (last $ init a) == 1 && last a == [] && citeId c == citeId (head . last $ init a) isLocSet = citeLocator c /= "" setPageFirst :: Reference -> Reference setPageFirst r = if ('–' `elem` page r || '-' `elem` page r) then r { pageFirst = takeWhile (not . flip elem "–-") $ page r} else r 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 readNum :: String -> Int readNum s = case reads s of [(x,"")] -> x _ -> 0 citeproc-hs-0.3.9/src/Text/CSL/Input/0000755000175000001440000000000012223317047016350 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Input/Bibutils.hs0000644000175000001440000001173012223317047020463 0ustar andreausers{-# 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 (..) ) where import Data.ByteString.Lazy.UTF8 ( fromString ) import Data.Char import System.FilePath ( takeExtension ) import Text.CSL.Pickle import Text.CSL.Reference import Text.CSL.Input.Json import Text.CSL.Input.MODS import Text.JSON.Generic #ifdef USE_BIBUTILS 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] #ifdef USE_BIBUTILS readBiblioFile f = case getExt f of ".mods" -> readBiblioFile' f mods_in ".bib" -> readBiblioFile' f biblatex_in ".bibtex" -> readBiblioFile' f bibtex_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 ".json" -> readJsonInput f ".native" -> readFile f >>= return . decodeJSON _ -> error $ "citeproc: the format of the bibliographic database could not be recognized\n" ++ "using the file extension." #else readBiblioFile f | ".mods" <- getExt f = readModsCollectionFile f | ".json" <- getExt f = readJsonInput f | ".native" <- getExt f = readFile f >>= return . decodeJSON | otherwise = error $ "citeproc: Bibliography format not supported.\n" ++ "citeproc-hs was not compiled with bibutils support." #endif data BibFormat = Mods | Json | Native #ifdef USE_BIBUTILS | Bibtex | BibLatex | Ris | Endnote | EndnotXml | Isi | Medline | Copac #endif readBiblioString :: BibFormat -> String -> IO [Reference] readBiblioString b s | Mods <- b = return $ readXmlString xpModsCollection (fromString s) | Json <- b = return $ readJsonInputString s | Native <- b = return $ decodeJSON s #ifdef USE_BIBUTILS | Bibtex <- b = go bibtex_in | BibLatex <- b = go biblatex_in | 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 #endif | otherwise = error "in readBiblioString" #ifdef USE_BIBUTILS where go f = withTempDir "citeproc" $ \tdir -> do let tfile = tdir "bibutils-tmp.biblio" writeFile tfile s readBiblioFile' tfile f #endif #ifdef USE_BIBUTILS readBiblioFile' :: FilePath -> BiblioIn -> IO [Reference] readBiblioFile' fin bin | bin == mods_in = readModsCollectionFile fin | otherwise = withTempDir "citeproc" $ \tdir -> do let tfile = tdir "bibutils-tmp" param <- bibl_initparams bin mods_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 <- readModsCollectionFile tfile return $! refs -- | 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 citeproc-hs-0.3.9/src/Text/CSL/Input/MODS.hs0000644000175000001440000004733412223317047017461 0ustar andreausers{-# LANGUAGE PatternGuards, CPP #-} {-# OPTIONS_GHC -fno-warn-orphans #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Input.MODS -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- An ugly MODS parser -- ----------------------------------------------------------------------------- module Text.CSL.Input.MODS where import Text.CSL.Eval ( split ) import Text.CSL.Output.Plain ( (<+>), tail' ) import Text.CSL.Pickle import Text.CSL.Reference import Text.CSL.Style ( betterThen ) import Data.Char ( isDigit, isLower ) import qualified Data.Map as M -- | Read a file with a single MODS record. readModsFile :: FilePath -> IO Reference readModsFile = readXmlFile xpMods -- | Read a file with a collection of MODS records. readModsCollectionFile :: FilePath -> IO [Reference] readModsCollectionFile = readXmlFile xpModsCollection xpModsCollection :: PU [Reference] xpModsCollection = xpIElem "modsCollection" $ xpList xpMods xpMods :: PU Reference xpMods = xpIElem "mods" xpReference xpReference :: PU Reference xpReference = xpWrap ( \ ((ref,oref) , (ck,(ty,gn),ti,i,d) ,((au,ed,tr,sp),(re,it,pu',dr),(co,ce,dg,om)) ,((di',pg,vl,is),(nu,sc,ch,vs)) , (di,ac,pu,pp,et) , ((ac',uri),ln,st,no) ) -> ref { refId = ck `betterThen` take 10 (concat . words $ fst ti) , refType = if ty /= NoType then ty else if refType ref == Book then Chapter else refType ref , title = fst ti , titleShort = snd ti , author = au , editor = ed `betterThen` editor ref , edition = et `betterThen` edition ref , translator = tr `betterThen` translator ref , recipient = re `betterThen` recipient ref , interviewer = it `betterThen` interviewer ref , composer = co `betterThen` composer ref , director = dr `betterThen` director ref , collectionEditor = ce `betterThen` collectionEditor ref , publisherPlace = pp `betterThen` publisherPlace ref , numberOfVolumes = vs `betterThen` numberOfVolumes ref , containerAuthor = containerAuthor ref , url = uri , note = no , isbn = i , doi = d , genre = genre ref `betterThen` gn , issued = issued ref `betterThen` di `betterThen` di' , accessed = accessed ref `betterThen` ac `betterThen` ac' , page = page ref `betterThen` pg , volume = volume ref `betterThen` vl , issue = issue ref `betterThen` is `betterThen` number ref `betterThen` nu , number = number ref `betterThen` nu , section = section ref `betterThen` sc , chapterNumber = chapterNumber ref `betterThen` ch , language = language ref `betterThen` ln , status = status ref `betterThen` st , publisher = fromAgent pu `betterThen` publisher ref `betterThen` fromAgent pu' `betterThen` fromAgent dg `betterThen` fromAgent om `betterThen` fromAgent sp , originalDate = issued oref , originalTitle = title oref , originalPublisher = publisher oref , originalPublisherPlace = publisherPlace oref } , \r -> ( (emptyReference,emptyReference) , (refId r,(refType r,genre r), (title r, titleShort r), isbn r, doi r) ,((author r, editor r, translator r, director r) ,(recipient r, interviewer r, emptyAgents, director r) ,(composer r, collectionEditor r, emptyAgents, emptyAgents)) ,((issued r, page r, volume r, issue r) ,(number r, section r, chapterNumber r, numberOfVolumes r)) , (issued r, accessed r, emptyAgents, publisherPlace r, edition r) ,((accessed r, url r), status r, language r, note r) )) $ xp6Tuple (xpPair (xpDefault emptyReference $ xpRelatedItem "host") (xpDefault emptyReference $ xpRelatedItem "original")) (xp5Tuple xpCiteKey xpRefType xpTitle xpIsbn xpDoi) xpAgents xpPart xpOrigin (xp4Tuple xpUrl xpLang xpStatus xpNote) xpCiteKey :: PU String xpCiteKey = xpDefault [] $ xpChoice (xpAttr "ID" xpText) (xpElemWithAttrValue "identifier" "type" "citekey" xpText) xpLift xpOrigin :: PU ([RefDate],[RefDate],[Agent],String,String) xpOrigin = xpDefault ([],[],[],[],[]) . xpIElem "originInfo" $ xp5Tuple (xpDefault [] $ xpWrap (readDate,show) $ xpIElem "dateIssued" xpText0) (xpDefault [] $ xpWrap (readDate,show) $ xpIElem "dateCaptured" xpText0) (xpDefault [] $ xpList $ xpWrap (\s -> Agent [] [] [] s [] [] False, show) $ xpIElem "publisher" xpText0) (xpDefault [] $ xpIElem "place" $ xpIElem "placeTerm" xpText0) (xpDefault [] $ xpIElem "edition" $ xpText0) xpRefType :: PU (RefType, String) xpRefType = xpDefault (NoType,[]) $ xpWrap (readRefType, const []) xpGenre xpGenre :: PU [String] xpGenre = xpList $ xpIElem "genre" $ xpChoice xpZero (xpPair (xpDefault [] $ xpAttr "authority" xpText) xpText) $ xpLift . snd xpRelatedItem :: String -> PU Reference xpRelatedItem t = xpIElem "relatedItem" . xpAddFixedAttr "type" t $ xpWrap ( \(((t3l,t3s),(t4l,_)) ,((ty,gn),ct) ,((ca,ed,tr,sp),(re,it,pu',dr),(co,ce,dg,om)) ,((di,pg,vl,is),(nu,sc,ch,vs)) , (di',ac,pu,pp,et) , (ln, st) ) -> emptyReference { refType = ty , title = fst ct , containerAuthor = ca , containerTitle = if t3l /= [] then t3l else fst ct , containerTitleShort = if t3s /= [] then t3s else snd ct , collectionTitle = t4l , volumeTitle = if t3l /= [] then fst ct else [] , editor = ed , edition = et , translator = tr , recipient = re , interviewer = it , publisherPlace = pp , composer = co , director = dr , collectionEditor = ce , issued = di `betterThen` di' , accessed = ac , page = pg , volume = vl , issue = is `betterThen` nu , number = nu , section = sc , chapterNumber = ch , genre = gn , numberOfVolumes = vs , language = ln , status = st , publisher = fromAgent $ pu `betterThen` pu' `betterThen` dg `betterThen` om `betterThen` sp } , \r -> (((volumeTitle r,[]),(collectionTitle r,[])) ,((refType r,genre r), (containerTitle r, containerTitleShort r)) ,((containerAuthor r, editor r, translator r, director r) ,(recipient r, interviewer r, emptyAgents, director r) ,(composer r, collectionEditor r, emptyAgents, emptyAgents)) ,((issued r, page r, volume r, issue r) ,(number r, section r, chapterNumber r, numberOfVolumes r)) , (issued r, accessed r,emptyAgents, publisherPlace r, edition r) , (language r, status r) )) $ xp6Tuple xpNestedTitles (xpPair xpRefType xpTitle) xpAgents xpPart xpOrigin (xpPair xpLang xpStatus) xpNestedTitles :: PU ((String, String), (String, String)) xpNestedTitles = xpDefault (([],[]),([],[])) . getRelated $ xpPair xpTitle (getRelated xpTitle) where getRelated = xpIElem "relatedItem" . xpAddFixedAttr "type" "host" xpTitle :: PU (String,String) xpTitle = xpWrap (\((a,b),c) -> createTitle a b c , \s -> (s,[])) $ xpPair (xpIElem "titleInfo" $ xpPair (xpIElem "title" xpText0) (xpDefault [] $ xpIElem "subTitle" xpText0)) (xpDefault [] $ xpIElem "titleInfo" $ xpAddFixedAttr "type" "abbreviated" $ xpElem "title" xpText0) where createTitle [] [] [] = ([],[]) createTitle s [] [] = breakLong s createTitle s [] ab = (s ,ab) createTitle s sub [] = (s ++ colon s ++ sub, s) createTitle s sub ab = (s ++ colon s ++ sub, ab) colon s = if last s == '!' || last s == '?' then " " else ": " breakLong s = let (a,b) = break (== ':') s in if b /= [] then (s,a) else (s, []) xpAgents :: PU (([Agent],[Agent],[Agent],[Agent]) ,([Agent],[Agent],[Agent],[Agent]) ,([Agent],[Agent],[Agent],[Agent])) xpAgents = xpTriple (xp4Tuple (xpAgent "author" "aut") (xpAgent "editor" "edt") (xpAgent "translator" "trl") (xpAgent "sponsor" "spn")) (xp4Tuple (xpAgent "recipient" "rcp") (xpAgent "interviewer" "ivr") (xpAgent "publisher" "pbl") (xpAgent "director" "drt")) (xp4Tuple (xpAgent "composer" "cmp") (xpAgent "collector" "xol") (xpAgent "degree grantor" "dgg") (xpAgent "organizer of meeting" "orm")) xpAgent :: String -> String -> PU [Agent] xpAgent sa sb = xpDefault [] $ xpList $ xpIElem "name" $ xpChoice xpZero (xpIElem "role" $ xpIElem "roleTerm" xpText0) (\x -> if x == sa || x == sb then xpickle else xpZero) instance XmlPickler Agent where xpickle = xpAlt tag ps where tag _ = 0 ps = [ personal, others ] personal = xpWrap ( uncurry parseName , \(Agent gn _ _ fn _ _ _) -> (gn,fn)) $ xpAddFixedAttr "type" "personal" xpNameData others = xpWrap (\s -> Agent [] [] [] [] [] s False, undefined) $ xpElem "namePart" xpText0 -- | "von Hicks,! Jr., Michael" or "la Martine,! III, Martin B. de" or -- "Rossato, Jr., Andrea G. B." or "Paul, III, Juan". parseName :: [String] -> String -> Agent parseName gn fn | ("!":sf:",":xs) <- gn = parse xs (sf ++ ".") True | ("!":sf :xs) <- gn , sf /= [] , last sf == ',' = parse xs sf True | (sf:",":xs) <- gn = parse xs (sf ++ ".") False | (sf :xs) <- gn , sf /= [], last sf == ',' = parse xs sf False | otherwise = parse gn "" False where parse g s b = Agent (getGiven g) (getDrop g) (getNonDrop fn) (getFamily fn) s [] b setInit s = if length s == 1 then s ++ "." else s getDrop = unwords . reverse . takeWhile (and . map isLower) . reverse getGiven = map setInit . reverse . dropWhile (and . map isLower) . reverse getNonDrop = unwords . takeWhile (and . map isLower) . words getFamily = unwords . dropWhile (and . map isLower) . words xpNameData :: PU ([String],String) xpNameData = xpWrap (readName,const []) $ xpList $ xpElem "namePart" $ xpPair (xpAttr "type" xpText) xpText0 where readName x = (readg x, readf x) readf = foldr (\(k,v) xs -> if k == "family" then v else xs) [] readg = foldr (\(k,v) xs -> if k == "given" then v:xs else xs) [] xpPart :: PU (([RefDate],String,String,String) ,(String,String,String,String)) xpPart = xpDefault none . xpIElem "part" . xpWrap (readIt none,const []) $ xpList xpDetail where none = (([],"","",""),("","","","")) readIt r [] = r readIt acc@((d,p,v,i),(n,s,c,vs)) (x:xs) | Date y <- x = readIt ((y,p,v,i),(n,s,c,vs)) xs | Page y <- x = readIt ((d,y,v,i),(n,s,c,vs)) xs | Volume y <- x = readIt ((d,p,y,i),(n,s,c,vs)) xs | Issue y <- x = readIt ((d,p,v,y),(n,s,c,vs)) xs | Number y <- x = readIt ((d,p,v,i),(y,s,c,vs)) xs | ChapterNr y <- x = readIt ((d,p,v,i),(n,s,y,vs)) xs | Section y <- x = readIt ((d,p,v,i),(n,y,c,vs)) xs | NrVols y <- x = readIt ((d,p,v,i),(n,s,c, y)) xs | otherwise = acc data Detail = Date [RefDate] | Page String | Volume String | Issue String | Number String | ChapterNr String | Section String | NrVols String deriving ( Eq, Show ) xpDetail :: PU Detail xpDetail = xpAlt tag ps where tag _ = 0 ps = [ xpWrap (Date, const []) $ xpDate , xpWrap (Page, show) $ xpPage , xpWrap (NrVols, show) $ xpVolumes , xpWrap (Volume, show) $ xp "volume" , xpWrap (Issue, show) $ xp "issue" , xpWrap (Number, show) $ xp "number" , xpWrap (Number, show) $ xp "report number" , xpWrap (Section, show) $ xp "section" , xpWrap (ChapterNr,show) $ xp "chapter" ] xpDate = xpWrap (readDate,show) (xpElem "date" xpText0) xp s = xpElemWithAttrValue "detail" "type" s $ xpElem "number" xpText xpPage :: PU String xpPage = xpChoice (xpElemWithAttrValue "detail" "type" "page" $ xpIElem "number" xpText) (xpElemWithAttrValue "extent" "unit" "page" $ xpPair (xpElem "start" xpText) (xpElem "end" xpText)) (\(s,e) -> xpLift (s ++ "-" ++ e)) xpVolumes :: PU String xpVolumes = xpElemWithAttrValue "extent" "unit" "volumes" $ xpElem "total" xpText xpUrl :: PU ([RefDate],String) xpUrl = xpDefault ([],[]) . xpIElem "location" $ xpPair (xpWrap (readDate,show) $ xpDefault [] $ xpAttr "dateLastAccessed" xpText) (xpDefault [] $ xpElem "url" xpText) xpIsbn :: PU String xpIsbn = xpDefault [] $ xpIdentifier "isbn" xpDoi :: PU String xpDoi = xpDefault [] $ xpIdentifier "doi" xpIdentifier :: String -> PU String xpIdentifier i = xpIElem "identifier" $ xpAddFixedAttr "type" i xpText xpNote :: PU (String) xpNote = xpDefault [] $ xpIElem "note" xpText xpLang :: PU String xpLang = xpDefault [] $ xpChoice (xpIElem "recordInfo" $ xpIElem "languageOfCataloging" $ xpIElem "language" $ xpIElem "languageTerm" xpText) (xpIElem "recordInfo" $ xpIElem "languageOfCataloging" $ xpIElem "languageTerm" xpText) xpLift xpStatus :: PU String xpStatus = xpDefault [] $ --xpElemWithAttrValue "note" "type" "publication status" xpText xpIElem "note" $ xpAddFixedAttr "type" "publication status" xpText readDate :: String -> [RefDate] readDate s = (parseDate $ takeWhile (/= '/') s) ++ (parseDate . tail' $ dropWhile (/= '/') s) -- | Possible formats: "YYYY", "YYYY-MM", "YYYY-MM-DD". parseDate :: String -> [RefDate] parseDate s = case split (== '-') (unwords $ words s) of [y,m,d] -> [RefDate y m [] d [] []] [y,m] -> [RefDate y m [] [] [] []] [y] -> if and (map isDigit y) then [RefDate y [] [] [] [] []] else [RefDate [] [] [] [] y []] _ -> [] emptyAgents :: [Agent] emptyAgents = [] fromAgent :: [Agent] -> String fromAgent = foldr (<+>) [] . map show readRefType :: [String] -> (RefType, String) readRefType [] = (NoType,[]) readRefType (t:ts) = case M.lookup t genreTypeMapping of Just x -> (x, if ts /= [] then head ts else []) Nothing -> if ts /= [] then case M.lookup (head ts) genreTypeMapping of Just x -> (x, t) Nothing -> (ArticleJournal, t) else (ArticleJournal, []) -- The string constants come from http://www.loc.gov/standards/valuelist/marcgt.html, which are used in the -- "" element (http://www.loc.gov/standards/mods/userguide/genre.html) genreTypeMapping :: M.Map String RefType genreTypeMapping = M.fromList [ ( "book", Book ) , ( "book chapter", Chapter ) , ( "periodical", ArticleJournal ) , ( "newspaper", ArticleNewspaper ) , ( "magazine", ArticleNewspaper ) , ( "magazine article", ArticleNewspaper ) , ( "encyclopedia", EntryEncyclopedia) , ( "conference publication", Book ) , ( "academic journal", ArticleJournal ) , ( "collection", Chapter ) , ( "legal case and case notes", LegalCase ) , ( "legislation", Legislation ) , ( "instruction", Book ) , ( "motion picture", MotionPicture ) , ( "film", MotionPicture ) , ( "tvBroadcast", MotionPicture ) , ( "videoRecording", MotionPicture ) , ( "videorecording", MotionPicture ) , ( "patent", Patent ) , ( "Ph.D. thesis", Thesis ) , ( "Masters thesis", Thesis ) , ( "report", Report ) , ( "technical report", Report ) , ( "review", Review ) , ( "thesis", Thesis ) , ( "unpublished", NoType ) , ( "web page", Webpage ) , ( "webpage", Webpage ) , ( "web site", Webpage ) ] citeproc-hs-0.3.9/src/Text/CSL/Input/Json.hs0000644000175000001440000002261212223317047017620 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Input.Json -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- A module for reading Json CSL data. -- ----------------------------------------------------------------------------- module Text.CSL.Input.Json where import Control.Arrow import Control.Monad.State import Data.Generics import Data.Char (toLower, toUpper) import Data.List import qualified Data.Map as M import Data.Ratio import Text.JSON.Generic import Text.JSON.String ( runGetJSON, readJSTopType ) import Text.CSL.Reference import Text.CSL.Style readJsonInput :: FilePath -> IO [Reference] readJsonInput f = readJsonInputString `fmap` readFile f readJsonInputString :: String -> [Reference] readJsonInputString s = let jrefs = procJSObject editJsonInput $ readJsonString s refs r = case readJSData r of Ok ref -> ref Error er -> error ("readJSData: " ++ er) in case jrefs of JSObject o -> map (refs . snd) $ fromJSObject o JSArray ar -> map (refs ) $ ar _ -> error $ "citeproc: error in reading the Json bibliographic data." readJsonFile :: FilePath -> IO JSValue readJsonFile f = readJsonString `fmap` readFile f readJsonString :: String -> JSValue readJsonString = let rmCom = unlines . filter (\x -> not (" *" `isPrefixOf` x || "/*" `isPrefixOf` x)) . lines in either error id . runGetJSON readJSTopType . rmCom readJsonAbbrevFile :: FilePath -> IO [Abbrev] readJsonAbbrevFile f = readJsonAbbrev `fmap` readJsonFile f readJsonAbbrev :: JSValue -> [Abbrev] readJsonAbbrev = mapSndObj (mapSndObj (M.fromList . mapSndObj fromJString)) where mapSndObj f = map (second f) . fromObj readJsonCitations :: JSValue -> [Cite] readJsonCitations jv | JSArray (JSObject o:_) <- jv , Just (JSArray ar) <- lookup "citationItems" (fromJSObject o ) , Just (JSObject o') <- lookup "properties" (fromJSObject o ) , idx <- lookup "noteIndex" (fromJSObject o') = map (readCite $ readCitNum $ fmap toString idx) ar | otherwise = error ("error in reading CITATIONS:\n" ++ show jv) where readCitNum j | Just (JSString js) <- j = fromJSString js | otherwise = [] readCite :: String -> JSValue -> Cite readCite n c = case readJSData c of Ok cite -> cite { citeNoteNumber = n } Error er -> error ("citations: " ++ er) editJsonCiteItems :: (String, JSValue) -> (String, JSValue) editJsonCiteItems (s,j) | "id" <- s = ("citeId" , toString j) | "label" <- s = ("citeLabel" , toString j) | "locator" <- s = ("citeLocator" , toString j) | "note-number" <- s = ("citeNoteNumber", toString j) | "near-note" <- s = ("nearNote" , toJSBool j) | "prefix" <- s = ("citePrefix" , affixes j) | "suffix" <- s = ("citeSuffix" , affixes j) | "suppress-author" <- s = ("suppressAuthor", toJSBool j) | "author-only" <- s = ("authorInText" , toJSBool j) | "author-in-text" <- s = ("authorInText" , toJSBool j) | otherwise = (s,j) where affixes v | JSString js <- v = JSString . toJSString . show . PlainText . fromJSString $ js | otherwise = affixes $ toString v editJsonInput :: (String, JSValue) -> (String, JSValue) editJsonInput (s,j) | "dropping-particle" <- s = ("droppingPart" , j) | "non-dropping-particle" <- s = ("nonDroppingPart", j) | "comma-suffix" <- s = ("commaSuffix", toJSBool j) | "id" <- s = ("refId" , toString j) | "shortTitle" <- s = ("titleShort" , j) | isRefDate s , JSObject js <- j = (camel s , JSArray (editDate $ fromJSObject js)) | "family" <- s = ("familyName" , j) | "suffix" <- s = ("nameSuffix" , j) | "URL" <- s = ("url" , j) | "edition" <- s = ("edition" , toString j) | "volume" <- s = ("volume" , toString j) | "issue" <- s = ("issue" , toString j) | "number" <- s = ("number" , toString j) | "page" <- s = ("page" , toString j) | "section" <- s = ("section" , toString j) | "given" <- s , JSString js <- j = ("givenName" , JSArray . map (JSString . toJSString) . words $ fromJSString js) | "type" <- s , JSString js <- j = ("refType" , JSString . toJSString . format . camel $ fromJSString js) | (c:cs) <- s = (toLower c : camel cs , j) | otherwise = (s,j) where camel x | '-':y:ys <- x = toUpper y : camel ys | '_':y:ys <- x = toUpper y : camel ys | y:ys <- x = y : camel ys | otherwise = [] format (x:xs) = toUpper x : xs format [] = [] zipDate x = zip (take (length x) ["year", "month", "day"]) . map toString $ x editDate x = let seas = case lookup "season" x of Just o -> [("season",toString o)] _ -> [] raw = case lookup "raw" x of Just o -> [("other",o)] _ -> [] lit = case lookup "literal" x of Just o -> [("other",o)] _ -> [] cir = case lookup "circa" x of Just o -> [("circa",toString o)] _ -> [] rest = flip (++) (seas ++ lit ++ raw ++ cir) in case lookup "dateParts" x of Just (JSArray (JSArray x':[])) -> [JSObject . toJSObject . rest $ zipDate x'] Just (JSArray (JSArray x': JSArray y':[])) -> [JSObject . toJSObject $ zipDate x' ,JSObject . toJSObject $ zipDate y'] _ -> [JSObject . toJSObject $ rest []] toString :: JSValue -> JSValue toString x | JSString js <- x = JSString js | JSRational _ n <- x = JSString . toJSString . show $ numerator n | otherwise = JSString . toJSString $ [] toJSBool :: JSValue -> JSValue toJSBool x | JSBool b <- x = JSBool b | JSRational _ n <- x = JSBool (numerator n /= 0) | JSString js <- x = JSBool (fromJSString js /= []) | otherwise = JSBool False procJSObject :: ((String, JSValue) -> (String, JSValue)) -> JSValue -> JSValue procJSObject f jv | JSObject o <- jv = JSObject . toJSObject . map f . map (second $ procJSObject f) . fromJSObject $ o | JSArray ar <- jv = JSArray . map (procJSObject f) $ ar | otherwise = jv mapJSArray :: (JSValue -> JSValue) -> JSValue -> JSValue mapJSArray f jv | JSArray ar <- jv = JSArray $ map (mapJSArray f) ar | otherwise = f jv isRefDate :: String -> Bool isRefDate = flip elem [ "issued", "event-date", "accessed", "container", "original-date"] readJSData :: (Data a) => JSValue -> Result a readJSData j = readType j `ext1R` jList `extR` (value :: Result String) `extR` (value :: Result Affix ) where value :: (JSON a) => Result a value = readJSON j jList :: (Data e) => Result [e] jList = case j of JSArray j' -> mapM readJSData j' _ -> Error $ "fromJSON: Prelude.[] bad data: " ++ show j -- | Build a datatype from a JSON object. Uses selectFields which -- allows to provied default values for fields not present in the JSON -- object. Useble with non algebraic datatype with record fields. readType :: (Data a) => JSValue -> Result a readType (JSObject ob) = construct where construct = selectFields (fromJSObject ob) (constrFields con) >>= evalStateT (fromConstrM f con) . zip (constrFields con) resType :: Result a -> a resType _ = error "resType" typ = dataTypeOf $ resType construct con = indexConstr typ 1 f :: (Data a) => StateT [(String,JSValue)] Result a f = do js <- get case js of j':js' -> do put js' lift $ readJSData (snd j') [] -> lift $ Error ("construct: empty list") readType j = fromJSON j selectFields :: [(String, JSValue)] -> [String] -> Result [JSValue] selectFields fjs = mapM sel where sel f = maybe (fb f) Ok $ lookup f fjs fb f = maybe (Error $ "selectFields: no field " ++ f) Ok $ lookup f defaultJson fromObj :: JSValue -> [(String, JSValue)] fromObj (JSObject o) = fromJSObject o fromObj _ = [] fromJString :: JSValue -> String fromJString j | JSString x <- j = fromJSString x | otherwise = [] defaultJson :: [(String, JSValue)] defaultJson = fromObj (toJSON emptyReference) ++ fromObj emptyRefDate ++ fromObj emptyPerson ++ fromObj emptyCite' where emptyRefDate = toJSON $ RefDate [] [] [] [] [] [] emptyPerson = toJSON $ Agent [] [] [] [] [] [] False emptyCite' = toJSON $ emptyCite citeproc-hs-0.3.9/src/Text/CSL/Proc/0000755000175000001440000000000012223317047016154 5ustar andreausersciteproc-hs-0.3.9/src/Text/CSL/Proc/Disamb.hs0000644000175000001440000003434412223317047017717 0ustar andreausers{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- 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, elemIndices, find, findIndex, sortBy, mapAccumL , nub, nubBy, groupBy, isPrefixOf ) import Data.Maybe import Data.Ord ( comparing ) import Text.CSL.Eval import Text.CSL.Output.Plain import Text.CSL.Reference import Text.CSL.Style -- | 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 rmNameHash . proc rmGivenNames 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 = if hasNamesOpt then disambAddNames givenNames $ needNames ++ if hasYSuffOpt && givenNames == NoGiven then [] else needYSuff else map (\cd -> cd {disambed = collision cd} ) $ needNames ++ 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) && reEval /= [] then map (uncurry $ reEvaluate s reEval) $ zip refs groups else groups withYearS = if hasYSuffOpt then map (mapCitationGroup $ setYearSuffCollision hasNamesOpt needYSuff) $ reEvaluated else rmYearSuff $ reEvaluated yearSuffs = when_ hasYSuffOpt . generateYearSuffix bibs . query getYearSuffixes $ withYearS addGNames = if hasGNameOpt then newGName else [] addNames = proc (updateContrib givenNames newNames addGNames) processed = if hasYSuffOpt then proc (updateYearSuffixes yearSuffs) . addNames $ withYearS else addNames $ 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 rmNameHash . proc rmGivenNames 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 ByCite [] _ o = o updateContrib g c n o | OContrib k r s d dd <- o = case filter (key &&& sameAs >>> uncurry (:) >>> elem k) c of x:_ -> OContrib k r (processGNames $ disambed x) [] dd _ -> if null c then OContrib k r (processGNames s) d dd else o | otherwise = o where processGNames = if g /= NoGiven then proc' (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 [] (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, 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,r),out) -> if refId r `elem` map key l then return . second (flip Output emptyFormatting) $ (,) c $ evalLayout (citLayout ct) (EvalCite c) True lo ms (citOptions ct) as r else [out] -- | 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 o | IfThen (Condition {disambiguation = d}) _ _ <- o = [d /= []] | otherwise = [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 rmNameHash . proc rmGivenNames . whatToGet citeData = nubBy (\a b -> collide a == collide b && key a == key b) $ concatMap (mapGroupOutput $ getCiteData) g findDupl f = filter (flip (>) 1 . length . flip elemIndices (map f citeData) . f) citeData duplicates = if b2 then findDupl (collide &&& citYear) else findDupl collide rmExtras :: [Output] -> [Output] rmExtras os | Output x f : xs <- os = if null (rmExtras x) then rmExtras xs else Output (rmExtras x) f : rmExtras xs | OContrib _ _ x _ _ : xs <- os = OContrib [] [] x [] [] : rmExtras xs | OYear y _ f : xs <- os = OYear y [] f : rmExtras xs | OYearSuf s _ _ f : xs <- os = OYearSuf s [] [] 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 = if query contribsQ x /= [] then query contribsQ x else [CD [] [] [] [] [] [] []] yearsQ = query getYears years o = if yearsQ o /= [] then yearsQ o else [([],[])] 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 _ s d dd <- o = [CD k s 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 = flip zip suffs . concat . -- sort clashing cites using their position in the sorted bibliography getFst . map sort' . map (filter ((/=) 0 . snd)) . map (map getP) . -- group clashing cites getFst . 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 . 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 collision 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 :: Output -> [(String,[Output])] getYearSuffixes o | OYearSuf _ k c _ <- o = [(k,c)] | otherwise = [] 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 head' l rest = map (\(b,x) -> if b then tail_ x else head' 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 [] = [] same l = map (flip 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 = and . same citeproc-hs-0.3.9/src/Text/CSL/Proc/Collapse.hs0000644000175000001440000002255412223317047020262 0ustar andreausers{-# 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 Control.Arrow ( (&&&), (>>>), second ) import Data.Char import Data.List ( groupBy ) import Text.CSL.Eval import Text.CSL.Proc.Disamb import Text.CSL.Style 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 | CG [a] f d os <- cg = mapCitationGroup process . CG [a] f d $ tail' os | otherwise = mapCitationGroup process cg where tail' x = if length x > 1 then tail x else x hasLocator = or . query hasLocator' hasLocator' o | OLoc _ _ <- o = [True] | otherwise = [False] citNum o | OCitNum i f <- o = [(i,f)] | otherwise = [] numOf = foldr (\x _ -> x) (0,emptyFormatting) . query citNum newNum = map numOf >>> (map fst >>> groupConsec) &&& map snd >>> uncurry zip process xs = if hasLocator xs then xs else flip concatMap (newNum xs) $ \(x,f) -> if length x > 2 then return $ Output [ OCitNum (head x) f , OPan [Str "\x2013"] , OCitNum (last x) f ] emptyFormatting else map (flip OCitNum f) x 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 = if null (query contribsQ y) then [] else proc rmNameHash . proc rmGivenNames $ head (query contribsQ y) 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] | OPan {} : _ <- 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 `betterThen` (layDelim . citLayout . citation $ s) afterCD = getOptionVal "after-collapse-delimiter" . citOptions . citation $ s afterColDel = afterCD `betterThen` 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 = emptyAffix, citeSuffix = emptyAffix} 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' rmNameHash . proc' rmGivenNames $ 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 (PlainText []) = True checkAffix (PandocText []) = 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 = format where format c x = if isNumStyle [x] then x else flip Output emptyFormatting $ addCiteAff citePrefix True c ++ [x] ++ addCiteAff citeSuffix False c addCiteAff g x c = case g c of PlainText [] -> [] PlainText p | x -> [Output (rtfParser emptyFormatting p) emptyFormatting, OSpace] PlainText p -> [Output (rtfParser emptyFormatting p) emptyFormatting] PandocText [] -> [] PandocText p | x -> [OPan p, OSpace] PandocText p -> [OPan p] isNumStyle :: [Output] -> Bool isNumStyle = null . query authorOrDate . proc rmLocator where rmLocator o | OLoc {} <- o = ONull | otherwise = o authorOrDate o | OContrib {} <- o = ['a'] | OYear {} <- o = ['a'] | OYearSuf {} <- o = ['a'] | OStr {} <- o = ['a'] | otherwise = [] -- | Group consecutive integers: -- -- > groupConsec [1,2,3,5,6,8,9] == [[1,2,3],[5,6],[8,9]] groupConsec :: [Int] -> [[Int]] groupConsec = groupConsec' [] where groupConsec' x [] = x groupConsec' [] (y:ys) = groupConsec' [[y]] ys groupConsec' xs (y:ys) = if y - head (last xs) == length (last xs) then groupConsec' (init xs ++ [last xs ++ [y]]) ys else groupConsec' ( xs ++ [ [y]]) ys citeproc-hs-0.3.9/src/Text/CSL/Test.hs0000644000175000001440000003646612223317050016535 0ustar andreausers{-# LANGUAGE PatternGuards, CPP #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Test -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- A module for reading Frank's citeproc-js testsuite. -- ----------------------------------------------------------------------------- module Text.CSL.Test ( toTest , runTS , test, test',test_ , runTest , Test (..) ) where import Control.Arrow import Control.Monad.State import Data.ByteString.Lazy.UTF8 ( fromString ) import Data.Char (toLower, chr) import Data.List import Data.Maybe (isJust) import Data.Time import System.Directory import System.Locale import Text.ParserCombinators.Parsec import Text.JSON.Generic import Text.CSL.Input.Json import Text.CSL.Output.Pandoc import Text.CSL.Output.Plain import Text.CSL.Reference import Text.CSL.Pickle ( readXmlString ) import Text.CSL.Parser ( xpStyle, xpLocale, langBase ) import Text.CSL.Proc import Text.CSL.Style import Text.Pandoc.Definition #ifdef EMBED_DATA_FILES import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.UTF8 as U import Text.CSL.Parser ( localeFiles ) #else import System.IO.Unsafe import Data.IORef import Paths_citeproc_hs ( getDataFileName ) import Text.CSL.Parser ( readLocaleFile ) import Text.CSL.Pickle ( readXmlFile ) #endif data Test = Test { testMode :: String , testInput :: [Reference] , testCSL :: Style , testAbbrevs :: [Abbrev] , testResult :: String , testBibSect :: BibOpts , testCitItems :: Maybe Citations , testCitations :: Maybe Citations } deriving ( Show ) toTest :: JSValue -> Test toTest ob = Test mode input style abbrevs result bibsection cites cites' where getObj f = case procJSObject f ob of JSObject o -> fromJSObject o _ -> error "error #217" object = getObj id objectI = getObj editJsonInput objectC = getObj editJsonCiteItems look s = case lookup s object of Just (JSString x) -> fromJSString x _ -> error $ "in test " ++ s ++ " section." style = readXmlString xpStyle . fromString $ look "csl" mode = look "mode" result = look "result" abbrevs = case lookup "abbreviations" object of Just o -> readJsonAbbrev o _ -> [] bibsection = case lookup "bibsection" objectI of Just (JSObject o) -> getBibOpts $ fromJSObject o _ -> Select [] [] cites = case lookup "citation_items" objectC of Just (JSArray cs) -> Just $ map readCite cs _ -> Nothing cites' = case lookup "citations" objectC of Just (JSArray cs) -> Just $ map readJsonCitations cs _ -> Nothing readCite c = case readJSData c of Ok cite -> cite Error er -> error ("citationItems: " ++ er) refs r = case readJSData r of Ok ref -> ref Error er -> error ("readJSData: " ++ er) input = case lookup "input" objectI of Just (JSArray ar) -> map refs ar _ -> error $ "in test input section." getFieldValue o | JSObject os <- o , [("field",JSString f),("value",JSString v)] <- fromJSObject os = (fromJSString f, fromJSString v) | otherwise = error "bibsection: could not parse fields and values" getBibOpts o = let getSec s = case lookup s o of Just (JSArray ar) -> map getFieldValue ar _ -> [] select = getSec "select" include = getSec "include" exclude = getSec "exclude" quash = getSec "quash" in case () of _ | select /= [] -> Select select quash | include /= [] -> Include include quash | exclude /= [] -> Exclude exclude quash | quash /= [] -> Select [] quash | otherwise -> Select [] [] readTestFile :: FilePath -> IO JSValue readTestFile f = do s <- readFile f let fields = ["CSL","RESULT","MODE","INPUT","CITATION-ITEMS","CITATIONS","BIBSECTION","BIBENTRIES", "ABBREVIATIONS"] format = map (toLower . \x -> if x == '-' then '_' else x) return . toJson . zip (map format fields) . map (fieldsParser s) $ fields toJson :: [(String,String)] -> JSValue toJson = JSObject . toJSObject . map getIt where getIt (s,j) | s `elem` ["result","csl","mode"] = (,) s . JSString $ toJSString j | s `elem` ["bibentries"] = (,) s . JSBool $ False | j == [] = (,) s . JSBool $ False | otherwise = (,) s . either error id . resultToEither $ decode j fieldsParser :: String -> String -> String fieldsParser s f = either (const []) id $ parse (fieldParser f) "" s fieldParser :: String -> Parser String fieldParser s = manyTill anyChar (try $ fieldMarkS) >> manyTill anyChar (try $ fieldMarkE) where fieldMarkS = string ">>" >> many (oneOf "= ") >> string s >> many (oneOf "= ") >> string ">>\n" fieldMarkE = string "\n<<" >> many (oneOf "= ") >> string s >> many (oneOf "= ") >> string "<<\n" pandocBib :: [String] -> String pandocBib [] = [] pandocBib s = "
\n" ++ concatMap (\x -> " " ++ "
" ++ x ++ "
\n") s ++ "
" pandocToHTML :: [Inline] -> String pandocToHTML [] = [] pandocToHTML (i:xs) | Str s <- i = (check . entityToChar $ s) ++ pandocToHTML xs | Emph is <- i = "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs | SmallCaps is <- i = "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs | Strong is <- i = "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs | Superscript is <- i = "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs | Subscript is <- i = "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs | Space <- i = " " ++ pandocToHTML xs | Quoted t is <- i = case t of DoubleQuote -> "“" ++ pandocToHTML is ++ "”" ++ pandocToHTML xs SingleQuote -> "‘" ++ pandocToHTML is ++ "’" ++ pandocToHTML xs | Link is x <- i = case snd x of "emph" -> "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs "strong" -> "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs "nodecor" -> "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs "baseline" -> "" ++ pandocToHTML is ++ "" ++ pandocToHTML xs _ -> pandocToHTML is ++ pandocToHTML xs | otherwise = [] where check ('&':[]) = "&" check ('<':ys) = "<" ++ check ys check ('>':ys) = ">" ++ check ys check (y :ys) = y : check ys check [] = [] unlines' :: [String] -> String unlines' [] = [] unlines' (x:[]) = x unlines' (x:xs) = x ++ "\n" ++ unlines' xs #ifndef EMBED_DATA_FILES localeCache :: IORef [(String, Locale)] localeCache = System.IO.Unsafe.unsafePerformIO $ newIORef [] getCachedLocale :: String -> IO [Locale] getCachedLocale n = maybe [] return `fmap` lookup n `fmap` readIORef localeCache putCachedLocale :: String -> Locale -> IO () putCachedLocale n t = modifyIORef localeCache $ \l -> (n, t) : l #endif runTest :: Test -> IO (Bool,String) runTest t = do let locale = case styleDefaultLocale $ testCSL t of x | length x == 2 -> maybe "en-US" id (lookup x langBase) | otherwise -> take 5 x #ifdef EMBED_DATA_FILES ls <- case lookup ("locales-" ++ locale ++ ".xml") localeFiles of Just x' -> return $ readXmlString xpLocale $ L.fromChunks [x'] _ -> return $ Locale [] [] [] [] [] #else ls' <- getCachedLocale locale ls <- case ls' of [] -> do l <- getDataFileName ("locales/locales-" ++ locale ++ ".xml") b <- doesFileExist l r <- if b then readXmlFile xpLocale l else readLocaleFile $ take 2 locale putCachedLocale locale r return r [x] -> return x _ -> return $ Locale [] [] [] [] [] #endif let opts = procOpts { bibOpts = testBibSect t} style' = testCSL t style = style' {styleLocale = mergeLocales (styleDefaultLocale style') ls $ styleLocale style' ,styleAbbrevs = testAbbrevs t} cites = case (testCitations t, testCitItems t) of (Just cs, _ ) -> cs (_, Just cs) -> cs _ -> [map (\r -> emptyCite { citeId = refId r }) $ testInput t] (BD cits bib) = citeproc opts style (testInput t) cites output = superscript $ case testMode t of "citation" -> unlines' . map (pandocToHTML . renderPandoc_ style) $ cits _ -> pandocBib . map (pandocToHTML . renderPandoc_ style) $ bib return (output == getResult t, output) test :: FilePath -> IO Bool test = doTest readJsonFile 0 test' :: Int -> FilePath -> IO Bool test' = doTest readJsonFile test_ :: Int -> FilePath -> IO Bool test_ = doTest readTestFile doTest :: (FilePath -> IO JSValue) -> Int -> FilePath -> IO Bool doTest rf v f = do when (v >= 2) $ putStrLn f t <- toTest `fmap` rf f (r,o) <- runTest t if r then return () else do let putStrLn' = when (v >= 1) . putStrLn putStrLn $ (tail . takeWhile (/= '.') . dropWhile (/= '_')) f ++ " failed!" putStrLn' "++++++++++++++++++++++++++++++++++++++++++++++++++++++++" putStrLn' $ f ++ " failed!" putStrLn' "Expected:" putStrLn' $ getResult t putStrLn' "\nGot:" putStrLn' $ o when (v >= 3) $ putStrLn (show t) putStrLn' "++++++++++++++++++++++++++++++++++++++++++++++++++++++++" return r runTS :: [String] -> Int -> FilePath -> IO () runTS gs v f = do st <- getCurrentTime putStrLn $ (++) (formatTime defaultTimeLocale "%H:%M:%S" st) $ " <--------------START" dc <- sort `fmap` filter (isInfixOf ".json") `fmap` getDirectoryContents f let groupTests = map (head . map fst &&& map snd) . groupBy (\x y -> fst x == fst y) . map (takeWhile (/= '_') &&& tail . dropWhile (/= '_')) runGroups g = do putStrLn "------------------------------------------------------------" putStrLn $ "GROUP \"" ++ fst g ++ "\" has " ++ show (length $ snd g) ++ " tests to run" putStrLn "------------------------------------------------------------" r' <- mapM (test' v . (++) (f ++ fst g ++ "_")) $ snd g return r' filterGroup = if gs /= [] then filter (flip elem gs . fst) else id r <- mapM runGroups $ filterGroup $ groupTests dc putStrLn " ------------------------------------------------------------" putStrLn "| TEST SUMMARY:" putStrLn "------------------------------------------------------------" putStrLn $ "\t" ++ (show $ sum $ map length r) ++ " tests in " ++ (show $ length r) ++ " groups" putStrLn $ "\t" ++ (show $ sum $ map (length . filter id ) r) ++ " successes" putStrLn $ "\t" ++ (show $ sum $ map (length . filter not) r) ++ " failures" et <- getCurrentTime putStrLn $ (++) (formatTime defaultTimeLocale "%H:%M:%S" et) $ " <--------------END" putStrLn $ "Time: " ++ show (diffUTCTime et st) getResult :: Test -> String getResult t = if isJust (testCitations t) && testMode t == "citation" then unlines' . map (\(a,b) -> drop (length (show b) + 5) a) . flip zip ([0..] :: [Int]) . lines . testResult $ t else testResult t superscript :: String -> String superscript [] = [] superscript (x:xs) = let a = lookup x (map (first (chr . readNum)) sups) in case a of Nothing -> x : superscript xs Just x' -> "" ++ [chr $ readNum x'] ++ "" ++ superscript xs where sups = [("0x00AA","0x0061"),("0x00B2","0x0032"),("0x00B3","0x0033"),("0x00B9","0x0031") ,("0x00BA","0x006F"),("0x02B0","0x0068"),("0x02B1","0x0266"),("0x02B2","0x006A") ,("0x02B3","0x0072"),("0x02B4","0x0279"),("0x02B5","0x027B"),("0x02B6","0x0281") ,("0x02B7","0x0077"),("0x02B8","0x0079"),("0x02E0","0x0263"),("0x02E1","0x006C") ,("0x02E2","0x0073"),("0x02E3","0x0078"),("0x02E4","0x0295"),("0x1D2C","0x0041") ,("0x1D2D","0x00C6"),("0x1D2E","0x0042"),("0x1D30","0x0044"),("0x1D31","0x0045") ,("0x1D32","0x018E"),("0x1D33","0x0047"),("0x1D34","0x0048"),("0x1D35","0x0049") ,("0x1D36","0x004A"),("0x1D37","0x004B"),("0x1D38","0x004C"),("0x1D39","0x004D") ,("0x1D3A","0x004E"),("0x1D3C","0x004F"),("0x1D3D","0x0222"),("0x1D3E","0x0050") ,("0x1D3F","0x0052"),("0x1D40","0x0054"),("0x1D41","0x0055"),("0x1D42","0x0057") ,("0x1D43","0x0061"),("0x1D44","0x0250"),("0x1D45","0x0251"),("0x1D46","0x1D02") ,("0x1D47","0x0062"),("0x1D48","0x0064"),("0x1D49","0x0065"),("0x1D4A","0x0259") ,("0x1D4B","0x025B"),("0x1D4C","0x025C"),("0x1D4D","0x0067"),("0x1D4F","0x006B") ,("0x1D50","0x006D"),("0x1D51","0x014B"),("0x1D52","0x006F"),("0x1D53","0x0254") ,("0x1D54","0x1D16"),("0x1D55","0x1D17"),("0x1D56","0x0070"),("0x1D57","0x0074") ,("0x1D58","0x0075"),("0x1D59","0x1D1D"),("0x1D5A","0x026F"),("0x1D5B","0x0076") ,("0x1D5C","0x1D25"),("0x1D5D","0x03B2"),("0x1D5E","0x03B3"),("0x1D5F","0x03B4") ,("0x1D60","0x03C6"),("0x1D61","0x03C7"),("0x2070","0x0030"),("0x2071","0x0069") ,("0x2074","0x0034"),("0x2075","0x0035"),("0x2076","0x0036"),("0x2077","0x0037") ,("0x2078","0x0038"),("0x2079","0x0039"),("0x207A","0x002B"),("0x207B","0x2212") ,("0x207C","0x003D"),("0x207D","0x0028"),("0x207E","0x0029"),("0x207F","0x006E") ,("0x3194","0x4E09"),("0x3195","0x56DB"),("0x3196","0x4E0A"),("0x3197","0x4E2D") ,("0x3198","0x4E0B"),("0x3199","0x7532"),("0x319A","0x4E59"),("0x319B","0x4E19") ,("0x319C","0x4E01"),("0x319D","0x5929"),("0x319E","0x5730"),("0x319F","0x4EBA") ,("0x02C0","0x0294"),("0x02C1","0x0295"),("0x06E5","0x0648"),("0x06E6","0x064A")] citeproc-hs-0.3.9/src/Text/CSL/Proc.hs0000644000175000001440000004002712223317050016505 0ustar andreausers{-# LANGUAGE PatternGuards, DeriveDataTypeable #-} ----------------------------------------------------------------------------- -- | -- 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 ) import Data.List import Data.Ord ( comparing ) import Text.CSL.Eval hiding ( trim ) import Text.CSL.Output.Plain import Text.CSL.Parser import Text.CSL.Proc.Collapse import Text.CSL.Proc.Disamb import Text.CSL.Reference import Text.CSL.Style data ProcOpts = ProcOpts { bibOpts :: BibOpts } 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 ) procOpts :: ProcOpts procOpts = ProcOpts (Select [] []) -- | With a 'Style', a list of 'Reference's and the list of citation -- groups (the list of citations with their locator), produce the -- 'FormattedOutput' for each citation group. processCitations :: ProcOpts -> Style -> [Reference] -> Citations -> [[FormattedOutput]] processCitations ops s rs = citations . citeproc ops s rs -- | With a 'Style' and the list of 'Reference's produce the -- 'FormattedOutput' for the bibliography. processBibliography :: ProcOpts -> Style -> [Reference] -> [[FormattedOutput]] processBibliography ops s rs = bibliography $ citeproc ops s rs [map (\r -> emptyCite { citeId = refId r}) rs] -- | With a 'Style', a list of 'Reference's and the list of -- 'Citations', produce the 'FormattedOutput' for each citation group -- and the bibliography. citeproc :: ProcOpts -> Style -> [Reference] -> Citations -> BiblioData citeproc ops s rs cs = BD citsOutput biblioOutput where -- the list of bib entries, as a list of Reference, with -- position, locator and year suffix set. biblioRefs = procRefs s . map (getReference rs) . nubBy (\a b -> citeId a == citeId b) . concat $ cs biblioOutput = if "disambiguate-add-year-suffix" `elem` getCitDisambOptions s then map formatOutputList $ map (proc (updateYearSuffixes yearS) . map addYearSuffix) $ procBiblio (bibOpts ops) s biblioRefs else map formatOutputList $ procBiblio (bibOpts ops) s biblioRefs citsAndRefs = processCites biblioRefs cs (yearS,citG) = disambCitations s biblioRefs cs $ map (procGroup s) citsAndRefs citsOutput = map (formatCitLayout s) . collapseCitGroups s $ citG -- | 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) $ rs sortItems :: Show a => [(a,[Sorting])] -> [a] sortItems [] = [] sortItems l = case head . concatMap (map snd) $ result of [] -> concatMap (map fst) result _ -> if or $ map ((<) 1 . length) result then concatMap sortItems result else concatMap (map fst) result where result = process l process = sortBy (comparing $ head' . snd) >>> groupBy (\a b -> head' (snd a) == head' (snd b)) >>> map (map $ second tail') -- | 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 = maybe [] process mb where process b = flip map (render b) $ uncurry formatBiblioLayout (layFormat &&& layDelim $ bibLayout b) render b = subsequentAuthorSubstitute b . map (evalBib b) . filterRefs bos $ rs evalBib b r = evalLayout (bibLayout b) (EvalBiblio emptyCite {citePosition = "first"}) False l ms (mergeOptions (bibOptions b) opts) as r 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" -> head' . query namesQ . queryContrib "partial-each" -> query namesQ . queryContrib _ -> queryContrib getPartialEach x xs = concat . head' . map fst . reverse . sortBy (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 r) of Just x | Just v' <- (fromValue x :: Maybe RefType ) -> v == toShow (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] ) -> v == [] && v' == [] || v == show v' | Just v' <- (fromValue x :: Maybe [RefDate]) -> v == [] && 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, 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 ) . foldr (\x _ -> [x]) [] . 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 -> [FormattedOutput] formatCitLayout s (CG co f d cs) | [a] <- co = formatAuth a : formatCits (fst >>> citeId &&& citeHash >>> setAsSupAu $ a) cs | otherwise = formatCits id cs where formatAuth = formatOutput . localMod formatCits g = formatOutputList . appendOutput formatting . addAffixes f . addDelim d . map (fst &&& localMod >>> uncurry addCiteAffixes) . g formatting = unsetAffixes f localMod = if cs /= [] then uncurry $ localModifiers s (co /= []) else snd setAsSupAu h = map $ \(c,o) -> if (citeId c, citeHash c) == h then flip (,) o c { authorInText = False , suppressAuthor = True } else flip (,) o c addAffixes :: Formatting -> [Output] -> [Output] addAffixes f os | [] <- os = [] | [ONull] <- os = [] | otherwise = pref ++ suff where pref = if prefix f /= [] then [OStr (prefix f) emptyFormatting] ++ os else os suff = if suffix f /= [] && elem (head $ suffix f) ",.:?!" && [head $ suffix f] == lastOutput then [OStr (tail $ suffix f) emptyFormatting] else suff' suff' = if suffix f /= [] then [OStr (suffix f) emptyFormatting] else [] lastOutput = case renderPlain (formatOutputList os) of [] -> "" x -> [last x] -- | 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 . proc rmFormatting . contribOnly s | suppressAuthor c = check . rmContrib . return | otherwise = id where isPunct = and . map (flip elem ".,;:!? ") 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 rmFormatting f | Formatting {} <- f = emptyFormatting { prefix = prefix f , suffix = suffix f} | otherwise = f 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 {} <- o = Output [ OStr (query getRefTerm s) emptyFormatting , OSpace, o] emptyFormatting | OContrib _ "author" _ _ _ <- o = o | OContrib _ "authorsub" _ _ _ <- o = o | Output ot f <- o = Output (cleanOutput $ map (contribOnly s) ot) f | OStr x _ <- o , "ibid" <- filter (/= '.') (map toLower x) = o | otherwise = ONull where getRefTerm :: CslTerm -> String getRefTerm t | CT "reference" Long _ _ x _ _ <- t = capitalize x | otherwise = [] citeproc-hs-0.3.9/LICENSE0000644000175000001440000000267212223317046014130 0ustar andreausersCopyright (c) Andrea Rossato All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 2. 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. 3. Neither the name of the author nor the names of his contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE REGENTS 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 AUTHORS 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. citeproc-hs-0.3.9/Setup.lhs0000644000175000001440000000011412223317046014720 0ustar andreausers#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain citeproc-hs-0.3.9/citeproc-hs.cabal0000644000175000001440000001311512223317046016321 0ustar andreausersname: citeproc-hs version: 0.3.9 homepage: http://gorgias.mine.nu/repos/citeproc-hs/ synopsis: A Citation Style Language implementation in Haskell description: citeproc-hs is 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: . . For the API documentation please see "Text.CSL". category: Text license: BSD3 license-file: LICENSE author: Andrea Rossato maintainer: andrea.rossato@unitn.it bug-reports: http://code.google.com/p/citeproc-hs/issues/list cabal-version: >= 1.6 build-type: Simple data-files: locales/locales-af-ZA.xml locales/locales-ar-AR.xml locales/locales-bg-BG.xml locales/locales-ca-AD.xml locales/locales-cs-CZ.xml locales/locales-da-DK.xml locales/locales-de-AT.xml locales/locales-de-CH.xml locales/locales-de-DE.xml locales/locales-el-GR.xml locales/locales-en-GB.xml locales/locales-en-US.xml locales/locales-es-ES.xml locales/locales-et-EE.xml locales/locales-eu.xml locales/locales-fa-IR.xml locales/locales-fi-FI.xml locales/locales-fr-CA.xml locales/locales-fr-FR.xml locales/locales-he-IL.xml locales/locales-hr-HR.xml locales/locales-hu-HU.xml locales/locales-is-IS.xml locales/locales-it-IT.xml locales/locales-ja-JP.xml locales/locales-km-KH.xml locales/locales-ko-KR.xml locales/locales-lt-LT.xml locales/locales-lv-LV.xml locales/locales-mn-MN.xml locales/locales-nb-NO.xml locales/locales-nl-NL.xml locales/locales-nn-NO.xml locales/locales-pl-PL.xml locales/locales-pt-BR.xml locales/locales-pt-PT.xml locales/locales-ro-RO.xml locales/locales-ru-RU.xml locales/locales-sk-SK.xml locales/locales-sl-SI.xml locales/locales-sr-RS.xml locales/locales-sv-SE.xml locales/locales-th-TH.xml locales/locales-tr-TR.xml locales/locales-uk-UA.xml locales/locales-vi-VN.xml locales/locales-zh-CN.xml locales/locales-zh-TW.xml flag small_base description: Choose the new smaller, split-up base package. flag bibutils description: Use Chris Putnam's Bibutils. default: True flag network description: Use network and HTTP to retrieve csl file from URIs. default: True flag hexpat description: Use hexpat to parse XML 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 library exposed-modules: Text.CSL Text.CSL.Eval Text.CSL.Eval.Common Text.CSL.Eval.Date Text.CSL.Eval.Names Text.CSL.Eval.Output Text.CSL.Pickle Text.CSL.Parser Text.CSL.Proc Text.CSL.Proc.Collapse Text.CSL.Proc.Disamb Text.CSL.Reference Text.CSL.Style Text.CSL.Input.MODS Text.CSL.Input.Bibutils Text.CSL.Input.Json Text.CSL.Output.Pandoc Text.CSL.Output.Plain Text.CSL.Test other-modules: Paths_citeproc_hs ghc-options: -funbox-strict-fields -Wall ghc-prof-options: -prof -auto-all hs-source-dirs: src build-depends: containers, directory, mtl, json, utf8-string, bytestring, filepath, pandoc-types >= 1.8 && < 1.13 if flag(bibutils) build-depends: hs-bibutils >= 0.3 extensions: CPP cpp-options: -DUSE_BIBUTILS if flag(network) build-depends: network >= 2, HTTP >= 4000.0.9 extensions: CPP cpp-options: -DUSE_NETWORK if flag(hexpat) build-depends: hexpat >= 0.20.2 exposed-modules: Text.CSL.Pickle.Hexpat cpp-options: -DUSE_HEXPAT else build-depends: xml exposed-modules: Text.CSL.Pickle.Xml if flag(embed_data_files) build-depends: template-haskell, file-embed extensions: CPP cpp-options: -DEMBED_DATA_FILES if flag(unicode_collation) build-depends: text, text-icu extensions: CPP cpp-options: -DUNICODE_COLLATION if impl(ghc >= 6.10) build-depends: base >= 4, syb, parsec, old-locale, time else build-depends: base >= 3 && < 4 citeproc-hs-0.3.9/test/0000755000175000001440000000000012223317050014066 5ustar andreausersciteproc-hs-0.3.9/test/loc.hs0000644000175000001440000000074312223317050015203 0ustar andreausersimport Control.Monad import System.Exit main = do foo <- getContents let actual_loc = filter (not.null) $ filter isntcomment $ map (dropWhile (==' ')) $ lines foo loc = length actual_loc putStrLn $ show loc -- uncomment the following to check for mistakes in isntcomment -- putStr $ unlines $ actual_loc isntcomment ('-':'-':_) = False isntcomment ('{':'-':_) = False -- pragmas isntcomment _ = True citeproc-hs-0.3.9/test/test.hs0000644000175000001440000000117412223317050015404 0ustar andreausersimport System.Environment import Text.CSL.Eval (split) import Text.CSL.Test -- a dir with a final slash testDir = "citeproc-test/processor-tests/machines/" testDirH = "citeproc-test/processor-tests/humans/" main :: IO () main = do args <- getArgs case args of [x,y,z] -> if z == "txt" then test_ 2 (testDirH ++ x ++ "_" ++ y ++ ".txt" ) >> return () else test' 2 (testDir ++ x ++ "_" ++ y ++ ".json") >> return () [x,y] -> test' 2 (testDir ++ x ++ "_" ++ y ++ ".json") >> return () [x] -> runTS (split (== ',') x) 0 testDir x -> runTS x 0 testDir citeproc-hs-0.3.9/test/createTest.hs0000644000175000001440000000235512223317050016532 0ustar andreausersimport System.Environment import Text.CSL import Text.CSL.Test import Text.JSON.Generic main :: IO () main = do args <- getArgs case args of [c,r] -> readStruff c r [] >>= putStrLn _ -> error "usage: kljlkjljlkjlkjl" readStruff :: String -> String -> String -> IO String readStruff c r s = do c' <- readFile c r' <- readBiblioFile r return $ mode "citation" ++ result [] ++ citationItems r' ++ csl c' ++ input r' mode :: String -> String mode s = ">>===== MODE =====>>\n" ++ s ++ "\n<<===== MODE =====<<\n\n" result :: String -> String result s = ">>===== RESULT =====>>\n" ++ s ++ "\n<<===== RESULT =====<<\n\n" citationItems :: [Reference] -> String citationItems l = ">>===== CITATION-ITEMS =====>>\n[\n [\n" ++ toId ++ "\n ]\n]\n<<===== CITATION-ITEMS =====<<\n\n" where toId = foldr addComma [] toStringList addComma x xs = if length xs < 1 then x ++ xs else x ++ ",\n" ++ xs toStringList = flip map l $ \x -> " {\n \"id\": \"" ++ refId x ++ "\"\n }" csl :: String -> String csl s = ">>===== CSL =====>>\n" ++ s ++ "<<===== CSL =====<<\n\n" input :: [Reference] -> String input s = ">>===== INPUT =====>>\n" ++ encodeJSON s ++ "\n<<===== INPUT =====<<\n\n" citeproc-hs-0.3.9/locales/0000755000175000001440000000000012223317047014537 5ustar andreausersciteproc-hs-0.3.9/locales/locales-pl-PL.xml0000644000175000001440000002351212223317047017630 0ustar andreausers 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 available at przez circa ca cytowane wydanie wydania wyd. et al. w przygotowaniu z ibid. w w druku internet wywiad list brak daty b.d. online zaprezentowano na referencja referencje ref. ref. pobrano scale version 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 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. akap. cz. sekc. s.v. s.vv. w. w. t. t. ¶¶ § §§ director directors redaktor redaktorzy edytor edytorzy illustrator illustrators tłumacz tłumacze redaktor & tłumacz redaktorzy & tłumacze dir. dirs. red. red. red. red. ill. ills. tłum. tłum. red. & tłum. red. & tłum. directed by zredagowane przez zredagowane przez illustrated by przeprowadzony przez dla by przetłumaczone przez zredagowane & przetłumaczone przez przez dir. red. red. illus. 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 citeproc-hs-0.3.9/locales/locales-de-CH.xml0000644000175000001440000002353412223317046017567 0ustar andreausers 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 available at 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 scale 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 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. Abs. Teil Abschn. s.v. s.vv. V. V. Bd. Bd. ¶¶ § §§ director directors Herausgeber Herausgeber Herausgeber Herausgeber illustrator illustrators Übersetzer Übersetzer Herausgeber & Übersetzer Herausgeber & Übersetzer dir. dirs. Hrsg. Hrsg. Hrsg. Hrsg. ill. ills. Übers. Übers. Hrsg. & Übers. Hrsg. & Übers directed by herausgegeben von herausgegeben von illustrated by interviewt von an by übersetzt von herausgegeben und übersetzt von von dir. hg. von hg. von illus. ü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 citeproc-hs-0.3.9/locales/locales-de-DE.xml0000644000175000001440000002355312223317046017566 0ustar andreausers 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 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. 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 directed by herausgegeben von herausgegeben von illustriert von interviewt von an von übersetzt von herausgegeben und übersetzt von 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 citeproc-hs-0.3.9/locales/locales-fi-FI.xml0000644000175000001440000002347212223317046017602 0ustar andreausers 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 available at tekijä noin n. viitattu painos painokset p. ym. tulossa alkaen mt. teoksessa painossa internet haastattelu kirje ei päivämäärää n.d. verkossa esitetty tilaisuudessa viittaus viittaukset viit.. viit. noudettu scale version 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 muistiinpano muistiinpanot opus opukset 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 l. n. op. s. ss. kappale osa osa s.v. s.vv. säk. säk. vol. vol. ¶¶ § §§ director directors toimittaja toimittajat toimittaja toimittajat illustrator illustrators suomentaja suomentajat toimittaja ja suomentaja toimittajat ja suomentajat dir. dirs. toim. toim. toim. toim. ill. ills. suom. suom. toim. ja suom. toim. ja suom. directed by toimittanut toimittanut illustrated by haastatellut vastaanottaja by suomentanut toimittanut ja suomentanut dir. toim. toim. illus. suom. toim. ja suom. tammikuu helmikuu maaliskuu huhtikuu toukokuu kesäkuu heinäkuu elokuu syyskuu lokakuu marraskuu joulukuu tammi helmi maalis huhti touko kesä heinä elo syys loka marras joulu kevät kesä syksy talvi citeproc-hs-0.3.9/locales/locales-de-AT.xml0000644000175000001440000002353412223317046017601 0ustar andreausers 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 available at 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 scale 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 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. Abs. Teil Abschn. s.v. s.vv. V. V. Bd. Bd. ¶¶ § §§ director directors Herausgeber Herausgeber Herausgeber Herausgeber illustrator illustrators Übersetzer Übersetzer Herausgeber & Übersetzer Herausgeber & Übersetzer dir. dirs. Hrsg. Hrsg. Hrsg. Hrsg. ill. ills. Übers. Übers. Hrsg. & Übers. Hrsg. & Übers directed by herausgegeben von herausgegeben von illustrated by interviewt von an by übersetzt von herausgegeben und übersetzt von von dir. hg. von hg. von illus. ü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 citeproc-hs-0.3.9/locales/locales-zh-CN.xml0000644000175000001440000002367712223317047017637 0ustar andreausers 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 nd 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 line note notes opus opera 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 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by 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 citeproc-hs-0.3.9/locales/locales-cs-CZ.xml0000644000175000001440000002347412223317046017631 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 přístup a a další anonymous anon. v available at by circa c. citován vydání vydání vyd. et al. nadcházející z ibid. v v tisku internet interview dopis bez data nedatováno online prezentován v reference references ref. refs. získáno scale version 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 číslo řádek řádky poznámka poznámky opus opera strana strany odstavec odstavce část části sekce sekce sub verbo sub verbis verš verše ročník ročníky kn. kap. sl. obr. l. čís. l. n. op. s. s. odst. č. sek. s.v. s.vv. v. v. roč. roč. ¶¶ § §§ director directors editor editoři editor editors illustrator illustrators překladatel překladatelé editor a překladatel editoři a překladatelé dir. dirs. ed. ed. ed. ed. ill. ills. překl. překl. ed. a překl. ed. a překl. directed by editoval editoval illustrated by rozhovor vedl pro by přeložil editoval a přeložil by dir. ed. ed. illus. překl. 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 citeproc-hs-0.3.9/locales/locales-sv-SE.xml0000644000175000001440000002370612223317047017646 0ustar andreausers 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 inget datum nd online presenterad vid referens referenser ref. refs. 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 stycke stycken del delar avsnitt avsnitt sub verbo sub verbis vers verser volym volumer bok kap kol fig f num l. n. op s ss st del avs s.v. s.vv. vers verser vol vols ¶¶ § §§ 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 reds ed. eds. ill. ills. övers övers ed. & tran. eds. & trans. directed by redigerad av edited by illustrated by intervju av till by översatt av edited & translated by by dir. red ed. illus. övers ed. & trans. by Januari Februari Mars April Maj Juni Juli Augusti September Oktober November December Jan Feb Mar Apr Maj Jun Jul Aug Sep Okt Nov Dec Vår Sommar Höst Vinter citeproc-hs-0.3.9/locales/locales-ro-RO.xml0000644000175000001440000002375412223317047017652 0ustar andreausers 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 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. 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. coordonat de ediție de ediție de ilustrații de interviu de în de traducere de ediție & traducere de 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 citeproc-hs-0.3.9/locales/locales-th-TH.xml0000644000175000001440000002746112223317047017637 0ustar andreausers 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. แปล แปลและเรียบเรียงโดย มกราคม กุมภาพันธ์ มีนาคม เมษายน พฤษภาคม มิถุนายน กรกฎาคม สิงหาคม กันยายน ตุลาคาม พฤศจิกายน ธันวาคม ม.ค. ก.พ. มี.ค. เม.ย. พ.ค. มิ.ย. ก.ค. ส.ค. ก.ย. ต.ค. พ.ย. ธ.ค. ฤดูใบไม้ผลิ ฤดูร้อน ฤดูใบไม้ร่วง ฤดูหนาว citeproc-hs-0.3.9/locales/locales-pt-BR.xml0000644000175000001440000002343012223317047017627 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 acessado e e outros anônimo anon em available at 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 scale version AD BC º primeiro segundo terceiro quarto quinto sexto sétimo oitavo nono décimo 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 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. parag. pt. seç. s.v. s.vv. v. vv. vol. vols. ¶¶ § §§ director directors organizador organizadores editor editors illustrator illustrators tradutor tradutores editor e tradutor editores e tradutores dir. dirs. org. orgs. ed. eds. ill. ills. trad. trads. ed. e trad. eds. e trads. directed by organizado por editado por illustrated by entrevista de para by traduzido por editado & traduzido por por dir. org. ed. illus. 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 citeproc-hs-0.3.9/locales/locales-en-GB.xml0000644000175000001440000002372712223317046017603 0ustar andreausers 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 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. 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by 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 citeproc-hs-0.3.9/locales/locales-el-GR.xml0000644000175000001440000002601712223317046017614 0ustar andreausers 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. μετάφρ. μετάφρ. και επιμέλ. Ιανουάριος Φεβρουάριος Μάρτιος Απρίλιος Μάιος Ιούνιος Ιούλιος Αύγουστος Σεπτέμβριος Οκτώβριος Νοέμβριος Δεκέμβριος Ιανουαρίου Φεβρουαρίου Μαρτίου Απριλίου Μαΐου Ιουνίου Ιουλίου Αυγούστου Σεπτεμβρίου Οκτωβρίου Νοεμβρίου Δεκεμβρίου Άνοιξη Καλοκαίρι Φθινόπωρο Χειμώνας citeproc-hs-0.3.9/locales/locales-fr-FR.xml0000644000175000001440000002517412223317047017626 0ustar andreausers 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 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. 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. réalisé par édité par sous la direction de illustré par entretien réalisé par à par traduit par édité et traduit par 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 citeproc-hs-0.3.9/locales/locales-ko-KR.xml0000644000175000001440000002373512223317047017636 0ustar andreausers 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 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. directed by 편집자: edited by illustrated by interview by to by 번역자: edited & translated by 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 citeproc-hs-0.3.9/locales/locales-ja-JP.xml0000644000175000001440000002367712223317047017621 0ustar andreausers 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 近刊 から 前掲 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 l. n. op p p 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. directed by 編集者: edited by illustrated by interview by to by 翻訳者: edited & translated by 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 citeproc-hs-0.3.9/locales/locales-da-DK.xml0000644000175000001440000002345112223317046017565 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 åbnet og med flere anonym anon. available at af cirka ca. citeret udgave udgaver udg. et al. kommende fra ibid. i i tryk internet interview brev ingen dato udateret online præsenteret ved reference referencer ref. refr. hentet scale version e.Kr f.Kr « » . første anden tredje fjerde femte sjette syvende ottende niende tiende bog bøger kapitel kapitler kolonne kolonner figur figurer folio folier nummer numre linje linjer note noter opus opuser side sider afsnit afsnit del dele sektion sektionerne sub verbo sub verbis vers vers bind bind b. kap. kol. fig. fol. nr. l. n. op. s. s. afs. d. sekt. s.v. s.vv. v. v. bd. bd. ¶¶ § §§ director directors redaktør redaktører redaktør redaktører illustrator illustrators oversætter oversættere redaktør & oversætter redaktører & oversættere dir. dirs. red. red. red. red. ill. ills. overs. overs. red. & overs. red. & overs. directed by redigeret af redigeret af illustrated by interviewet af modtaget af by oversat af redigeret & oversat af af dir. 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 citeproc-hs-0.3.9/locales/locales-uk-UA.xml0000644000175000001440000002415512223317047017632 0ustar andreausers 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 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 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by by dir. ed ed. illus. trans ed. & trans. by Січень Лютий Березень Квітень Травень Червень Липень Серпень Вересень Жовтень Листопад Грудень Січ Лют Бер Квіт Трав Чер Лип Сер Вер Жов Лис Груд Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-lt-LT.xml0000644000175000001440000002404012223317047017635 0ustar andreausers Valdemaras Klumbys This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 žiūrėta ir ir kt. anonimas anon. available at circa ca. cituojama pagal leidimas leidimai leid. et al. ruošiamas ibid. spaudoje prieiga per internetą interviu laiškas sine anno s.a. interaktyvus pristatytas nuoroda nuorodos nuor. nuor. gauta scale version po Kr. pr. Kr. , -asis pirmasis antrasis trečiasis ketvirtasis penktasis šeštasis septintasis aštuntasis devintasis dešimtasis knyga knygos skyrius skyriai skiltis skiltys iliustracija iliustracijos lapas lapai numeris numeriai eilutė eilutės pastaba pastabos opus opera 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. l. n. op. p. p. pastr. d. posk. žr. žr. eilėr. eilėr. t. t. ¶¶ § §§ director directors sudarytojas sudarytojai atsakingasis redaktorius atsakingieji redaktoriai illustrator illustrators vertėjas vertėjai sudarytojas ir vertėjas sudarytojai ir vertėjai dir. dirs. sud. sud. ats. red. ats. red. ill. ills. vert. vert. sud. ir vert. sud. ir vert. directed by sudarė parengė illustrated by interviu ėmė gavo by vertė sudarė ir vertė dir. sud. pareng. illus. 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 citeproc-hs-0.3.9/locales/locales-fr-CA.xml0000644000175000001440000002517212223317047017600 0ustar andreausers 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. 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 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. 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. réalisé par édité par sous la direction de illustré par entretien réalisé par à par traduit par édité et traduit par 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 citeproc-hs-0.3.9/locales/locales-ru-RU.xml0000644000175000001440000002541112223317047017656 0ustar andreausers 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 просмотрено и и др. аноним анон. на available at circa ca. цитируется по цит. по издание издания изд. и др. ожидается от там же в в печати Интернет интервью письмо без даты б. д. online представлено на reference references ref. refs. извлечено scale version н. э. до н. э. « » й первый второй третий четвертый пятый шестой седьмой восьмой девятый десятый книга книги глава главы столбец столбцы рисунок рисунки лист листы выпуск выпуски строка строки примечание примечания сочинение сочинения страница страницы параграф параграфы часть части раздел разделы смотри смотри стих стихи том тома кн. гл. стб. рис. л. l. n. соч. с. с. пара. ч. разд. см. см. ст. ст. т. тт. ¶¶ § §§ director directors редактор редакторы ответственный редактор ответственные редакторы illustrator illustrators переводчик переводчики редактор и переводчик редакторы и переводчики dir. dirs. ред. ред. отв. ред. отв. ред. ill. ills. перев. перев. ред. и перев. ред. и перев. directed by отредактировано отредактировано illustrated by интервью к by переведено отредактировано и переведено dir. ред. отв. ред. illus. перев. ред. и перев. январь февраль март апрель май июнь июль август сентябрь октябрь ноябрь декабрь янв. фев. мар. апр. май июн. июл. авг. сен. окт. ноя. дек. весна лета осень зима citeproc-hs-0.3.9/locales/locales-et-EE.xml0000644000175000001440000002327712223317046017612 0ustar andreausers 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 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 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 citeproc-hs-0.3.9/locales/locales-nn-NO.xml0000644000175000001440000002341612223317047017634 0ustar andreausers 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 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. 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. regissert av redigert av redigert av illustrert av intervjua av til av omsett av redigert & omsett av 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 citeproc-hs-0.3.9/locales/locales-lv-LV.xml0000644000175000001440000002765112223317047017654 0ustar andreausers 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 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. 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 citeproc-hs-0.3.9/locales/locales-nl-NL.xml0000644000175000001440000002553712223317047017635 0ustar andreausers 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 bezocht 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 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. 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. geregisseerd door bewerkt door bewerkt door geïllustreerd door geïnterviewd door ontvangen door door vertaald door bewerkt & vertaald door 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 citeproc-hs-0.3.9/locales/locales-tr-TR.xml0000644000175000001440000002345212223317047017657 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 erişildi ve ve diğerleri anonim anonim de available at by circa c. kaynak baskı baskı ed ve diğerleri gelecek adresinden erişildi ibid. içinde basımda internet kişisel iletişim mektup tarih yok y.y. çevrimiçi sunulan reference references ref. refs. tarihinde scale version 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 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ı l. n. op s ss par kıs böl s.v. s.vv. v vv c c ¶¶ § §§ director directors editör editörler editör editör illustrator illustrators çeviren çevirenler editör & çeviren editörler & çevirenler dir. dirs. ed ed ed. ed. ill. ills. çev. çev. ed. & çev. ed. & çev. directed by editör düzenleyen illustrated by Röportaj yapan to by çeviren düzenleyen & çeviren by dir. ed. ed. illus. ç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ış citeproc-hs-0.3.9/locales/locales-is-IS.xml0000644000175000001440000002343312223317047017632 0ustar andreausers 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 available at 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 version 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 númer númer lína línur skilaboð skilaboð tónverk tónverk blaðsíða blaðsíður málsgrein málsgreinar hluti hlutar hluti hlutar sub verbo sub verbis vers vers bindi bindi b. k. d. mynd. handr. nr. l. n. tónv. bls. bls. málsgr. hl. hl. s.v. s.vv. v. v. bindi bindi ¶¶ § §§ director directors ritstjóri ritstjórar ritstjóri ritstjórar illustrator illustrators þýðandi þýðendur ritstjóri og þýðandi ritstjórar og þýðendur dir. dirs. ritstj. ritstj. ritstj. ritstj. ill. ills. þýð. þýð. ritstj. og þýð. ritstj. og þýð. directed by ritstjóri ritstjóri illustrated by viðtal tók til by þýddi ritstjóri og þýðandi eftir dir. ritst. ritst. illus. þýð. ritst. 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 citeproc-hs-0.3.9/locales/locales-sr-RS.xml0000644000175000001440000002513412223317047017654 0ustar andreausers 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. directed by уредио edited by illustrated by интервјуисао прима by превео edited & translated by by dir. ур. ed. illus. прев. ed. & trans. by Јануар Фебруар Март Април Мај Јуни Јули Август Септембар Октобар Новембар Децембар Јан. Феб. Март Апр. Мај Јуни Јули Авг. Сеп. Окт. Нов. Дец. Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-ca-AD.xml0000644000175000001440000002334312223317046017552 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 accedit 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 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. 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. dirigit per editat per editat per il·lustrat per entrevistat per a per traduït per editat i traduït per 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 citeproc-hs-0.3.9/locales/locales-eu.xml0000644000175000001440000002374512223317046017324 0ustar andreausers 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 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. 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 citeproc-hs-0.3.9/locales/locales-af-ZA.xml0000644000175000001440000002373612223317046017611 0ustar andreausers 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 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 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. directed by onder redaksie van edited by illustrated by interview by to by vertaal deur edited & translated by 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 citeproc-hs-0.3.9/locales/locales-he-IL.xml0000644000175000001440000002406212223317047017603 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 גישה ו and others anonymous anon available at by circa c. cited edition editions ed ואחרים forthcoming מתוך שם בתוך in press internet interview letter no date nd 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 ספר ספרים פרק פרקים טור טורים figure figures folio folios מספר מספרים שורה שורות note notes אופוס אופרה עמוד עמודים paragraph פיסקה part parts section sections sub verbo sub verbis בית בתים כרך כרכים bk chap col fig f no l. n. op 'עמ 'עמ 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 ed. eds. ill. ills. tran trans ed. & tran. eds. & trans. directed by נערך ע"י edited by illustrated by interview by to by תורגם ע"י edited & translated by 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 citeproc-hs-0.3.9/locales/locales-pt-PT.xml0000644000175000001440000002373712223317047017661 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 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 reference references ref. refs. obtido scale versão AD BC « » th st nd rd th th th primeiro segundo terceiro quarto quinto sexto sétimo oitavo nono décimo livro livros capítulo capítulos coluna colunas figura figuras fólio fólios número número linha linhas nota notas opus opera 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 par pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors editor editores editor editors illustrator illustrators tradutor tradutores editor & translator editors & translators dir. dirs. ed eds ed. eds. ill. ills. trad trads ed. & tran. eds. & trans. directed by editado por edited by illustrated by entrevistado por para by traduzido por edited & translated by by dir. ed ed. illus. trad ed. & trans. by 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 citeproc-hs-0.3.9/locales/locales-mn-MN.xml0000644000175000001440000002364312223317047017633 0ustar andreausers 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 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 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by 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 citeproc-hs-0.3.9/locales/locales-vi-VN.xml0000644000175000001440000002417612223317047017652 0ustar andreausers 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 anonymous anon at available at by circa c. cited edition editions ed và c.s. sắp tới từ n.t. trong in press internet interview letter no date không ngày online presented at the reference references ref. refs. truy vấn 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 dòng dòng note notes opus opera trang trang đoạn văn đoạn văn part parts section sections sub verbo sub verbis verse verses volume volumes bk chap col fig f số p.h l. n. op tr tr para pt sec s.v. s.vv. v vv vol vols ¶¶ § §§ director directors biên tập viên biên tập viên editor editors illustrator illustrators biên dịch viên biên dịch viên editor & translator editors & translators dir. dirs. b.t.v b.t.v ed. eds. ill. ills. b.d.v b.d.v ed. & tran. eds. & trans. directed by biên tập bởi edited by illustrated by interview by to by biên dịch bởi edited & translated by by dir. b.t ed. illus. b.d ed. & trans. by 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 Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-it-IT.xml0000644000175000001440000002337712223317047017643 0ustar andreausers 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 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. 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 directed by a cura di edited by illustrated by intervista di a by tradotto da a cura di e tradotto da di 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 citeproc-hs-0.3.9/locales/locales-nb-NO.xml0000644000175000001440000002344412223317047017621 0ustar andreausers 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 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. 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. regissert av redigert av redigert av illustrert av intervjuet av til av oversatt av redigert & oversatt av 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 citeproc-hs-0.3.9/locales/locales-es-ES.xml0000644000175000001440000002346712223317046017630 0ustar andreausers 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á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á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. dirigido por editado por editado por ilustrado por entrevistado por a por traducido por editado y traducido por de 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 citeproc-hs-0.3.9/locales/locales-hr-HR.xml0000644000175000001440000002410012223317047017616 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 pristupljeno i i ostali anonim anon. na pristupačno na od circa c. citirano izdanje izdanja izd. i ostali u pripremi od ibid. u u štampi internet intervju pismo bez datuma bez datuma na internetu predstavljeno na reference reference ref. ref. preuzeto skala verzija AD BC th st nd rd th th th prvi drugi treći četvrti peti šesti sedmi osmi deveti deseti knjiga knjige poglavlje poglavlja kolona kolone crtež crteži folija folije broj brojevi linija linije beleška beleške opus opera stranica stranice paragraf paragrafi deo delova odeljak odeljaka sub verbo sub verbis strofa strofe tom tomova knj pog kol црт fol izd l n op str. str. par deo od s.v. s.vv. s s tom tomova ¶¶ § §§ director directors priređivač priređivači priređivač priređivači ilustrator ilustratori prevodilac prevodioci priređivač & prevodilac priređivači & prevodioci prir. prir. prir. prir. prir. prir. il. il. prev. prev. prir. & prev. prir. & prev. directed by priredio priredio ilustrovao intervjuisao prima od preveo priredio & preveo by by dir. prir. prir. ilus. prev. prir. & prev. by januar februar mart april maj jun jul avgust septembar oktobar novembar decembar jan. feb. mart apr. maj jun jul avg. sep. okt. nov. dec. proleće leto jesen zima citeproc-hs-0.3.9/locales/locales-hu-HU.xml0000644000175000001440000002377412223317047017644 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 elérés és és mások név nélkül nn available at by circa c. idézi edition editions ed et al. megjelenés alatt forrás ibid. in nyomtatás alatt internet interjú levél no date nd online előadás reference references ref. refs. elérés scale version AD BC » « th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth könyv könyv fejezet fejezet oszlop oszlop ábra ábra fóliáns fóliáns szám szám sor sor jegyzet jegyzet opus opera 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 l. n. op o o bek rész szak s.v. s.vv. vsz vsz vol vols ¶¶ § §§ director directors szerkesztő szerkesztő editor editors illustrator illustrators fordító fordító editor & translator editors & translators dir. dirs. szerk szerk ed. eds. ill. ills. ford ford ed. & tran. eds. & trans. directed by szerkesztette edited by illustrated by interjúkészítő címzett by fordította edited & translated by by dir. szerk ed. illus. ford ed. & trans. by 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 Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-zh-TW.xml0000644000175000001440000002367012223317047017662 0ustar andreausers 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. directed by 編者是 edited by illustrated by 訪問者是 授與 by 譯者是 edited & translated by by dir. ed. illus. ed. & trans. by 一月 二月 三月 四月 五月 六月 七月 八月 九月 十月 十一月 十二月 1月 2月 3月 4月 5月 6月 7月 8月 9月 10月 11月 12月 Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-en-US.xml0000644000175000001440000002372712223317046017642 0ustar andreausers 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 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. 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by 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 citeproc-hs-0.3.9/locales/locales-bg-BG.xml0000644000175000001440000002475712223317046017575 0ustar andreausers 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. directed by редактиран от edited by illustrated by интервюиран от до by преведен от edited & translated by by dir. ред ed. illus. прев ed. & trans. by Януари Февруари Март Април Май Юни Юли Август Септември Октомври Ноември Декември Яну Фев Мар Апр Май Юни Юли Авг Сеп Окт Ное Дек Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-fa-IR.xml0000644000175000001440000002536212223317046017606 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 دسترسی و و دیگران ناشناس ناشناس در available at توسط circa c. یادکرد ویرایش ویرایش‌های ویرایش و دیگران forthcoming از همان در زیر چاپ اینترنت مصاحبه نامه بدون تاریخ بدون تاریخ برخط ارائه شده در مرجع مراجع مرجع مراجع retrieved scale version AD BC th st nd rd th th th اول دوم سوم چهارم پنجم ششم هفتم هشتم نهم دهم کتاب کتاب‌های فصل فصل‌های ستون ستون‌های تصویر تصاویر برگ برگ‌های شماره شماره‌های خط خطوط یادداشت یادداشت‌های قطعه قطعات صفحه صفحات پاراگراف پاراگراف‌های بخش بخش‌های قسمت قسمت‌های sub verbo sub verbis بیت بیت‌های جلد جلدهای کتاب فصل ستون تصویر برگ ش l. n. قطعه ص صص پاراگراف بخش قسمت s.v s.vv بیت ابیات ج جج ¶¶ § §§ director directors ویرایشگر ویرایشگران ویرایشگر ویرایشگران illustrator illustrators مترجم مترجمین ویرایشگر و مترجم ویرایشگران و مترجمین dir. dirs. ویرایشگر ویرایشگران ویرایشگر ویرایشگران ill. ills. مترجم مترجمین ویرایشگر و مترجم ویرایشگران و مترجمین directed by edited by ویراسته‌ی illustrated by مصاحبه توسط به by ترجمه‌ی ترجمه و ویراسته‌ی توسط dir. ویراسته‌ی ویراسته‌ی illus. ترجمه‌ی ترجمه و ویراسته‌ی ژانویه فوریه مارس آوریل می ژوئن جولای آگوست سپتامبر اکتبر نوامبر دسامبر ژانویه فوریه مارس آوریل می ژوئن جولای آگوست سپتامبر اکتبر نوامبر دسامبر بهار تابستان پاییز زمستان citeproc-hs-0.3.9/locales/locales-ar-AR.xml0000644000175000001440000002512112223317046017603 0ustar andreausers 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. ترجمة ترجمه واشرف على الطباعه يناير فبراير مارس ابريل مايو يونيو يوليو اغسطس سبتمبر اكتوبر نوفمبر ديسمبر يناير فبراير مارس ابريل مايو يونيو يوليو اغسطس سبتمبر اكتوبر نوفمبر ديسمبر الربيع الصيف الخريف الشتاء citeproc-hs-0.3.9/locales/locales-sl-SI.xml0000644000175000001440000002375712223317047017646 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+00:00 dostopano in in drugi anonimni anon pri available at by circa c. citirano izdaja izdaje iz idr. pred izidom od isto v v tisku internet intervju pismo no date b.d. na spletu predstavljeno na reference references ref. refs. pridobljeno scale version AD BC th st nd rd th th th first second third fourth fifth sixth seventh eighth ninth tenth knjiga knjige poglavje poglavja stolpec stolpci slika slike folio folii številka številke vrstica vrstice opomba opombe opus opera stran strani odstavek odstavki del deli odsek odseki sub verbo sub verbis verz verzi letnik letniki knj pogl sto sl f št l. n. op str str odst del odsk s.v. s.vv. v v let let ¶¶ § §§ director directors urednik uredniki editor editors illustrator illustrators prevajalec prevajalci editor & translator editors & translators dir. dirs. ur ur ed. eds. ill. ills. prev prev ed. & tran. eds. & trans. directed by uredil edited by illustrated by intervjuval za by prevedel edited & translated by by dir. ur ed. illus. prev ed. & trans. 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 Spring Summer Autumn Winter citeproc-hs-0.3.9/locales/locales-sk-SK.xml0000644000175000001440000002371312223317047017637 0ustar andreausers This work is licensed under a Creative Commons Attribution-ShareAlike 3.0 License 2012-07-04T23:31:02+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 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 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. directed by zostavil zostavil illustrated by rozhovor urobil adresát by preložil zostavil & preložil by 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 citeproc-hs-0.3.9/locales/locales-km-KH.xml0000644000175000001440000002473512223317047017623 0ustar andreausers 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. 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. directed by edited by edited by illustrated by interview by to by translated by edited & translated by 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