pandoc-citeproc-0.17.0.2: 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 # 
Instance details

Defined in Text.CSL.Style

Data Formatted Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Read Formatted Source # 
Instance details

Defined in Text.CSL.Style

Show Formatted Source # 
Instance details

Defined in Text.CSL.Style

IsString Formatted Source # 
Instance details

Defined in Text.CSL.Style

Generic Formatted Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Formatted :: Type -> Type #

Semigroup Formatted Source # 
Instance details

Defined in Text.CSL.Style

Monoid Formatted Source # 
Instance details

Defined in Text.CSL.Style

FromJSON Formatted Source # 
Instance details

Defined in Text.CSL.Style

ToJSON Formatted Source # 
Instance details

Defined in Text.CSL.Style

ToYaml Formatted Source # 
Instance details

Defined in Text.CSL.Style

Walkable Inline Formatted Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

type Rep Formatted = D1 (MetaData "Formatted" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" True) (C1 (MetaCons "Formatted" PrefixI True) (S1 (MetaSel (Just "unFormatted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Inline])))

data Style Source #

The representation of a parsed CSL style.

Instances
Data Style Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Style Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style Source # 
Instance details

Defined in Text.CSL.Style

data Locale Source #

Instances
Eq Locale Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Locale Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Locale Source # 
Instance details

Defined in Text.CSL.Style

Generic Locale Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Locale :: Type -> Type #

Methods

from :: Locale -> Rep Locale x #

to :: Rep Locale x -> Locale #

type Rep Locale Source # 
Instance details

Defined in Text.CSL.Style

mergeLocales :: Text -> 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 # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data CslTerm Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show CslTerm Source # 
Instance details

Defined in Text.CSL.Style

Generic CslTerm Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CslTerm :: Type -> Type #

Methods

from :: CslTerm -> Rep CslTerm x #

to :: Rep CslTerm x -> CslTerm #

type Rep CslTerm Source # 
Instance details

Defined in Text.CSL.Style

newtype Abbreviations Source #

Constructors

Abbreviations 
Instances
Data Abbreviations Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Abbreviations Source # 
Instance details

Defined in Text.CSL.Style

Generic Abbreviations Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Abbreviations :: Type -> Type #

FromJSON Abbreviations Source # 
Instance details

Defined in Text.CSL.Style

type Rep Abbreviations Source # 
Instance details

Defined in Text.CSL.Style

type Rep Abbreviations = D1 (MetaData "Abbreviations" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" True) (C1 (MetaCons "Abbreviations" PrefixI True) (S1 (MetaSel (Just "unAbbreviations") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Text (Map Text (Map Text Text))))))

data Citation Source #

Constructors

Citation 

Fields

Instances
Data Citation Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Citation Source # 
Instance details

Defined in Text.CSL.Style

Generic Citation Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Citation :: Type -> Type #

Methods

from :: Citation -> Rep Citation x #

to :: Rep Citation x -> Citation #

type Rep Citation Source # 
Instance details

Defined in Text.CSL.Style

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

data Bibliography Source #

Constructors

Bibliography 

Fields

Instances
Data Bibliography Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Bibliography Source # 
Instance details

Defined in Text.CSL.Style

Generic Bibliography Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Bibliography :: Type -> Type #

type Rep Bibliography Source # 
Instance details

Defined in Text.CSL.Style

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

type Option = (Text, Text) Source #

data Layout Source #

Constructors

Layout 
Instances
Data Layout Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Layout Source # 
Instance details

Defined in Text.CSL.Style

Generic Layout Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Layout :: Type -> Type #

Methods

from :: Layout -> Rep Layout x #

to :: Rep Layout x -> Layout #

type Rep Layout Source # 
Instance details

Defined in Text.CSL.Style

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

data Element Source #

Instances
Eq Element Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Element Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Element Source # 
Instance details

Defined in Text.CSL.Style

Generic Element Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Element :: Type -> Type #

Methods

from :: Element -> Rep Element x #

to :: Rep Element x -> Element #

type Rep Element Source # 
Instance details

Defined in Text.CSL.Style

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

data IfThen Source #

Constructors

IfThen Condition Match [Element] 
Instances
Eq IfThen Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data IfThen Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show IfThen Source # 
Instance details

Defined in Text.CSL.Style

Generic IfThen Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep IfThen :: Type -> Type #

Methods

from :: IfThen -> Rep IfThen x #

to :: Rep IfThen x -> IfThen #

type Rep IfThen Source # 
Instance details

Defined in Text.CSL.Style

data Condition Source #

Constructors

Condition 
Instances
Eq Condition Source # 
Instance details

Defined in Text.CSL.Style

Data Condition Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Condition Source # 
Instance details

Defined in Text.CSL.Style

Generic Condition Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Condition :: Type -> Type #

type Rep Condition Source # 
Instance details

Defined in Text.CSL.Style

data Match Source #

Constructors

Any 
All 
None 
Instances
Eq Match Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Match Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Match Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Generic Match Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

type Rep Match Source # 
Instance details

Defined in Text.CSL.Style

type Rep Match = D1 (MetaData "Match" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "Any" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "All" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type)))

