Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype CiteprocOptions = CiteprocOptions {}
- 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
- prettyCiteprocError :: CiteprocError -> Text
- newtype ItemId = ItemId {}
- data CitationItem a = CitationItem {}
- 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 {}
- data VariableForm
- data TextType
- 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 {}
- 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 {}
- emptyTerm :: Term
- data SortDirection
- data SortKey a
- data SortKeyValue = SortKeyValue SortDirection (Maybe Lang) (Maybe [Text])
- data LayoutOptions = LayoutOptions {}
- data Collapsing
- data Layout a = Layout {
- layoutOptions :: LayoutOptions
- layoutFormatting :: Formatting
- layoutElements :: [Element a]
- layoutSortKeys :: [SortKey a]
- data DisambiguationStrategy = DisambiguationStrategy {}
- data GivenNameDisambiguationRule
- data Lang = Lang {
- langLanguage :: Text
- langVariant :: Maybe Text
- parseLang :: Text -> Lang
- renderLang :: Lang -> Text
- data Locale = Locale {}
- data DisambiguationData = DisambiguationData {}
- data NameHints
- data Reference a = Reference {}
- 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 {}
Documentation
newtype CiteprocOptions Source #
Options affecting the output in ways that go beyond what can be specified in styles.
CiteprocOptions | |
|
Instances
Eq CiteprocOptions Source # | |
Defined in Citeproc.Types (==) :: CiteprocOptions -> CiteprocOptions -> Bool # (/=) :: CiteprocOptions -> CiteprocOptions -> Bool # | |
Show CiteprocOptions Source # | |
Defined in Citeproc.Types 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
.
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 #
Instances
Eq CiteprocError Source # | |
Defined in Citeproc.Types (==) :: CiteprocError -> CiteprocError -> Bool # (/=) :: CiteprocError -> CiteprocError -> Bool # | |
Show CiteprocError Source # | |
Defined in Citeproc.Types showsPrec :: Int -> CiteprocError -> ShowS # show :: CiteprocError -> String # showList :: [CiteprocError] -> ShowS # |
The identifier used to identify a work in a bibliographic database.
data CitationItem a Source #
The part of a citation corresponding to a single work, possibly including a label, locator, prefix and suffix.
Instances
data CitationItemType Source #
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)
).
Citation | |
|
Instances
Eq a => Eq (Citation a) Source # | |
Ord a => Ord (Citation a) Source # | |
Show a => Show (Citation a) Source # | |
ToJSON a => ToJSON (Citation a) Source # | |
Defined in Citeproc.Types | |
FromJSON a => FromJSON (Citation a) Source # | |
data ElementType a Source #
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 (==) :: ElementType a -> ElementType a -> Bool # (/=) :: ElementType a -> ElementType a -> Bool # | |
Show (ElementType a) Source # | |
Defined in Citeproc.Types showsPrec :: Int -> ElementType a -> ShowS # show :: ElementType a -> String # showList :: [ElementType a] -> ShowS # |
data NumberForm Source #
Instances
Eq NumberForm Source # | |
Defined in Citeproc.Types (==) :: NumberForm -> NumberForm -> Bool # (/=) :: NumberForm -> NumberForm -> Bool # | |
Show NumberForm Source # | |
Defined in Citeproc.Types showsPrec :: Int -> NumberForm -> ShowS # show :: NumberForm -> String # showList :: [NumberForm] -> ShowS # |
data ShowDateParts Source #
Instances
Eq ShowDateParts Source # | |
Defined in Citeproc.Types (==) :: ShowDateParts -> ShowDateParts -> Bool # (/=) :: ShowDateParts -> ShowDateParts -> Bool # | |
Show ShowDateParts Source # | |
Defined in Citeproc.Types showsPrec :: Int -> ShowDateParts -> ShowS # show :: ShowDateParts -> String # showList :: [ShowDateParts] -> ShowS # |
DP | |
|
data VariableForm Source #
Instances
Eq VariableForm Source # | |
Defined in Citeproc.Types (==) :: VariableForm -> VariableForm -> Bool # (/=) :: VariableForm -> VariableForm -> Bool # | |
Show VariableForm Source # | |
Defined in Citeproc.Types showsPrec :: Int -> VariableForm -> ShowS # show :: VariableForm -> String # showList :: [VariableForm] -> ShowS # |
data NameFormat Source #
Instances
Eq NameFormat Source # | |
Defined in Citeproc.Types (==) :: NameFormat -> NameFormat -> Bool # (/=) :: NameFormat -> NameFormat -> Bool # | |
Show NameFormat Source # | |
Defined in Citeproc.Types showsPrec :: Int -> NameFormat -> ShowS # show :: NameFormat -> String # showList :: [NameFormat] -> ShowS # |
data NameAsSortOrder Source #
Instances
Eq NameAsSortOrder Source # | |
Defined in Citeproc.Types (==) :: NameAsSortOrder -> NameAsSortOrder -> Bool # (/=) :: NameAsSortOrder -> NameAsSortOrder -> Bool # | |
Show NameAsSortOrder Source # | |
Defined in Citeproc.Types showsPrec :: Int -> NameAsSortOrder -> ShowS # show :: NameAsSortOrder -> String # showList :: [NameAsSortOrder] -> ShowS # |
data NamesFormat Source #
NamesFormat | |
|
Instances
Eq NamesFormat Source # | |
Defined in Citeproc.Types (==) :: NamesFormat -> NamesFormat -> Bool # (/=) :: NamesFormat -> NamesFormat -> Bool # | |
Show NamesFormat Source # | |
Defined in Citeproc.Types showsPrec :: Int -> NamesFormat -> ShowS # show :: NamesFormat -> String # showList :: [NamesFormat] -> ShowS # |
Name | |
|
extractParticles :: Name -> Name Source #
isByzantineName :: Name -> Bool Source #
data DelimiterPrecedes Source #
Instances
Eq DelimiterPrecedes Source # | |
Defined in Citeproc.Types (==) :: DelimiterPrecedes -> DelimiterPrecedes -> Bool # (/=) :: DelimiterPrecedes -> DelimiterPrecedes -> Bool # | |
Show DelimiterPrecedes Source # | |
Defined in Citeproc.Types showsPrec :: Int -> DelimiterPrecedes -> ShowS # show :: DelimiterPrecedes -> String # showList :: [DelimiterPrecedes] -> ShowS # |
data Formatting Source #
Instances
Eq Formatting Source # | |
Defined in Citeproc.Types (==) :: Formatting -> Formatting -> Bool # (/=) :: Formatting -> Formatting -> Bool # | |
Show Formatting Source # | |
Defined in Citeproc.Types showsPrec :: Int -> Formatting -> ShowS # show :: Formatting -> String # showList :: [Formatting] -> ShowS # | |
Semigroup Formatting Source # | |
Defined in Citeproc.Types (<>) :: Formatting -> Formatting -> Formatting # sconcat :: NonEmpty Formatting -> Formatting # stimes :: Integral b => b -> Formatting -> Formatting # | |
Monoid Formatting Source # | |
Defined in Citeproc.Types mempty :: Formatting # mappend :: Formatting -> Formatting -> Formatting # mconcat :: [Formatting] -> Formatting # |
data FontVariant Source #
Instances
Eq FontVariant Source # | |
Defined in Citeproc.Types (==) :: FontVariant -> FontVariant -> Bool # (/=) :: FontVariant -> FontVariant -> Bool # | |
Show FontVariant Source # | |
Defined in Citeproc.Types showsPrec :: Int -> FontVariant -> ShowS # show :: FontVariant -> String # showList :: [FontVariant] -> ShowS # |
data FontWeight Source #
Instances
Eq FontWeight Source # | |
Defined in Citeproc.Types (==) :: FontWeight -> FontWeight -> Bool # (/=) :: FontWeight -> FontWeight -> Bool # | |
Show FontWeight Source # | |
Defined in Citeproc.Types showsPrec :: Int -> FontWeight -> ShowS # show :: FontWeight -> String # showList :: [FontWeight] -> ShowS # |
data TextDecoration Source #
Instances
Eq TextDecoration Source # | |
Defined in Citeproc.Types (==) :: TextDecoration -> TextDecoration -> Bool # (/=) :: TextDecoration -> TextDecoration -> Bool # | |
Show TextDecoration Source # | |
Defined in Citeproc.Types showsPrec :: Int -> TextDecoration -> ShowS # show :: TextDecoration -> String # showList :: [TextDecoration] -> ShowS # |
data VerticalAlign Source #
Instances
Eq VerticalAlign Source # | |
Defined in Citeproc.Types (==) :: VerticalAlign -> VerticalAlign -> Bool # (/=) :: VerticalAlign -> VerticalAlign -> Bool # | |
Show VerticalAlign Source # | |
Defined in Citeproc.Types showsPrec :: Int -> VerticalAlign -> ShowS # show :: VerticalAlign -> String # showList :: [VerticalAlign] -> ShowS # |
data DisplayStyle Source #
Instances
Eq DisplayStyle Source # | |
Defined in Citeproc.Types (==) :: DisplayStyle -> DisplayStyle -> Bool # (/=) :: DisplayStyle -> DisplayStyle -> Bool # | |
Show DisplayStyle Source # | |
Defined in Citeproc.Types showsPrec :: Int -> DisplayStyle -> ShowS # show :: DisplayStyle -> String # showList :: [DisplayStyle] -> ShowS # |
data DemoteNonDroppingParticle Source #
Instances
Eq DemoteNonDroppingParticle Source # | |
Defined in Citeproc.Types | |
Show DemoteNonDroppingParticle Source # | |
Defined in Citeproc.Types showsPrec :: Int -> DemoteNonDroppingParticle -> ShowS # show :: DemoteNonDroppingParticle -> String # showList :: [DemoteNonDroppingParticle] -> ShowS # |
data StyleOptions Source #
Instances
Eq StyleOptions Source # | |
Defined in Citeproc.Types (==) :: StyleOptions -> StyleOptions -> Bool # (/=) :: StyleOptions -> StyleOptions -> Bool # | |
Show StyleOptions Source # | |
Defined in Citeproc.Types showsPrec :: Int -> StyleOptions -> ShowS # show :: StyleOptions -> String # showList :: [StyleOptions] -> ShowS # |
data SubsequentAuthorSubstitute Source #
Instances
Eq SubsequentAuthorSubstitute Source # | |
Defined in Citeproc.Types | |
Show SubsequentAuthorSubstitute Source # | |
Defined in Citeproc.Types showsPrec :: Int -> SubsequentAuthorSubstitute -> ShowS # show :: SubsequentAuthorSubstitute -> String # showList :: [SubsequentAuthorSubstitute] -> ShowS # |
data SubsequentAuthorSubstituteRule Source #
Instances
Eq SubsequentAuthorSubstituteRule Source # | |
Defined in Citeproc.Types | |
Show SubsequentAuthorSubstituteRule Source # | |
Defined in Citeproc.Types |
data SecondFieldAlign Source #
Instances
Eq SecondFieldAlign Source # | |
Defined in Citeproc.Types (==) :: SecondFieldAlign -> SecondFieldAlign -> Bool # (/=) :: SecondFieldAlign -> SecondFieldAlign -> Bool # | |
Show SecondFieldAlign Source # | |
Defined in Citeproc.Types showsPrec :: Int -> SecondFieldAlign -> ShowS # show :: SecondFieldAlign -> String # showList :: [SecondFieldAlign] -> ShowS # |
data PageRangeFormat Source #
Instances
Eq PageRangeFormat Source # | |
Defined in Citeproc.Types (==) :: PageRangeFormat -> PageRangeFormat -> Bool # (/=) :: PageRangeFormat -> PageRangeFormat -> Bool # | |
Ord PageRangeFormat Source # | |
Defined in Citeproc.Types 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 showsPrec :: Int -> PageRangeFormat -> ShowS # show :: PageRangeFormat -> String # showList :: [PageRangeFormat] -> ShowS # |
Style | |
|
data TermGender Source #
Instances
Eq TermGender Source # | |
Defined in Citeproc.Types (==) :: TermGender -> TermGender -> Bool # (/=) :: TermGender -> TermGender -> Bool # | |
Ord TermGender Source # | |
Defined in Citeproc.Types 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 showsPrec :: Int -> TermGender -> ShowS # show :: TermGender -> String # showList :: [TermGender] -> ShowS # |
data TermNumber Source #
Instances
Eq TermNumber Source # | |
Defined in Citeproc.Types (==) :: TermNumber -> TermNumber -> Bool # (/=) :: TermNumber -> TermNumber -> Bool # | |
Ord TermNumber Source # | |
Defined in Citeproc.Types 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 showsPrec :: Int -> TermNumber -> ShowS # show :: TermNumber -> String # showList :: [TermNumber] -> ShowS # |
Term | |
|
data SortDirection Source #
Instances
Eq SortDirection Source # | |
Defined in Citeproc.Types (==) :: SortDirection -> SortDirection -> Bool # (/=) :: SortDirection -> SortDirection -> Bool # | |
Show SortDirection Source # | |
Defined in Citeproc.Types showsPrec :: Int -> SortDirection -> ShowS # show :: SortDirection -> String # showList :: [SortDirection] -> ShowS # |
data SortKeyValue Source #
SortKeyValue SortDirection (Maybe Lang) (Maybe [Text]) |
Instances
Eq SortKeyValue Source # | |
Defined in Citeproc.Types (==) :: SortKeyValue -> SortKeyValue -> Bool # (/=) :: SortKeyValue -> SortKeyValue -> Bool # | |
Ord SortKeyValue Source # | |
Defined in Citeproc.Types compare :: SortKeyValue -> SortKeyValue -> Ordering # (<) :: SortKeyValue -> SortKeyValue -> Bool # (<=) :: SortKeyValue -> SortKeyValue -> Bool # (>) :: SortKeyValue -> SortKeyValue -> Bool # (>=) :: SortKeyValue -> SortKeyValue -> Bool # max :: SortKeyValue -> SortKeyValue -> SortKeyValue # min :: SortKeyValue -> SortKeyValue -> SortKeyValue # | |
Show SortKeyValue Source # | |
Defined in Citeproc.Types showsPrec :: Int -> SortKeyValue -> ShowS # show :: SortKeyValue -> String # showList :: [SortKeyValue] -> ShowS # |
data LayoutOptions Source #
Instances
Eq LayoutOptions Source # | |
Defined in Citeproc.Types (==) :: LayoutOptions -> LayoutOptions -> Bool # (/=) :: LayoutOptions -> LayoutOptions -> Bool # | |
Show LayoutOptions Source # | |
Defined in Citeproc.Types showsPrec :: Int -> LayoutOptions -> ShowS # show :: LayoutOptions -> String # showList :: [LayoutOptions] -> ShowS # |
data Collapsing Source #
Instances
Eq Collapsing Source # | |
Defined in Citeproc.Types (==) :: Collapsing -> Collapsing -> Bool # (/=) :: Collapsing -> Collapsing -> Bool # | |
Show Collapsing Source # | |
Defined in Citeproc.Types showsPrec :: Int -> Collapsing -> ShowS # show :: Collapsing -> String # showList :: [Collapsing] -> ShowS # |
Layout | |
|
data DisambiguationStrategy Source #
Instances
Eq DisambiguationStrategy Source # | |
Defined in Citeproc.Types | |
Ord DisambiguationStrategy Source # | |
Defined in Citeproc.Types 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 showsPrec :: Int -> DisambiguationStrategy -> ShowS # show :: DisambiguationStrategy -> String # showList :: [DisambiguationStrategy] -> ShowS # |
data GivenNameDisambiguationRule Source #
Instances
A parsed IETF language tag, with language and optional variant.
For example, Lang "en" (Just US)
corresponds to en-US
.
Lang | |
|
Defines locale-specific terms, punctuation styles, and date formats.
Locale | |
|
data DisambiguationData Source #
Instances
Show DisambiguationData Source # | |
Defined in Citeproc.Types showsPrec :: Int -> DisambiguationData -> ShowS # show :: DisambiguationData -> String # showList :: [DisambiguationData] -> ShowS # |
Encodes bibliographic data for a single work.
Reference | |
|
Instances
Functor Reference Source # | |
Foldable Reference Source # | |
Defined in Citeproc.Types 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 # toList :: Reference a -> [a] # length :: Reference a -> Int # 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 # | |
ToJSON a => ToJSON (Reference a) Source # | |
Defined in Citeproc.Types | |
(Eq a, FromJSON a) => FromJSON (Reference a) Source # | |
newtype ReferenceMap a Source #
ReferenceMap | |
|
Instances
Show a => Show (ReferenceMap a) Source # | |
Defined in Citeproc.Types 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.
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 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 |
Instances
Eq Variable Source # | |
Ord Variable Source # | |
Defined in Citeproc.Types | |
Show Variable Source # | |
IsString Variable Source # | |
Defined in Citeproc.Types fromString :: String -> Variable # | |
Semigroup Variable Source # | |
Monoid Variable Source # | |
ToJSON Variable Source # | |
Defined in Citeproc.Types | |
ToJSONKey Variable Source # | |
Defined in Citeproc.Types | |
FromJSON Variable Source # | |
FromJSONKey Variable Source # | |
Defined in Citeproc.Types |
toVariable :: Text -> Variable Source #
fromVariable :: Variable -> Text Source #
lookupVariable :: CiteprocOutput a => Variable -> Reference a -> Maybe (Val a) Source #
Formatted Formatting [Output a] | |
InNote (Output a) | |
Literal a | |
Tagged Tag (Output a) | |
NullOutput |
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 (==) :: VariableType -> VariableType -> Bool # (/=) :: VariableType -> VariableType -> Bool # | |
Show VariableType Source # | |
Defined in Citeproc.Types 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
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.
Result | |
|
Instances
Functor Result Source # | |
Foldable Result Source # | |
Defined in Citeproc.Types 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 # minimum :: Ord a => Result a -> a # | |
Traversable Result Source # | |
Show a => Show (Result a) Source # | |
ToJSON a => ToJSON (Result a) Source # | |
Defined in Citeproc.Types | |
FromJSON a => FromJSON (Result a) Source # | |
Inputs for citation processing.
Inputs | |
|