pandoc-citeproc-0.12.2.5: Supports using pandoc with citeproc

Copyright(c) Andrea Rossato
LicenseBSD-style (see LICENSE)
MaintainerAndrea Rossato <andrea.rossato@unitn.it>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

Text.CSL.Style

Description

The Style types

Synopsis

Documentation

newtype Formatted Source #

Constructors

Formatted 

Fields

Instances

Eq Formatted Source # 
Data Formatted Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Formatted -> c Formatted #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Formatted #

toConstr :: Formatted -> Constr #

dataTypeOf :: Formatted -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Formatted) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Formatted) #

gmapT :: (forall b. Data b => b -> b) -> Formatted -> Formatted #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Formatted -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Formatted -> r #

gmapQ :: (forall d. Data d => d -> u) -> Formatted -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Formatted -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Formatted -> m Formatted #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Formatted -> m Formatted #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Formatted -> m Formatted #

Ord Formatted Source # 
Read Formatted Source # 
Show Formatted Source # 
IsString Formatted Source # 
Generic Formatted Source # 

Associated Types

type Rep Formatted :: * -> * #

Monoid Formatted Source # 
ToJSON Formatted Source # 
FromJSON Formatted Source # 
ToYaml Formatted Source # 
Walkable Inline Formatted Source # 

Methods

walk :: (Inline -> Inline) -> Formatted -> Formatted #

walkM :: (Monad m, Applicative m, Functor m) => (Inline -> m Inline) -> Formatted -> m Formatted #

query :: Monoid c => (Inline -> c) -> Formatted -> c #

Walkable Formatted Formatted Source # 

Methods

walk :: (Formatted -> Formatted) -> Formatted -> Formatted #

walkM :: (Monad m, Applicative m, Functor m) => (Formatted -> m Formatted) -> Formatted -> m Formatted #

query :: Monoid c => (Formatted -> c) -> Formatted -> c #

type Rep Formatted Source # 
type Rep Formatted = D1 * (MetaData "Formatted" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" True) (C1 * (MetaCons "Formatted" PrefixI True) (S1 * (MetaSel (Just Symbol "unFormatted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Inline])))

data Style Source #

The representation of a parsed CSL style.

Instances

Data Style Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Style -> c Style #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Style #

toConstr :: Style -> Constr #

dataTypeOf :: Style -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Style) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style) #

gmapT :: (forall b. Data b => b -> b) -> Style -> Style #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r #

gmapQ :: (forall d. Data d => d -> u) -> Style -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Style -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Style -> m Style #

Read Style Source # 
Show Style Source # 

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 

Associated Types

type Rep Style :: * -> * #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style Source # 

data Locale Source #

Instances

Eq Locale Source # 

Methods

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

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

Data Locale Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Locale -> c Locale #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Locale #

toConstr :: Locale -> Constr #

dataTypeOf :: Locale -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Locale) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Locale) #

gmapT :: (forall b. Data b => b -> b) -> Locale -> Locale #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Locale -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Locale -> r #

gmapQ :: (forall d. Data d => d -> u) -> Locale -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Locale -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Locale -> m Locale #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Locale -> m Locale #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Locale -> m Locale #

Read Locale Source # 
Show Locale Source # 
Generic Locale Source # 

Associated Types

type Rep Locale :: * -> * #

Methods

from :: Locale -> Rep Locale x #

to :: Rep Locale x -> Locale #

type Rep Locale Source # 

mergeLocales :: String -> Locale -> [Locale] -> [Locale] Source #

With the defaultLocale, the locales-xx-XX.xml loaded file and the parsed Style cs:locale elements, produce the final Locale as the only element of a list, taking into account CSL locale prioritization.

data CslTerm Source #

Instances

Eq CslTerm Source # 

Methods

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

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

Data CslTerm Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CslTerm -> c CslTerm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CslTerm #

toConstr :: CslTerm -> Constr #

dataTypeOf :: CslTerm -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CslTerm) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CslTerm) #

gmapT :: (forall b. Data b => b -> b) -> CslTerm -> CslTerm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CslTerm -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CslTerm -> r #

gmapQ :: (forall d. Data d => d -> u) -> CslTerm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CslTerm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CslTerm -> m CslTerm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CslTerm -> m CslTerm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CslTerm -> m CslTerm #

Read CslTerm Source # 
Show CslTerm Source # 
Generic CslTerm Source # 

Associated Types

type Rep CslTerm :: * -> * #

Methods

from :: CslTerm -> Rep CslTerm x #

to :: Rep CslTerm x -> CslTerm #