data DatePart Source #

Constructors

DatePart 
Instances
Eq DatePart Source # 
Instance details

Defined in Text.CSL.Style

Data DatePart Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show DatePart Source # 
Instance details

Defined in Text.CSL.Style

Generic DatePart Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep DatePart :: Type -> Type #

Methods

from :: DatePart -> Rep DatePart x #

to :: Rep DatePart x -> DatePart #

type Rep DatePart Source # 
Instance details

Defined in Text.CSL.Style

data Sort Source #

Instances
Eq Sort Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Sort Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Sort Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Sort -> ShowS #

show :: Sort -> String #

showList :: [Sort] -> ShowS #

Generic Sort Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Sort :: Type -> Type #

Methods

from :: Sort -> Rep Sort x #

to :: Rep Sort x -> Sort #

type Rep Sort Source # 
Instance details

Defined in Text.CSL.Style

data Sorting Source #

Constructors

Ascending Text 
Descending Text 
Instances
Eq Sorting Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Sorting Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Read Sorting Source # 
Instance details

Defined in Text.CSL.Style

Show Sorting Source # 
Instance details

Defined in Text.CSL.Style

Generic Sorting Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Sorting :: Type -> Type #

Methods

from :: Sorting -> Rep Sorting x #

to :: Rep Sorting x -> Sorting #

type Rep Sorting Source # 
Instance details

Defined in Text.CSL.Style

type Rep Sorting = D1 (MetaData "Sorting" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "Ascending" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "Descending" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data Form Source #

Constructors

Long 
Short 
Count 
Verb 
VerbShort 
Symbol 
NotSet 
Instances
Eq Form Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Form Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Form Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Form -> ShowS #

show :: Form -> String #

showList :: [Form] -> ShowS #

Generic Form Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Form :: Type -> Type #

Methods

from :: Form -> Rep Form x #

to :: Rep Form x -> Form #

type Rep Form Source # 
Instance details

Defined in Text.CSL.Style

type Rep Form = D1 (MetaData "Form" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) ((C1 (MetaCons "Long" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Short" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Count" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "Verb" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "VerbShort" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Symbol" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotSet" PrefixI False) (U1 :: Type -> Type))))

data Gender Source #

Constructors

Feminine 
Masculine 
Neuter 
Instances
Eq Gender Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Gender Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Gender Source # 
Instance details

Defined in Text.CSL.Style

Generic Gender Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Gender :: Type -> Type #

Methods

from :: Gender -> Rep Gender x #

to :: Rep Gender x -> Gender #

type Rep Gender Source # 
Instance details

Defined in Text.CSL.Style

type Rep Gender = D1 (MetaData "Gender" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "Feminine" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Masculine" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Neuter" PrefixI False) (U1 :: Type -> Type)))

data NumericForm Source #

Constructors

Numeric 
Ordinal 
Roman 
LongOrdinal 
Instances
Eq NumericForm Source # 
Instance details

Defined in Text.CSL.Style

Data NumericForm Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show NumericForm Source # 
Instance details

Defined in Text.CSL.Style

Generic NumericForm Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep NumericForm :: Type -> Type #

type Rep NumericForm Source # 
Instance details

Defined in Text.CSL.Style

