pandoc-citeproc-0.10.1.4: Supports using pandoc with citeproc

Copyright(c) Andrea Rossato
LicenseBSD-style (see LICENSE)
MaintainerAndrea Rossato <andrea.rossato@unitn.it>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

Text.CSL

Contents

Description

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: http://citationstyles.org/.

This module documents and exports the library API.

Synopsis

Introduction

citeproc-hs provides functions for reading bibliographic databases, for reading and parsing CSL files and for generating citations in an internal format, Formatted, that can be easily rendered into different final formats. At the present time only Pandoc and plain text rendering functions are provided by the library.

The library also provides a wrapper around hs-bibutils, the Haskell bindings to Chris Putnam's bibutils, a library that interconverts between various bibliography formats using a common MODS-format XML intermediate. For more information about hs-bibutils see here: http://hackage.haskell.org/package/hs-bibutils.

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: http://citationstyles.org/.

A (git) repository of styles can be found here: https://github.com/citation-style-language/styles.

Overview: A Simple Example

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:

https://bitbucket.org/bdarcus/citeproc-test/raw/18141149d1d3/styles/apa-x.csl

saved locally as apa-x.csl.

This would be a simple program that formats a list of citations according to that style:

import Text.CSL

cites :: [Cite]
cites = [emptyCite { citeId = "Caso2007"
                   , citeLabel = "page"
                   , citeLocator = "15"}
        ,emptyCite { citeId = "Rossato2006"
                   , citeLabel = "page"
                   , citeLocator = "10"}
        ]

main :: IO ()
main = do
  m <- readBiblioFile "mybibdb.bib"
  s <- readCSLFile Nothing "apa-x.csl"
  let result = citeproc procOpts s m $ [cites]
  putStrLn . unlines . map renderPlain . citations $ result

The result would be:

(Caso, 2007, p. 15; Rossato, 2006, p. 10)

Reading Bibliographic Databases

readBiblioFile :: FilePath -> IO [Reference] Source #

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.

Reference Representation

data Reference Source #

The Reference record.

Constructors

Reference 

Fields

Instances

Eq Reference Source # 
Data Reference Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Reference -> c Reference #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Reference #

toConstr :: Reference -> Constr #

dataTypeOf :: Reference -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Reference) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Reference) #

gmapT :: (forall b. Data b => b -> b) -> Reference -> Reference #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Reference -> r #

gmapQ :: (forall d. Data d => d -> u) -> Reference -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Reference -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Reference -> m Reference #

Read Reference Source # 
Show Reference Source # 
Generic Reference Source # 

Associated Types

type Rep Reference :: * -> * #