type Rep CslTerm Source # 

newtype Abbreviations Source #

Instances

Data Abbreviations Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Abbreviations -> c Abbreviations #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Abbreviations #

toConstr :: Abbreviations -> Constr #

dataTypeOf :: Abbreviations -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Abbreviations) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Abbreviations) #

gmapT :: (forall b. Data b => b -> b) -> Abbreviations -> Abbreviations #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Abbreviations -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Abbreviations -> r #

gmapQ :: (forall d. Data d => d -> u) -> Abbreviations -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Abbreviations -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Abbreviations -> m Abbreviations #

Read Abbreviations Source # 
Show Abbreviations Source # 
Generic Abbreviations Source # 

Associated Types

type Rep Abbreviations :: * -> * #

FromJSON Abbreviations Source # 
type Rep Abbreviations Source # 
type Rep Abbreviations = D1 * (MetaData "Abbreviations" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" True) (C1 * (MetaCons "Abbreviations" PrefixI True) (S1 * (MetaSel (Just Symbol "unAbbreviations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Map String (Map String (Map String String))))))

data Citation Source #

Constructors

Citation 

Fields

Instances

Data Citation Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Citation -> c Citation #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Citation #

toConstr :: Citation -> Constr #

dataTypeOf :: Citation -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Citation) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Citation) #

gmapT :: (forall b. Data b => b -> b) -> Citation -> Citation #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Citation -> r #

gmapQ :: (forall d. Data d => d -> u) -> Citation -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Citation -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Citation -> m Citation #

Read Citation Source # 
Show Citation Source # 
Generic Citation Source # 

Associated Types

type Rep Citation :: * -> * #

Methods

from :: Citation -> Rep Citation x #

to :: Rep Citation x -> Citation #

type Rep Citation Source # 
type Rep Citation = D1 * (MetaData "Citation" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Citation" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "citOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Option])) ((:*:) * (S1 * (MetaSel (Just Symbol "citSort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Sort])) (S1 * (MetaSel (Just Symbol "citLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Layout)))))

data Bibliography Source #

Constructors

Bibliography 

Fields

Instances

Data Bibliography Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bibliography -> c Bibliography #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bibliography #

toConstr :: Bibliography -> Constr #

dataTypeOf :: Bibliography -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Bibliography) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bibliography) #

gmapT :: (forall b. Data b => b -> b) -> Bibliography -> Bibliography #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bibliography -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bibliography -> r #

gmapQ :: (forall d. Data d => d -> u) -> Bibliography -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bibliography -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bibliography -> m Bibliography #

Read Bibliography Source # 
Show Bibliography Source # 
Generic Bibliography Source # 

Associated Types

type Rep Bibliography :: * -> * #

type Rep Bibliography Source # 
type Rep Bibliography = D1 * (MetaData "Bibliography" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Bibliography" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "bibOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Option])) ((:*:) * (S1 * (MetaSel (Just Symbol "bibSort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Sort])) (S1 * (MetaSel (Just Symbol "bibLayout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Layout)))))

data Layout Source #

Constructors

Layout 

Instances

Data Layout Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Layout -> c Layout #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Layout #

toConstr :: Layout -> Constr #

dataTypeOf :: Layout -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Layout) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Layout) #

gmapT :: (forall b. Data b => b -> b) -> Layout -> Layout #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Layout -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Layout -> r #

gmapQ :: (forall d. Data d => d -> u) -> Layout -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Layout -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Layout -> m Layout #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Layout -> m Layout #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Layout -> m Layout #

Read Layout Source # 
Show Layout Source # 
Generic Layout Source # 

Associated Types

type Rep Layout :: * -> * #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

type Rep Layout Source # 
type Rep Layout = D1 * (MetaData "Layout" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Layout" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "layFormat") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) ((:*:) * (S1 * (MetaSel (Just Symbol "layDelim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delimiter)) (S1 * (MetaSel (Just Symbol "elements") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Element])))))

data Element Source #

Instances

Eq Element Source # 

Methods

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

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

Data Element Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Element -> c Element #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Element #

toConstr :: Element -> Constr #

dataTypeOf :: Element -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Element) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Element) #

gmapT :: (forall b. Data b => b -> b) -> Element -> Element #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Element -> r #

gmapQ :: (forall d. Data d => d -> u) -> Element -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Element -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Element -> m Element #

Read Element Source # 
Show Element Source # 
Generic Element Source # 

Associated Types

type Rep Element :: * -> * #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