type Rep NumericForm = D1 (MetaData "NumericForm" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) ((C1 (MetaCons "Numeric" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Ordinal" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Roman" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LongOrdinal" PrefixI False) (U1 :: Type -> Type)))

data DateForm Source #

Instances
Eq DateForm Source # 
Instance details

Defined in Text.CSL.Style

Data DateForm Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show DateForm Source # 
Instance details

Defined in Text.CSL.Style

Generic DateForm Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep DateForm :: Type -> Type #

Methods

from :: DateForm -> Rep DateForm x #

to :: Rep DateForm x -> DateForm #

type Rep DateForm Source # 
Instance details

Defined in Text.CSL.Style

type Rep DateForm = D1 (MetaData "DateForm" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "TextDate" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "NumericDate" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoFormDate" PrefixI False) (U1 :: Type -> Type)))

data Plural Source #

Constructors

Contextual 
Always 
Never 
Instances
Eq Plural Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Plural Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Plural Source # 
Instance details

Defined in Text.CSL.Style

Generic Plural Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Plural :: Type -> Type #

Methods

from :: Plural -> Rep Plural x #

to :: Rep Plural x -> Plural #

type Rep Plural Source # 
Instance details

Defined in Text.CSL.Style

type Rep Plural = D1 (MetaData "Plural" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "Contextual" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Always" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Never" PrefixI False) (U1 :: Type -> Type)))

data Name Source #

Instances
Eq Name Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Name Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Name Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

type Rep Name Source # 
Instance details

Defined in Text.CSL.Style

type NameAttrs = [(Text, Text)] Source #

data NamePart Source #

Constructors

NamePart Text Formatting 
Instances
Eq NamePart Source # 
Instance details

Defined in Text.CSL.Style

Data NamePart Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show NamePart Source # 
Instance details

Defined in Text.CSL.Style

Generic NamePart Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep NamePart :: Type -> Type #

Methods

from :: NamePart -> Rep NamePart x #

to :: Rep NamePart x -> NamePart #

type Rep NamePart Source # 
Instance details

Defined in Text.CSL.Style

type Rep NamePart = D1 (MetaData "NamePart" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "NamePart" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatting)))

data Formatting Source #

Instances
Eq Formatting Source # 
Instance details

Defined in Text.CSL.Style

Data Formatting Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Read Formatting Source # 
Instance details

Defined in Text.CSL.Style

Show Formatting Source # 
Instance details

Defined in Text.CSL.Style

Generic Formatting Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Formatting :: Type -> Type #

type Rep Formatting Source # 
Instance details

Defined in Text.CSL.Style

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

data Quote Source #

Instances
Eq Quote Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Quote Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Quote Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Quote -> ShowS #

show :: Quote -> String #

showList :: [Quote] -> ShowS #

Generic Quote Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Quote :: Type -> Type #

Methods

from :: Quote -> Rep Quote x #

to :: Rep Quote x -> Quote #

type Rep Quote Source # 
Instance details

Defined in Text.CSL.Style

type Rep Quote = D1 (MetaData "Quote" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "NativeQuote" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ParsedQuote" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NoQuote" PrefixI False) (U1 :: Type -> Type)))

data CSInfo Source #

Instances
Data CSInfo Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show CSInfo Source # 
Instance details

Defined in Text.CSL.Style

Generic CSInfo Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CSInfo :: Type -> Type #

Methods

from :: CSInfo -> Rep CSInfo x #

to :: Rep CSInfo x -> CSInfo #

type Rep CSInfo Source # 
Instance details

Defined in Text.CSL.Style

data CSAuthor Source #

Constructors

CSAuthor Text Text Text 
Instances
Eq CSAuthor Source # 
Instance details

Defined in Text.CSL.Style

Data CSAuthor Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show CSAuthor Source # 
Instance details

Defined in Text.CSL.Style

Generic CSAuthor Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CSAuthor :: Type -> Type #

Methods

from :: CSAuthor -> Rep CSAuthor x #

to :: Rep CSAuthor x -> CSAuthor #

type Rep CSAuthor Source # 
Instance details

Defined in Text.CSL.Style

data CSCategory Source #

Constructors

CSCategory Text Text Text 
Instances
Eq CSCategory Source # 
Instance details

Defined in Text.CSL.Style

Data CSCategory Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show CSCategory Source # 
Instance details

Defined in Text.CSL.Style

Generic CSCategory Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CSCategory :: Type -> Type #

type Rep CSCategory Source # 
Instance details

