citeproc-0.8.1: Generates citations and bibliography from CSL styles.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Citeproc.Types

Synopsis

Documentation

data CiteprocOptions Source #

Options affecting the output in ways that go beyond what can be specified in styles.

Constructors

CiteprocOptions 

Fields

  • linkCitations :: Bool

    Create hyperlinks from citations to bibliography entries

  • linkBibliography :: Bool

    Enables the following options:

    • Automatically linkify any DOI, PMCID, PMID, or URL appearing in a bibliography entry.
    • When a bibliography entry has a DOI, PMCID, PMID, or URL available (in order of priority), but the style does not explicitly render at least one of them, add a hyperlink to the title instead.
    • A bibliography item with a DOI, PMCID, PMID, or URL available (in order of priority) will be wrapped in a hyperlink when the hyperlink has not already been applied to one of its parts (e.g. to the title).

Instances

Instances details
Show CiteprocOptions Source # 
Instance details

Defined in Citeproc.Types

Eq CiteprocOptions Source # 
Instance details

Defined in Citeproc.Types

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.

Instances

Instances details
CiteprocOutput Inlines Source # 
Instance details

Defined in Citeproc.Pandoc

CiteprocOutput (CslJson Text) Source # 
Instance details

Defined in Citeproc.CslJson

newtype ItemId Source #

The identifier used to identify a work in a bibliographic database.

Constructors

ItemId 

Fields

Instances

Instances details
FromJSON ItemId Source # 
Instance details

Defined in Citeproc.Types

ToJSON ItemId Source # 
Instance details

Defined in Citeproc.Types

Monoid ItemId Source # 
Instance details

Defined in Citeproc.Types

Semigroup ItemId Source # 
Instance details

Defined in Citeproc.Types

Show ItemId Source # 
Instance details

Defined in Citeproc.Types

Eq ItemId Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Ord ItemId Source # 
Instance details

Defined in Citeproc.Types

data CitationItem a Source #

The part of a citation corresponding to a single work, possibly including a label, locator, prefix and suffix.

Instances

Instances details
(FromJSON a, Eq a) => FromJSON (CitationItem a) Source # 
Instance details

Defined in Citeproc.Types

ToJSON a => ToJSON (CitationItem a) Source # 
Instance details

Defined in Citeproc.Types

Show a => Show (CitationItem a) Source # 
Instance details

Defined in Citeproc.Types

Eq a => Eq (CitationItem a) Source # 
Instance details

Defined in Citeproc.Types

Ord a => Ord (CitationItem a) Source # 
Instance details

Defined in Citeproc.Types

data Citation a Source #

A citation (which may include several items, e.g. in (Smith 2000; Jones 2010, p. 30)).

Instances

Instances details
(FromJSON a, Eq a) => FromJSON (Citation a) Source # 
Instance details

Defined in Citeproc.Types

ToJSON a => ToJSON (Citation a) Source # 
Instance details

Defined in Citeproc.Types