type Rep Element Source # 
type Rep Element = D1 * (MetaData "Element" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Choose" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * IfThen)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [IfThen])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Element]))))) (C1 * (MetaCons "Macro" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))) ((:+:) * (C1 * (MetaCons "Const" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) ((:+:) * (C1 * (MetaCons "Variable" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Form))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delimiter))))) (C1 * (MetaCons "Term" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Form))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Label" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Form))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Plural))))) ((:+:) * (C1 * (MetaCons "Number" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * NumericForm)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))) (C1 * (MetaCons "Names" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Name]))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delimiter)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Element])))))))) ((:+:) * (C1 * (MetaCons "Substitute" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Element]))) ((:+:) * (C1 * (MetaCons "Group" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delimiter)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Element]))))) (C1 * (MetaCons "Date" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * DateForm)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Delimiter)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [DatePart])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))))))))

data IfThen Source #

Constructors

IfThen Condition Match [Element] 

Instances

Eq IfThen Source # 

Methods

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

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

Data IfThen Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IfThen -> c IfThen #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IfThen #

toConstr :: IfThen -> Constr #

dataTypeOf :: IfThen -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IfThen) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IfThen) #

gmapT :: (forall b. Data b => b -> b) -> IfThen -> IfThen #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IfThen -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IfThen -> r #

gmapQ :: (forall d. Data d => d -> u) -> IfThen -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IfThen -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IfThen -> m IfThen #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IfThen -> m IfThen #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IfThen -> m IfThen #

Read IfThen Source # 
Show IfThen Source # 
Generic IfThen Source # 

Associated Types

type Rep IfThen :: * -> * #

Methods

from :: IfThen -> Rep IfThen x #

to :: Rep IfThen x -> IfThen #

type Rep IfThen Source # 

data Condition Source #

Instances

Eq Condition Source # 
Data Condition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Condition -> c Condition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Condition #

toConstr :: Condition -> Constr #

dataTypeOf :: Condition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Condition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Condition) #

gmapT :: (forall b. Data b => b -> b) -> Condition -> Condition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Condition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition -> m Condition #

Read Condition Source # 
Show Condition Source # 
Generic Condition Source # 

Associated Types

type Rep Condition :: * -> * #

type Rep Condition Source # 

data Match Source #

Constructors

Any 
All 
None 

Instances

Eq Match Source # 

Methods

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

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

Data Match Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match -> c Match #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Match #

toConstr :: Match -> Constr #

dataTypeOf :: Match -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Match) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Match) #

gmapT :: (forall b. Data b => b -> b) -> Match -> Match #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r #

gmapQ :: (forall d. Data d => d -> u) -> Match -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Match -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match -> m Match #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match #

Read Match Source # 
Show Match Source # 

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Generic Match Source # 

Associated Types

type Rep Match :: * -> * #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

type Rep Match Source # 
type Rep Match = D1 * (MetaData "Match" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "Any" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "All" PrefixI False) (U1 *)) (C1 * (MetaCons "None" PrefixI False) (U1 *))))

data DatePart Source #

Instances

Eq DatePart Source # 
Data DatePart Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatePart -> c DatePart #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatePart #

toConstr :: DatePart -> Constr #

dataTypeOf :: DatePart -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DatePart) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatePart) #

gmapT :: (forall b. Data b => b -> b) -> DatePart -> DatePart #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatePart -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatePart -> r #

gmapQ :: (forall d. Data d => d -> u) -> DatePart -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DatePart -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatePart -> m DatePart #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatePart -> m DatePart #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatePart -> m DatePart #

Read DatePart Source # 
Show DatePart Source # 
Generic DatePart Source # 

Associated Types

type Rep DatePart :: * -> * #

Methods

from :: DatePart -> Rep DatePart x #

to :: Rep DatePart x -> DatePart #

type Rep DatePart Source # 

data Sort Source #

Instances

Eq Sort Source # 

Methods

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

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

Data Sort Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sort -> c Sort #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sort #

toConstr :: Sort -> Constr #

dataTypeOf :: Sort -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sort) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sort) #

gmapT :: (forall b. Data b => b -> b) -> Sort -> Sort #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sort -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sort -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sort -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sort -> m Sort #

Read Sort Source # 
Show Sort Source # 

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

Generic Sort Source # 

Associated Types

type Rep Sort :: * -> * #

Methods

from :: Sort -> Rep Sort x #

to :: Rep Sort x -> Sort #

type Rep Sort Source # 

data Sorting Source #

Instances

Eq Sorting Source # 

Methods

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

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

Data Sorting Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sorting -> c Sorting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sorting #

toConstr :: Sorting -> Constr #

