Copyright | (c) Andrea Rossato |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Andrea Rossato <andrea.rossato@unitn.it> |
Stability | unstable |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
The Style types
- readCSLString :: String -> [Inline]
- writeCSLString :: [Inline] -> String
- newtype Formatted = Formatted {
- unFormatted :: [Inline]
- data Style = Style {
- styleVersion :: String
- styleClass :: String
- styleInfo :: Maybe CSInfo
- styleDefaultLocale :: String
- styleLocale :: [Locale]
- styleAbbrevs :: Abbreviations
- csOptions :: [Option]
- csMacros :: [MacroMap]
- citation :: Citation
- biblio :: Maybe Bibliography
- data Locale = Locale {
- localeVersion :: String
- localeLang :: String
- localeOptions :: [Option]
- localeTerms :: [CslTerm]
- localeDate :: [Element]
- mergeLocales :: String -> Locale -> [Locale] -> [Locale]
- data CslTerm = CT {
- cslTerm :: String
- termForm :: Form
- termGender :: Gender
- termGenderForm :: Gender
- termSingular :: String
- termPlural :: String
- termMatch :: String
- newTerm :: CslTerm
- findTerm :: String -> Form -> [CslTerm] -> Maybe CslTerm
- findTerm' :: String -> Form -> Gender -> [CslTerm] -> Maybe CslTerm
- newtype Abbreviations = Abbreviations {}
- type MacroMap = (String, [Element])
- data Citation = Citation {}
- data Bibliography = Bibliography {}
- type Option = (String, String)
- mergeOptions :: [Option] -> [Option] -> [Option]
- data Layout = Layout {}
- 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
- data IfThen = IfThen Condition Match [Element]
- data Condition = Condition {
- isType :: [String]
- isSet :: [String]
- isNumeric :: [String]
- isUncertainDate :: [String]
- isPosition :: [String]
- disambiguation :: [String]
- isLocator :: [String]
- type Delimiter = String
- data Match
- match :: Match -> [Bool] -> Bool
- data DatePart = DatePart {
- dpName :: String
- dpForm :: String
- dpRangeDelim :: String
- dpFormatting :: Formatting
- defaultDate :: [DatePart]
- data Sort
- data Sorting
- compare' :: String -> String -> Ordering
- data Form
- data Gender
- data NumericForm
- = Numeric
- | Ordinal
- | Roman
- | LongOrdinal
- data DateForm
- data Plural
- = Contextual
- | Always
- | Never
- data Name
- type NameAttrs = [(String, String)]
- data NamePart = NamePart String Formatting
- isPlural :: Plural -> Int -> Bool
- isName :: Name -> Bool
- isNames :: Element -> Bool
- hasEtAl :: [Name] -> Bool
- data Formatting = Formatting {
- prefix :: String
- suffix :: String
- fontFamily :: String
- fontStyle :: String
- fontVariant :: String
- fontWeight :: String
- textDecoration :: String
- verticalAlign :: String
- textCase :: String
- display :: String
- quotes :: Quote
- stripPeriods :: Bool
- noCase :: Bool
- noDecor :: Bool
- hyperlink :: String
- emptyFormatting :: Formatting
- rmTitleCase :: Formatting -> Formatting
- rmTitleCase' :: Output -> Output
- data Quote
- mergeFM :: Formatting -> Formatting -> Formatting
- data CSInfo = CSInfo {
- csiTitle :: String
- csiAuthor :: CSAuthor
- csiCategories :: [CSCategory]
- csiId :: String
- csiUpdated :: String
- data CSAuthor = CSAuthor String String String
- data CSCategory = CSCategory String String String
- data CiteprocError
- data Output
- = ONull
- | OSpace
- | OPan [Inline]
- | ODel String
- | OStr String Formatting
- | OErr CiteprocError
- | OLabel String Formatting
- | ONum Int Formatting
- | OCitNum Int Formatting
- | OCitLabel String Formatting
- | ODate [Output]
- | OYear String String Formatting
- | OYearSuf String String [Output] Formatting
- | OName Agent [Output] [[Output]] Formatting
- | OContrib String String [Output] [Output] [[Output]]
- | OLoc [Output] Formatting
- | Output [Output] Formatting
- type Citations = [[Cite]]
- data Cite = Cite {}
- emptyCite :: Cite
- data CitationGroup = CG [(Cite, Output)] Formatting Delimiter [(Cite, Output)]
- data BiblioData = BD {
- citations :: [Formatted]
- bibliography :: [Formatted]
- citationIds :: [String]
- data CiteData = CD {}
- data NameData = ND {
- nameKey :: Agent
- nameCollision :: [Output]
- nameDisambData :: [[Output]]
- nameDataSolved :: [Output]
- isPunctuationInQuote :: Style -> Bool
- object' :: [Pair] -> Value
- data Agent = Agent {}
- emptyAgent :: Agent
Documentation
readCSLString :: String -> [Inline] Source #
writeCSLString :: [Inline] -> String Source #
Formatted | |
|
The representation of a parsed CSL style.
Style | |
|
Locale | |
|
CT | |
|
newtype Abbreviations Source #
Condition | |
|
DatePart | |
|
defaultDate :: [DatePart] Source #
data NumericForm Source #
data Formatting Source #
Formatting | |
|
rmTitleCase :: Formatting -> Formatting Source #
rmTitleCase' :: Output -> Output Source #
mergeFM :: Formatting -> Formatting -> Formatting Source #
CSInfo | |
|
data CSCategory Source #
data CiteprocError Source #
The Output
generated by the evaluation of a style. Must be
further processed for disambiguation and collapsing.
ONull | |
OSpace | |
OPan [Inline] | |
ODel String | A delimiter string. |
OStr String Formatting | A simple |
OErr CiteprocError | Warning message |
OLabel String Formatting | A label used for roles |
ONum Int Formatting | A number (used to count contributors) |
OCitNum Int Formatting | The citation number |
OCitLabel String Formatting | The citation label |
ODate [Output] | A (possibly) ranged date |
OYear String String Formatting | The year and the citeId |
OYearSuf String String [Output] Formatting | The year suffix, the citeId and a holder for collision data |
OName Agent [Output] [[Output]] Formatting | A (family) name with the list of given names. |
OContrib String String [Output] [Output] [[Output]] | The citation key, the role (author, editor, etc.), the contributor(s), the output needed for year suf. disambiguation, and everything used for name disambiguation. |
OLoc [Output] Formatting | The citation's locator |
Output [Output] Formatting | Some nested |
Cite | |
|
data CitationGroup Source #
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 BiblioData Source #
BD | |
|
A record with all the data to produce the Formatted
of a
citation: the citation key, the part of the formatted citation that
may be colliding with other citations, the form of the citation
when a year suffix is used for disambiguation , the data to
disambiguate it (all possible contributors and all possible given
names), and, after processing, the disambiguated citation and its
year, initially empty.
ND | |
|
isPunctuationInQuote :: Style -> Bool Source #
Agent | |
|
emptyAgent :: Agent Source #