Copyright | (c) Andrea Rossato |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | Andrea Rossato <andrea.rossato@unitn.it> |
Stability | unstable |
Portability | unportable |
Safe Haskell | None |
Language | Haskell2010 |
The Style types
Synopsis
- readCSLString :: String -> [Inline]
- writeCSLString :: [Inline] -> String
- newtype Formatted = Formatted {
- unFormatted :: [Inline]
- data Style = Style {
- styleVersion :: String
- styleClass :: String
- styleInfo :: Maybe CSInfo
- styleDefaultLocale :: String
- styleLocale :: [Locale]
- styleAbbrevs :: Abbreviations
- csOptions :: [Option]
- csMacros :: [MacroMap]
- citation :: Citation
- biblio :: Maybe Bibliography
- data Locale = Locale {
- localeVersion :: String
- localeLang :: String
- localeOptions :: [Option]
- localeTerms :: [CslTerm]
- localeDate :: [Element]
- mergeLocales :: String -> Locale -> [Locale] -> [Locale]
- data CslTerm = CT {
- cslTerm :: String
- termForm :: Form
- termGender :: Gender
- termGenderForm :: Gender
- termSingular :: String
- termPlural :: String
- termMatch :: String
- newTerm :: CslTerm
- findTerm :: String -> Form -> [CslTerm] -> Maybe CslTerm
- findTerm' :: String -> Form -> Gender -> [CslTerm] -> Maybe CslTerm
- newtype Abbreviations = Abbreviations {}
- type MacroMap = (String, [Element])
- data Citation = Citation {}
- data Bibliography = Bibliography {}
- type Option = (String, String)
- mergeOptions :: [Option] -> [Option] -> [Option]
- data Layout = Layout {}
- data Element
- = Choose IfThen [IfThen] [Element]
- | Macro String Formatting
- | Const String Formatting
- | Variable [String] Form Formatting Delimiter
- | Term String Form Formatting Bool
- | Label String Form Formatting Plural
- | Number String NumericForm Formatting
- | Names [String] [Name] Formatting Delimiter [Element]
- | Substitute [Element]
- | Group Formatting Delimiter [Element]
- | Date [String] DateForm Formatting Delimiter [DatePart] String
- data IfThen = IfThen Condition Match [Element]
- data Condition = Condition {
- isType :: [String]
- isSet :: [String]
- isNumeric :: [String]
- isUncertainDate :: [String]
- isPosition :: [String]
- disambiguation :: [String]
- isLocator :: [String]
- type Delimiter = String
- data Match
- match :: Match -> [Bool] -> Bool
- data DatePart = DatePart {
- dpName :: String
- dpForm :: String
- dpRangeDelim :: String
- dpFormatting :: Formatting
- defaultDate :: [DatePart]
- data Sort
- data Sorting
- compare' :: String -> String -> Ordering
- data Form
- data Gender
- data NumericForm
- = Numeric
- | Ordinal
- | Roman
- | LongOrdinal
- data DateForm
- data Plural
- = Contextual
- | Always
- | Never
- data Name
- type NameAttrs = [(String, String)]
- data NamePart = NamePart String Formatting
- isPlural :: Plural -> Int -> Bool
- isName :: Name -> Bool
- isNames :: Element -> Bool
- hasEtAl :: [Name] -> Bool
- data Formatting = Formatting {
- prefix :: String
- suffix :: String
- fontFamily :: String
- fontStyle :: String
- fontVariant :: String
- fontWeight :: String
- textDecoration :: String
- verticalAlign :: String
- textCase :: String
- display :: String
- quotes :: Quote
- stripPeriods :: Bool
- noCase :: Bool
- noDecor :: Bool
- hyperlink :: String
- emptyFormatting :: Formatting
- rmTitleCase :: Formatting -> Formatting
- rmTitleCase' :: Output -> Output
- data Quote
- mergeFM :: Formatting -> Formatting -> Formatting
- data CSInfo = CSInfo {
- csiTitle :: String
- csiAuthor :: CSAuthor
- csiCategories :: [CSCategory]
- csiId :: String
- csiUpdated :: String
- data CSAuthor = CSAuthor String String String
- data CSCategory = CSCategory String String String
- data CiteprocError
- data Output
- = ONull
- | OSpace
- | OPan [Inline]
- | ODel String
- | OStr String Formatting
- | OErr CiteprocError
- | OLabel String Formatting
- | ONum Int Formatting
- | OCitNum Int Formatting
- | OCitLabel String Formatting
- | ODate [Output]
- | OYear String String Formatting
- | OYearSuf String String [Output] Formatting
- | OName Agent [Output] [[Output]] Formatting
- | OContrib String String [Output] [Output] [[Output]]
- | OLoc [Output] Formatting
- | Output [Output] Formatting
- type Citations = [[Cite]]
- data Cite = Cite {}
- emptyCite :: Cite
- data CitationGroup = CG [(Cite, Output)] Formatting Delimiter [(Cite, Output)]
- data BiblioData = BD {
- citations :: [Formatted]
- bibliography :: [Formatted]
- citationIds :: [String]
- data CiteData = CD {}
- data NameData = ND {
- nameKey :: Agent
- nameCollision :: [Output]
- nameDisambData :: [[Output]]
- nameDataSolved :: [Output]
- isPunctuationInQuote :: Style -> Bool
- object' :: [Pair] -> Value
- data Agent = Agent {}
- emptyAgent :: Agent
Documentation
readCSLString :: String -> [Inline] Source #
writeCSLString :: [Inline] -> String Source #
Formatted | |
|
Instances
The representation of a parsed CSL style.
Style | |
|
Instances
Locale | |
|
Instances
Eq Locale Source # | |
Data Locale Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Locale Source # | |
Defined in Text.CSL.Style type Rep Locale = D1 (MetaData "Locale" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "Locale" PrefixI True) ((S1 (MetaSel (Just "localeVersion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "localeLang") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "localeOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Option]) :*: (S1 (MetaSel (Just "localeTerms") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CslTerm]) :*: S1 (MetaSel (Just "localeDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Element]))))) |
CT | |
|
Instances
newtype Abbreviations Source #
Instances
Instances
Data Citation Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Citation Source # | |
Defined in Text.CSL.Style type Rep Citation = D1 (MetaData "Citation" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" 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 #
Instances
Instances
Data Layout Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Layout Source # | |
Defined in Text.CSL.Style type Rep Layout = D1 (MetaData "Layout" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" 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])))) |
Instances
Instances
Eq IfThen Source # | |
Data IfThen Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep IfThen Source # | |
Defined in Text.CSL.Style type Rep IfThen = D1 (MetaData "IfThen" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "IfThen" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Condition) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Match) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Element])))) |
Condition | |
|
Instances
Instances
Eq Match Source # | |
Data Match Source # | |
Defined in Text.CSL.Style 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 # 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 # | |
Generic Match Source # | |
type Rep Match Source # | |
DatePart | |
|
Instances
Eq DatePart Source # | |
Data DatePart Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep DatePart Source # | |
Defined in Text.CSL.Style type Rep DatePart = D1 (MetaData "DatePart" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "DatePart" PrefixI True) ((S1 (MetaSel (Just "dpName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "dpForm") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "dpRangeDelim") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "dpFormatting") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatting)))) |
defaultDate :: [DatePart] Source #
Instances
Instances
Eq Sorting Source # | |
Data Sorting Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Sorting Source # | |
Defined in Text.CSL.Style type Rep Sorting = D1 (MetaData "Sorting" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "Ascending" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "Descending" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
Instances
Eq Form Source # | |
Data Form Source # | |
Defined in Text.CSL.Style 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 # 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 # | |
Generic Form Source # | |
type Rep Form Source # | |
Defined in Text.CSL.Style type Rep Form = D1 (MetaData "Form" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" 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 :: * -> *)))) |
Instances
Eq Gender Source # | |
Data Gender Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Gender Source # | |
Defined in Text.CSL.Style |
data NumericForm Source #
Instances
Instances
Eq DateForm Source # | |
Data DateForm Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep DateForm Source # | |
Defined in Text.CSL.Style |
Instances
Eq Plural Source # | |
Data Plural Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep Plural Source # | |
Defined in Text.CSL.Style |
Name Form Formatting NameAttrs Delimiter [NamePart] | |
NameLabel Form Formatting Plural | |
EtAl Formatting String |
Instances
Instances
Eq NamePart Source # | |
Data NamePart Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep NamePart Source # | |
Defined in Text.CSL.Style type Rep NamePart = D1 (MetaData "NamePart" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "NamePart" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Formatting))) |
data Formatting Source #
Formatting | |
|
Instances
rmTitleCase :: Formatting -> Formatting Source #
rmTitleCase' :: Output -> Output Source #
Instances
Eq Quote Source # | |
Data Quote Source # | |
Defined in Text.CSL.Style 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 # 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 # | |
Read Quote Source # | |
Show Quote Source # | |
Generic Quote Source # | |
type Rep Quote Source # | |
Defined in Text.CSL.Style |
mergeFM :: Formatting -> Formatting -> Formatting Source #
CSInfo | |
|
Instances
Data CSInfo Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep CSInfo Source # | |
Defined in Text.CSL.Style type Rep CSInfo = D1 (MetaData "CSInfo" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "CSInfo" PrefixI True) ((S1 (MetaSel (Just "csiTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "csiAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CSAuthor)) :*: (S1 (MetaSel (Just "csiCategories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CSCategory]) :*: (S1 (MetaSel (Just "csiId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "csiUpdated") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |
Instances
Eq CSAuthor Source # | |
Data CSAuthor Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep CSAuthor Source # | |
Defined in Text.CSL.Style type Rep CSAuthor = D1 (MetaData "CSAuthor" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" False) (C1 (MetaCons "CSAuthor" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) |
data CSCategory Source #
Instances
data CiteprocError Source #
Instances
The Output
generated by the evaluation of a style. Must be
further processed for disambiguation and collapsing.
ONull | |
OSpace | |
OPan [Inline] | |
ODel String | A delimiter string. |
OStr String Formatting | A simple |
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 |
Instances
Cite | |
|
Instances
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.
Instances
data BiblioData Source #
BD | |
|
Instances
Data BiblioData Source # | |
Defined in Text.CSL.Style 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 # | |
Defined in Text.CSL.Style showsPrec :: Int -> BiblioData -> ShowS # show :: BiblioData -> String # showList :: [BiblioData] -> ShowS # | |
Generic BiblioData Source # | |
Defined in Text.CSL.Style type Rep BiblioData :: * -> * # from :: BiblioData -> Rep BiblioData x # to :: Rep BiblioData x -> BiblioData # | |
type Rep BiblioData Source # | |
Defined in Text.CSL.Style type Rep BiblioData = D1 (MetaData "BiblioData" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" 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 [String])))) |
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.
Instances
ND | |
|
Instances
Eq NameData Source # | |
Data NameData Source # | |
Defined in Text.CSL.Style 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 # | |
type Rep NameData Source # | |
Defined in Text.CSL.Style type Rep NameData = D1 (MetaData "NameData" "Text.CSL.Style" "pandoc-citeproc-0.14.5-8kXKYZAAxQk7DUQ5Gc4EH8" 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])))) |
isPunctuationInQuote :: Style -> Bool Source #
Agent | |
|
Instances
emptyAgent :: Agent Source #