citeproc-0.4.0.1: Generates citations and bibliography from CSL styles.
Safe HaskellNone
LanguageHaskell2010

Citeproc.Types

Synopsis

Documentation

newtype 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

Instances

Instances details
Eq CiteprocOptions Source # 
Instance details

Defined in Citeproc.Types

Show CiteprocOptions Source # 
Instance details

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

toText :: a -> Text Source #

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 #

addQuotes :: a -> a Source #

movePunctuationInsideQuotes :: a -> a Source #

inNote :: a -> a Source #

mapText :: (Text -> Text) -> a -> a Source #

addHyperlink :: Text -> a -> a Source #

Instances

Instances details
CiteprocOutput Inlines Source # 
Instance details

Defined in Citeproc.Pandoc

Methods

toText :: Inlines -> Text Source #

fromText :: Text -> Inlines Source #

dropTextWhile :: (Char -> Bool) -> Inlines -> Inlines Source #

dropTextWhileEnd :: (Char -> Bool) -> Inlines -> Inlines Source #

addFontVariant :: FontVariant -> Inlines -> Inlines Source #

addFontStyle :: FontStyle -> Inlines -> Inlines Source #

addFontWeight :: FontWeight -> Inlines -> Inlines Source #

addTextDecoration :: TextDecoration -> Inlines -> Inlines Source #

addVerticalAlign :: VerticalAlign -> Inlines -> Inlines Source #

addTextCase :: Maybe Lang -> TextCase -> Inlines -> Inlines Source #

addDisplay :: DisplayStyle -> Inlines -> Inlines Source #

addQuotes :: Inlines -> Inlines Source #

movePunctuationInsideQuotes :: Inlines -> Inlines Source #

inNote :: Inlines -> Inlines Source #

mapText :: (Text -> Text) -> Inlines -> Inlines Source #

addHyperlink :: Text -> Inlines -> Inlines Source #

CiteprocOutput (CslJson Text) Source # 
Instance details

Defined in Citeproc.CslJson

Methods

toText :: CslJson Text -> Text Source #

fromText :: Text -> CslJson Text Source #

dropTextWhile :: (Char -> Bool) -> CslJson Text -> CslJson Text Source #

dropTextWhileEnd :: (Char -> Bool) -> CslJson Text -> CslJson Text Source #

addFontVariant :: FontVariant -> CslJson Text -> CslJson Text Source #

addFontStyle :: FontStyle -> CslJson Text -> CslJson Text Source #

addFontWeight :: FontWeight -> CslJson Text -> CslJson Text Source #

addTextDecoration :: TextDecoration -> CslJson Text -> CslJson Text Source #

addVerticalAlign :: VerticalAlign -> CslJson Text -> CslJson Text Source #

addTextCase :: Maybe Lang -> TextCase -> CslJson Text -> CslJson Text Source #

addDisplay :: DisplayStyle -> CslJson Text -> CslJson Text Source #

addQuotes :: CslJson Text -> CslJson Text Source #

movePunctuationInsideQuotes :: CslJson Text -> CslJson Text Source #

inNote :: CslJson Text -> CslJson Text Source #

mapText :: (Text -> Text) -> CslJson Text -> CslJson Text Source #

addHyperlink :: Text -> CslJson Text -> CslJson Text Source #

data CiteprocError Source #

Instances

Instances details
Eq CiteprocError Source # 
Instance details

Defined in Citeproc.Types

Show CiteprocError Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> CiteprocError -> ShowS

show :: CiteprocError -> String

showList :: [CiteprocError] -> ShowS

newtype ItemId Source #

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

Constructors

ItemId 

Fields

Instances

Instances details
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

Methods

compare :: ItemId -> ItemId -> Ordering

(<) :: ItemId -> ItemId -> Bool

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

(>) :: ItemId -> ItemId -> Bool

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

max :: ItemId -> ItemId -> ItemId

min :: ItemId -> ItemId -> ItemId

Show ItemId Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> ItemId -> ShowS

show :: ItemId -> String

showList :: [ItemId] -> ShowS