dataTypeOf :: Sorting -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Sorting) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sorting) #

gmapT :: (forall b. Data b => b -> b) -> Sorting -> Sorting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sorting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sorting -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sorting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sorting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sorting -> m Sorting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sorting -> m Sorting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sorting -> m Sorting #

Ord Sorting Source # 
Read Sorting Source # 
Show Sorting Source # 
Generic Sorting Source # 

Associated Types

type Rep Sorting :: * -> * #

Methods

from :: Sorting -> Rep Sorting x #

to :: Rep Sorting x -> Sorting #

type Rep Sorting Source # 
type Rep Sorting = D1 * (MetaData "Sorting" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "Ascending" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) (C1 * (MetaCons "Descending" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

data Form Source #

Constructors

Long 
Short 
Count 
Verb 
VerbShort 
Symbol 
NotSet 

Instances

Eq Form Source # 

Methods

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

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

Data Form Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Form -> c Form #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Form #

toConstr :: Form -> Constr #

dataTypeOf :: Form -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Form) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Form) #

gmapT :: (forall b. Data b => b -> b) -> Form -> Form #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Form -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Form -> r #

gmapQ :: (forall d. Data d => d -> u) -> Form -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Form -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Form -> m Form #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Form -> m Form #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Form -> m Form #

Read Form Source # 
Show Form Source # 

Methods

showsPrec :: Int -> Form -> ShowS #

show :: Form -> String #

showList :: [Form] -> ShowS #

Generic Form Source # 

Associated Types

type Rep Form :: * -> * #

Methods

from :: Form -> Rep Form x #

to :: Rep Form x -> Form #

type Rep Form Source # 
type Rep Form = D1 * (MetaData "Form" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Long" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Short" PrefixI False) (U1 *)) (C1 * (MetaCons "Count" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Verb" PrefixI False) (U1 *)) (C1 * (MetaCons "VerbShort" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Symbol" PrefixI False) (U1 *)) (C1 * (MetaCons "NotSet" PrefixI False) (U1 *)))))

data Gender Source #

Constructors

Feminine 
Masculine 
Neuter 

Instances

Eq Gender Source # 

Methods

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

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

Data Gender Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Gender -> c Gender #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Gender #

toConstr :: Gender -> Constr #

dataTypeOf :: Gender -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Gender) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Gender) #

gmapT :: (forall b. Data b => b -> b) -> Gender -> Gender #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Gender -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Gender -> r #

gmapQ :: (forall d. Data d => d -> u) -> Gender -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Gender -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Gender -> m Gender #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Gender -> m Gender #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Gender -> m Gender #

Read Gender Source # 
Show Gender Source # 
Generic Gender Source # 

Associated Types

type Rep Gender :: * -> * #

Methods

from :: Gender -> Rep Gender x #

to :: Rep Gender x -> Gender #

type Rep Gender Source # 
type Rep Gender = D1 * (MetaData "Gender" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "Feminine" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Masculine" PrefixI False) (U1 *)) (C1 * (MetaCons "Neuter" PrefixI False) (U1 *))))

data NumericForm Source #

Constructors

Numeric 
Ordinal 
Roman 
LongOrdinal 

Instances

Eq NumericForm Source # 
Data NumericForm Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumericForm -> c NumericForm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NumericForm #

toConstr :: NumericForm -> Constr #

dataTypeOf :: NumericForm -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NumericForm) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NumericForm) #

gmapT :: (forall b. Data b => b -> b) -> NumericForm -> NumericForm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumericForm -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumericForm -> r #

gmapQ :: (forall d. Data d => d -> u) -> NumericForm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NumericForm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumericForm -> m NumericForm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumericForm -> m NumericForm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumericForm -> m NumericForm #

Read NumericForm Source # 
Show NumericForm Source # 
Generic NumericForm Source # 

Associated Types

type Rep NumericForm :: * -> * #

type Rep NumericForm Source # 
type Rep NumericForm = D1 * (MetaData "NumericForm" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Numeric" PrefixI False) (U1 *)) (C1 * (MetaCons "Ordinal" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Roman" PrefixI False) (U1 *)) (C1 * (MetaCons "LongOrdinal" PrefixI False) (U1 *))))

data DateForm Source #

Instances

Eq DateForm Source # 
Data DateForm Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DateForm -> c DateForm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DateForm #

toConstr :: DateForm -> Constr #

dataTypeOf :: DateForm -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DateForm) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DateForm) #

gmapT :: (forall b. Data b => b -> b) -> DateForm -> DateForm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DateForm -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DateForm -> r #

