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 Reference type
Synopsis
- newtype Literal = Literal {}
- data Value = Data a => Value a
- type ReferenceMap = [(String, Value)]
- mkRefMap :: Maybe Reference -> ReferenceMap
- fromValue :: Data a => Value -> Maybe a
- isValueSet :: Value -> Bool
- data Empty = Empty
- data Season
- seasonToInt :: Season -> Maybe Int
- data RefDate = RefDate {}
- handleLiteral :: RefDate -> [RefDate]
- toDatePart :: RefDate -> [Int]
- setCirca :: Bool -> RefDate -> RefDate
- data RefType
- = NoType
- | Article
- | ArticleMagazine
- | ArticleNewspaper
- | ArticleJournal
- | Bill
- | Book
- | Broadcast
- | Chapter
- | Dataset
- | Entry
- | EntryDictionary
- | EntryEncyclopedia
- | Figure
- | Graphic
- | Interview
- | Legislation
- | LegalCase
- | Manuscript
- | Map
- | MotionPicture
- | MusicalScore
- | Pamphlet
- | PaperConference
- | Patent
- | Post
- | PostWeblog
- | PersonalCommunication
- | Report
- | Review
- | ReviewBook
- | Song
- | Speech
- | Thesis
- | Treaty
- | Webpage
- newtype CNum = CNum {}
- newtype CLabel = CLabel {}
- data Reference = Reference {
- refId :: Literal
- refType :: RefType
- author :: [Agent]
- editor :: [Agent]
- translator :: [Agent]
- recipient :: [Agent]
- interviewer :: [Agent]
- composer :: [Agent]
- director :: [Agent]
- illustrator :: [Agent]
- originalAuthor :: [Agent]
- containerAuthor :: [Agent]
- collectionEditor :: [Agent]
- editorialDirector :: [Agent]
- reviewedAuthor :: [Agent]
- issued :: [RefDate]
- eventDate :: [RefDate]
- accessed :: [RefDate]
- container :: [RefDate]
- originalDate :: [RefDate]
- submitted :: [RefDate]
- title :: Formatted
- titleShort :: Formatted
- reviewedTitle :: Formatted
- containerTitle :: Formatted
- volumeTitle :: Formatted
- collectionTitle :: Formatted
- containerTitleShort :: Formatted
- collectionNumber :: Formatted
- originalTitle :: Formatted
- publisher :: Formatted
- originalPublisher :: Formatted
- publisherPlace :: Formatted
- originalPublisherPlace :: Formatted
- authority :: Formatted
- jurisdiction :: Formatted
- archive :: Formatted
- archivePlace :: Formatted
- archiveLocation :: Formatted
- event :: Formatted
- eventPlace :: Formatted
- page :: Formatted
- pageFirst :: Formatted
- numberOfPages :: Formatted
- version :: Formatted
- volume :: Formatted
- numberOfVolumes :: Formatted
- issue :: Formatted
- chapterNumber :: Formatted
- medium :: Formatted
- status :: Formatted
- edition :: Formatted
- section :: Formatted
- source :: Formatted
- genre :: Formatted
- note :: Formatted
- annote :: Formatted
- abstract :: Formatted
- keyword :: Formatted
- number :: Formatted
- references :: Formatted
- url :: Literal
- doi :: Literal
- isbn :: Literal
- issn :: Literal
- pmcid :: Literal
- pmid :: Literal
- callNumber :: Literal
- dimensions :: Literal
- scale :: Literal
- categories :: [Literal]
- language :: Literal
- citationNumber :: CNum
- firstReferenceNoteNumber :: Int
- citationLabel :: CLabel
- emptyReference :: Reference
- numericVars :: [String]
- getReference :: [Reference] -> Cite -> Maybe Reference
- processCites :: [Reference] -> [[Cite]] -> [[(Cite, Maybe Reference)]]
- setPageFirst :: Reference -> Reference
- setNearNote :: Style -> [[Cite]] -> [[Cite]]
- parseEDTFDate :: String -> [RefDate]
Documentation
Instances
Eq Literal Source # | |
Data Literal Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal # toConstr :: Literal -> Constr # dataTypeOf :: Literal -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) # gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r # gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal # | |
Read Literal Source # | |
Show Literal Source # | |
IsString Literal Source # | |
Defined in Text.CSL.Reference fromString :: String -> Literal # | |
Generic Literal Source # | |
Semigroup Literal Source # | |
Monoid Literal Source # | |
ToJSON Literal Source # | |
Defined in Text.CSL.Reference | |
FromJSON Literal Source # | |
ToYaml Literal Source # | |
Defined in Text.CSL.Reference toYaml :: Literal -> YamlBuilder # | |
type Rep Literal Source # | |
Defined in Text.CSL.Reference |
An existential type to wrap the different types a Reference
is
made of. This way we can create a map to make queries easier.
type ReferenceMap = [(String, Value)] Source #
isValueSet :: Value -> Bool Source #
Instances
Data Empty Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Empty -> c Empty # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Empty # dataTypeOf :: Empty -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Empty) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Empty) # gmapT :: (forall b. Data b => b -> b) -> Empty -> Empty # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Empty -> r # gmapQ :: (forall d. Data d => d -> u) -> Empty -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Empty -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Empty -> m Empty # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Empty -> m Empty # | |
Generic Empty Source # | |
type Rep Empty Source # | |
Instances
Eq Season Source # | |
Data Season Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Season -> c Season # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Season # toConstr :: Season -> Constr # dataTypeOf :: Season -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Season) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Season) # gmapT :: (forall b. Data b => b -> b) -> Season -> Season # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Season -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Season -> r # gmapQ :: (forall d. Data d => d -> u) -> Season -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Season -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Season -> m Season # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Season -> m Season # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Season -> m Season # | |
Read Season Source # | |
Show Season Source # | |
Generic Season Source # | |
ToYaml Season Source # | |
Defined in Text.CSL.Reference toYaml :: Season -> YamlBuilder # | |
type Rep Season Source # | |
Defined in Text.CSL.Reference type Rep Season = D1 (MetaData "Season" "Text.CSL.Reference" "pandoc-citeproc-0.14.4-GpO8Frq2QSw6TtNRuoOjZN" False) ((C1 (MetaCons "Spring" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Summer" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Autumn" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Winter" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RawSeason" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |
Instances
handleLiteral :: RefDate -> [RefDate] Source #
toDatePart :: RefDate -> [Int] Source #
Instances
Eq RefType Source # | |
Data RefType Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefType -> c RefType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefType # toConstr :: RefType -> Constr # dataTypeOf :: RefType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefType) # gmapT :: (forall b. Data b => b -> b) -> RefType -> RefType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefType -> r # gmapQ :: (forall d. Data d => d -> u) -> RefType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RefType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefType -> m RefType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefType -> m RefType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefType -> m RefType # | |
Read RefType Source # | |
Show RefType Source # | |
Generic RefType Source # | |
ToJSON RefType Source # | |
Defined in Text.CSL.Reference | |
FromJSON RefType Source # | |
ToYaml RefType Source # | |
Defined in Text.CSL.Reference toYaml :: RefType -> YamlBuilder # | |
type Rep RefType Source # | |
Defined in Text.CSL.Reference type Rep RefType = D1 (MetaData "RefType" "Text.CSL.Reference" "pandoc-citeproc-0.14.4-GpO8Frq2QSw6TtNRuoOjZN" False) (((((C1 (MetaCons "NoType" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Article" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ArticleMagazine" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ArticleNewspaper" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "ArticleJournal" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Bill" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Book" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Broadcast" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Chapter" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "Dataset" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Entry" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "EntryDictionary" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "EntryEncyclopedia" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Figure" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Graphic" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Interview" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Legislation" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "LegalCase" PrefixI False) (U1 :: * -> *)))))) :+: ((((C1 (MetaCons "Manuscript" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Map" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "MotionPicture" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "MusicalScore" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Pamphlet" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PaperConference" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Patent" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Post" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "PostWeblog" PrefixI False) (U1 :: * -> *))))) :+: (((C1 (MetaCons "PersonalCommunication" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Report" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Review" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ReviewBook" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "Song" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Speech" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Thesis" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Treaty" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Webpage" PrefixI False) (U1 :: * -> *))))))) |
Instances
Eq CNum Source # | |
Data CNum Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CNum -> c CNum # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CNum # dataTypeOf :: CNum -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CNum) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CNum) # gmapT :: (forall b. Data b => b -> b) -> CNum -> CNum # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CNum -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CNum -> r # gmapQ :: (forall d. Data d => d -> u) -> CNum -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CNum -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CNum -> m CNum # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CNum -> m CNum # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CNum -> m CNum # | |
Num CNum Source # | |
Read CNum Source # | |
Show CNum Source # | |
Generic CNum Source # | |
ToJSON CNum Source # | |
Defined in Text.CSL.Reference | |
FromJSON CNum Source # | |
ToYaml CNum Source # | |
Defined in Text.CSL.Reference toYaml :: CNum -> YamlBuilder # | |
type Rep CNum Source # | |
Defined in Text.CSL.Reference |
Instances
Eq CLabel Source # | |
Data CLabel Source # | |
Defined in Text.CSL.Reference gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CLabel -> c CLabel # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CLabel # toConstr :: CLabel -> Constr # dataTypeOf :: CLabel -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CLabel) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CLabel) # gmapT :: (forall b. Data b => b -> b) -> CLabel -> CLabel # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CLabel -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CLabel -> r # gmapQ :: (forall d. Data d => d -> u) -> CLabel -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CLabel -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CLabel -> m CLabel # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CLabel -> m CLabel # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CLabel -> m CLabel # | |
Read CLabel Source # | |
Show CLabel Source # | |
Generic CLabel Source # | |
Semigroup CLabel Source # | |
Monoid CLabel Source # | |
ToJSON CLabel Source # | |
Defined in Text.CSL.Reference | |
FromJSON CLabel Source # | |
ToYaml CLabel Source # | |
Defined in Text.CSL.Reference toYaml :: CLabel -> YamlBuilder # | |
type Rep CLabel Source # | |
Defined in Text.CSL.Reference |
The Reference
record.
Instances
numericVars :: [String] Source #
setPageFirst :: Reference -> Reference Source #
parseEDTFDate :: String -> [RefDate] Source #