Semigroup ItemId Source # 
Instance details

Defined in Citeproc.Types

Methods

(<>) :: ItemId -> ItemId -> ItemId

sconcat :: NonEmpty ItemId -> ItemId

stimes :: Integral b => b -> ItemId -> ItemId

Monoid ItemId Source # 
Instance details

Defined in Citeproc.Types

FromJSON ItemId Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser ItemId

parseJSONList :: Value -> Parser [ItemId]

ToJSON ItemId Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: ItemId -> Value

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.

Instances

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

Defined in Citeproc.Types

Methods

(==) :: CitationItem a -> CitationItem a -> Bool

(/=) :: CitationItem a -> CitationItem a -> Bool

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

Defined in Citeproc.Types

Methods

compare :: CitationItem a -> CitationItem a -> Ordering

(<) :: CitationItem a -> CitationItem a -> Bool

(<=) :: CitationItem a -> CitationItem a -> Bool

(>) :: CitationItem a -> CitationItem a -> Bool

(>=) :: CitationItem a -> CitationItem a -> Bool

max :: CitationItem a -> CitationItem a -> CitationItem a

min :: CitationItem a -> CitationItem a -> CitationItem a

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

Defined in Citeproc.Types

Methods

showsPrec :: Int -> CitationItem a -> ShowS

show :: CitationItem a -> String

showList :: [CitationItem a] -> ShowS

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

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser (CitationItem a)

parseJSONList :: Value -> Parser [CitationItem a]

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

Defined in Citeproc.Types

Methods

toJSON :: CitationItem a -> Value

toEncoding :: CitationItem a -> Encoding

toJSONList :: [CitationItem a] -> Value

toEncodingList :: [CitationItem a] -> Encoding

data CitationItemType Source #

Constructors

AuthorOnly

e.g., Smith

SuppressAuthor

e.g., (2000, p. 30)

NormalCite

e.g., (Smith 2000, p. 30)

Instances

Instances details
Eq CitationItemType Source # 
Instance details

Defined in Citeproc.Types

Ord CitationItemType Source # 
Instance details

Defined in Citeproc.Types

Show CitationItemType Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> CitationItemType -> ShowS

show :: CitationItemType -> String

showList :: [CitationItemType] -> ShowS

FromJSON CitationItemType Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser CitationItemType

parseJSONList :: Value -> Parser [CitationItemType]

ToJSON CitationItemType 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)).

Constructors

Citation 

Fields

Instances

Instances details
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

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

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

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser (Citation a)

parseJSONList :: Value -> Parser [Citation a]

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

Defined in Citeproc.Types

Methods

toJSON :: Citation a -> Value

toEncoding :: Citation a -> Encoding

toJSONList :: [Citation a] -> Value

toEncodingList :: [Citation a] -> Encoding

data ElementType a Source #

Instances

Instances details
Eq (ElementType a) Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: ElementType a -> ElementType a -> Bool

(/=) :: ElementType a -> ElementType a -> Bool