gmapQ :: (forall d. Data d => d -> u) -> DateForm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DateForm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DateForm -> m DateForm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DateForm -> m DateForm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DateForm -> m DateForm #

Read DateForm Source # 
Show DateForm Source # 
Generic DateForm Source # 

Associated Types

type Rep DateForm :: * -> * #

Methods

from :: DateForm -> Rep DateForm x #

to :: Rep DateForm x -> DateForm #

type Rep DateForm Source # 
type Rep DateForm = D1 * (MetaData "DateForm" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "TextDate" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NumericDate" PrefixI False) (U1 *)) (C1 * (MetaCons "NoFormDate" PrefixI False) (U1 *))))

data Plural Source #

Constructors

Contextual 
Always 
Never 

Instances

Eq Plural Source # 

Methods

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

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

Data Plural Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Plural -> c Plural #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Plural #

toConstr :: Plural -> Constr #

dataTypeOf :: Plural -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Plural) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Plural) #

gmapT :: (forall b. Data b => b -> b) -> Plural -> Plural #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Plural -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Plural -> r #

gmapQ :: (forall d. Data d => d -> u) -> Plural -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Plural -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Plural -> m Plural #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Plural -> m Plural #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Plural -> m Plural #

Read Plural Source # 
Show Plural Source # 
Generic Plural Source # 

Associated Types

type Rep Plural :: * -> * #

Methods

from :: Plural -> Rep Plural x #

to :: Rep Plural x -> Plural #

type Rep Plural Source # 
type Rep Plural = D1 * (MetaData "Plural" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "Contextual" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Always" PrefixI False) (U1 *)) (C1 * (MetaCons "Never" PrefixI False) (U1 *))))

data Name Source #

Instances

Eq Name Source # 

Methods

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

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

Data Name Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Read Name Source # 
Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

type Rep Name Source # 

data NamePart Source #

Constructors

NamePart String Formatting 

Instances

Eq NamePart Source # 
Data NamePart Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NamePart -> c NamePart #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NamePart #

toConstr :: NamePart -> Constr #

dataTypeOf :: NamePart -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NamePart) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NamePart) #

gmapT :: (forall b. Data b => b -> b) -> NamePart -> NamePart #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NamePart -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NamePart -> r #

gmapQ :: (forall d. Data d => d -> u) -> NamePart -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NamePart -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NamePart -> m NamePart #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NamePart -> m NamePart #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NamePart -> m NamePart #

Read NamePart Source # 
Show NamePart Source # 
Generic NamePart Source # 

Associated Types

type Rep NamePart :: * -> * #

Methods

from :: NamePart -> Rep NamePart x #

to :: Rep NamePart x -> NamePart #

type Rep NamePart Source # 
type Rep NamePart = D1 * (MetaData "NamePart" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "NamePart" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))

data Formatting Source #

Instances

Eq Formatting Source # 
Data Formatting Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Formatting -> c Formatting #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Formatting #

toConstr :: Formatting -> Constr #

dataTypeOf :: Formatting -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Formatting) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Formatting) #

gmapT :: (forall b. Data b => b -> b) -> Formatting -> Formatting #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Formatting -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Formatting -> r #

gmapQ :: (forall d. Data d => d -> u) -> Formatting -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Formatting -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Formatting -> m Formatting #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Formatting -> m Formatting #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Formatting -> m Formatting #

Ord Formatting Source # 
Read Formatting Source # 
Show Formatting Source # 
Generic Formatting Source # 

Associated Types

type Rep Formatting :: * -> * #

type Rep Formatting Source # 
type Rep Formatting = D1 * (MetaData "Formatting" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Formatting" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "prefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Just Symbol "suffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "fontFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "fontStyle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "fontVariant") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "fontWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "textDecoration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "verticalAlign") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "textCase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "display") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "quotes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Quote)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "stripPeriods") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "noCase") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))) ((:*:) * (S1 * (MetaSel (Just Symbol "noDecor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "hyperlink") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))))

data Quote Source #

Instances

Eq Quote Source # 

Methods

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

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

Data Quote Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quote -> c Quote #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quote #

toConstr :: Quote -> Constr #

dataTypeOf :: Quote -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Quote) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quote) #

gmapT :: (forall b. Data b => b -> b) -> Quote -> Quote #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quote -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quote -> r #

gmapQ :: (forall d. Data d => d -> u) -> Quote -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quote -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quote -> m Quote #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quote -> m Quote #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quote -> m Quote #

Ord Quote Source # 

Methods

compare :: Quote -> Quote -> Ordering #

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

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