Show a => Show (Citation a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Citation a -> ShowS #

show :: Citation a -> String #

showList :: [Citation a] -> ShowS #

Eq a => Eq (Citation a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Citation a -> Citation a -> Bool #

(/=) :: Citation a -> Citation a -> Bool #

Ord a => Ord (Citation a) Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Citation a -> Citation a -> Ordering #

(<) :: Citation a -> Citation a -> Bool #

(<=) :: Citation a -> Citation a -> Bool #

(>) :: Citation a -> Citation a -> Bool #

(>=) :: Citation a -> Citation a -> Bool #

max :: Citation a -> Citation a -> Citation a #

min :: Citation a -> Citation a -> Citation a #

data Element a Source #

Constructors

Element (ElementType a) Formatting 

Instances

Instances details
Show (Element a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Element a -> ShowS #

show :: Element a -> String #

showList :: [Element a] -> ShowS #

Eq (Element a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Element a -> Element a -> Bool #

(/=) :: Element a -> Element a -> Bool #

data NumberForm Source #

Instances

Instances details
Show NumberForm Source # 
Instance details

Defined in Citeproc.Types

Eq NumberForm Source # 
Instance details

Defined in Citeproc.Types

data Pluralize Source #

Instances

Instances details
Show Pluralize Source # 
Instance details

Defined in Citeproc.Types

Eq Pluralize Source # 
Instance details

Defined in Citeproc.Types

data DateType Source #

Instances

Instances details
Show DateType Source # 
Instance details

Defined in Citeproc.Types

Eq DateType Source # 
Instance details

Defined in Citeproc.Types

Ord DateType Source # 
Instance details

Defined in Citeproc.Types

data Date Source #

Instances

Instances details
FromJSON Date Source # 
Instance details

Defined in Citeproc.Types

ToJSON Date Source # 
Instance details

Defined in Citeproc.Types

Show Date Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

Eq Date Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Ord Date Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Date -> Date -> Ordering #

(<) :: Date -> Date -> Bool #

(<=) :: Date -> Date -> Bool #

(>) :: Date -> Date -> Bool #

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

newtype DateParts Source #

Constructors

DateParts [Int] 

data ShowDateParts Source #

Constructors

YearMonthDay 
YearMonth 
Year 

Instances

Instances details
Show ShowDateParts Source # 
Instance details

Defined in Citeproc.Types

Eq ShowDateParts Source # 
Instance details

Defined in Citeproc.Types

data DPName Source #

Constructors

DPYear 
DPMonth 
DPDay 

Instances

Instances details
Show DPName Source # 
Instance details

Defined in Citeproc.Types

Eq DPName Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Ord DPName Source # 
Instance details

Defined in Citeproc.Types

data DPForm Source #

Instances

Instances details
Show DPForm Source # 
Instance details

Defined in Citeproc.Types

Eq DPForm Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

data DP Source #

Instances

Instances details
Show DP Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DP -> ShowS #

show :: DP -> String #

showList :: [DP] -> ShowS #

Eq DP Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

data VariableForm Source #

Constructors

ShortForm 
LongForm 

Instances

Instances details
Show VariableForm Source # 
Instance details

Defined in Citeproc.Types

Eq VariableForm Source # 
Instance details

Defined in Citeproc.Types

data TextType Source #

Instances

Instances details
Show TextType Source # 
Instance details

Defined in Citeproc.Types

Eq TextType Source # 
Instance details

Defined in Citeproc.Types

data NameForm Source #

Constructors

LongName 
ShortName 
CountName 

Instances

Instances details
Show NameForm Source # 
Instance details

Defined in Citeproc.Types

Eq NameForm Source # 
Instance details

Defined in Citeproc.Types

data Name Source #

Instances

Instances details
FromJSON Name Source # 
Instance details

Defined in Citeproc.Types

ToJSON Name Source # 
Instance details

Defined in Citeproc.Types

Show Name Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Ord Name Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

data Position Source #

Instances

Instances details
Show Position Source # 
Instance details

Defined in Citeproc.Types

Eq Position Source # 
Instance details

Defined in Citeproc.Types

Ord Position Source # 
Instance details

Defined in Citeproc.Types

data Match Source #

Constructors

MatchAll 
MatchAny 
MatchNone 

Instances

Instances details
Show Match Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Eq Match Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

data FontStyle Source #

Instances

Instances details
Show FontStyle Source # 
Instance details

Defined in Citeproc.Types

Eq FontStyle Source # 
Instance details

Defined in Citeproc.Types

data FontVariant Source #

Instances

Instances details
Show FontVariant Source # 
Instance details

Defined in Citeproc.Types

Eq FontVariant Source # 
Instance details

Defined in Citeproc.Types

data FontWeight Source #

Instances

Instances details
Show FontWeight Source # 
Instance details

Defined in Citeproc.Types

Eq FontWeight Source # 
Instance details

Defined in Citeproc.Types

data VerticalAlign Source #

Instances

Instances details
Show VerticalAlign Source # 
Instance details

Defined in Citeproc.Types

Eq VerticalAlign Source # 
Instance details

Defined in Citeproc.Types

data TextCase Source #

Instances

Instances details
Show TextCase Source # 
Instance details

Defined in Citeproc.Types

Eq TextCase Source # 
Instance details

Defined in Citeproc.Types

data Style a Source #

Instances

Instances details
Show (Style a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Style a -> ShowS #

show :: Style a -> String #

showList :: [Style a] -> ShowS #

Eq (Style a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Style a -> Style a -> Bool #

(/=) :: Style a -> Style a -> Bool #

data TermMatch Source #

Instances

Instances details
Show TermMatch Source # 
Instance details

Defined in Citeproc.Types

Eq TermMatch Source # 
Instance details

Defined in Citeproc.Types

Ord TermMatch Source # 
Instance details

Defined in Citeproc.Types

data TermNumber Source #

Constructors

Singular 
Plural 

data TermForm Source #

Constructors

Long 
Short 
Verb 
VerbShort 
Symbol 

Instances

Instances details
Show TermForm Source # 
Instance details

Defined in Citeproc.Types

Eq TermForm Source # 
Instance details

Defined in Citeproc.Types

Ord TermForm Source # 
Instance details

Defined in Citeproc.Types

data Term Source #

Instances

Instances details
Show Term Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Term -> ShowS #

show :: Term -> String #

showList :: [Term] -> ShowS #

Eq Term Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Ord Term Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Term -> Term -> Ordering #

(<) :: Term -> Term -> Bool #

(<=) :: Term -> Term -> Bool #

(>) :: Term -> Term -> Bool #

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

max :: Term -> Term -> Term #

min :: Term -> Term -> Term #

data SortDirection Source #

Constructors

Ascending 
Descending 

Instances

Instances details
Show SortDirection Source # 
Instance details

Defined in Citeproc.Types

Eq SortDirection Source # 
Instance details

Defined in Citeproc.Types

data SortKey a Source #

Instances

Instances details
Show (SortKey a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> SortKey a -> ShowS #

show :: SortKey a -> String #

showList :: [SortKey a] -> ShowS #

Eq (SortKey a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: SortKey a -> SortKey a -> Bool #

(/=) :: SortKey a -> SortKey a -> Bool #

data SortKeyValue Source #

Instances

Instances details
Show SortKeyValue Source # 
Instance details

Defined in Citeproc.Types

Eq SortKeyValue Source # 
Instance details

Defined in Citeproc.Types

data Layout a Source #

Instances

Instances details
Show (Layout a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Layout a -> ShowS #

show :: Layout a -> String #

showList :: [Layout a] -> ShowS #

Eq (Layout a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Layout a -> Layout a -> Bool #

(/=) :: Layout a -> Layout a -> Bool #

data Lang #

Represents a BCP 47 language tag (https://tools.ietf.org/html/bcp47).

Instances

Instances details
IsString Lang 
Instance details

Defined in Text.Collate.Lang

Methods

fromString :: String -> Lang #

Show Lang 
Instance details

Defined in Text.Collate.Lang

Methods

showsPrec :: Int -> Lang -> ShowS #

show :: Lang -> String #

showList :: [Lang] -> ShowS #

Binary Lang 
Instance details

Defined in Text.Collate.Lang

Methods

put :: Lang -> Put #

get :: Get Lang #

putList :: [Lang] -> Put #

Eq Lang 
Instance details

Defined in Text.Collate.Lang

Methods

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

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

Ord Lang 
Instance details

Defined in Text.Collate.Lang

Methods

compare :: Lang -> Lang -> Ordering #

(<) :: Lang -> Lang -> Bool #

(<=) :: Lang -> Lang -> Bool #

(>) :: Lang -> Lang -> Bool #

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

max :: Lang -> Lang -> Lang #

min :: Lang -> Lang -> Lang #

Lift Lang 
Instance details

Defined in Text.Collate.Lang

Methods

lift :: Quote m => Lang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Lang -> Code m Lang #

parseLang :: Text -> Either String Lang #

Parse a BCP 47 language tag as a Lang.

renderLang :: Lang -> Text #

Render a Lang in BCP 47 form.

data Locale Source #

Defines locale-specific terms, punctuation styles, and date formats.

Instances

Instances details
Monoid Locale Source # 
Instance details

Defined in Citeproc.Types

Semigroup Locale Source # 
Instance details

Defined in Citeproc.Types

Show Locale Source # 
Instance details

Defined in Citeproc.Types

Eq Locale Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

data Reference a Source #

Encodes bibliographic data for a single work.

Constructors

Reference 

Fields

Instances

Instances details
Foldable Reference Source # 
Instance details

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 #

toList :: Reference a -> [a] #

null :: Reference a -> Bool #

length :: Reference a -> Int #

elem :: Eq a => a -> Reference a -> Bool #

maximum :: Ord a => Reference a -> a #

minimum :: Ord a => Reference a -> a #

sum :: Num a => Reference a -> a #

product :: Num a => Reference a -> a #

Traversable Reference Source # 
Instance details

Defined in Citeproc.Types

Methods

traverse :: Applicative f => (a -> f b) -> Reference a -> f (Reference b) #

sequenceA :: Applicative f => Reference (f a) -> f (Reference a) #

mapM :: Monad m => (a -> m b) -> Reference a -> m (Reference b) #

sequence :: Monad m => Reference (m a) -> m (Reference a) #

Functor Reference Source # 
Instance details

Defined in Citeproc.Types

Methods

fmap :: (a -> b) -> Reference a -> Reference b #

(<$) :: a -> Reference b -> Reference a #

(Eq a, FromJSON a) => FromJSON (Reference a) Source # 
Instance details

Defined in Citeproc.Types

ToJSON a => ToJSON (Reference a) Source # 
Instance details

Defined in Citeproc.Types

Show a => Show (Reference a) Source # 
Instance details

Defined in Citeproc.Types

Eq a => Eq (Reference a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Reference a -> Reference a -> Bool #

(/=) :: Reference a -> Reference a -> Bool #

Ord a => Ord (Reference a) Source # 
Instance details

Defined in Citeproc.Types

newtype ReferenceMap a Source #

Constructors

ReferenceMap 

Instances

Instances details
Show a => Show (ReferenceMap a) Source # 
Instance details

Defined in Citeproc.Types

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.

data Val 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

SubstitutedVal

Value suppressed through substitution

Instances

Instances details
Foldable Val Source # 
Instance details

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 #

toList :: Val a -> [a] #

null :: Val a -> Bool #

length :: Val a -> Int #

elem :: Eq a => a -> Val a -> Bool #

maximum :: Ord a => Val a -> a #

minimum :: Ord a => Val a -> a #

sum :: Num a => Val a -> a #

product :: Num a => Val a -> a #

Traversable Val Source # 
Instance details

Defined in Citeproc.Types

Methods

traverse :: Applicative f => (a -> f b) -> Val a -> f (Val b) #

sequenceA :: Applicative f => Val (f a) -> f (Val a) #

mapM :: Monad m => (a -> m b) -> Val a -> m (Val b) #

sequence :: Monad m => Val (m a) -> m (Val a) #

Functor Val Source # 
Instance details

Defined in Citeproc.Types

Methods

fmap :: (a -> b) -> Val a -> Val b #

(<$) :: a -> Val b -> Val a #

ToJSON a => ToJSON (Val a) Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: Val a -> Value #

toEncoding :: Val a -> Encoding #

toJSONList :: [Val a] -> Value #

toEncodingList :: [Val a] -> Encoding #

Show a => Show (Val a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Val a -> ShowS #

show :: Val a -> String #

showList :: [Val a] -> ShowS #

Eq a => Eq (Val a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Val a -> Val a -> Bool #

(/=) :: Val a -> Val a -> Bool #

Ord a => Ord (Val a) Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Val a -> Val a -> Ordering #

(<) :: Val a -> Val a -> Bool #

(<=) :: Val a -> Val a -> Bool #

(>) :: Val a -> Val a -> Bool #

(>=) :: Val a -> Val a -> Bool #

max :: Val a -> Val a -> Val a #

min :: Val a -> Val a -> Val a #

data Variable Source #

Instances

Instances details
FromJSON Variable Source # 
Instance details

Defined in Citeproc.Types

FromJSONKey Variable Source # 
Instance details

Defined in Citeproc.Types

ToJSON Variable Source # 
Instance details

Defined in Citeproc.Types

ToJSONKey Variable Source # 
Instance details

Defined in Citeproc.Types

IsString Variable Source # 
Instance details

Defined in Citeproc.Types

Monoid Variable Source # 
Instance details

Defined in Citeproc.Types

Semigroup Variable Source # 
Instance details

Defined in Citeproc.Types

Show Variable Source # 
Instance details

Defined in Citeproc.Types

Eq Variable Source # 
Instance details

Defined in Citeproc.Types

Ord Variable Source # 
Instance details

Defined in Citeproc.Types

data Output a Source #

Instances

Instances details
Show a => Show (Output a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Output a -> ShowS #

show :: Output a -> String #

showList :: [Output a] -> ShowS #

Eq a => Eq (Output a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Output a -> Output a -> Bool #

(/=) :: Output a -> Output a -> Bool #

Uniplate (Output a) Source # 
Instance details

Defined in Citeproc.Types

Methods

uniplate :: Output a -> (Str (Output a), Str (Output a) -> Output a) #

descend :: (Output a -> Output a) -> Output a -> Output a #

descendM :: Applicative m => (Output a -> m (Output a)) -> Output a -> m (Output a) #

Biplate (Output a) (Output a) Source # 
Instance details

Defined in Citeproc.Types

Methods

biplate :: Output a -> (Str (Output a), Str (Output a) -> Output a) #

descendBi :: (Output a -> Output a) -> Output a -> Output a #

descendBiM :: Applicative m => (Output a -> m (Output a)) -> Output a -> m (Output a) #

data Identifier Source #

Instances

Instances details
Show Identifier Source # 
Instance details

Defined in Citeproc.Types

Eq Identifier Source # 
Instance details

Defined in Citeproc.Types

data Tag Source #

Instances

Instances details
Show Tag Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Eq Tag Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

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.

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.

data Result a Source #

Result of citation processing.

Constructors

Result 

Fields

  • resultCitations :: [a]

    List of formatted citations corresponding to the citations given to citeproc

  • resultBibliography :: [(Text, a)]

    List of formatted bibliography entries (if the style calls for a bibliography), each a pair consisting of the item identifier and the formatted entry

  • resultWarnings :: [Text]

    Warnings from citation processing

Instances

Instances details
Foldable Result Source # 
Instance details

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 #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 
Instance details

Defined in Citeproc.Types

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Functor Result Source # 
Instance details

Defined in Citeproc.Types

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

FromJSON a => FromJSON (Result a) Source # 
Instance details

Defined in Citeproc.Types

ToJSON a => ToJSON (Result a) Source # 
Instance details

Defined in Citeproc.Types

Show a => Show (Result a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

data Inputs a Source #

Inputs for citation processing.

Instances

Instances details
(FromJSON a, Eq a) => FromJSON (Inputs a) Source # 
Instance details

Defined in Citeproc.Types

ToJSON a => ToJSON (Inputs a) Source # 
Instance details

Defined in Citeproc.Types

Show a => Show (Inputs a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Inputs a -> ShowS #

show :: Inputs a -> String #

showList :: [Inputs a] -> ShowS #