Show (ElementType a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> ElementType a -> ShowS

show :: ElementType a -> String

showList :: [ElementType a] -> ShowS

data Element a Source #

Constructors

Element (ElementType a) Formatting 

Instances

Instances details
Eq (Element a) Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show (Element a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Element a -> ShowS

show :: Element a -> String

showList :: [Element a] -> ShowS

data NumberForm Source #

Instances

Instances details
Eq NumberForm Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: NumberForm -> NumberForm -> Bool

(/=) :: NumberForm -> NumberForm -> Bool

Show NumberForm Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NumberForm -> ShowS

show :: NumberForm -> String

showList :: [NumberForm] -> ShowS

data Pluralize Source #

Instances

Instances details
Eq Pluralize Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Pluralize -> Pluralize -> Bool

(/=) :: Pluralize -> Pluralize -> Bool

Show Pluralize Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Pluralize -> ShowS

show :: Pluralize -> String

showList :: [Pluralize] -> ShowS

data DateType Source #

Instances

Instances details
Eq DateType Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: DateType -> DateType -> Bool

(/=) :: DateType -> DateType -> Bool

Ord DateType Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: DateType -> DateType -> Ordering

(<) :: DateType -> DateType -> Bool

(<=) :: DateType -> DateType -> Bool

(>) :: DateType -> DateType -> Bool

(>=) :: DateType -> DateType -> Bool

max :: DateType -> DateType -> DateType

min :: DateType -> DateType -> DateType

Show DateType Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DateType -> ShowS

show :: DateType -> String

showList :: [DateType] -> ShowS

data Date Source #

Constructors

Date 

Fields

Instances

Instances details
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

Show Date Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Date -> ShowS

show :: Date -> String

showList :: [Date] -> ShowS

FromJSON Date Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser Date

parseJSONList :: Value -> Parser [Date]

ToJSON Date Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: Date -> Value

toEncoding :: Date -> Encoding

toJSONList :: [Date] -> Value

toEncodingList :: [Date] -> Encoding

rawDateEDTF :: Text -> Maybe Date Source #

newtype DateParts Source #

Constructors

DateParts [Int] 

Instances

Instances details
Eq DateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: DateParts -> DateParts -> Bool

(/=) :: DateParts -> DateParts -> Bool

Ord DateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: DateParts -> DateParts -> Ordering

(<) :: DateParts -> DateParts -> Bool

(<=) :: DateParts -> DateParts -> Bool

(>) :: DateParts -> DateParts -> Bool

(>=) :: DateParts -> DateParts -> Bool

max :: DateParts -> DateParts -> DateParts

min :: DateParts -> DateParts -> DateParts

Show DateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DateParts -> ShowS

show :: DateParts -> String

showList :: [DateParts] -> ShowS

FromJSON DateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser DateParts

parseJSONList :: Value -> Parser [DateParts]

ToJSON DateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: DateParts -> Value

toEncoding :: DateParts -> Encoding

toJSONList :: [DateParts] -> Value

toEncodingList :: [DateParts] -> Encoding

data ShowDateParts Source #

Constructors

YearMonthDay 
YearMonth 
Year 

Instances

Instances details
Eq ShowDateParts Source # 
Instance details

Defined in Citeproc.Types

Show ShowDateParts Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> ShowDateParts -> ShowS

show :: ShowDateParts -> String

showList :: [ShowDateParts] -> ShowS

data DPName Source #

Constructors

DPYear 
DPMonth 
DPDay 

Instances

Instances details
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

Methods

compare :: DPName -> DPName -> Ordering

(<) :: DPName -> DPName -> Bool

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

(>) :: DPName -> DPName -> Bool

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

max :: DPName -> DPName -> DPName

min :: DPName -> DPName -> DPName

Show DPName Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DPName -> ShowS

show :: DPName -> String

showList :: [DPName] -> ShowS

data DPForm Source #

Instances

Instances details
Eq DPForm Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show DPForm Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DPForm -> ShowS

show :: DPForm -> String

showList :: [DPForm] -> ShowS

data DP Source #

Constructors

DP 

Instances

Instances details
Eq DP Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show DP Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DP -> ShowS

show :: DP -> String

showList :: [DP] -> ShowS

data VariableForm Source #

Constructors

ShortForm 
LongForm 

Instances

Instances details
Eq VariableForm Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: VariableForm -> VariableForm -> Bool

(/=) :: VariableForm -> VariableForm -> Bool

Show VariableForm Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> VariableForm -> ShowS

show :: VariableForm -> String

showList :: [VariableForm] -> ShowS

data TextType Source #

Instances

Instances details
Eq TextType Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TextType -> TextType -> Bool

(/=) :: TextType -> TextType -> Bool

Show TextType Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TextType -> ShowS

show :: TextType -> String

showList :: [TextType] -> ShowS

data NameFormat Source #

Instances

Instances details
Eq NameFormat Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: NameFormat -> NameFormat -> Bool

(/=) :: NameFormat -> NameFormat -> Bool

Show NameFormat Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NameFormat -> ShowS

show :: NameFormat -> String

showList :: [NameFormat] -> ShowS

data NameAsSortOrder Source #

Instances

Instances details
Eq NameAsSortOrder Source # 
Instance details

Defined in Citeproc.Types

Show NameAsSortOrder Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NameAsSortOrder -> ShowS

show :: NameAsSortOrder -> String

showList :: [NameAsSortOrder] -> ShowS

data NamesFormat Source #

Constructors

NamesFormat 

Fields

Instances

Instances details
Eq NamesFormat Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: NamesFormat -> NamesFormat -> Bool

(/=) :: NamesFormat -> NamesFormat -> Bool

Show NamesFormat Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NamesFormat -> ShowS

show :: NamesFormat -> String

showList :: [NamesFormat] -> ShowS

data NameForm Source #

Constructors

LongName 
ShortName 
CountName 

Instances

Instances details
Eq NameForm Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: NameForm -> NameForm -> Bool

(/=) :: NameForm -> NameForm -> Bool

Show NameForm Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NameForm -> ShowS

show :: NameForm -> String

showList :: [NameForm] -> ShowS

data Name Source #

Constructors

Name 

Fields

Instances

Instances details
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

Show Name Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Name -> ShowS

show :: Name -> String

showList :: [Name] -> ShowS

FromJSON Name Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser Name

parseJSONList :: Value -> Parser [Name]

ToJSON Name Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: Name -> Value

toEncoding :: Name -> Encoding

toJSONList :: [Name] -> Value

toEncodingList :: [Name] -> Encoding

data DelimiterPrecedes Source #

Instances

Instances details
Eq DelimiterPrecedes Source # 
Instance details

Defined in Citeproc.Types

Show DelimiterPrecedes Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DelimiterPrecedes -> ShowS

show :: DelimiterPrecedes -> String

showList :: [DelimiterPrecedes] -> ShowS

data Condition Source #

Instances

Instances details
Eq Condition Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Condition -> Condition -> Bool

(/=) :: Condition -> Condition -> Bool

Show Condition Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Condition -> ShowS

show :: Condition -> String

showList :: [Condition] -> ShowS

data Position Source #

Instances

Instances details
Eq Position Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Position -> Position -> Bool

(/=) :: Position -> Position -> Bool

Ord Position Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Position -> Position -> Ordering

(<) :: Position -> Position -> Bool

(<=) :: Position -> Position -> Bool

(>) :: Position -> Position -> Bool

(>=) :: Position -> Position -> Bool

max :: Position -> Position -> Position

min :: Position -> Position -> Position

Show Position Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Position -> ShowS

show :: Position -> String

showList :: [Position] -> ShowS

data Match Source #

Constructors

MatchAll 
MatchAny 
MatchNone 

Instances

Instances details
Eq Match Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show Match Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Match -> ShowS

show :: Match -> String

showList :: [Match] -> ShowS

data Formatting Source #

Instances

Instances details
Eq Formatting Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Formatting -> Formatting -> Bool

(/=) :: Formatting -> Formatting -> Bool

Show Formatting Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Formatting -> ShowS

show :: Formatting -> String

showList :: [Formatting] -> ShowS

Semigroup Formatting Source # 
Instance details

Defined in Citeproc.Types

Methods

(<>) :: Formatting -> Formatting -> Formatting

sconcat :: NonEmpty Formatting -> Formatting

stimes :: Integral b => b -> Formatting -> Formatting

Monoid Formatting Source # 
Instance details

Defined in Citeproc.Types

data FontStyle Source #

Instances

Instances details
Eq FontStyle Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: FontStyle -> FontStyle -> Bool

(/=) :: FontStyle -> FontStyle -> Bool

Show FontStyle Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> FontStyle -> ShowS

show :: FontStyle -> String

showList :: [FontStyle] -> ShowS

data FontVariant Source #

Instances

Instances details
Eq FontVariant Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: FontVariant -> FontVariant -> Bool

(/=) :: FontVariant -> FontVariant -> Bool

Show FontVariant Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> FontVariant -> ShowS

show :: FontVariant -> String

showList :: [FontVariant] -> ShowS

data FontWeight Source #

Instances

Instances details
Eq FontWeight Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: FontWeight -> FontWeight -> Bool

(/=) :: FontWeight -> FontWeight -> Bool

Show FontWeight Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> FontWeight -> ShowS

show :: FontWeight -> String

showList :: [FontWeight] -> ShowS

data TextDecoration Source #

Instances

Instances details
Eq TextDecoration Source # 
Instance details

Defined in Citeproc.Types

Show TextDecoration Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TextDecoration -> ShowS

show :: TextDecoration -> String

showList :: [TextDecoration] -> ShowS

data VerticalAlign Source #

Instances

Instances details
Eq VerticalAlign Source # 
Instance details

Defined in Citeproc.Types

Show VerticalAlign Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> VerticalAlign -> ShowS

show :: VerticalAlign -> String

showList :: [VerticalAlign] -> ShowS

data DisplayStyle Source #

Instances

Instances details
Eq DisplayStyle Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: DisplayStyle -> DisplayStyle -> Bool

(/=) :: DisplayStyle -> DisplayStyle -> Bool

Show DisplayStyle Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DisplayStyle -> ShowS

show :: DisplayStyle -> String

showList :: [DisplayStyle] -> ShowS

data TextCase Source #

Instances

Instances details
Eq TextCase Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TextCase -> TextCase -> Bool

(/=) :: TextCase -> TextCase -> Bool

Show TextCase Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TextCase -> ShowS

show :: TextCase -> String

showList :: [TextCase] -> ShowS

data SecondFieldAlign Source #

Instances

Instances details
Eq SecondFieldAlign Source # 
Instance details

Defined in Citeproc.Types

Show SecondFieldAlign Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> SecondFieldAlign -> ShowS

show :: SecondFieldAlign -> String

showList :: [SecondFieldAlign] -> ShowS

data Style a Source #

Constructors

Style 

Instances

Instances details
Eq (Style a) Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show (Style a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Style a -> ShowS

show :: Style a -> String

showList :: [Style a] -> ShowS

data TermMatch Source #

Instances

Instances details
Eq TermMatch Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TermMatch -> TermMatch -> Bool

(/=) :: TermMatch -> TermMatch -> Bool

Ord TermMatch Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: TermMatch -> TermMatch -> Ordering

(<) :: TermMatch -> TermMatch -> Bool

(<=) :: TermMatch -> TermMatch -> Bool

(>) :: TermMatch -> TermMatch -> Bool

(>=) :: TermMatch -> TermMatch -> Bool

max :: TermMatch -> TermMatch -> TermMatch

min :: TermMatch -> TermMatch -> TermMatch

Show TermMatch Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TermMatch -> ShowS

show :: TermMatch -> String

showList :: [TermMatch] -> ShowS

data TermGender Source #

Constructors

Masculine 
Feminine 

Instances

Instances details
Eq TermGender Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TermGender -> TermGender -> Bool

(/=) :: TermGender -> TermGender -> Bool

Ord TermGender Source # 
Instance details

Defined in Citeproc.Types

Show TermGender Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TermGender -> ShowS

show :: TermGender -> String

showList :: [TermGender] -> ShowS

data TermNumber Source #

Constructors

Singular 
Plural 

Instances

Instances details
Eq TermNumber Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TermNumber -> TermNumber -> Bool

(/=) :: TermNumber -> TermNumber -> Bool

Ord TermNumber Source # 
Instance details

Defined in Citeproc.Types

Show TermNumber Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TermNumber -> ShowS

show :: TermNumber -> String

showList :: [TermNumber] -> ShowS

data TermForm Source #

Constructors

Long 
Short 
Verb 
VerbShort 
Symbol 

Instances

Instances details
Eq TermForm Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: TermForm -> TermForm -> Bool

(/=) :: TermForm -> TermForm -> Bool

Ord TermForm Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: TermForm -> TermForm -> Ordering

(<) :: TermForm -> TermForm -> Bool

(<=) :: TermForm -> TermForm -> Bool

(>) :: TermForm -> TermForm -> Bool

(>=) :: TermForm -> TermForm -> Bool

max :: TermForm -> TermForm -> TermForm

min :: TermForm -> TermForm -> TermForm

Show TermForm Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> TermForm -> ShowS

show :: TermForm -> String

showList :: [TermForm] -> ShowS

data Term Source #

Constructors

Term 

Instances

Instances details
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

Show Term Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Term -> ShowS

show :: Term -> String

showList :: [Term] -> ShowS

data SortDirection Source #

Constructors

Ascending 
Descending 

Instances

Instances details
Eq SortDirection Source # 
Instance details

Defined in Citeproc.Types

Show SortDirection Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> SortDirection -> ShowS

show :: SortDirection -> String

showList :: [SortDirection] -> ShowS

data SortKey a Source #

Instances

Instances details
Eq (SortKey a) Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show (SortKey a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> SortKey a -> ShowS

show :: SortKey a -> String

showList :: [SortKey a] -> ShowS

data SortKeyValue Source #

Constructors

SortKeyValue SortDirection (Maybe [Text]) 

Instances

Instances details
Eq SortKeyValue Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: SortKeyValue -> SortKeyValue -> Bool

(/=) :: SortKeyValue -> SortKeyValue -> Bool

Show SortKeyValue Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> SortKeyValue -> ShowS

show :: SortKeyValue -> String

showList :: [SortKeyValue] -> ShowS

data LayoutOptions Source #

Constructors

LayoutOptions 

Instances

Instances details
Eq LayoutOptions Source # 
Instance details

Defined in Citeproc.Types

Show LayoutOptions Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> LayoutOptions -> ShowS

show :: LayoutOptions -> String

showList :: [LayoutOptions] -> ShowS

data Collapsing Source #

Instances

Instances details
Eq Collapsing Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Collapsing -> Collapsing -> Bool

(/=) :: Collapsing -> Collapsing -> Bool

Show Collapsing Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Collapsing -> ShowS

show :: Collapsing -> String

showList :: [Collapsing] -> ShowS

data Layout a Source #

Instances

Instances details
Eq (Layout a) Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show (Layout a) Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Layout a -> ShowS

show :: Layout a -> String

showList :: [Layout a] -> ShowS

data Lang Source #

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

Constructors

Lang 

Fields

Instances

Instances details
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

Show Lang 
Instance details

Defined in Text.Collate.Lang

Methods

showsPrec :: Int -> Lang -> ShowS

show :: Lang -> String

showList :: [Lang] -> ShowS

IsString Lang 
Instance details

Defined in Text.Collate.Lang

Methods

fromString :: String -> Lang

Binary Lang 
Instance details

Defined in Text.Collate.Lang

Methods

put :: Lang -> Put

get :: Get Lang

putList :: [Lang] -> Put

Lift Lang 
Instance details

Defined in Text.Collate.Lang

Methods

lift :: Lang -> Q Exp

liftTyped :: Lang -> Q (TExp Lang)

parseLang :: Text -> Either String Lang Source #

Parse a BCP 47 language tag as a Lang.

renderLang :: Lang -> Text Source #

Render a Lang in BCP 47 form.

data Locale Source #

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

Constructors

Locale 

Fields

Instances

Instances details
Eq Locale Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show Locale Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Locale -> ShowS

show :: Locale -> String

showList :: [Locale] -> ShowS

Semigroup Locale Source # 
Instance details

Defined in Citeproc.Types

Methods

(<>) :: Locale -> Locale -> Locale

sconcat :: NonEmpty Locale -> Locale

stimes :: Integral b => b -> Locale -> Locale

Monoid Locale Source # 
Instance details

Defined in Citeproc.Types

data DisambiguationData Source #

Constructors

DisambiguationData 

Fields

Instances

Instances details
Show DisambiguationData Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> DisambiguationData -> ShowS

show :: DisambiguationData -> String

showList :: [DisambiguationData] -> ShowS

data NameHints Source #

Instances

Instances details
Show NameHints Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> NameHints -> ShowS

show :: NameHints -> String

showList :: [NameHints] -> ShowS

data Reference a Source #

Encodes bibliographic data for a single work.

Constructors

Reference 

Fields

Instances

Instances details
Functor Reference Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

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)

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

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Reference a -> ShowS

show :: Reference a -> String

showList :: [Reference a] -> ShowS

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

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser (Reference a)

parseJSONList :: Value -> Parser [Reference a]

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

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

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

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.

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

Instances

Instances details
Functor Val Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

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)

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

Defined in Citeproc.Types

Methods

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

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

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

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

valToText :: CiteprocOutput a => Val a -> Maybe Text Source #

data Variable Source #

Instances

Instances details
Eq Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: Variable -> Variable -> Bool

(/=) :: Variable -> Variable -> Bool

Ord Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

compare :: Variable -> Variable -> Ordering

(<) :: Variable -> Variable -> Bool

(<=) :: Variable -> Variable -> Bool

(>) :: Variable -> Variable -> Bool

(>=) :: Variable -> Variable -> Bool

max :: Variable -> Variable -> Variable

min :: Variable -> Variable -> Variable

Show Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Variable -> ShowS

show :: Variable -> String

showList :: [Variable] -> ShowS

IsString Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

fromString :: String -> Variable

Semigroup Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

(<>) :: Variable -> Variable -> Variable

sconcat :: NonEmpty Variable -> Variable

stimes :: Integral b => b -> Variable -> Variable

Monoid Variable Source # 
Instance details

Defined in Citeproc.Types

FromJSON Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser Variable

parseJSONList :: Value -> Parser [Variable]

FromJSONKey Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

fromJSONKey :: FromJSONKeyFunction Variable

fromJSONKeyList :: FromJSONKeyFunction [Variable]

ToJSON Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSON :: Variable -> Value

toEncoding :: Variable -> Encoding

toJSONList :: [Variable] -> Value

toEncodingList :: [Variable] -> Encoding

ToJSONKey Variable Source # 
Instance details

Defined in Citeproc.Types

Methods

toJSONKey :: ToJSONKeyFunction Variable

toJSONKeyList :: ToJSONKeyFunction [Variable]

data Output a Source #

Instances

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

Defined in Citeproc.Types

Methods

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

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

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

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 Tag Source #

Instances

Instances details
Eq Tag Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

Show Tag Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Tag -> ShowS

show :: Tag -> String

showList :: [Tag] -> ShowS

readAsInt :: Text -> Maybe Int Source #

data VariableType Source #

Instances

Instances details
Eq VariableType Source # 
Instance details

Defined in Citeproc.Types

Methods

(==) :: VariableType -> VariableType -> Bool

(/=) :: VariableType -> VariableType -> Bool

Show VariableType Source # 
Instance details

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

Instances details
Eq Abbreviations Source # 
Instance details

Defined in Citeproc.Types

Ord Abbreviations Source # 
Instance details

Defined in Citeproc.Types

Show Abbreviations Source # 
Instance details

Defined in Citeproc.Types

Methods

showsPrec :: Int -> Abbreviations -> ShowS

show :: Abbreviations -> String

showList :: [Abbreviations] -> ShowS

FromJSON Abbreviations Source # 
Instance details

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser Abbreviations

parseJSONList :: Value -> Parser [Abbreviations]

ToJSON Abbreviations Source # 
Instance details

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.

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
Functor Result Source # 
Instance details

Defined in Citeproc.Types

Methods

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

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

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)

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

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

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser (Result a)

parseJSONList :: Value -> Parser [Result a]

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

Defined in Citeproc.Types

Methods

toJSON :: Result a -> Value

toEncoding :: Result a -> Encoding

toJSONList :: [Result a] -> Value

toEncodingList :: [Result a] -> Encoding

data Inputs a Source #

Inputs for citation processing.

Constructors

Inputs 

Fields

Instances

Instances details
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

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

Defined in Citeproc.Types

Methods

parseJSON :: Value -> Parser (Inputs a)

parseJSONList :: Value -> Parser [Inputs a]

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

Defined in Citeproc.Types

Methods

toJSON :: Inputs a -> Value

toEncoding :: Inputs a -> Encoding

toJSONList :: [Inputs a] -> Value

toEncodingList :: [Inputs a] -> Encoding