(>) :: Quote -> Quote -> Bool #

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

max :: Quote -> Quote -> Quote #

min :: Quote -> Quote -> Quote #

Read Quote Source # 
Show Quote Source # 

Methods

showsPrec :: Int -> Quote -> ShowS #

show :: Quote -> String #

showList :: [Quote] -> ShowS #

Generic Quote Source # 

Associated Types

type Rep Quote :: * -> * #

Methods

from :: Quote -> Rep Quote x #

to :: Rep Quote x -> Quote #

type Rep Quote Source # 
type Rep Quote = D1 * (MetaData "Quote" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "NativeQuote" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ParsedQuote" PrefixI False) (U1 *)) (C1 * (MetaCons "NoQuote" PrefixI False) (U1 *))))

data CSInfo Source #

Instances

Data CSInfo Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CSInfo -> c CSInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CSInfo #

toConstr :: CSInfo -> Constr #

dataTypeOf :: CSInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CSInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CSInfo) #

gmapT :: (forall b. Data b => b -> b) -> CSInfo -> CSInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CSInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CSInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> CSInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CSInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CSInfo -> m CSInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CSInfo -> m CSInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CSInfo -> m CSInfo #

Read CSInfo Source # 
Show CSInfo Source # 
Generic CSInfo Source # 

Associated Types

type Rep CSInfo :: * -> * #

Methods

from :: CSInfo -> Rep CSInfo x #

to :: Rep CSInfo x -> CSInfo #

type Rep CSInfo Source # 

data CSAuthor Source #

Instances

Eq CSAuthor Source # 
Data CSAuthor Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CSAuthor -> c CSAuthor #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CSAuthor #

toConstr :: CSAuthor -> Constr #

dataTypeOf :: CSAuthor -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CSAuthor) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CSAuthor) #

gmapT :: (forall b. Data b => b -> b) -> CSAuthor -> CSAuthor #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CSAuthor -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CSAuthor -> r #

gmapQ :: (forall d. Data d => d -> u) -> CSAuthor -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CSAuthor -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CSAuthor -> m CSAuthor #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CSAuthor -> m CSAuthor #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CSAuthor -> m CSAuthor #

Read CSAuthor Source # 
Show CSAuthor Source # 
Generic CSAuthor Source # 

Associated Types

type Rep CSAuthor :: * -> * #

Methods

from :: CSAuthor -> Rep CSAuthor x #

to :: Rep CSAuthor x -> CSAuthor #

type Rep CSAuthor Source # 

data CSCategory Source #

Instances

Eq CSCategory Source # 
Data CSCategory Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CSCategory -> c CSCategory #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CSCategory #

toConstr :: CSCategory -> Constr #

dataTypeOf :: CSCategory -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CSCategory) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CSCategory) #

gmapT :: (forall b. Data b => b -> b) -> CSCategory -> CSCategory #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CSCategory -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CSCategory -> r #

gmapQ :: (forall d. Data d => d -> u) -> CSCategory -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CSCategory -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CSCategory -> m CSCategory #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CSCategory -> m CSCategory #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CSCategory -> m CSCategory #

Read CSCategory Source # 
Show CSCategory Source # 
Generic CSCategory Source # 

Associated Types

type Rep CSCategory :: * -> * #

type Rep CSCategory Source # 

data CiteprocError Source #

Instances

Eq CiteprocError Source # 
Data CiteprocError Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CiteprocError -> c CiteprocError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CiteprocError #

toConstr :: CiteprocError -> Constr #

dataTypeOf :: CiteprocError -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CiteprocError) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteprocError) #

gmapT :: (forall b. Data b => b -> b) -> CiteprocError -> CiteprocError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CiteprocError -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CiteprocError -> r #

gmapQ :: (forall d. Data d => d -> u) -> CiteprocError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CiteprocError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CiteprocError -> m CiteprocError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteprocError -> m CiteprocError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteprocError -> m CiteprocError #

Ord CiteprocError Source # 
Show CiteprocError Source # 
Generic CiteprocError Source # 

Associated Types

type Rep CiteprocError :: * -> * #