ToJSON Reference Source # 
FromJSON Reference Source # 
ToYaml Reference Source # 
type Rep Reference Source # 
type Rep Reference = D1 (MetaData "Reference" "Text.CSL.Reference" "pandoc-citeproc-0.10.1.4-GAoWjevWWAtLTJFVhEkzmU" False) (C1 (MetaCons "Reference" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "refId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) (S1 (MetaSel (Just Symbol "refType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RefType))) ((:*:) (S1 (MetaSel (Just Symbol "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "editor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "translator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "recipient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent]))) ((:*:) (S1 (MetaSel (Just Symbol "interviewer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) ((:*:) (S1 (MetaSel (Just Symbol "composer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "director") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "illustrator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "originalAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent]))) ((:*:) (S1 (MetaSel (Just Symbol "containerAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "collectionEditor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "editorialDirector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent])) (S1 (MetaSel (Just Symbol "reviewedAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Agent]))) ((:*:) (S1 (MetaSel (Just Symbol "issued") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate])) ((:*:) (S1 (MetaSel (Just Symbol "eventDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate])) (S1 (MetaSel (Just Symbol "accessed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate]))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "container") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate])) (S1 (MetaSel (Just Symbol "originalDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate]))) ((:*:) (S1 (MetaSel (Just Symbol "submitted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [RefDate])) (S1 (MetaSel (Just Symbol "title") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "titleShort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "reviewedTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "containerTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "volumeTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "collectionTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "containerTitleShort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "collectionNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "originalTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "publisher") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "originalPublisher") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "publisherPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "originalPublisherPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "authority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "jurisdiction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "archive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))))))) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "archivePlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "archiveLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "event") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "eventPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "page") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "pageFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "numberOfPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "volume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "numberOfVolumes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "issue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "chapterNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "medium") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "status") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "edition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "section") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "source") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) ((:*:) (S1 (MetaSel (Just Symbol "genre") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "note") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "annote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "abstract") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted))) ((:*:) (S1 (MetaSel (Just Symbol "keyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "number") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "references") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatted)) (S1 (MetaSel (Just Symbol "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))) ((:*:) (S1 (MetaSel (Just Symbol "doi") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) ((:*:) (S1 (MetaSel (Just Symbol "isbn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) (S1 (MetaSel (Just Symbol "issn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "pmcid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) (S1 (MetaSel (Just Symbol "pmid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))) ((:*:) (S1 (MetaSel (Just Symbol "callNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) ((:*:) (S1 (MetaSel (Just Symbol "dimensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)) (S1 (MetaSel (Just Symbol "scale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "categories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Literal])) (S1 (MetaSel (Just Symbol "language") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))) ((:*:) (S1 (MetaSel (Just Symbol "citationNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CNum)) ((:*:) (S1 (MetaSel (Just Symbol "firstReferenceNoteNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Just Symbol "citationLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal))))))))))

setNearNote :: Style -> [[Cite]] -> [[Cite]] Source #

CSL Parser, Representation, and Processing

readCSLFile :: Maybe String -> FilePath -> IO Style Source #

Read and parse a CSL style file into a localized sytle.

parseCSL :: String -> Style Source #

Parse a String into a Style (with default locale).

localizeCSL :: Maybe String -> Style -> IO Style Source #

Merge locale into a CSL style.

The Style Types

data Style Source #

The representation of a parsed CSL style.

Instances

Data Style Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Style -> c Style #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style #

toConstr :: Style -> Constr #

dataTypeOf :: Style -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Style) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) #

gmapT :: (forall b. Data b => b -> b) -> Style -> Style #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

Read Style Source # 
Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style Source # 

data Citation Source #

Constructors

Citation 

Fields

Instances

Data Citation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation #

toConstr :: Citation -> Constr #

dataTypeOf :: Citation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Citation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) #

gmapT :: (forall b. Data b => b -> b) -> Citation -> Citation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Citation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Citation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

Read Citation Source # 
Show Citation Source # 
Generic Citation Source # 

Associated Types

type Rep Citation :: * -> * #

Methods

from :: Citation -> Rep Citation x #

to :: Rep Citation x -> Citation #

type Rep Citation Source # 
type Rep Citation = D1 (MetaData "Citation" "Text.CSL.Style" "pandoc-citeproc-0.10.1.4-GAoWjevWWAtLTJFVhEkzmU" False) (C1 (MetaCons "Citation" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "citOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Option])) ((:*:) (S1 (MetaSel (Just Symbol "citSort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Sort])) (S1 (MetaSel (Just Symbol "citLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Layout)))))

data Bibliography Source #

Constructors

Bibliography 

Fields

Instances

Data Bibliography Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bibliography -> c Bibliography #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bibliography #

toConstr :: Bibliography -> Constr #

dataTypeOf :: Bibliography -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bibliography) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bibliography) #

gmapT :: (forall b. Data b => b -> b) -> Bibliography -> Bibliography #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bibliography -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bibliography -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bibliography -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bibliography -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

Read Bibliography Source # 
Show Bibliography Source # 
Generic Bibliography Source # 

Associated Types

type Rep Bibliography :: * -> * #

type Rep Bibliography Source # 
type Rep Bibliography = D1 (MetaData "Bibliography" "Text.CSL.Style" "pandoc-citeproc-0.10.1.4-GAoWjevWWAtLTJFVhEkzmU" False) (C1 (MetaCons "Bibliography" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "bibOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Option])) ((:*:) (S1 (MetaSel (Just Symbol "bibSort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Sort])) (S1 (MetaSel (Just Symbol "bibLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Layout)))))

data Cite Source #

Instances

Eq Cite Source # 

Methods

(==) :: Cite -> Cite -> Bool #

(/=) :: Cite -> Cite -> Bool #

Data Cite Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cite -> c Cite #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cite #

toConstr :: Cite -> Constr #

dataTypeOf :: Cite -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cite) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite) #

gmapT :: (forall b. Data b => b -> b) -> Cite -> Cite #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cite -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cite -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

Show Cite Source # 

Methods

showsPrec :: Int -> Cite -> ShowS #

show :: Cite -> String #

showList :: [Cite] -> ShowS #

Generic Cite Source # 

Associated Types

type Rep Cite :: * -> * #

Methods

from :: Cite -> Rep Cite x #

to :: Rep Cite x -> Cite #

FromJSON Cite Source # 

Methods

parseJSON :: Value -> Parser Cite #

FromJSON [[Cite]] Source # 

Methods

parseJSON :: Value -> Parser [[Cite]] #

type Rep Cite Source # 

newtype Abbreviations Source #

Instances

Data Abbreviations Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abbreviations -> c Abbreviations #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abbreviations #

toConstr :: Abbreviations -> Constr #

dataTypeOf :: Abbreviations -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Abbreviations) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abbreviations) #

gmapT :: (forall b. Data b => b -> b) -> Abbreviations -> Abbreviations #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abbreviations -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abbreviations -> r #

gmapQ :: (forall d. Data d => d -> u) -> Abbreviations -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Abbreviations -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

Read Abbreviations Source # 
Show Abbreviations Source # 
Generic Abbreviations Source # 

Associated Types

type Rep Abbreviations :: * -> * #

FromJSON Abbreviations Source # 
type Rep Abbreviations Source # 
type Rep Abbreviations = D1 (MetaData "Abbreviations" "Text.CSL.Style" "pandoc-citeproc-0.10.1.4-GAoWjevWWAtLTJFVhEkzmU" True) (C1 (MetaCons "Abbreviations" PrefixI True) (S1 (MetaSel (Just Symbol "unAbbreviations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String (Map String (Map String String))))))

High Level Processing

citeproc :: ProcOpts -> Style -> [Reference] -> Citations -> BiblioData Source #

With a Style, a list of References and the list of Citations, produce the Formatted for each citation group and the bibliography.

processCitations :: ProcOpts -> Style -> [Reference] -> Citations -> [Formatted] Source #

With a Style, a list of References and the list of citation groups (the list of citations with their locator), produce the Formatted for each citation group.

processBibliography :: ProcOpts -> Style -> [Reference] -> [Formatted] Source #

With a Style and the list of References produce the Formatted for the bibliography.

data BiblioData Source #

Constructors

BD 

Instances

Data BiblioData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BiblioData -> c BiblioData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BiblioData #

toConstr :: BiblioData -> Constr #

dataTypeOf :: BiblioData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BiblioData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BiblioData) #

gmapT :: (forall b. Data b => b -> b) -> BiblioData -> BiblioData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BiblioData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BiblioData -> r #

gmapQ :: (forall d. Data d => d -> u) -> BiblioData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BiblioData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

Show BiblioData Source # 
Generic BiblioData Source # 

Associated Types

type Rep BiblioData :: * -> * #

type Rep BiblioData Source # 
type Rep BiblioData = D1 (MetaData "BiblioData" "Text.CSL.Style" "pandoc-citeproc-0.10.1.4-GAoWjevWWAtLTJFVhEkzmU" False) (C1 (MetaCons "BD" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "citations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Formatted])) ((:*:) (S1 (MetaSel (Just Symbol "bibliography") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Formatted])) (S1 (MetaSel (Just Symbol "citationIds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))))

The output and the rendering functions

renderPlain :: Formatted -> String Source #

Render the Formatted into a plain text string.