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 |
This module provides functions for processing the evaluated
Output
for citation disambiguation.
Describe the disambiguation process.
Synopsis
- disambCitations :: Style -> [Reference] -> Citations -> [CitationGroup] -> ([(String, String)], [CitationGroup])
- mapDisambData :: (Output -> Output) -> CiteData -> CiteData
- mapCitationGroup :: ([Output] -> [Output]) -> CitationGroup -> CitationGroup
- data GiveNameDisambiguation
- = NoGiven
- | ByCite
- | AllNames
- | PrimaryName
- disambAddNames :: GiveNameDisambiguation -> [CiteData] -> [CiteData]
- disambAddGivenNames :: [NameData] -> [NameData]
- updateContrib :: GiveNameDisambiguation -> [CiteData] -> [NameData] -> Output -> Output
- updateOName :: [NameData] -> Output -> Output
- reEvaluate :: Style -> [CiteData] -> [(Cite, Maybe Reference)] -> CitationGroup -> CitationGroup
- hasIfDis :: IfThen -> [Bool]
- getCitDisambOptions :: Style -> [String]
- getDuplCiteData :: GiveNameDisambiguation -> Bool -> Bool -> [CitationGroup] -> [[CiteData]]
- rmExtras :: GiveNameDisambiguation -> [Output] -> [Output]
- getCiteData :: Output -> [CiteData]
- getYears :: Output -> [(String, String)]
- getDuplNameData :: [CitationGroup] -> [[NameData]]
- getDuplNames :: [CitationGroup] -> [[Output]]
- getName :: Output -> [NameData]
- generateYearSuffix :: [Reference] -> [(String, [Output])] -> [(String, String)]
- setYearSuffCollision :: Bool -> [CiteData] -> [Output] -> [Output]
- updateYearSuffixes :: [(String, String)] -> Output -> Output
- getYearSuffixes :: CitationGroup -> [(String, [Output])]
- rmYearSuff :: [CitationGroup] -> [CitationGroup]
- disambiguate :: Eq a => [[a]] -> [[a]]
- same :: Eq a => [a] -> [Bool]
- hasDuplicates :: Eq a => [a] -> Bool
- allTheSame :: Eq a => [a] -> Bool
- addYearSuffix :: Output -> Output
- hasYear :: Output -> Bool
- hasYearSuf :: Output -> Bool
- rmHashAndGivenNames :: Output -> Output
- rmGivenNames :: Output -> Output
- addGivenNames :: [Output] -> [Output]
- mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a]
Documentation
disambCitations :: Style -> [Reference] -> Citations -> [CitationGroup] -> ([(String, String)], [CitationGroup]) Source #
Given the Style
, the list of references and the citation
groups, disambiguate citations according to the style options.
mapCitationGroup :: ([Output] -> [Output]) -> CitationGroup -> CitationGroup Source #
data GiveNameDisambiguation Source #
Instances
Eq GiveNameDisambiguation Source # | |
Defined in Text.CSL.Proc.Disamb | |
Show GiveNameDisambiguation Source # | |
Defined in Text.CSL.Proc.Disamb showsPrec :: Int -> GiveNameDisambiguation -> ShowS # show :: GiveNameDisambiguation -> String # showList :: [GiveNameDisambiguation] -> ShowS # |
disambAddNames :: GiveNameDisambiguation -> [CiteData] -> [CiteData] Source #
disambAddGivenNames :: [NameData] -> [NameData] Source #
updateContrib :: GiveNameDisambiguation -> [CiteData] -> [NameData] -> Output -> Output Source #
reEvaluate :: Style -> [CiteData] -> [(Cite, Maybe Reference)] -> CitationGroup -> CitationGroup Source #
hasIfDis :: IfThen -> [Bool] Source #
Check if the Style
has any conditional for disambiguation. In
this case the conditional will be try after all other
disambiguation strategies have failed. To be used with the generic
query
function.
getCitDisambOptions :: Style -> [String] Source #
Get the list of disambiguation options set in the Style
for
citations.
getDuplCiteData :: GiveNameDisambiguation -> Bool -> Bool -> [CitationGroup] -> [[CiteData]] Source #
Group citation data (with possible alternative names) of
citations which have a duplicate (same collision
, and same
citYear
if year suffix disambiiguation is used). If the first
Bool
is False
, then we need to retrieve data for year suffix
disambiguation. The second Bool
is True
when comparing both
year and contributors' names for finding duplicates (when the
year-suffix option is set).
getCiteData :: Output -> [CiteData] Source #
For an evaluated citation get its CiteData
. The disambiguated
citation and the year fields are empty. Only the first list of
contributors' disambiguation data are collected for disambiguation
purposes.
getDuplNameData :: [CitationGroup] -> [[NameData]] Source #
getDuplNames :: [CitationGroup] -> [[Output]] Source #
getYearSuffixes :: CitationGroup -> [(String, [Output])] Source #
rmYearSuff :: [CitationGroup] -> [CitationGroup] Source #
disambiguate :: Eq a => [[a]] -> [[a]] Source #
Try to disambiguate a list of lists by returning the first non colliding element, if any, of each list:
disambiguate [[1,2],[1,3],[2]] = [[2],[3],[2]]
hasDuplicates :: Eq a => [a] -> Bool Source #
allTheSame :: Eq a => [a] -> Bool Source #
addYearSuffix :: Output -> Output Source #
Add the year suffix to the year. Needed for disambiguation.
hasYearSuf :: Output -> Bool Source #
rmHashAndGivenNames :: Output -> Output Source #
Removes all given names and name hashes from OName elements.
rmGivenNames :: Output -> Output Source #
addGivenNames :: [Output] -> [Output] Source #
Add, with proc
, a give name to the family name. Needed for
disambiguation.
mapGroupOutput :: (Output -> [a]) -> CitationGroup -> [a] Source #
Map the evaluated output of a citation group.