pandoc-citeproc-0.12.2.5: Supports using pandoc with citeproc

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

Text.CSL.Reference

Description

The Reference type

Synopsis

Documentation

newtype Literal Source #

Constructors

Literal 

Fields

Instances

Eq Literal Source # 

Methods

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

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

Data Literal Source # 

Methods

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 # 

Methods

fromString :: String -> Literal #

Generic Literal Source # 

Associated Types

type Rep Literal :: * -> * #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

Monoid Literal Source # 
ToJSON Literal Source # 
FromJSON Literal Source # 
ToYaml Literal Source # 
type Rep Literal Source # 
type Rep Literal = D1 * (MetaData "Literal" "Text.CSL.Reference" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" True) (C1 * (MetaCons "Literal" PrefixI True) (S1 * (MetaSel (Just Symbol "unLiteral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))

data Value Source #

An existential type to wrap the different types a Reference is made of. This way we can create a map to make queries easier.

Constructors

Data a => Value a 

Instances

data Empty Source #

Constructors

Empty 

Instances

Data Empty Source # 

Methods

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 #

toConstr :: Empty -> Constr #

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 # 

Associated Types

type Rep Empty :: * -> * #

Methods

from :: Empty -> Rep Empty x #

to :: Rep Empty x -> Empty #

type Rep Empty Source # 
type Rep Empty = D1 * (MetaData "Empty" "Text.CSL.Reference" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Empty" PrefixI False) (U1 *))

data RefDate Source #

Constructors

RefDate 

Instances

Eq RefDate Source # 

Methods

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

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

Data RefDate Source # 

Methods

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

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

toConstr :: RefDate -> Constr #

dataTypeOf :: RefDate -> DataType #

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

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

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

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

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

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

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

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

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

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

Read RefDate Source # 
Show RefDate Source # 
Generic RefDate Source # 

Associated Types

type Rep RefDate :: * -> * #

Methods

from :: RefDate -> Rep RefDate x #

to :: Rep RefDate x -> RefDate #

FromJSON RefDate Source # 
ToYaml RefDate Source # 
ToJSON [RefDate] Source # 
FromJSON [RefDate] Source # 
type Rep RefDate Source # 

data RefType Source #

Instances

Eq RefType Source # 

Methods

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

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

Data RefType Source # 

Methods

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 # 

Associated Types

type Rep RefType :: * -> * #

Methods

from :: RefType -> Rep RefType x #

to :: Rep RefType x -> RefType #

ToJSON RefType Source # 
FromJSON RefType Source # 
ToYaml RefType Source # 
type Rep RefType Source # 
type Rep RefType = D1 * (MetaData "RefType" "Text.CSL.Reference" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" 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 *))))))))

newtype CNum Source #

Constructors

CNum 

Fields

Instances

Eq CNum Source # 

Methods

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

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

Data CNum Source # 

Methods

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 #

toConstr :: CNum -> Constr #

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 # 

Methods

(+) :: CNum -> CNum -> CNum #

(-) :: CNum -> CNum -> CNum #

(*) :: CNum -> CNum -> CNum #

negate :: CNum -> CNum #

abs :: CNum -> CNum #

signum :: CNum -> CNum #

fromInteger :: Integer -> CNum #

Read CNum Source # 
Show CNum Source # 

Methods

showsPrec :: Int -> CNum -> ShowS #

show :: CNum -> String #

showList :: [CNum] -> ShowS #

Generic CNum Source # 

Associated Types

type Rep CNum :: * -> * #

Methods

from :: CNum -> Rep CNum x #

to :: Rep CNum x -> CNum #

ToJSON CNum Source # 
FromJSON CNum Source # 
ToYaml CNum Source # 

Methods

toYaml :: CNum -> YamlBuilder #

type Rep CNum Source # 
type Rep CNum = D1 * (MetaData "CNum" "Text.CSL.Reference" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" True) (C1 * (MetaCons "CNum" PrefixI True) (S1 * (MetaSel (Just Symbol "unCNum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)))

newtype CLabel Source #