Defined in Text.CSL.Style

data CiteprocError Source #

Instances
Eq CiteprocError Source # 
Instance details

Defined in Text.CSL.Style

Data CiteprocError Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show CiteprocError Source # 
Instance details

Defined in Text.CSL.Style

Generic CiteprocError Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CiteprocError :: Type -> Type #

type Rep CiteprocError Source # 
Instance details

Defined in Text.CSL.Style

type Rep CiteprocError = D1 (MetaData "CiteprocError" "Text.CSL.Style" "pandoc-citeproc-0.17.0.2-LTUsdt8W0rmDtuVXdpSBd6" False) (C1 (MetaCons "NoOutput" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ReferenceNotFound" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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] 
OStatus [Inline] 
ODel Text

A delimiter string.

OStr Text Formatting

A simple Value

OErr CiteprocError

Warning message

OLabel Text Formatting

A label used for roles

ONum Int Formatting

A number (used to count contributors)

OCitNum Int Formatting

The citation number

OCitLabel Text Formatting

The citation label

ODate [Output]

A (possibly) ranged date

OYear Text Text Formatting

The year and the citeId

OYearSuf Text Text [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 Text Text [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 # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Output Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Output Source # 
Instance details

Defined in Text.CSL.Style

Generic Output Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Output :: Type -> Type #

Methods

from :: Output -> Rep Output x #

to :: Rep Output x -> Output #

type Rep Output Source # 
Instance details

Defined in Text.CSL.Style

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

type Citations = [[Cite]] Source #

data Cite Source #

Instances
Eq Cite Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Cite Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Cite -> ShowS #

show :: Cite -> String #

showList :: [Cite] -> ShowS #

Generic Cite Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Cite :: Type -> Type #

Methods

from :: Cite -> Rep Cite x #

to :: Rep Cite x -> Cite #

FromJSON Cite Source # 
Instance details

Defined in Text.CSL.Style

FromJSON [[Cite]] Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

type Rep Cite Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Data CitationGroup Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Generic CitationGroup Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CitationGroup :: Type -> Type #

type Rep CitationGroup Source # 
Instance details

Defined in Text.CSL.Style

data BiblioData Source #

Constructors

BD 
Instances
Data BiblioData Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Generic BiblioData Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep BiblioData :: Type -> Type #

type Rep BiblioData Source # 
Instance details

Defined in Text.CSL.Style

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

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 

Fields

Instances
Eq CiteData Source # 
Instance details

Defined in Text.CSL.Style

Data CiteData Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Generic CiteData Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep CiteData :: Type -> Type #

Methods

from :: CiteData -> Rep CiteData x #

to :: Rep CiteData x -> CiteData #

type Rep CiteData Source # 
Instance details

Defined in Text.CSL.Style

data NameData Source #

Constructors

ND 
Instances
Eq NameData Source # 
Instance details

Defined in Text.CSL.Style

Data NameData Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Generic NameData Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep NameData :: Type -> Type #

Methods

from :: NameData -> Rep NameData x #

to :: Rep NameData x -> NameData #

type Rep NameData Source # 
Instance details

Defined in Text.CSL.Style

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

data Agent Source #

Instances
Eq Agent Source # 
Instance details

Defined in Text.CSL.Style

Methods

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

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

Data Agent Source # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

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 # 
Instance details

Defined in Text.CSL.Style

Show Agent Source # 
Instance details

Defined in Text.CSL.Style

Methods

showsPrec :: Int -> Agent -> ShowS #

show :: Agent -> String #

showList :: [Agent] -> ShowS #

Generic Agent Source # 
Instance details

Defined in Text.CSL.Style

Associated Types

type Rep Agent :: Type -> Type #

Methods

from :: Agent -> Rep Agent x #

to :: Rep Agent x -> Agent #

FromJSON Agent Source # 
Instance details

Defined in Text.CSL.Style

ToJSON Agent Source # 
Instance details

Defined in Text.CSL.Style

ToYaml Agent Source # 
Instance details

Defined in Text.CSL.Style

Methods

toYaml :: Agent -> YamlBuilder #

FromJSON [Agent] Source # 
Instance details

Defined in Text.CSL.Style

type Rep Agent Source # 
Instance details

Defined in Text.CSL.Style