type Rep CiteprocError Source # 
type Rep CiteprocError = D1 * (MetaData "CiteprocError" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * (C1 * (MetaCons "NoOutput" PrefixI False) (U1 *)) (C1 * (MetaCons "ReferenceNotFound" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))

data Output Source #

The Output generated by the evaluation of a style. Must be further processed for disambiguation and collapsing.

Constructors

ONull 
OSpace 
OPan [Inline] 
ODel String

A delimiter string.

OStr String Formatting

A simple String

OErr CiteprocError

Warning message

OLabel String Formatting

A label used for roles

ONum Int Formatting

A number (used to count contributors)

OCitNum Int Formatting

The citation number

OCitLabel String Formatting

The citation label

ODate [Output]

A (possibly) ranged date

OYear String String Formatting

The year and the citeId

OYearSuf String String [Output] Formatting

The year suffix, the citeId and a holder for collision data

OName Agent [Output] [[Output]] Formatting

A (family) name with the list of given names.

OContrib String String [Output] [Output] [[Output]]

The citation key, the role (author, editor, etc.), the contributor(s), the output needed for year suf. disambiguation, and everything used for name disambiguation.

OLoc [Output] Formatting

The citation's locator

Output [Output] Formatting

Some nested Output

Instances

Eq Output Source # 

Methods

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

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

Data Output Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Output -> c Output #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Output #

toConstr :: Output -> Constr #

dataTypeOf :: Output -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Output) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Output) #

gmapT :: (forall b. Data b => b -> b) -> Output -> Output #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Output -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Output -> r #

gmapQ :: (forall d. Data d => d -> u) -> Output -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Output -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Output -> m Output #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Output -> m Output #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Output -> m Output #

Ord Output Source # 
Show Output Source # 
Generic Output Source # 

Associated Types

type Rep Output :: * -> * #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

type Rep Output Source # 
type Rep Output = D1 * (MetaData "Output" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "ONull" PrefixI False) (U1 *)) (C1 * (MetaCons "OSpace" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "OPan" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Inline]))) (C1 * (MetaCons "ODel" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))) ((:+:) * ((:+:) * (C1 * (MetaCons "OStr" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) (C1 * (MetaCons "OErr" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CiteprocError)))) ((:+:) * (C1 * (MetaCons "OLabel" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) (C1 * (MetaCons "ONum" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "OCitNum" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) (C1 * (MetaCons "OCitLabel" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))) ((:+:) * (C1 * (MetaCons "ODate" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output]))) (C1 * (MetaCons "OYear" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))))) ((:+:) * ((:+:) * (C1 * (MetaCons "OYearSuf" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting))))) (C1 * (MetaCons "OName" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Agent)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output]))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [[Output]])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))))) ((:+:) * (C1 * (MetaCons "OContrib" PrefixI False) ((:*:) * ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [[Output]])))))) ((:+:) * (C1 * (MetaCons "OLoc" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))) (C1 * (MetaCons "Output" PrefixI False) ((:*:) * (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatting)))))))))

type Citations = [[Cite]] Source #

data Cite Source #

Instances

Eq Cite Source # 

Methods

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

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

Data Cite Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cite -> c Cite #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cite #

toConstr :: Cite -> Constr #

dataTypeOf :: Cite -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cite) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cite) #

gmapT :: (forall b. Data b => b -> b) -> Cite -> Cite #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cite -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cite -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cite -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cite -> m Cite #

Show Cite Source # 

Methods

showsPrec :: Int -> Cite -> ShowS #

show :: Cite -> String #

showList :: [Cite] -> ShowS #

Generic Cite Source # 

Associated Types

type Rep Cite :: * -> * #

Methods

from :: Cite -> Rep Cite x #

to :: Rep Cite x -> Cite #

FromJSON Cite Source # 
FromJSON [[Cite]] Source # 

Methods

parseJSON :: Value -> Parser [[Cite]] #

parseJSONList :: Value -> Parser [[[Cite]]] #

type Rep Cite Source # 

data CitationGroup Source #

A citation group: the first list has a single member when the citation group starts with an "author-in-text" cite, the Formatting to be applied, the Delimiter between individual citations and the list of evaluated citations.

Constructors

CG [(Cite, Output)] Formatting Delimiter [(Cite, Output)] 

Instances

Eq CitationGroup Source # 
Data CitationGroup Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CitationGroup -> c CitationGroup #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CitationGroup #

toConstr :: CitationGroup -> Constr #

dataTypeOf :: CitationGroup -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CitationGroup) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CitationGroup) #

gmapT :: (forall b. Data b => b -> b) -> CitationGroup -> CitationGroup #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CitationGroup -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CitationGroup -> r #

gmapQ :: (forall d. Data d => d -> u) -> CitationGroup -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CitationGroup -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CitationGroup -> m CitationGroup #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CitationGroup -> m CitationGroup #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CitationGroup -> m CitationGroup #

Show CitationGroup Source # 
Generic CitationGroup Source # 

Associated Types