Constructors

CLabel 

Fields

Instances

Eq CLabel Source # 

Methods

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

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

Data CLabel Source # 

Methods

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 # 

Associated Types

type Rep CLabel :: * -> * #

Methods

from :: CLabel -> Rep CLabel x #

to :: Rep CLabel x -> CLabel #

Monoid CLabel Source # 
ToJSON CLabel Source # 
FromJSON CLabel Source # 
ToYaml CLabel Source # 

Methods

toYaml :: CLabel -> YamlBuilder #

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

data Reference Source #

The Reference record.

Constructors

Reference 

Fields

Instances

Eq Reference Source # 
Data Reference Source # 

Methods

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

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

toConstr :: Reference -> Constr #

dataTypeOf :: Reference -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Reference Source # 
Show Reference Source # 
Generic Reference Source # 

Associated Types

type Rep Reference :: * -> * #

ToJSON Reference Source # 
FromJSON Reference Source # 
ToYaml Reference Source # 
type Rep Reference Source # 
type Rep Reference = D1 * (MetaData "Reference" "Text.CSL.Reference" "pandoc-citeproc-0.12.2.5-88tW4glOr2ILbcXQY5yB2X" False) (C1 * (MetaCons "Reference" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "refId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) (S1 * (MetaSel (Just Symbol "refType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * RefType))) ((:*:) * (S1 * (MetaSel (Just Symbol "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "editor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "translator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "recipient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent]))) ((:*:) * (S1 * (MetaSel (Just Symbol "interviewer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) ((:*:) * (S1 * (MetaSel (Just Symbol "composer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "director") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "illustrator") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "originalAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent]))) ((:*:) * (S1 * (MetaSel (Just Symbol "containerAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "collectionEditor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "editorialDirector") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent])) (S1 * (MetaSel (Just Symbol "reviewedAuthor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Agent]))) ((:*:) * (S1 * (MetaSel (Just Symbol "issued") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate])) ((:*:) * (S1 * (MetaSel (Just Symbol "eventDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate])) (S1 * (MetaSel (Just Symbol "accessed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate]))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "container") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate])) (S1 * (MetaSel (Just Symbol "originalDate") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate]))) ((:*:) * (S1 * (MetaSel (Just Symbol "submitted") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [RefDate])) (S1 * (MetaSel (Just Symbol "title") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "titleShort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "reviewedTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "containerTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "volumeTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "collectionTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "containerTitleShort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "collectionNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "originalTitle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "publisher") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "originalPublisher") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "publisherPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "originalPublisherPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "authority") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "jurisdiction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "archive") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "archivePlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "archiveLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "event") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "eventPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "page") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "pageFirst") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "numberOfPages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "version") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "volume") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "numberOfVolumes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "issue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "chapterNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "medium") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "status") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "edition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "section") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "source") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) ((:*:) * (S1 * (MetaSel (Just Symbol "genre") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "note") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "annote") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "abstract") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyword") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "number") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "references") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Formatted)) (S1 * (MetaSel (Just Symbol "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal))) ((:*:) * (S1 * (MetaSel (Just Symbol "doi") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) ((:*:) * (S1 * (MetaSel (Just Symbol "isbn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) (S1 * (MetaSel (Just Symbol "issn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "pmcid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) (S1 * (MetaSel (Just Symbol "pmid") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal))) ((:*:) * (S1 * (MetaSel (Just Symbol "callNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) ((:*:) * (S1 * (MetaSel (Just Symbol "dimensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal)) (S1 * (MetaSel (Just Symbol "scale") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "categories") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Literal])) (S1 * (MetaSel (Just Symbol "language") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Literal))) ((:*:) * (S1 * (MetaSel (Just Symbol "citationNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CNum)) ((:*:) * (S1 * (MetaSel (Just Symbol "firstReferenceNoteNumber") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Int)) (S1 * (MetaSel (Just Symbol "citationLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * CLabel))))))))))

setNearNote :: Style -> [[Cite]] -> [[Cite]] Source #