Portability | unportable |
---|---|
Stability | unstable |
Maintainer | Andrea Rossato <andrea.rossato@unitn.it> |
Text.CSL.Style
Description
The Style types
- data Style = Style {
- styleVersion :: String
- styleClass :: String
- styleInfo :: Maybe CSInfo
- styleDefaultLocale :: String
- styleLocale :: [Locale]
- csOptions :: [Option]
- csMacros :: [MacroMap]
- citation :: Citation
- biblio :: Maybe Bibliography
- data Locale = Locale {
- localeVersion :: String
- localeLang :: String
- localeOptions :: [Option]
- localeTermMap :: [TermMap]
- localeDate :: [Element]
- mergeLocales :: String -> Locale -> [Locale] -> [Locale]
- type TermMap = ((String, Form), (String, String))
- 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
- | ShortNames [String] Formatting Delimiter
- | 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 NumericForm
- = Numeric
- | Ordinal
- | Roman
- | LongOrdinal
- data DateForm
- = TextDate
- | NumericDate
- | NoFormDate
- data Plural
- = Contextual
- | Always
- | Never
- data Name
- type NameAttrs = [(String, String)]
- data NamePart = NamePart String Formatting
- 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 :: Bool
- stripPeriods :: Bool
- noCase :: Bool
- noDecor :: Bool
- emptyFormatting :: Formatting
- unsetAffixes :: Formatting -> Formatting
- 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 FormattedOutput
- = FO Formatting [FormattedOutput]
- | FN String Formatting
- | FS String Formatting
- | FDel String
- | FPan [Inline]
- | FNull
- data Output
- = ONull
- | OSpace
- | OPan [Inline]
- | ODel String
- | OStr String Formatting
- | ONum Int Formatting
- | OCitNum Int Formatting
- | OYear String String Formatting
- | OYearSuf String String [Output] Formatting
- | OName String [Output] [[Output]] Formatting
- | OContrib String String [Output] [Output] [[Output]]
- | Output [Output] Formatting
- data Affix
- = PlainText String
- | PandocText [Inline]
- 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
- emptyAffix :: Affix
- emptyCite :: Cite
- data CitationGroup = CG [(Cite, Output)] Formatting Delimiter [(Cite, Output)]
- data BiblioData = BD {
- citations :: [[FormattedOutput]]
- bibliography :: [[FormattedOutput]]
- data CiteData = CD {}
- data NameData = ND {
- nameKey :: String
- nameCollision :: [Output]
- nameDisambData :: [[Output]]
- nameDataSolved :: [Output]
- formatOutputList :: [Output] -> [FormattedOutput]
- formatOutput :: Output -> FormattedOutput
- mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a]
- proc :: (Typeable a, Data b) => (a -> a) -> b -> b
- query :: (Typeable a, Data b) => (a -> [c]) -> b -> [c]
- rmGivenNames :: Output -> Output
- rmNameHash :: Output -> Output
- rmContribs :: Output -> Output
- addGivenNames :: [Output] -> [Output]
- addYearSuffix :: Output -> Output
- hasYear :: Output -> Bool
- hasYearSuf :: Output -> Bool
- betterThen :: Eq a => [a] -> [a] -> [a]
Documentation
The representation of a parsed CSL style.
Constructors
Style | |
Fields
|
Constructors
Locale | |
Fields
|
mergeOptions :: [Option] -> [Option] -> [Option]Source
Constructors
Constructors
Condition | |
Fields
|
Constructors
DatePart | |
Fields
|
Constructors
Ascending String | |
Descending String |
data NumericForm Source
Constructors
Numeric | |
Ordinal | |
Roman | |
LongOrdinal |
Constructors
TextDate | |
NumericDate | |
NoFormDate |
Constructors
Contextual | |
Always | |
Never |
Constructors
Name Form Formatting NameAttrs Delimiter [NamePart] | |
NameLabel Form Formatting Plural | |
EtAl Formatting String |
Constructors
NamePart String Formatting |
data Formatting Source
Constructors
Formatting | |
Fields
|
mergeFM :: Formatting -> Formatting -> FormattingSource
Constructors
CSInfo | |
Fields
|
data CSCategory Source
Constructors
CSCategory String String String |
data FormattedOutput Source
The formatted output, produced after post-processing the evaluated citations.
Constructors
FO Formatting [FormattedOutput] | |
FN String Formatting | |
FS String Formatting | |
FDel String | |
FPan [Inline] | |
FNull |
Instances
The Output
generated by the evaluation of a style. Must be
further processed for disambiguation and collapsing.
Constructors
ONull | |
OSpace | |
OPan [Inline] | |
ODel String | A delimiter string. |
OStr String Formatting | A simple |
ONum Int Formatting | A number (used to count contributors) |
OCitNum Int Formatting | The citation number |
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. |
Output [Output] Formatting | Some nested |
Constructors
PlainText String | |
PandocText [Inline] |
Constructors
Cite | |
Fields
|
data CitationGroup Source
A citation group: a list of evaluated citations, the Formatting
to be applied to them, and the Delimiter
between individual
citations.
data BiblioData Source
Constructors
BD | |
Fields
|
Instances
A record with all the data to produce the FormattedOutput
of a
citation: the citation key, the part of the citation that may be
colliding with other citations (the list of contributors for the
same year), the data to disambiguate it (all possible contributors
and all possible given names), and the disambiguated citation and
its year.
Constructors
CD | |
Constructors
ND | |
Fields
|
formatOutputList :: [Output] -> [FormattedOutput]Source
formatOutput :: Output -> FormattedOutputSource
Convert evaluated Output
into FormattedOutput
, ready for the
output filters.
mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a]Source
Map the evaluated output of a citation group.
rmNameHash :: Output -> OutputSource
rmContribs :: Output -> OutputSource
Removes all contributors' names.
addGivenNames :: [Output] -> [Output]Source
Add, with proc
, a give name to the family name. Needed for
disambiguation.
addYearSuffix :: Output -> OutputSource
Add the year suffix to the year. Needed for disambiguation.
hasYearSuf :: Output -> BoolSource
betterThen :: Eq a => [a] -> [a] -> [a]Source