Safe Haskell | None |
---|---|
Language | Haskell2010 |
Citeproc.Types
Synopsis
- newtype CiteprocOptions = CiteprocOptions {
- linkCitations :: Bool
- defaultCiteprocOptions :: CiteprocOptions
- class (Semigroup a, Monoid a, Show a, Eq a, Ord a) => CiteprocOutput a where
- toText :: a -> Text
- fromText :: Text -> a
- dropTextWhile :: (Char -> Bool) -> a -> a
- dropTextWhileEnd :: (Char -> Bool) -> a -> a
- addFontVariant :: FontVariant -> a -> a
- addFontStyle :: FontStyle -> a -> a
- addFontWeight :: FontWeight -> a -> a
- addTextDecoration :: TextDecoration -> a -> a
- addVerticalAlign :: VerticalAlign -> a -> a
- addTextCase :: Maybe Lang -> TextCase -> a -> a
- addDisplay :: DisplayStyle -> a -> a
- addQuotes :: a -> a
- movePunctuationInsideQuotes :: a -> a
- inNote :: a -> a
- mapText :: (Text -> Text) -> a -> a
- addHyperlink :: Text -> a -> a
- addFormatting :: CiteprocOutput a => Formatting -> a -> a
- data CiteprocError
- = CiteprocXMLError Text
- | CiteprocParseError Text
- | CiteprocLocaleNotFound Text
- prettyCiteprocError :: CiteprocError -> Text
- newtype ItemId = ItemId {
- unItemId :: Text
- data CitationItem a = CitationItem {
- citationItemId :: ItemId
- citationItemLabel :: Maybe Text
- citationItemLocator :: Maybe Text
- citationItemType :: CitationItemType
- citationItemPrefix :: Maybe a
- citationItemSuffix :: Maybe a
- data CitationItemType
- data Citation a = Citation {
- citationId :: Maybe Text
- citationNoteNumber :: Maybe Int
- citationItems :: [CitationItem a]
- data ElementType a
- data Element a = Element (ElementType a) Formatting
- data NumberForm
- data Pluralize
- data DateType
- data Date = Date {
- dateParts :: [DateParts]
- dateCirca :: Bool
- dateSeason :: Maybe Int
- dateLiteral :: Maybe Text
- rawDateEDTF :: Text -> Maybe Date
- newtype DateParts = DateParts [Int]
- data ShowDateParts
- data DPName
- data DPForm
- data DP = DP {
- dpName :: DPName
- dpForm :: DPForm
- dpRangeDelimiter :: Text
- dpFormatting :: Formatting
- data VariableForm
- data TextType
- = TextVariable VariableForm Variable
- | TextMacro Text
- | TextTerm Term
- | TextValue Text
- data NameFormat = NameFormat {
- nameGivenFormatting :: Maybe Formatting
- nameFamilyFormatting :: Maybe Formatting
- nameAndStyle :: Maybe TermForm
- nameDelimiter :: Text
- nameDelimiterPrecedesEtAl :: DelimiterPrecedes
- nameDelimiterPrecedesLast :: DelimiterPrecedes
- nameEtAlMin :: Maybe Int
- nameEtAlUseFirst :: Maybe Int
- nameEtAlSubsequentUseFirst :: Maybe Int
- nameEtAlSubsequentMin :: Maybe Int
- nameEtAlUseLast :: Bool
- nameForm :: NameForm
- nameInitialize :: Bool
- nameInitializeWith :: Maybe Text
- nameAsSortOrder :: Maybe NameAsSortOrder
- nameSortSeparator :: Text
- defaultNameFormat :: NameFormat
- data NameAsSortOrder
- data NamesFormat = NamesFormat {
- namesLabel :: Maybe (TermForm, Pluralize, Formatting)
- namesEtAl :: Maybe (Text, Formatting)
- namesName :: Maybe (NameFormat, Formatting)
- namesLabelBeforeName :: Bool
- data NameForm
- data Name = Name {
- nameFamily :: Maybe Text
- nameGiven :: Maybe Text
- nameDroppingParticle :: Maybe Text
- nameNonDroppingParticle :: Maybe Text
- nameSuffix :: Maybe Text
- nameCommaSuffix :: Bool
- nameStaticOrdering :: Bool
- nameLiteral :: Maybe Text
- extractParticles :: Name -> Name
- isByzantineName :: Name -> Bool
- data DelimiterPrecedes
- data Condition
- data Position
- data Match
- data Formatting = Formatting {
- formatLang :: Maybe Lang
- formatFontStyle :: Maybe FontStyle
- formatFontVariant :: Maybe FontVariant
- formatFontWeight :: Maybe FontWeight
- formatTextDecoration :: Maybe TextDecoration
- formatVerticalAlign :: Maybe VerticalAlign
- formatPrefix :: Maybe Text
- formatSuffix :: Maybe Text
- formatDisplay :: Maybe DisplayStyle
- formatTextCase :: Maybe TextCase
- formatDelimiter :: Maybe Text
- formatStripPeriods :: Bool
- formatQuotes :: Bool
- formatAffixesInside :: Bool
- data FontStyle
- data FontVariant
- data FontWeight
- data TextDecoration
- data VerticalAlign
- data DisplayStyle
- data TextCase
- data DemoteNonDroppingParticle
- data StyleOptions = StyleOptions {
- styleIsNoteStyle :: Bool
- styleDefaultLocale :: Maybe Lang
- styleDemoteNonDroppingParticle :: DemoteNonDroppingParticle
- styleInitializeWithHyphen :: Bool
- stylePageRangeFormat :: Maybe PageRangeFormat
- stylePageRangeDelimiter :: Maybe Text
- styleDisambiguation :: DisambiguationStrategy
- styleNearNoteDistance :: Maybe Int
- styleCiteGroupDelimiter :: Maybe Text
- styleLineSpacing :: Maybe Int
- styleEntrySpacing :: Maybe Int
- styleHangingIndent :: Bool
- styleSecondFieldAlign :: Maybe SecondFieldAlign
- styleSubsequentAuthorSubstitute :: Maybe SubsequentAuthorSubstitute
- styleUsesYearSuffixVariable :: Bool
- data SubsequentAuthorSubstitute = SubsequentAuthorSubstitute Text SubsequentAuthorSubstituteRule
- data SubsequentAuthorSubstituteRule
- data SecondFieldAlign
- data PageRangeFormat
- data Style a = Style {
- styleCslVersion :: (Int, Int, Int)
- styleOptions :: StyleOptions
- styleCitation :: Layout a
- styleBibliography :: Maybe (Layout a)
- styleLocales :: [Locale]
- styleAbbreviations :: Maybe Abbreviations
- data TermMatch
- data TermGender
- data TermNumber
- data TermForm
- data Term = Term {
- termName :: Text
- termForm :: TermForm
- termNumber :: Maybe TermNumber
- termGender :: Maybe TermGender
- termGenderForm :: Maybe TermGender
- termMatch :: Maybe TermMatch
- emptyTerm :: Term
- data SortDirection
- data SortKey a
- data SortKeyValue = SortKeyValue SortDirection (Maybe [Text])
- data LayoutOptions = LayoutOptions {
- layoutCollapse :: Maybe Collapsing
- layoutYearSuffixDelimiter :: Maybe Text
- layoutAfterCollapseDelimiter :: Maybe Text
- data Collapsing
- data Layout a = Layout {
- layoutOptions :: LayoutOptions
- layoutFormatting :: Formatting
- layoutElements :: [Element a]
- layoutSortKeys :: [SortKey a]
- data DisambiguationStrategy = DisambiguationStrategy {
- disambiguateAddNames :: Bool
- disambiguateAddGivenNames :: Maybe GivenNameDisambiguationRule
- disambiguateAddYearSuffix :: Bool
- data GivenNameDisambiguationRule
- data Lang = Lang {
- langLanguage :: Text
- langScript :: Maybe Text
- langRegion :: Maybe Text
- langVariants :: [Text]
- langExtensions :: [(Text, [(Text, Text)])]
- langPrivateUse :: [Text]
- parseLang :: Text -> Either String Lang
- renderLang :: Lang -> Text
- data Locale = Locale {
- localeLanguage :: Maybe Lang
- localePunctuationInQuote :: Maybe Bool
- localeLimitDayOrdinalsToDay1 :: Maybe Bool
- localeDate :: Map DateType (Element Text)
- localeTerms :: Map Text [(Term, Text)]
- data DisambiguationData = DisambiguationData {
- disambYearSuffix :: Maybe Int
- disambNameMap :: Map Name NameHints
- disambEtAlNames :: Maybe Int
- disambCondition :: Bool
- data NameHints
- data Reference a = Reference {
- referenceId :: ItemId
- referenceType :: Text
- referenceDisambiguation :: Maybe DisambiguationData
- referenceVariables :: Map Variable (Val a)
- newtype ReferenceMap a = ReferenceMap {
- unReferenceMap :: Map ItemId (Reference a)
- makeReferenceMap :: [Reference a] -> ([Reference a], ReferenceMap a)
- lookupReference :: ItemId -> ReferenceMap a -> Maybe (Reference a)
- data Val a
- valToText :: CiteprocOutput a => Val a -> Maybe Text
- data Variable
- toVariable :: Text -> Variable
- fromVariable :: Variable -> Text
- lookupVariable :: CiteprocOutput a => Variable -> Reference a -> Maybe (Val a)
- data Output a
- = Formatted Formatting [Output a]
- | InNote (Output a)
- | Literal a
- | Tagged Tag (Output a)
- | NullOutput
- data Tag
- outputToText :: CiteprocOutput a => Output a -> Text
- renderOutput :: CiteprocOutput a => CiteprocOptions -> Output a -> a
- grouped :: [Output a] -> Output a
- formatted :: Formatting -> [Output a] -> Output a
- readAsInt :: Text -> Maybe Int
- variableType :: Variable -> VariableType
- data VariableType
- data Abbreviations
- lookupAbbreviation :: CiteprocOutput a => Variable -> Val a -> Abbreviations -> Maybe (Val a)
- data Result a = Result {
- resultCitations :: [a]
- resultBibliography :: [(Text, a)]
- resultWarnings :: [Text]
- data Inputs a = Inputs {
- inputsCitations :: Maybe [Citation a]
- inputsReferences :: Maybe [Reference a]
- inputsStyle :: Maybe Text
- inputsAbbreviations :: Maybe Abbreviations
- inputsLang :: Maybe Lang
Documentation
newtype CiteprocOptions Source #
Options affecting the output in ways that go beyond what can be specified in styles.
Constructors
CiteprocOptions | |
Fields
|
Instances
Eq CiteprocOptions Source # | |
Defined in Citeproc.Types Methods (==) :: CiteprocOptions -> CiteprocOptions -> Bool (/=) :: CiteprocOptions -> CiteprocOptions -> Bool | |
Show CiteprocOptions Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> CiteprocOptions -> ShowS show :: CiteprocOptions -> String showList :: [CiteprocOptions] -> ShowS |
class (Semigroup a, Monoid a, Show a, Eq a, Ord a) => CiteprocOutput a where Source #
CSL styles require certain formatting transformations to
be defined. These are defined in the CiteprocOutput
class.
The library may be used with any structured format that defines
these operations. See the CslJson
module for an instance
that corresponds to the markup allowed in CSL JSON. See
the Pandoc
module for an instance for Pandoc Inlines
.
Methods
fromText :: Text -> a Source #
dropTextWhile :: (Char -> Bool) -> a -> a Source #
dropTextWhileEnd :: (Char -> Bool) -> a -> a Source #
addFontVariant :: FontVariant -> a -> a Source #
addFontStyle :: FontStyle -> a -> a Source #
addFontWeight :: FontWeight -> a -> a Source #
addTextDecoration :: TextDecoration -> a -> a Source #
addVerticalAlign :: VerticalAlign -> a -> a Source #
addTextCase :: Maybe Lang -> TextCase -> a -> a Source #
addDisplay :: DisplayStyle -> a -> a Source #
movePunctuationInsideQuotes :: a -> a Source #
mapText :: (Text -> Text) -> a -> a Source #
addHyperlink :: Text -> a -> a Source #
Instances
addFormatting :: CiteprocOutput a => Formatting -> a -> a Source #
data CiteprocError Source #
Constructors
CiteprocXMLError Text | |
CiteprocParseError Text | |
CiteprocLocaleNotFound Text |
Instances
Eq CiteprocError Source # | |
Defined in Citeproc.Types | |
Show CiteprocError Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> CiteprocError -> ShowS show :: CiteprocError -> String showList :: [CiteprocError] -> ShowS |
prettyCiteprocError :: CiteprocError -> Text Source #
The identifier used to identify a work in a bibliographic database.
Instances
Eq ItemId Source # | |
Ord ItemId Source # | |
Show ItemId Source # | |
Semigroup ItemId Source # | |
Monoid ItemId Source # | |
FromJSON ItemId Source # | |
Defined in Citeproc.Types | |
ToJSON ItemId Source # | |
Defined in Citeproc.Types Methods toEncoding :: ItemId -> Encoding toJSONList :: [ItemId] -> Value toEncodingList :: [ItemId] -> Encoding |
data CitationItem a Source #
The part of a citation corresponding to a single work, possibly including a label, locator, prefix and suffix.
Constructors
CitationItem | |
Fields
|
Instances
data CitationItemType Source #
Constructors
AuthorOnly | e.g., Smith |
SuppressAuthor | e.g., (2000, p. 30) |
NormalCite | e.g., (Smith 2000, p. 30) |
Instances
A citation (which may include several items, e.g.
in (Smith 2000; Jones 2010, p. 30)
).
Constructors
Citation | |
Fields
|
Instances
Eq a => Eq (Citation a) Source # | |
Ord a => Ord (Citation a) Source # | |
Show a => Show (Citation a) Source # | |
FromJSON a => FromJSON (Citation a) Source # | |
Defined in Citeproc.Types | |
ToJSON a => ToJSON (Citation a) Source # | |
Defined in Citeproc.Types Methods toEncoding :: Citation a -> Encoding toJSONList :: [Citation a] -> Value toEncodingList :: [Citation a] -> Encoding |
data ElementType a Source #
Constructors
EText TextType | |
EDate Variable DateType (Maybe ShowDateParts) [DP] | |
ENumber Variable NumberForm | |
ENames [Variable] NamesFormat [Element a] | |
ELabel Variable TermForm Pluralize | |
EGroup Bool [Element a] | |
EChoose [(Match, [Condition], [Element a])] |
Instances
Eq (ElementType a) Source # | |
Defined in Citeproc.Types | |
Show (ElementType a) Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> ElementType a -> ShowS show :: ElementType a -> String showList :: [ElementType a] -> ShowS |
Constructors
Element (ElementType a) Formatting |
Instances
data NumberForm Source #
Constructors
NumberNumeric | |
NumberOrdinal | |
NumberLongOrdinal | |
NumberRoman |
Instances
Eq NumberForm Source # | |
Defined in Citeproc.Types | |
Show NumberForm Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> NumberForm -> ShowS show :: NumberForm -> String showList :: [NumberForm] -> ShowS |
Constructors
ContextualPluralize | |
AlwaysPluralize | |
NeverPluralize |
Constructors
LocalizedNumeric | |
LocalizedText | |
NonLocalized |
Constructors
Date | |
Fields
|
Instances
Eq Date Source # | |
Ord Date Source # | |
Show Date Source # | |
FromJSON Date Source # | |
Defined in Citeproc.Types | |
ToJSON Date Source # | |
Defined in Citeproc.Types Methods toEncoding :: Date -> Encoding toJSONList :: [Date] -> Value toEncodingList :: [Date] -> Encoding |
rawDateEDTF :: Text -> Maybe Date Source #
Constructors
DateParts [Int] |
Instances
Eq DateParts Source # | |
Ord DateParts Source # | |
Defined in Citeproc.Types | |
Show DateParts Source # | |
FromJSON DateParts Source # | |
Defined in Citeproc.Types | |
ToJSON DateParts Source # | |
Defined in Citeproc.Types Methods toEncoding :: DateParts -> Encoding toJSONList :: [DateParts] -> Value toEncodingList :: [DateParts] -> Encoding |
data ShowDateParts Source #
Constructors
YearMonthDay | |
YearMonth | |
Year |
Instances
Eq ShowDateParts Source # | |
Defined in Citeproc.Types | |
Show ShowDateParts Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> ShowDateParts -> ShowS show :: ShowDateParts -> String showList :: [ShowDateParts] -> ShowS |
Constructors
DPNumeric | |
DPNumericLeadingZeros | |
DPOrdinal | |
DPLong | |
DPShort |
Constructors
DP | |
Fields
|
data VariableForm Source #
Instances
Eq VariableForm Source # | |
Defined in Citeproc.Types | |
Show VariableForm Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> VariableForm -> ShowS show :: VariableForm -> String showList :: [VariableForm] -> ShowS |
Constructors
TextVariable VariableForm Variable | |
TextMacro Text | |
TextTerm Term | |
TextValue Text |
data NameFormat Source #
Constructors
NameFormat | |
Fields
|
Instances
Eq NameFormat Source # | |
Defined in Citeproc.Types | |
Show NameFormat Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> NameFormat -> ShowS show :: NameFormat -> String showList :: [NameFormat] -> ShowS |
data NameAsSortOrder Source #
Constructors
NameAsSortOrderFirst | |
NameAsSortOrderAll |
Instances
Eq NameAsSortOrder Source # | |
Defined in Citeproc.Types Methods (==) :: NameAsSortOrder -> NameAsSortOrder -> Bool (/=) :: NameAsSortOrder -> NameAsSortOrder -> Bool | |
Show NameAsSortOrder Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> NameAsSortOrder -> ShowS show :: NameAsSortOrder -> String showList :: [NameAsSortOrder] -> ShowS |
data NamesFormat Source #
Constructors
NamesFormat | |
Fields
|
Instances
Eq NamesFormat Source # | |
Defined in Citeproc.Types | |
Show NamesFormat Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> NamesFormat -> ShowS show :: NamesFormat -> String showList :: [NamesFormat] -> ShowS |
Constructors
Name | |
Fields
|
Instances
Eq Name Source # | |
Ord Name Source # | |
Show Name Source # | |
FromJSON Name Source # | |
Defined in Citeproc.Types | |
ToJSON Name Source # | |
Defined in Citeproc.Types Methods toEncoding :: Name -> Encoding toJSONList :: [Name] -> Value toEncodingList :: [Name] -> Encoding |
extractParticles :: Name -> Name Source #
isByzantineName :: Name -> Bool Source #
data DelimiterPrecedes Source #
Instances
Eq DelimiterPrecedes Source # | |
Defined in Citeproc.Types Methods (==) :: DelimiterPrecedes -> DelimiterPrecedes -> Bool (/=) :: DelimiterPrecedes -> DelimiterPrecedes -> Bool | |
Show DelimiterPrecedes Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> DelimiterPrecedes -> ShowS show :: DelimiterPrecedes -> String showList :: [DelimiterPrecedes] -> ShowS |
Constructors
FirstPosition | |
IbidWithLocator | |
Ibid | |
NearNote | |
Subsequent |
data Formatting Source #
Constructors
Formatting | |
Fields
|
Instances
Eq Formatting Source # | |
Defined in Citeproc.Types | |
Show Formatting Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> Formatting -> ShowS show :: Formatting -> String showList :: [Formatting] -> ShowS | |
Semigroup Formatting Source # | |
Defined in Citeproc.Types Methods (<>) :: Formatting -> Formatting -> Formatting sconcat :: NonEmpty Formatting -> Formatting stimes :: Integral b => b -> Formatting -> Formatting | |
Monoid Formatting Source # | |
Defined in Citeproc.Types Methods mempty :: Formatting mappend :: Formatting -> Formatting -> Formatting mconcat :: [Formatting] -> Formatting |
Constructors
NormalFont | |
ItalicFont | |
ObliqueFont |
data FontVariant Source #
Constructors
NormalVariant | |
SmallCapsVariant |
Instances
Eq FontVariant Source # | |
Defined in Citeproc.Types | |
Show FontVariant Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> FontVariant -> ShowS show :: FontVariant -> String showList :: [FontVariant] -> ShowS |
data FontWeight Source #
Constructors
NormalWeight | |
BoldWeight | |
LightWeight |
Instances
Eq FontWeight Source # | |
Defined in Citeproc.Types | |
Show FontWeight Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> FontWeight -> ShowS show :: FontWeight -> String showList :: [FontWeight] -> ShowS |
data TextDecoration Source #
Constructors
NoDecoration | |
UnderlineDecoration |
Instances
Eq TextDecoration Source # | |
Defined in Citeproc.Types Methods (==) :: TextDecoration -> TextDecoration -> Bool (/=) :: TextDecoration -> TextDecoration -> Bool | |
Show TextDecoration Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> TextDecoration -> ShowS show :: TextDecoration -> String showList :: [TextDecoration] -> ShowS |
data VerticalAlign Source #
Constructors
BaselineAlign | |
SupAlign | |
SubAlign |
Instances
Eq VerticalAlign Source # | |
Defined in Citeproc.Types | |
Show VerticalAlign Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> VerticalAlign -> ShowS show :: VerticalAlign -> String showList :: [VerticalAlign] -> ShowS |
data DisplayStyle Source #
Constructors
DisplayBlock | |
DisplayLeftMargin | |
DisplayRightInline | |
DisplayIndent |
Instances
Eq DisplayStyle Source # | |
Defined in Citeproc.Types | |
Show DisplayStyle Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> DisplayStyle -> ShowS show :: DisplayStyle -> String showList :: [DisplayStyle] -> ShowS |
Constructors
Lowercase | |
Uppercase | |
CapitalizeFirst | |
CapitalizeAll | |
SentenceCase | |
TitleCase |
data DemoteNonDroppingParticle Source #
Constructors
DemoteDisplayAndSort | |
DemoteSortOnly | |
DemoteNever |
Instances
Eq DemoteNonDroppingParticle Source # | |
Defined in Citeproc.Types Methods (==) :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool (/=) :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool | |
Show DemoteNonDroppingParticle Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> DemoteNonDroppingParticle -> ShowS show :: DemoteNonDroppingParticle -> String showList :: [DemoteNonDroppingParticle] -> ShowS |
data StyleOptions Source #
Constructors
StyleOptions | |
Fields
|
Instances
Eq StyleOptions Source # | |
Defined in Citeproc.Types | |
Show StyleOptions Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> StyleOptions -> ShowS show :: StyleOptions -> String showList :: [StyleOptions] -> ShowS |
data SubsequentAuthorSubstitute Source #
Constructors
SubsequentAuthorSubstitute Text SubsequentAuthorSubstituteRule |
Instances
Eq SubsequentAuthorSubstitute Source # | |
Defined in Citeproc.Types Methods (==) :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool (/=) :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool | |
Show SubsequentAuthorSubstitute Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> SubsequentAuthorSubstitute -> ShowS show :: SubsequentAuthorSubstitute -> String showList :: [SubsequentAuthorSubstitute] -> ShowS |
data SubsequentAuthorSubstituteRule Source #
Constructors
CompleteAll | |
CompleteEach | |
PartialEach | |
PartialFirst |
Instances
Eq SubsequentAuthorSubstituteRule Source # | |
Defined in Citeproc.Types Methods (==) :: SubsequentAuthorSubstituteRule -> SubsequentAuthorSubstituteRule -> Bool (/=) :: SubsequentAuthorSubstituteRule -> SubsequentAuthorSubstituteRule -> Bool | |
Show SubsequentAuthorSubstituteRule Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> SubsequentAuthorSubstituteRule -> ShowS show :: SubsequentAuthorSubstituteRule -> String showList :: [SubsequentAuthorSubstituteRule] -> ShowS |
data SecondFieldAlign Source #
Constructors
SecondFieldAlignFlush | |
SecondFieldAlignMargin |
Instances
Eq SecondFieldAlign Source # | |
Defined in Citeproc.Types Methods (==) :: SecondFieldAlign -> SecondFieldAlign -> Bool (/=) :: SecondFieldAlign -> SecondFieldAlign -> Bool | |
Show SecondFieldAlign Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> SecondFieldAlign -> ShowS show :: SecondFieldAlign -> String showList :: [SecondFieldAlign] -> ShowS |
data PageRangeFormat Source #
Instances
Eq PageRangeFormat Source # | |
Defined in Citeproc.Types Methods (==) :: PageRangeFormat -> PageRangeFormat -> Bool (/=) :: PageRangeFormat -> PageRangeFormat -> Bool | |
Ord PageRangeFormat Source # | |
Defined in Citeproc.Types Methods compare :: PageRangeFormat -> PageRangeFormat -> Ordering (<) :: PageRangeFormat -> PageRangeFormat -> Bool (<=) :: PageRangeFormat -> PageRangeFormat -> Bool (>) :: PageRangeFormat -> PageRangeFormat -> Bool (>=) :: PageRangeFormat -> PageRangeFormat -> Bool max :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat min :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat | |
Show PageRangeFormat Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> PageRangeFormat -> ShowS show :: PageRangeFormat -> String showList :: [PageRangeFormat] -> ShowS |
Constructors
Style | |
Fields
|
Constructors
LastDigit | |
LastTwoDigits | |
WholeNumber |
data TermGender Source #
Instances
Eq TermGender Source # | |
Defined in Citeproc.Types | |
Ord TermGender Source # | |
Defined in Citeproc.Types Methods compare :: TermGender -> TermGender -> Ordering (<) :: TermGender -> TermGender -> Bool (<=) :: TermGender -> TermGender -> Bool (>) :: TermGender -> TermGender -> Bool (>=) :: TermGender -> TermGender -> Bool max :: TermGender -> TermGender -> TermGender min :: TermGender -> TermGender -> TermGender | |
Show TermGender Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> TermGender -> ShowS show :: TermGender -> String showList :: [TermGender] -> ShowS |
data TermNumber Source #
Instances
Eq TermNumber Source # | |
Defined in Citeproc.Types | |
Ord TermNumber Source # | |
Defined in Citeproc.Types Methods compare :: TermNumber -> TermNumber -> Ordering (<) :: TermNumber -> TermNumber -> Bool (<=) :: TermNumber -> TermNumber -> Bool (>) :: TermNumber -> TermNumber -> Bool (>=) :: TermNumber -> TermNumber -> Bool max :: TermNumber -> TermNumber -> TermNumber min :: TermNumber -> TermNumber -> TermNumber | |
Show TermNumber Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> TermNumber -> ShowS show :: TermNumber -> String showList :: [TermNumber] -> ShowS |
Constructors
Term | |
Fields
|
data SortDirection Source #
Constructors
Ascending | |
Descending |
Instances
Eq SortDirection Source # | |
Defined in Citeproc.Types | |
Show SortDirection Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> SortDirection -> ShowS show :: SortDirection -> String showList :: [SortDirection] -> ShowS |
Constructors
SortKeyVariable SortDirection Variable | |
SortKeyMacro SortDirection [Element a] |
Instances
data SortKeyValue Source #
Constructors
SortKeyValue SortDirection (Maybe [Text]) |
Instances
Eq SortKeyValue Source # | |
Defined in Citeproc.Types | |
Show SortKeyValue Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> SortKeyValue -> ShowS show :: SortKeyValue -> String showList :: [SortKeyValue] -> ShowS |
data LayoutOptions Source #
Constructors
LayoutOptions | |
Fields
|
Instances
Eq LayoutOptions Source # | |
Defined in Citeproc.Types | |
Show LayoutOptions Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> LayoutOptions -> ShowS show :: LayoutOptions -> String showList :: [LayoutOptions] -> ShowS |
data Collapsing Source #
Instances
Eq Collapsing Source # | |
Defined in Citeproc.Types | |
Show Collapsing Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> Collapsing -> ShowS show :: Collapsing -> String showList :: [Collapsing] -> ShowS |
Constructors
Layout | |
Fields
|
data DisambiguationStrategy Source #
Constructors
DisambiguationStrategy | |
Fields
|
Instances
Eq DisambiguationStrategy Source # | |
Defined in Citeproc.Types Methods (==) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool (/=) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool | |
Ord DisambiguationStrategy Source # | |
Defined in Citeproc.Types Methods compare :: DisambiguationStrategy -> DisambiguationStrategy -> Ordering (<) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool (<=) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool (>) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool (>=) :: DisambiguationStrategy -> DisambiguationStrategy -> Bool max :: DisambiguationStrategy -> DisambiguationStrategy -> DisambiguationStrategy min :: DisambiguationStrategy -> DisambiguationStrategy -> DisambiguationStrategy | |
Show DisambiguationStrategy Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> DisambiguationStrategy -> ShowS show :: DisambiguationStrategy -> String showList :: [DisambiguationStrategy] -> ShowS |
data GivenNameDisambiguationRule Source #
Instances
Represents a BCP 47 language tag (https://tools.ietf.org/html/bcp47).
Constructors
Lang | |
Fields
|
Instances
Eq Lang | |
Ord Lang | |
Show Lang | |
IsString Lang | |
Defined in Text.Collate.Lang Methods fromString :: String -> Lang | |
Binary Lang | |
Lift Lang | |
renderLang :: Lang -> Text Source #
Render a Lang
in BCP 47 form.
Defines locale-specific terms, punctuation styles, and date formats.
Constructors
Locale | |
Fields
|
data DisambiguationData Source #
Constructors
DisambiguationData | |
Fields
|
Instances
Show DisambiguationData Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> DisambiguationData -> ShowS show :: DisambiguationData -> String showList :: [DisambiguationData] -> ShowS |
Encodes bibliographic data for a single work.
Constructors
Reference | |
Fields
|
Instances
Functor Reference Source # | |
Foldable Reference Source # | |
Defined in Citeproc.Types Methods fold :: Monoid m => Reference m -> m foldMap :: Monoid m => (a -> m) -> Reference a -> m foldMap' :: Monoid m => (a -> m) -> Reference a -> m foldr :: (a -> b -> b) -> b -> Reference a -> b foldr' :: (a -> b -> b) -> b -> Reference a -> b foldl :: (b -> a -> b) -> b -> Reference a -> b foldl' :: (b -> a -> b) -> b -> Reference a -> b foldr1 :: (a -> a -> a) -> Reference a -> a foldl1 :: (a -> a -> a) -> Reference a -> a elem :: Eq a => a -> Reference a -> Bool maximum :: Ord a => Reference a -> a minimum :: Ord a => Reference a -> a | |
Traversable Reference Source # | |
Show a => Show (Reference a) Source # | |
(Eq a, FromJSON a) => FromJSON (Reference a) Source # | |
Defined in Citeproc.Types | |
ToJSON a => ToJSON (Reference a) Source # | |
Defined in Citeproc.Types Methods toJSON :: Reference a -> Value toEncoding :: Reference a -> Encoding toJSONList :: [Reference a] -> Value toEncodingList :: [Reference a] -> Encoding |
newtype ReferenceMap a Source #
Constructors
ReferenceMap | |
Fields
|
Instances
Show a => Show (ReferenceMap a) Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> ReferenceMap a -> ShowS show :: ReferenceMap a -> String showList :: [ReferenceMap a] -> ShowS |
makeReferenceMap :: [Reference a] -> ([Reference a], ReferenceMap a) Source #
Returns a pair consisting of the cleaned up list of references and a reference map. If the original reference list contains items with the same id, then the one that occurs last in the list is retained, and the others are omittedfrom the cleaned-up list.
lookupReference :: ItemId -> ReferenceMap a -> Maybe (Reference a) Source #
Value associated with a certain variable in a bibliographic entry.
Constructors
TextVal Text | Plain text value |
FancyVal a | Formatted value with parameterized type |
NumVal Int | Numerical value |
NamesVal [Name] | Structured names |
DateVal Date | Structured date |
Instances
Functor Val Source # | |
Foldable Val Source # | |
Defined in Citeproc.Types Methods fold :: Monoid m => Val m -> m foldMap :: Monoid m => (a -> m) -> Val a -> m foldMap' :: Monoid m => (a -> m) -> Val a -> m foldr :: (a -> b -> b) -> b -> Val a -> b foldr' :: (a -> b -> b) -> b -> Val a -> b foldl :: (b -> a -> b) -> b -> Val a -> b foldl' :: (b -> a -> b) -> b -> Val a -> b foldr1 :: (a -> a -> a) -> Val a -> a foldl1 :: (a -> a -> a) -> Val a -> a elem :: Eq a => a -> Val a -> Bool maximum :: Ord a => Val a -> a | |
Traversable Val Source # | |
Eq a => Eq (Val a) Source # | |
Show a => Show (Val a) Source # | |
ToJSON a => ToJSON (Val a) Source # | |
Defined in Citeproc.Types Methods toEncoding :: Val a -> Encoding toJSONList :: [Val a] -> Value toEncodingList :: [Val a] -> Encoding |
valToText :: CiteprocOutput a => Val a -> Maybe Text Source #
Instances
Eq Variable Source # | |
Ord Variable Source # | |
Show Variable Source # | |
IsString Variable Source # | |
Defined in Citeproc.Types Methods fromString :: String -> Variable | |
Semigroup Variable Source # | |
Monoid Variable Source # | |
FromJSON Variable Source # | |
Defined in Citeproc.Types | |
FromJSONKey Variable Source # | |
Defined in Citeproc.Types | |
ToJSON Variable Source # | |
Defined in Citeproc.Types Methods toEncoding :: Variable -> Encoding toJSONList :: [Variable] -> Value toEncodingList :: [Variable] -> Encoding | |
ToJSONKey Variable Source # | |
Defined in Citeproc.Types |
toVariable :: Text -> Variable Source #
fromVariable :: Variable -> Text Source #
lookupVariable :: CiteprocOutput a => Variable -> Reference a -> Maybe (Val a) Source #
Constructors
Formatted Formatting [Output a] | |
InNote (Output a) | |
Literal a | |
Tagged Tag (Output a) | |
NullOutput |
Constructors
TagTerm | |
TagCitationNumber Int | |
TagCitationLabel | |
TagItem CitationItemType ItemId | |
TagName Name | |
TagNames Variable NamesFormat [Name] | |
TagDate Date | |
TagYearSuffix Int | |
TagLocator |
outputToText :: CiteprocOutput a => Output a -> Text Source #
renderOutput :: CiteprocOutput a => CiteprocOptions -> Output a -> a Source #
variableType :: Variable -> VariableType Source #
data VariableType Source #
Instances
Eq VariableType Source # | |
Defined in Citeproc.Types | |
Show VariableType Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> VariableType -> ShowS show :: VariableType -> String showList :: [VariableType] -> ShowS |
data Abbreviations Source #
An abbreviations map. These are typically stored in a JSON serialization: for examples of the format, see https://github.com/citation-style-language/abbreviations. Abbreviations are substituted in the output when the variable and its content are matched by something in the abbreviations map.
Instances
Eq Abbreviations Source # | |
Defined in Citeproc.Types | |
Ord Abbreviations Source # | |
Defined in Citeproc.Types Methods compare :: Abbreviations -> Abbreviations -> Ordering (<) :: Abbreviations -> Abbreviations -> Bool (<=) :: Abbreviations -> Abbreviations -> Bool (>) :: Abbreviations -> Abbreviations -> Bool (>=) :: Abbreviations -> Abbreviations -> Bool max :: Abbreviations -> Abbreviations -> Abbreviations min :: Abbreviations -> Abbreviations -> Abbreviations | |
Show Abbreviations Source # | |
Defined in Citeproc.Types Methods showsPrec :: Int -> Abbreviations -> ShowS show :: Abbreviations -> String showList :: [Abbreviations] -> ShowS | |
FromJSON Abbreviations Source # | |
Defined in Citeproc.Types | |
ToJSON Abbreviations Source # | |
Defined in Citeproc.Types Methods toJSON :: Abbreviations -> Value toEncoding :: Abbreviations -> Encoding toJSONList :: [Abbreviations] -> Value toEncodingList :: [Abbreviations] -> Encoding |
lookupAbbreviation :: CiteprocOutput a => Variable -> Val a -> Abbreviations -> Maybe (Val a) Source #
Returns an abbreviation if the variable and its value match something in the abbreviations map.
Result of citation processing.
Constructors
Result | |
Fields
|
Instances
Functor Result Source # | |
Foldable Result Source # | |
Defined in Citeproc.Types Methods fold :: Monoid m => Result m -> m foldMap :: Monoid m => (a -> m) -> Result a -> m foldMap' :: Monoid m => (a -> m) -> Result a -> m foldr :: (a -> b -> b) -> b -> Result a -> b foldr' :: (a -> b -> b) -> b -> Result a -> b foldl :: (b -> a -> b) -> b -> Result a -> b foldl' :: (b -> a -> b) -> b -> Result a -> b foldr1 :: (a -> a -> a) -> Result a -> a foldl1 :: (a -> a -> a) -> Result a -> a elem :: Eq a => a -> Result a -> Bool maximum :: Ord a => Result a -> a | |
Traversable Result Source # | |
Show a => Show (Result a) Source # | |
FromJSON a => FromJSON (Result a) Source # | |
Defined in Citeproc.Types | |
ToJSON a => ToJSON (Result a) Source # | |
Defined in Citeproc.Types Methods toEncoding :: Result a -> Encoding toJSONList :: [Result a] -> Value toEncodingList :: [Result a] -> Encoding |
Inputs for citation processing.
Constructors
Inputs | |
Fields
|
Instances
Show a => Show (Inputs a) Source # | |
(FromJSON a, Eq a) => FromJSON (Inputs a) Source # | |
Defined in Citeproc.Types | |
ToJSON a => ToJSON (Inputs a) Source # | |
Defined in Citeproc.Types Methods toEncoding :: Inputs a -> Encoding toJSONList :: [Inputs a] -> Value toEncodingList :: [Inputs a] -> Encoding |