type Rep CitationGroup :: * -> * #

type Rep CitationGroup Source # 

data BiblioData Source #

Constructors

BD 

Instances

Data BiblioData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BiblioData -> c BiblioData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BiblioData #

toConstr :: BiblioData -> Constr #

dataTypeOf :: BiblioData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BiblioData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BiblioData) #

gmapT :: (forall b. Data b => b -> b) -> BiblioData -> BiblioData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BiblioData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BiblioData -> r #

gmapQ :: (forall d. Data d => d -> u) -> BiblioData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BiblioData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BiblioData -> m BiblioData #

Show BiblioData Source # 
Generic BiblioData Source # 

Associated Types

type Rep BiblioData :: * -> * #

type Rep BiblioData Source # 
type Rep BiblioData = D1 * (MetaData "BiblioData" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "BD" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "citations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Formatted])) ((:*:) * (S1 * (MetaSel (Just Symbol "bibliography") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Formatted])) (S1 * (MetaSel (Just Symbol "citationIds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])))))

data CiteData Source #

A record with all the data to produce the Formatted of a citation: the citation key, the part of the formatted citation that may be colliding with other citations, the form of the citation when a year suffix is used for disambiguation , the data to disambiguate it (all possible contributors and all possible given names), and, after processing, the disambiguated citation and its year, initially empty.

Constructors

CD 

Instances

Eq CiteData Source # 
Data CiteData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CiteData -> c CiteData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CiteData #

toConstr :: CiteData -> Constr #

dataTypeOf :: CiteData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c CiteData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CiteData) #

gmapT :: (forall b. Data b => b -> b) -> CiteData -> CiteData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CiteData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CiteData -> r #

gmapQ :: (forall d. Data d => d -> u) -> CiteData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CiteData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CiteData -> m CiteData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteData -> m CiteData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CiteData -> m CiteData #

Show CiteData Source # 
Generic CiteData Source # 

Associated Types

type Rep CiteData :: * -> * #

Methods

from :: CiteData -> Rep CiteData x #

to :: Rep CiteData x -> CiteData #

type Rep CiteData Source # 

data NameData Source #

Constructors

ND 

Instances

Eq NameData Source # 
Data NameData Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameData -> c NameData #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameData #

toConstr :: NameData -> Constr #

dataTypeOf :: NameData -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c NameData) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameData) #

gmapT :: (forall b. Data b => b -> b) -> NameData -> NameData #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameData -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameData -> r #

gmapQ :: (forall d. Data d => d -> u) -> NameData -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NameData -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameData -> m NameData #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameData -> m NameData #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameData -> m NameData #

Show NameData Source # 
Generic NameData Source # 

Associated Types

type Rep NameData :: * -> * #

Methods

from :: NameData -> Rep NameData x #

to :: Rep NameData x -> NameData #

type Rep NameData Source # 
type Rep NameData = D1 * (MetaData "NameData" "Text.CSL.Style" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "ND" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "nameKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Agent)) (S1 * (MetaSel (Just Symbol "nameCollision") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output]))) ((:*:) * (S1 * (MetaSel (Just Symbol "nameDisambData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [[Output]])) (S1 * (MetaSel (Just Symbol "nameDataSolved") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Output])))))

data Agent Source #

Instances

Eq Agent Source # 

Methods

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

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

Data Agent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Agent -> c Agent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Agent #

toConstr :: Agent -> Constr #

dataTypeOf :: Agent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Agent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Agent) #

gmapT :: (forall b. Data b => b -> b) -> Agent -> Agent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Agent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Agent -> r #

gmapQ :: (forall d. Data d => d -> u) -> Agent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Agent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Agent -> m Agent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Agent -> m Agent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Agent -> m Agent #

Ord Agent Source # 

Methods

compare :: Agent -> Agent -> Ordering #

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

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

(>) :: Agent -> Agent -> Bool #

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

max :: Agent -> Agent -> Agent #

min :: Agent -> Agent -> Agent #

Read Agent Source # 
Show Agent Source # 

Methods

showsPrec :: Int -> Agent -> ShowS #

show :: Agent -> String #

showList :: [Agent] -> ShowS #

Generic Agent Source # 

Associated Types

type Rep Agent :: * -> * #

Methods

from :: Agent -> Rep Agent x #

to :: Rep Agent x -> Agent #

ToJSON Agent Source # 
FromJSON Agent Source # 
ToYaml Agent Source # 

Methods

toYaml :: Agent -> YamlBuilder #

FromJSON [Agent] Source # 
type Rep Agent Source #