{-# LANGUAGE StrictData #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module Citeproc.Types
( CiteprocOptions(..)
, defaultCiteprocOptions
, CiteprocOutput(..)
, addFormatting
, CiteprocError(..)
, prettyCiteprocError
, ItemId(..)
, CitationItem(..)
, CitationItemType(..)
, Citation(..)
, ElementType(..)
, Element(..)
, NumberForm(..)
, Pluralize(..)
, DateType(..)
, Date(..)
, rawDateEDTF
, DateParts(..)
, ShowDateParts(..)
, DPName(..)
, DPForm(..)
, DP(..)
, VariableForm(..)
, TextType(..)
, NameFormat(..)
, defaultNameFormat
, NameAsSortOrder(..)
, NamesFormat(..)
, NameForm(..)
, Name(..)
, extractParticles
, isByzantineName
, DelimiterPrecedes(..)
, Condition(..)
, Position(..)
, Match(..)
, Formatting(..)
, FontStyle(..)
, FontVariant(..)
, FontWeight(..)
, TextDecoration(..)
, VerticalAlign(..)
, DisplayStyle(..)
, TextCase(..)
, DemoteNonDroppingParticle(..)
, StyleOptions(..)
, SubsequentAuthorSubstitute(..)
, SubsequentAuthorSubstituteRule(..)
, SecondFieldAlign(..)
, PageRangeFormat(..)
, Style(..)
, TermMatch(..)
, TermGender(..)
, TermNumber(..)
, TermForm(..)
, Term(..)
, emptyTerm
, SortDirection(..)
, SortKey(..)
, SortKeyValue(..)
, LayoutOptions(..)
, Collapsing(..)
, Layout(..)
, DisambiguationStrategy(..)
, GivenNameDisambiguationRule(..)
, Lang(..)
, parseLang
, renderLang
, Locale(..)
, DisambiguationData(..)
, NameHints(..)
, Reference(..)
, ReferenceMap(..)
, makeReferenceMap
, lookupReference
, Val(..)
, valToText
, Variable
, toVariable
, fromVariable
, lookupVariable
, Output(..)
, Identifier(..)
, identifierToURL
, fixShortDOI
, Tag(..)
, outputToText
, renderOutput
, grouped
, formatted
, readAsInt
, variableType
, VariableType(..)
, Abbreviations
, lookupAbbreviation
, Result(..)
, Inputs(..)
)
where
import qualified Data.Set as Set
import qualified Data.Map as M
import qualified Data.Text.Read as TR
import qualified Data.Scientific as S
import qualified Data.CaseInsensitive as CI
import Control.Monad (foldM, guard, mzero)
import Control.Applicative ((<|>), optional)
import Data.Char (isLower, isDigit, isLetter, isSpace)
import Data.Text (Text)
import qualified Data.Text as T
import Data.List (elemIndex)
import Data.Maybe
import qualified Data.Vector as V
import Data.Aeson (FromJSON (..), ToJSON (..), ToJSONKey (..),
FromJSONKey (..), FromJSONKeyFunction (..),
withArray, withObject, object, Value(..),
(.:), (.:?), (.!=))
import Data.Aeson.Types (typeMismatch, Parser, toJSONKeyText)
import Data.Coerce
import Data.Generics.Uniplate.Direct
import qualified Data.Attoparsec.Text as P
import Safe (readMay)
import Data.String (IsString)
import Citeproc.Unicode (Lang(..), parseLang, renderLang)
data CiteprocOptions =
CiteprocOptions
{ CiteprocOptions -> Bool
linkCitations :: Bool
, CiteprocOptions -> Bool
linkBibliography :: Bool
}
deriving (Int -> CiteprocOptions -> ShowS
[CiteprocOptions] -> ShowS
CiteprocOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CiteprocOptions] -> ShowS
$cshowList :: [CiteprocOptions] -> ShowS
show :: CiteprocOptions -> String
$cshow :: CiteprocOptions -> String
showsPrec :: Int -> CiteprocOptions -> ShowS
$cshowsPrec :: Int -> CiteprocOptions -> ShowS
Show, CiteprocOptions -> CiteprocOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CiteprocOptions -> CiteprocOptions -> Bool
$c/= :: CiteprocOptions -> CiteprocOptions -> Bool
== :: CiteprocOptions -> CiteprocOptions -> Bool
$c== :: CiteprocOptions -> CiteprocOptions -> Bool
Eq)
defaultCiteprocOptions :: CiteprocOptions
defaultCiteprocOptions :: CiteprocOptions
defaultCiteprocOptions =
CiteprocOptions
{ linkCitations :: Bool
linkCitations = Bool
False
, linkBibliography :: Bool
linkBibliography = Bool
False
}
data CiteprocError =
CiteprocXMLError Text
| CiteprocParseError Text
| CiteprocLocaleNotFound Text
deriving (Int -> CiteprocError -> ShowS
[CiteprocError] -> ShowS
CiteprocError -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CiteprocError] -> ShowS
$cshowList :: [CiteprocError] -> ShowS
show :: CiteprocError -> String
$cshow :: CiteprocError -> String
showsPrec :: Int -> CiteprocError -> ShowS
$cshowsPrec :: Int -> CiteprocError -> ShowS
Show, CiteprocError -> CiteprocError -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CiteprocError -> CiteprocError -> Bool
$c/= :: CiteprocError -> CiteprocError -> Bool
== :: CiteprocError -> CiteprocError -> Bool
$c== :: CiteprocError -> CiteprocError -> Bool
Eq)
prettyCiteprocError :: CiteprocError -> Text
prettyCiteprocError :: CiteprocError -> Text
prettyCiteprocError (CiteprocXMLError Text
t) =
Text
"CiteprocXMLError: " forall a. Semigroup a => a -> a -> a
<> Text
t
prettyCiteprocError (CiteprocParseError Text
t) =
Text
"CiteprocParseError: " forall a. Semigroup a => a -> a -> a
<> Text
t
prettyCiteprocError (CiteprocLocaleNotFound Text
t) =
Text
"CiteprocLocaleNotFound: " forall a. Semigroup a => a -> a -> a
<> Text
t
class (Semigroup a, Monoid a, Show a, Eq a, Ord a) => CiteprocOutput a where
toText :: a -> Text
fromText :: Text -> a
dropTextWhile :: (Char -> Bool) -> a -> a
dropTextWhileEnd :: (Char -> Bool) -> a -> a
addFontVariant :: FontVariant -> a -> a
addFontStyle :: FontStyle -> a -> a
addFontWeight :: FontWeight -> a -> a
addTextDecoration :: TextDecoration -> a -> a
addVerticalAlign :: VerticalAlign -> a -> a
addTextCase :: Maybe Lang -> TextCase -> a -> a
addDisplay :: DisplayStyle -> a -> a
addQuotes :: a -> a
movePunctuationInsideQuotes :: a -> a
inNote :: a -> a
mapText :: (Text -> Text) -> a -> a
addHyperlink :: Text -> a -> a
localizeQuotes :: Locale -> a -> a
addFormatting :: CiteprocOutput a => Formatting -> a -> a
addFormatting :: forall a. CiteprocOutput a => Formatting -> a -> a
addFormatting Formatting
f a
x =
if Text -> Bool
T.null (forall a. CiteprocOutput a => a -> Text
toText a
x)
then forall a. Monoid a => a
mempty
else
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => DisplayStyle -> a -> a
addDisplay (Formatting -> Maybe DisplayStyle
formatDisplay Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Bool
affixesInside then forall a. a -> a
id else forall {a}. CiteprocOutput a => a -> a
addPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. CiteprocOutput a => a -> a
addSuffix) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Formatting -> Bool
formatQuotes Formatting
f then forall {a}. CiteprocOutput a => a -> a
addQuotes else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => VerticalAlign -> a -> a
addVerticalAlign (Formatting -> Maybe VerticalAlign
formatVerticalAlign Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => TextDecoration -> a -> a
addTextDecoration (Formatting -> Maybe TextDecoration
formatTextDecoration Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => FontWeight -> a -> a
addFontWeight (Formatting -> Maybe FontWeight
formatFontWeight Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => FontVariant -> a -> a
addFontVariant (Formatting -> Maybe FontVariant
formatFontVariant Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (forall a. CiteprocOutput a => Maybe Lang -> TextCase -> a -> a
addTextCase (Formatting -> Maybe Lang
formatLang Formatting
f)) (Formatting -> Maybe TextCase
formatTextCase Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id forall a. CiteprocOutput a => FontStyle -> a -> a
addFontStyle (Formatting -> Maybe FontStyle
formatFontStyle Formatting
f) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Bool
affixesInside then forall {a}. CiteprocOutput a => a -> a
addPrefix forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. CiteprocOutput a => a -> a
addSuffix else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Formatting -> Bool
formatStripPeriods Formatting
f then forall a. CiteprocOutput a => (Text -> Text) -> a -> a
mapText ((Char -> Bool) -> Text -> Text
T.filter (forall a. Eq a => a -> a -> Bool
/=Char
'.')) else forall a. a -> a
id)
forall a b. (a -> b) -> a -> b
$ a
x
where
addPrefix :: a -> a
addPrefix a
z = case Formatting -> Maybe Text
formatPrefix Formatting
f of
Just Text
s -> forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a. CiteprocOutput a => [a] -> [a]
fixPunct [forall a. CiteprocOutput a => Text -> a
fromText Text
s, a
z]
Maybe Text
Nothing -> a
z
addSuffix :: a -> a
addSuffix a
z = case Formatting -> Maybe Text
formatSuffix Formatting
f of
Just Text
s -> forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a. CiteprocOutput a => [a] -> [a]
fixPunct [a
z, forall a. CiteprocOutput a => Text -> a
fromText Text
s]
Maybe Text
Nothing -> a
z
affixesInside :: Bool
affixesInside = Formatting -> Bool
formatAffixesInside Formatting
f
newtype ItemId = ItemId { ItemId -> Text
unItemId :: Text }
deriving (Int -> ItemId -> ShowS
[ItemId] -> ShowS
ItemId -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ItemId] -> ShowS
$cshowList :: [ItemId] -> ShowS
show :: ItemId -> String
$cshow :: ItemId -> String
showsPrec :: Int -> ItemId -> ShowS
$cshowsPrec :: Int -> ItemId -> ShowS
Show, ItemId -> ItemId -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ItemId -> ItemId -> Bool
$c/= :: ItemId -> ItemId -> Bool
== :: ItemId -> ItemId -> Bool
$c== :: ItemId -> ItemId -> Bool
Eq, Eq ItemId
ItemId -> ItemId -> Bool
ItemId -> ItemId -> Ordering
ItemId -> ItemId -> ItemId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ItemId -> ItemId -> ItemId
$cmin :: ItemId -> ItemId -> ItemId
max :: ItemId -> ItemId -> ItemId
$cmax :: ItemId -> ItemId -> ItemId
>= :: ItemId -> ItemId -> Bool
$c>= :: ItemId -> ItemId -> Bool
> :: ItemId -> ItemId -> Bool
$c> :: ItemId -> ItemId -> Bool
<= :: ItemId -> ItemId -> Bool
$c<= :: ItemId -> ItemId -> Bool
< :: ItemId -> ItemId -> Bool
$c< :: ItemId -> ItemId -> Bool
compare :: ItemId -> ItemId -> Ordering
$ccompare :: ItemId -> ItemId -> Ordering
Ord, NonEmpty ItemId -> ItemId
ItemId -> ItemId -> ItemId
forall b. Integral b => b -> ItemId -> ItemId
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> ItemId -> ItemId
$cstimes :: forall b. Integral b => b -> ItemId -> ItemId
sconcat :: NonEmpty ItemId -> ItemId
$csconcat :: NonEmpty ItemId -> ItemId
<> :: ItemId -> ItemId -> ItemId
$c<> :: ItemId -> ItemId -> ItemId
Semigroup, Semigroup ItemId
ItemId
[ItemId] -> ItemId
ItemId -> ItemId -> ItemId
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [ItemId] -> ItemId
$cmconcat :: [ItemId] -> ItemId
mappend :: ItemId -> ItemId -> ItemId
$cmappend :: ItemId -> ItemId -> ItemId
mempty :: ItemId
$cmempty :: ItemId
Monoid, [ItemId] -> Encoding
[ItemId] -> Value
ItemId -> Encoding
ItemId -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ItemId] -> Encoding
$ctoEncodingList :: [ItemId] -> Encoding
toJSONList :: [ItemId] -> Value
$ctoJSONList :: [ItemId] -> Value
toEncoding :: ItemId -> Encoding
$ctoEncoding :: ItemId -> Encoding
toJSON :: ItemId -> Value
$ctoJSON :: ItemId -> Value
ToJSON, Value -> Parser [ItemId]
Value -> Parser ItemId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ItemId]
$cparseJSONList :: Value -> Parser [ItemId]
parseJSON :: Value -> Parser ItemId
$cparseJSON :: Value -> Parser ItemId
FromJSON)
data CitationItemType =
AuthorOnly
| SuppressAuthor
| NormalCite
deriving (Int -> CitationItemType -> ShowS
[CitationItemType] -> ShowS
CitationItemType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CitationItemType] -> ShowS
$cshowList :: [CitationItemType] -> ShowS
show :: CitationItemType -> String
$cshow :: CitationItemType -> String
showsPrec :: Int -> CitationItemType -> ShowS
$cshowsPrec :: Int -> CitationItemType -> ShowS
Show, CitationItemType -> CitationItemType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CitationItemType -> CitationItemType -> Bool
$c/= :: CitationItemType -> CitationItemType -> Bool
== :: CitationItemType -> CitationItemType -> Bool
$c== :: CitationItemType -> CitationItemType -> Bool
Eq, Eq CitationItemType
CitationItemType -> CitationItemType -> Bool
CitationItemType -> CitationItemType -> Ordering
CitationItemType -> CitationItemType -> CitationItemType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CitationItemType -> CitationItemType -> CitationItemType
$cmin :: CitationItemType -> CitationItemType -> CitationItemType
max :: CitationItemType -> CitationItemType -> CitationItemType
$cmax :: CitationItemType -> CitationItemType -> CitationItemType
>= :: CitationItemType -> CitationItemType -> Bool
$c>= :: CitationItemType -> CitationItemType -> Bool
> :: CitationItemType -> CitationItemType -> Bool
$c> :: CitationItemType -> CitationItemType -> Bool
<= :: CitationItemType -> CitationItemType -> Bool
$c<= :: CitationItemType -> CitationItemType -> Bool
< :: CitationItemType -> CitationItemType -> Bool
$c< :: CitationItemType -> CitationItemType -> Bool
compare :: CitationItemType -> CitationItemType -> Ordering
$ccompare :: CitationItemType -> CitationItemType -> Ordering
Ord)
instance FromJSON CitationItemType where
parseJSON :: Value -> Parser CitationItemType
parseJSON Value
x = forall a. FromJSON a => Value -> Parser a
parseJSON Value
x forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
\case
String
"author-only" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
AuthorOnly
String
"suppress-author" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
SuppressAuthor
String
"normal-cite" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
NormalCite
String
t -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"Unknown type " forall a. [a] -> [a] -> [a]
++ String
t
instance ToJSON CitationItemType where
toJSON :: CitationItemType -> Value
toJSON CitationItemType
AuthorOnly = Value
"author-only"
toJSON CitationItemType
SuppressAuthor = Value
"suppress-author"
toJSON CitationItemType
NormalCite = Value
"normal-cite"
data CitationItem a =
CitationItem
{ forall a. CitationItem a -> ItemId
citationItemId :: ItemId
, forall a. CitationItem a -> Maybe Text
citationItemLabel :: Maybe Text
, forall a. CitationItem a -> Maybe Text
citationItemLocator :: Maybe Text
, forall a. CitationItem a -> CitationItemType
citationItemType :: CitationItemType
, forall a. CitationItem a -> Maybe a
citationItemPrefix :: Maybe a
, forall a. CitationItem a -> Maybe a
citationItemSuffix :: Maybe a
, forall a. CitationItem a -> Maybe (Reference a)
citationItemData :: Maybe (Reference a)
} deriving (Int -> CitationItem a -> ShowS
forall a. Show a => Int -> CitationItem a -> ShowS
forall a. Show a => [CitationItem a] -> ShowS
forall a. Show a => CitationItem a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CitationItem a] -> ShowS
$cshowList :: forall a. Show a => [CitationItem a] -> ShowS
show :: CitationItem a -> String
$cshow :: forall a. Show a => CitationItem a -> String
showsPrec :: Int -> CitationItem a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CitationItem a -> ShowS
Show, CitationItem a -> CitationItem a -> Bool
forall a. Eq a => CitationItem a -> CitationItem a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CitationItem a -> CitationItem a -> Bool
$c/= :: forall a. Eq a => CitationItem a -> CitationItem a -> Bool
== :: CitationItem a -> CitationItem a -> Bool
$c== :: forall a. Eq a => CitationItem a -> CitationItem a -> Bool
Eq, CitationItem a -> CitationItem a -> Bool
CitationItem a -> CitationItem a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (CitationItem a)
forall a. Ord a => CitationItem a -> CitationItem a -> Bool
forall a. Ord a => CitationItem a -> CitationItem a -> Ordering
forall a.
Ord a =>
CitationItem a -> CitationItem a -> CitationItem a
min :: CitationItem a -> CitationItem a -> CitationItem a
$cmin :: forall a.
Ord a =>
CitationItem a -> CitationItem a -> CitationItem a
max :: CitationItem a -> CitationItem a -> CitationItem a
$cmax :: forall a.
Ord a =>
CitationItem a -> CitationItem a -> CitationItem a
>= :: CitationItem a -> CitationItem a -> Bool
$c>= :: forall a. Ord a => CitationItem a -> CitationItem a -> Bool
> :: CitationItem a -> CitationItem a -> Bool
$c> :: forall a. Ord a => CitationItem a -> CitationItem a -> Bool
<= :: CitationItem a -> CitationItem a -> Bool
$c<= :: forall a. Ord a => CitationItem a -> CitationItem a -> Bool
< :: CitationItem a -> CitationItem a -> Bool
$c< :: forall a. Ord a => CitationItem a -> CitationItem a -> Bool
compare :: CitationItem a -> CitationItem a -> Ordering
$ccompare :: forall a. Ord a => CitationItem a -> CitationItem a -> Ordering
Ord)
instance (FromJSON a, Eq a) => FromJSON (CitationItem a) where
parseJSON :: Value -> Parser (CitationItem a)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CitationItem" forall a b. (a -> b) -> a -> b
$ \Object
v -> forall a.
ItemId
-> Maybe Text
-> Maybe Text
-> CitationItemType
-> Maybe a
-> Maybe a
-> Maybe (Reference a)
-> CitationItem a
CitationItem
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ItemId
ItemId forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Text
asText)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"label"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"locator" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser Text
asText)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ( (Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type")
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Maybe Bool
suppressAuth <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"suppress-author"
Maybe Bool
authorOnly <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"author-only"
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
case Maybe Bool
suppressAuth of
Just Bool
True -> CitationItemType
SuppressAuthor
Maybe Bool
_ -> case Maybe Bool
authorOnly of
Just Bool
True -> CitationItemType
AuthorOnly
Maybe Bool
_ -> CitationItemType
NormalCite) )
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"prefix"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"suffix"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"itemData"
instance ToJSON a => ToJSON (CitationItem a) where
toJSON :: CitationItem a -> Value
toJSON CitationItem a
i = [Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
[ ( Key
"id", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> ItemId
citationItemId CitationItem a
i) )
, (Key
"type", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. CitationItem a -> CitationItemType
citationItemType CitationItem a
i) ] forall a. [a] -> [a] -> [a]
++
[ ( Key
"label", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> Maybe Text
citationItemLabel CitationItem a
i) )
| forall a. Maybe a -> Bool
isJust (forall a. CitationItem a -> Maybe Text
citationItemLabel CitationItem a
i) ] forall a. [a] -> [a] -> [a]
++
[ (Key
"locator", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> Maybe Text
citationItemLocator CitationItem a
i) )
| forall a. Maybe a -> Bool
isJust (forall a. CitationItem a -> Maybe Text
citationItemLocator CitationItem a
i) ] forall a. [a] -> [a] -> [a]
++
[ (Key
"prefix", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> Maybe a
citationItemPrefix CitationItem a
i))
| forall a. Maybe a -> Bool
isJust (forall a. CitationItem a -> Maybe a
citationItemPrefix CitationItem a
i) ] forall a. [a] -> [a] -> [a]
++
[ (Key
"suffix", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> Maybe a
citationItemSuffix CitationItem a
i))
| forall a. Maybe a -> Bool
isJust (forall a. CitationItem a -> Maybe a
citationItemSuffix CitationItem a
i) ] forall a. [a] -> [a] -> [a]
++
[ (Key
"itemData", forall a. ToJSON a => a -> Value
toJSON (forall a. CitationItem a -> Maybe (Reference a)
citationItemData CitationItem a
i))
| forall a. Maybe a -> Bool
isJust (forall a. CitationItem a -> Maybe (Reference a)
citationItemData CitationItem a
i) ]
data Citation a =
Citation { forall a. Citation a -> Maybe Text
citationId :: Maybe Text
, forall a. Citation a -> Maybe Int
citationNoteNumber :: Maybe Int
, forall a. Citation a -> [CitationItem a]
citationItems :: [CitationItem a] }
deriving (Int -> Citation a -> ShowS
forall a. Show a => Int -> Citation a -> ShowS
forall a. Show a => [Citation a] -> ShowS
forall a. Show a => Citation a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Citation a] -> ShowS
$cshowList :: forall a. Show a => [Citation a] -> ShowS
show :: Citation a -> String
$cshow :: forall a. Show a => Citation a -> String
showsPrec :: Int -> Citation a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Citation a -> ShowS
Show, Citation a -> Citation a -> Bool
forall a. Eq a => Citation a -> Citation a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Citation a -> Citation a -> Bool
$c/= :: forall a. Eq a => Citation a -> Citation a -> Bool
== :: Citation a -> Citation a -> Bool
$c== :: forall a. Eq a => Citation a -> Citation a -> Bool
Eq, Citation a -> Citation a -> Bool
Citation a -> Citation a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Citation a)
forall a. Ord a => Citation a -> Citation a -> Bool
forall a. Ord a => Citation a -> Citation a -> Ordering
forall a. Ord a => Citation a -> Citation a -> Citation a
min :: Citation a -> Citation a -> Citation a
$cmin :: forall a. Ord a => Citation a -> Citation a -> Citation a
max :: Citation a -> Citation a -> Citation a
$cmax :: forall a. Ord a => Citation a -> Citation a -> Citation a
>= :: Citation a -> Citation a -> Bool
$c>= :: forall a. Ord a => Citation a -> Citation a -> Bool
> :: Citation a -> Citation a -> Bool
$c> :: forall a. Ord a => Citation a -> Citation a -> Bool
<= :: Citation a -> Citation a -> Bool
$c<= :: forall a. Ord a => Citation a -> Citation a -> Bool
< :: Citation a -> Citation a -> Bool
$c< :: forall a. Ord a => Citation a -> Citation a -> Bool
compare :: Citation a -> Citation a -> Ordering
$ccompare :: forall a. Ord a => Citation a -> Citation a -> Ordering
Ord)
instance (FromJSON a, Eq a) => FromJSON (Citation a) where
parseJSON :: Value -> Parser (Citation a)
parseJSON Value
v =
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"Citation"
(\Array
ary ->
case Array
ary forall a. Vector a -> Int -> Maybe a
V.!? Int
0 of
Just Value
v' -> (forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Citation" forall a b. (a -> b) -> a -> b
$ \Object
o
-> forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"citationID"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"properties"
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"noteIndex"))
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"citationItems") Value
v'
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v'
Maybe Value
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Empty array") Value
v
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Citation"
(\Object
o -> forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"citationID"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"citationNoteNumber"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"citationItems") Value
v
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v)
instance ToJSON a => ToJSON (Citation a) where
toJSON :: Citation a -> Value
toJSON Citation a
c =
[Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
[ (Key
"citationID", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Citation a -> Maybe Text
citationId Citation a
c) | forall a. Maybe a -> Bool
isJust (forall a. Citation a -> Maybe Text
citationId Citation a
c) ] forall a. [a] -> [a] -> [a]
++
[ (Key
"citationItems" , forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Citation a -> [CitationItem a]
citationItems Citation a
c) ] forall a. [a] -> [a] -> [a]
++
case forall a. Citation a -> Maybe Int
citationNoteNumber Citation a
c of
Maybe Int
Nothing -> []
Just Int
n -> [ (Key
"citationNoteNumber", forall a. ToJSON a => a -> Value
toJSON Int
n) ]
data Match =
MatchAll
| MatchAny
| MatchNone
deriving (Int -> Match -> ShowS
[Match] -> ShowS
Match -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Match] -> ShowS
$cshowList :: [Match] -> ShowS
show :: Match -> String
$cshow :: Match -> String
showsPrec :: Int -> Match -> ShowS
$cshowsPrec :: Int -> Match -> ShowS
Show, Match -> Match -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Match -> Match -> Bool
$c/= :: Match -> Match -> Bool
== :: Match -> Match -> Bool
$c== :: Match -> Match -> Bool
Eq)
data Condition =
HasVariable Variable
| HasType Text
| IsUncertainDate Variable
| IsNumeric Variable
| HasLocatorType Variable
| HasPosition Position
| WouldDisambiguate
deriving (Int -> Condition -> ShowS
[Condition] -> ShowS
Condition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Condition] -> ShowS
$cshowList :: [Condition] -> ShowS
show :: Condition -> String
$cshow :: Condition -> String
showsPrec :: Int -> Condition -> ShowS
$cshowsPrec :: Int -> Condition -> ShowS
Show, Condition -> Condition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Condition -> Condition -> Bool
$c/= :: Condition -> Condition -> Bool
== :: Condition -> Condition -> Bool
$c== :: Condition -> Condition -> Bool
Eq)
data Position =
FirstPosition
| IbidWithLocator
| Ibid
| NearNote
| Subsequent
deriving (Int -> Position -> ShowS
[Position] -> ShowS
Position -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Position] -> ShowS
$cshowList :: [Position] -> ShowS
show :: Position -> String
$cshow :: Position -> String
showsPrec :: Int -> Position -> ShowS
$cshowsPrec :: Int -> Position -> ShowS
Show, Position -> Position -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Position -> Position -> Bool
$c/= :: Position -> Position -> Bool
== :: Position -> Position -> Bool
$c== :: Position -> Position -> Bool
Eq, Eq Position
Position -> Position -> Bool
Position -> Position -> Ordering
Position -> Position -> Position
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Position -> Position -> Position
$cmin :: Position -> Position -> Position
max :: Position -> Position -> Position
$cmax :: Position -> Position -> Position
>= :: Position -> Position -> Bool
$c>= :: Position -> Position -> Bool
> :: Position -> Position -> Bool
$c> :: Position -> Position -> Bool
<= :: Position -> Position -> Bool
$c<= :: Position -> Position -> Bool
< :: Position -> Position -> Bool
$c< :: Position -> Position -> Bool
compare :: Position -> Position -> Ordering
$ccompare :: Position -> Position -> Ordering
Ord)
data DateType =
LocalizedNumeric
| LocalizedText
| NonLocalized
deriving (Int -> DateType -> ShowS
[DateType] -> ShowS
DateType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateType] -> ShowS
$cshowList :: [DateType] -> ShowS
show :: DateType -> String
$cshow :: DateType -> String
showsPrec :: Int -> DateType -> ShowS
$cshowsPrec :: Int -> DateType -> ShowS
Show, DateType -> DateType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateType -> DateType -> Bool
$c/= :: DateType -> DateType -> Bool
== :: DateType -> DateType -> Bool
$c== :: DateType -> DateType -> Bool
Eq, Eq DateType
DateType -> DateType -> Bool
DateType -> DateType -> Ordering
DateType -> DateType -> DateType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DateType -> DateType -> DateType
$cmin :: DateType -> DateType -> DateType
max :: DateType -> DateType -> DateType
$cmax :: DateType -> DateType -> DateType
>= :: DateType -> DateType -> Bool
$c>= :: DateType -> DateType -> Bool
> :: DateType -> DateType -> Bool
$c> :: DateType -> DateType -> Bool
<= :: DateType -> DateType -> Bool
$c<= :: DateType -> DateType -> Bool
< :: DateType -> DateType -> Bool
$c< :: DateType -> DateType -> Bool
compare :: DateType -> DateType -> Ordering
$ccompare :: DateType -> DateType -> Ordering
Ord)
data ShowDateParts =
YearMonthDay
| YearMonth
| Year
deriving (Int -> ShowDateParts -> ShowS
[ShowDateParts] -> ShowS
ShowDateParts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShowDateParts] -> ShowS
$cshowList :: [ShowDateParts] -> ShowS
show :: ShowDateParts -> String
$cshow :: ShowDateParts -> String
showsPrec :: Int -> ShowDateParts -> ShowS
$cshowsPrec :: Int -> ShowDateParts -> ShowS
Show, ShowDateParts -> ShowDateParts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShowDateParts -> ShowDateParts -> Bool
$c/= :: ShowDateParts -> ShowDateParts -> Bool
== :: ShowDateParts -> ShowDateParts -> Bool
$c== :: ShowDateParts -> ShowDateParts -> Bool
Eq)
data DPName =
DPYear
| DPMonth
| DPDay
deriving (Int -> DPName -> ShowS
[DPName] -> ShowS
DPName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DPName] -> ShowS
$cshowList :: [DPName] -> ShowS
show :: DPName -> String
$cshow :: DPName -> String
showsPrec :: Int -> DPName -> ShowS
$cshowsPrec :: Int -> DPName -> ShowS
Show, DPName -> DPName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DPName -> DPName -> Bool
$c/= :: DPName -> DPName -> Bool
== :: DPName -> DPName -> Bool
$c== :: DPName -> DPName -> Bool
Eq, Eq DPName
DPName -> DPName -> Bool
DPName -> DPName -> Ordering
DPName -> DPName -> DPName
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DPName -> DPName -> DPName
$cmin :: DPName -> DPName -> DPName
max :: DPName -> DPName -> DPName
$cmax :: DPName -> DPName -> DPName
>= :: DPName -> DPName -> Bool
$c>= :: DPName -> DPName -> Bool
> :: DPName -> DPName -> Bool
$c> :: DPName -> DPName -> Bool
<= :: DPName -> DPName -> Bool
$c<= :: DPName -> DPName -> Bool
< :: DPName -> DPName -> Bool
$c< :: DPName -> DPName -> Bool
compare :: DPName -> DPName -> Ordering
$ccompare :: DPName -> DPName -> Ordering
Ord)
data DPForm =
DPNumeric
| DPNumericLeadingZeros
| DPOrdinal
| DPLong
| DPShort
deriving (Int -> DPForm -> ShowS
[DPForm] -> ShowS
DPForm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DPForm] -> ShowS
$cshowList :: [DPForm] -> ShowS
show :: DPForm -> String
$cshow :: DPForm -> String
showsPrec :: Int -> DPForm -> ShowS
$cshowsPrec :: Int -> DPForm -> ShowS
Show, DPForm -> DPForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DPForm -> DPForm -> Bool
$c/= :: DPForm -> DPForm -> Bool
== :: DPForm -> DPForm -> Bool
$c== :: DPForm -> DPForm -> Bool
Eq)
data DP =
DP
{ DP -> DPName
dpName :: DPName
, DP -> DPForm
dpForm :: DPForm
, DP -> Text
dpRangeDelimiter :: Text
, DP -> Formatting
dpFormatting :: Formatting
}
deriving (Int -> DP -> ShowS
[DP] -> ShowS
DP -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DP] -> ShowS
$cshowList :: [DP] -> ShowS
show :: DP -> String
$cshow :: DP -> String
showsPrec :: Int -> DP -> ShowS
$cshowsPrec :: Int -> DP -> ShowS
Show, DP -> DP -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DP -> DP -> Bool
$c/= :: DP -> DP -> Bool
== :: DP -> DP -> Bool
$c== :: DP -> DP -> Bool
Eq)
data VariableForm =
ShortForm
| LongForm
deriving (Int -> VariableForm -> ShowS
[VariableForm] -> ShowS
VariableForm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariableForm] -> ShowS
$cshowList :: [VariableForm] -> ShowS
show :: VariableForm -> String
$cshow :: VariableForm -> String
showsPrec :: Int -> VariableForm -> ShowS
$cshowsPrec :: Int -> VariableForm -> ShowS
Show, VariableForm -> VariableForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableForm -> VariableForm -> Bool
$c/= :: VariableForm -> VariableForm -> Bool
== :: VariableForm -> VariableForm -> Bool
$c== :: VariableForm -> VariableForm -> Bool
Eq)
data TextType =
TextVariable VariableForm Variable
| TextMacro Text
| TextTerm Term
| TextValue Text
deriving (Int -> TextType -> ShowS
[TextType] -> ShowS
TextType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextType] -> ShowS
$cshowList :: [TextType] -> ShowS
show :: TextType -> String
$cshow :: TextType -> String
showsPrec :: Int -> TextType -> ShowS
$cshowsPrec :: Int -> TextType -> ShowS
Show, TextType -> TextType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextType -> TextType -> Bool
$c/= :: TextType -> TextType -> Bool
== :: TextType -> TextType -> Bool
$c== :: TextType -> TextType -> Bool
Eq)
data NumberForm =
NumberNumeric
| NumberOrdinal
| NumberLongOrdinal
| NumberRoman
deriving (Int -> NumberForm -> ShowS
[NumberForm] -> ShowS
NumberForm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumberForm] -> ShowS
$cshowList :: [NumberForm] -> ShowS
show :: NumberForm -> String
$cshow :: NumberForm -> String
showsPrec :: Int -> NumberForm -> ShowS
$cshowsPrec :: Int -> NumberForm -> ShowS
Show, NumberForm -> NumberForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumberForm -> NumberForm -> Bool
$c/= :: NumberForm -> NumberForm -> Bool
== :: NumberForm -> NumberForm -> Bool
$c== :: NumberForm -> NumberForm -> Bool
Eq)
data Pluralize =
ContextualPluralize
| AlwaysPluralize
| NeverPluralize
deriving (Int -> Pluralize -> ShowS
[Pluralize] -> ShowS
Pluralize -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Pluralize] -> ShowS
$cshowList :: [Pluralize] -> ShowS
show :: Pluralize -> String
$cshow :: Pluralize -> String
showsPrec :: Int -> Pluralize -> ShowS
$cshowsPrec :: Int -> Pluralize -> ShowS
Show, Pluralize -> Pluralize -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pluralize -> Pluralize -> Bool
$c/= :: Pluralize -> Pluralize -> Bool
== :: Pluralize -> Pluralize -> Bool
$c== :: Pluralize -> Pluralize -> Bool
Eq)
data NamesFormat =
NamesFormat
{ NamesFormat -> Maybe (TermForm, Pluralize, Formatting)
namesLabel :: Maybe (TermForm, Pluralize, Formatting)
, NamesFormat -> Maybe (Text, Formatting)
namesEtAl :: Maybe (Text, Formatting)
, NamesFormat -> Maybe (NameFormat, Formatting)
namesName :: Maybe (NameFormat, Formatting)
, NamesFormat -> Bool
namesLabelBeforeName :: Bool
} deriving (Int -> NamesFormat -> ShowS
[NamesFormat] -> ShowS
NamesFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NamesFormat] -> ShowS
$cshowList :: [NamesFormat] -> ShowS
show :: NamesFormat -> String
$cshow :: NamesFormat -> String
showsPrec :: Int -> NamesFormat -> ShowS
$cshowsPrec :: Int -> NamesFormat -> ShowS
Show, NamesFormat -> NamesFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NamesFormat -> NamesFormat -> Bool
$c/= :: NamesFormat -> NamesFormat -> Bool
== :: NamesFormat -> NamesFormat -> Bool
$c== :: NamesFormat -> NamesFormat -> Bool
Eq)
data DelimiterPrecedes =
PrecedesContextual
| PrecedesAfterInvertedName
| PrecedesAlways
| PrecedesNever
deriving (Int -> DelimiterPrecedes -> ShowS
[DelimiterPrecedes] -> ShowS
DelimiterPrecedes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DelimiterPrecedes] -> ShowS
$cshowList :: [DelimiterPrecedes] -> ShowS
show :: DelimiterPrecedes -> String
$cshow :: DelimiterPrecedes -> String
showsPrec :: Int -> DelimiterPrecedes -> ShowS
$cshowsPrec :: Int -> DelimiterPrecedes -> ShowS
Show, DelimiterPrecedes -> DelimiterPrecedes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DelimiterPrecedes -> DelimiterPrecedes -> Bool
$c/= :: DelimiterPrecedes -> DelimiterPrecedes -> Bool
== :: DelimiterPrecedes -> DelimiterPrecedes -> Bool
$c== :: DelimiterPrecedes -> DelimiterPrecedes -> Bool
Eq)
data NameForm =
LongName
| ShortName
| CountName
deriving (Int -> NameForm -> ShowS
[NameForm] -> ShowS
NameForm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameForm] -> ShowS
$cshowList :: [NameForm] -> ShowS
show :: NameForm -> String
$cshow :: NameForm -> String
showsPrec :: Int -> NameForm -> ShowS
$cshowsPrec :: Int -> NameForm -> ShowS
Show, NameForm -> NameForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameForm -> NameForm -> Bool
$c/= :: NameForm -> NameForm -> Bool
== :: NameForm -> NameForm -> Bool
$c== :: NameForm -> NameForm -> Bool
Eq)
data NameFormat =
NameFormat
{ NameFormat -> Maybe Formatting
nameGivenFormatting :: Maybe Formatting
, NameFormat -> Maybe Formatting
nameFamilyFormatting :: Maybe Formatting
, NameFormat -> Maybe TermForm
nameAndStyle :: Maybe TermForm
, NameFormat -> Text
nameDelimiter :: Text
, NameFormat -> DelimiterPrecedes
nameDelimiterPrecedesEtAl :: DelimiterPrecedes
, NameFormat -> DelimiterPrecedes
nameDelimiterPrecedesLast :: DelimiterPrecedes
, NameFormat -> Maybe Int
nameEtAlMin :: Maybe Int
, NameFormat -> Maybe Int
nameEtAlUseFirst :: Maybe Int
, NameFormat -> Maybe Int
nameEtAlSubsequentUseFirst :: Maybe Int
, NameFormat -> Maybe Int
nameEtAlSubsequentMin :: Maybe Int
, NameFormat -> Bool
nameEtAlUseLast :: Bool
, NameFormat -> NameForm
nameForm :: NameForm
, NameFormat -> Bool
nameInitialize :: Bool
, NameFormat -> Maybe Text
nameInitializeWith :: Maybe Text
, NameFormat -> Maybe NameAsSortOrder
nameAsSortOrder :: Maybe NameAsSortOrder
, NameFormat -> Text
nameSortSeparator :: Text
} deriving (Int -> NameFormat -> ShowS
[NameFormat] -> ShowS
NameFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameFormat] -> ShowS
$cshowList :: [NameFormat] -> ShowS
show :: NameFormat -> String
$cshow :: NameFormat -> String
showsPrec :: Int -> NameFormat -> ShowS
$cshowsPrec :: Int -> NameFormat -> ShowS
Show, NameFormat -> NameFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameFormat -> NameFormat -> Bool
$c/= :: NameFormat -> NameFormat -> Bool
== :: NameFormat -> NameFormat -> Bool
$c== :: NameFormat -> NameFormat -> Bool
Eq)
defaultNameFormat :: NameFormat
defaultNameFormat :: NameFormat
defaultNameFormat =
NameFormat
{ nameGivenFormatting :: Maybe Formatting
nameGivenFormatting = forall a. Maybe a
Nothing
, nameFamilyFormatting :: Maybe Formatting
nameFamilyFormatting = forall a. Maybe a
Nothing
, nameAndStyle :: Maybe TermForm
nameAndStyle = forall a. Maybe a
Nothing
, nameDelimiter :: Text
nameDelimiter = Text
", "
, nameDelimiterPrecedesEtAl :: DelimiterPrecedes
nameDelimiterPrecedesEtAl = DelimiterPrecedes
PrecedesContextual
, nameDelimiterPrecedesLast :: DelimiterPrecedes
nameDelimiterPrecedesLast = DelimiterPrecedes
PrecedesContextual
, nameEtAlMin :: Maybe Int
nameEtAlMin = forall a. Maybe a
Nothing
, nameEtAlUseFirst :: Maybe Int
nameEtAlUseFirst = forall a. Maybe a
Nothing
, nameEtAlSubsequentUseFirst :: Maybe Int
nameEtAlSubsequentUseFirst = forall a. Maybe a
Nothing
, nameEtAlSubsequentMin :: Maybe Int
nameEtAlSubsequentMin = forall a. Maybe a
Nothing
, nameEtAlUseLast :: Bool
nameEtAlUseLast = Bool
False
, nameForm :: NameForm
nameForm = NameForm
LongName
, nameInitialize :: Bool
nameInitialize = Bool
True
, nameInitializeWith :: Maybe Text
nameInitializeWith = forall a. Maybe a
Nothing
, nameAsSortOrder :: Maybe NameAsSortOrder
nameAsSortOrder = forall a. Maybe a
Nothing
, nameSortSeparator :: Text
nameSortSeparator = Text
", "
}
data NameAsSortOrder =
NameAsSortOrderFirst
| NameAsSortOrderAll
deriving (Int -> NameAsSortOrder -> ShowS
[NameAsSortOrder] -> ShowS
NameAsSortOrder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameAsSortOrder] -> ShowS
$cshowList :: [NameAsSortOrder] -> ShowS
show :: NameAsSortOrder -> String
$cshow :: NameAsSortOrder -> String
showsPrec :: Int -> NameAsSortOrder -> ShowS
$cshowsPrec :: Int -> NameAsSortOrder -> ShowS
Show, NameAsSortOrder -> NameAsSortOrder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameAsSortOrder -> NameAsSortOrder -> Bool
$c/= :: NameAsSortOrder -> NameAsSortOrder -> Bool
== :: NameAsSortOrder -> NameAsSortOrder -> Bool
$c== :: NameAsSortOrder -> NameAsSortOrder -> Bool
Eq)
data ElementType a =
EText TextType
| EDate Variable DateType (Maybe ShowDateParts) [DP]
| ENumber Variable NumberForm
| ENames [Variable] NamesFormat [Element a]
| ELabel Variable TermForm Pluralize
| EGroup Bool [Element a]
| EChoose [(Match, [Condition], [Element a])]
deriving (Int -> ElementType a -> ShowS
forall a. Int -> ElementType a -> ShowS
forall a. [ElementType a] -> ShowS
forall a. ElementType a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ElementType a] -> ShowS
$cshowList :: forall a. [ElementType a] -> ShowS
show :: ElementType a -> String
$cshow :: forall a. ElementType a -> String
showsPrec :: Int -> ElementType a -> ShowS
$cshowsPrec :: forall a. Int -> ElementType a -> ShowS
Show, ElementType a -> ElementType a -> Bool
forall a. ElementType a -> ElementType a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ElementType a -> ElementType a -> Bool
$c/= :: forall a. ElementType a -> ElementType a -> Bool
== :: ElementType a -> ElementType a -> Bool
$c== :: forall a. ElementType a -> ElementType a -> Bool
Eq)
data Formatting =
Formatting
{ Formatting -> Maybe Lang
formatLang :: Maybe Lang
, Formatting -> Maybe FontStyle
formatFontStyle :: Maybe FontStyle
, Formatting -> Maybe FontVariant
formatFontVariant :: Maybe FontVariant
, Formatting -> Maybe FontWeight
formatFontWeight :: Maybe FontWeight
, Formatting -> Maybe TextDecoration
formatTextDecoration :: Maybe TextDecoration
, Formatting -> Maybe VerticalAlign
formatVerticalAlign :: Maybe VerticalAlign
, Formatting -> Maybe Text
formatPrefix :: Maybe Text
, Formatting -> Maybe Text
formatSuffix :: Maybe Text
, Formatting -> Maybe DisplayStyle
formatDisplay :: Maybe DisplayStyle
, Formatting -> Maybe TextCase
formatTextCase :: Maybe TextCase
, Formatting -> Maybe Text
formatDelimiter :: Maybe Text
, Formatting -> Bool
formatStripPeriods :: Bool
, Formatting -> Bool
formatQuotes :: Bool
, Formatting -> Bool
formatAffixesInside :: Bool
} deriving (Int -> Formatting -> ShowS
[Formatting] -> ShowS
Formatting -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Formatting] -> ShowS
$cshowList :: [Formatting] -> ShowS
show :: Formatting -> String
$cshow :: Formatting -> String
showsPrec :: Int -> Formatting -> ShowS
$cshowsPrec :: Int -> Formatting -> ShowS
Show, Formatting -> Formatting -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Formatting -> Formatting -> Bool
$c/= :: Formatting -> Formatting -> Bool
== :: Formatting -> Formatting -> Bool
$c== :: Formatting -> Formatting -> Bool
Eq)
defaultFormatting :: Formatting
defaultFormatting :: Formatting
defaultFormatting = Maybe Lang
-> Maybe FontStyle
-> Maybe FontVariant
-> Maybe FontWeight
-> Maybe TextDecoration
-> Maybe VerticalAlign
-> Maybe Text
-> Maybe Text
-> Maybe DisplayStyle
-> Maybe TextCase
-> Maybe Text
-> Bool
-> Bool
-> Bool
-> Formatting
Formatting forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing Bool
False Bool
False Bool
False
combineFormatting :: Formatting -> Formatting -> Formatting
combineFormatting :: Formatting -> Formatting -> Formatting
combineFormatting
(Formatting Maybe Lang
la1 Maybe FontStyle
a1 Maybe FontVariant
b1 Maybe FontWeight
c1 Maybe TextDecoration
d1 Maybe VerticalAlign
e1 Maybe Text
f1 Maybe Text
g1 Maybe DisplayStyle
h1 Maybe TextCase
i1 Maybe Text
j1 Bool
k1 Bool
l1 Bool
m1)
(Formatting Maybe Lang
la2 Maybe FontStyle
a2 Maybe FontVariant
b2 Maybe FontWeight
c2 Maybe TextDecoration
d2 Maybe VerticalAlign
e2 Maybe Text
f2 Maybe Text
g2 Maybe DisplayStyle
h2 Maybe TextCase
i2 Maybe Text
j2 Bool
k2 Bool
l2 Bool
m2) =
Maybe Lang
-> Maybe FontStyle
-> Maybe FontVariant
-> Maybe FontWeight
-> Maybe TextDecoration
-> Maybe VerticalAlign
-> Maybe Text
-> Maybe Text
-> Maybe DisplayStyle
-> Maybe TextCase
-> Maybe Text
-> Bool
-> Bool
-> Bool
-> Formatting
Formatting (Maybe Lang
la1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Lang
la2) (Maybe FontStyle
a1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontStyle
a2) (Maybe FontVariant
b1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontVariant
b2) (Maybe FontWeight
c1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontWeight
c2)
(Maybe TextDecoration
d1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe TextDecoration
d2) (Maybe VerticalAlign
e1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe VerticalAlign
e2) (Maybe Text
f1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
f2)
(Maybe Text
g1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
g2) (Maybe DisplayStyle
h1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe DisplayStyle
h2) (Maybe TextCase
i1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe TextCase
i2)
(Maybe Text
j1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
j2) (Bool
k1 Bool -> Bool -> Bool
|| Bool
k2) (Bool
l1 Bool -> Bool -> Bool
|| Bool
l2) (Bool
m1 Bool -> Bool -> Bool
|| Bool
m2)
instance Semigroup Formatting where
<> :: Formatting -> Formatting -> Formatting
(<>) = Formatting -> Formatting -> Formatting
combineFormatting
instance Monoid Formatting where
mempty :: Formatting
mempty = Formatting
defaultFormatting
mappend :: Formatting -> Formatting -> Formatting
mappend = forall a. Semigroup a => a -> a -> a
(<>)
data TextCase =
Lowercase
| Uppercase
| CapitalizeFirst
| CapitalizeAll
| SentenceCase
| TitleCase
deriving (Int -> TextCase -> ShowS
[TextCase] -> ShowS
TextCase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextCase] -> ShowS
$cshowList :: [TextCase] -> ShowS
show :: TextCase -> String
$cshow :: TextCase -> String
showsPrec :: Int -> TextCase -> ShowS
$cshowsPrec :: Int -> TextCase -> ShowS
Show, TextCase -> TextCase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextCase -> TextCase -> Bool
$c/= :: TextCase -> TextCase -> Bool
== :: TextCase -> TextCase -> Bool
$c== :: TextCase -> TextCase -> Bool
Eq)
data DisplayStyle =
DisplayBlock
| DisplayLeftMargin
| DisplayRightInline
| DisplayIndent
deriving (Int -> DisplayStyle -> ShowS
[DisplayStyle] -> ShowS
DisplayStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisplayStyle] -> ShowS
$cshowList :: [DisplayStyle] -> ShowS
show :: DisplayStyle -> String
$cshow :: DisplayStyle -> String
showsPrec :: Int -> DisplayStyle -> ShowS
$cshowsPrec :: Int -> DisplayStyle -> ShowS
Show, DisplayStyle -> DisplayStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayStyle -> DisplayStyle -> Bool
$c/= :: DisplayStyle -> DisplayStyle -> Bool
== :: DisplayStyle -> DisplayStyle -> Bool
$c== :: DisplayStyle -> DisplayStyle -> Bool
Eq)
data FontStyle =
NormalFont
| ItalicFont
| ObliqueFont
deriving (Int -> FontStyle -> ShowS
[FontStyle] -> ShowS
FontStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontStyle] -> ShowS
$cshowList :: [FontStyle] -> ShowS
show :: FontStyle -> String
$cshow :: FontStyle -> String
showsPrec :: Int -> FontStyle -> ShowS
$cshowsPrec :: Int -> FontStyle -> ShowS
Show, FontStyle -> FontStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontStyle -> FontStyle -> Bool
$c/= :: FontStyle -> FontStyle -> Bool
== :: FontStyle -> FontStyle -> Bool
$c== :: FontStyle -> FontStyle -> Bool
Eq)
data FontVariant =
NormalVariant
| SmallCapsVariant
deriving (Int -> FontVariant -> ShowS
[FontVariant] -> ShowS
FontVariant -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontVariant] -> ShowS
$cshowList :: [FontVariant] -> ShowS
show :: FontVariant -> String
$cshow :: FontVariant -> String
showsPrec :: Int -> FontVariant -> ShowS
$cshowsPrec :: Int -> FontVariant -> ShowS
Show, FontVariant -> FontVariant -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontVariant -> FontVariant -> Bool
$c/= :: FontVariant -> FontVariant -> Bool
== :: FontVariant -> FontVariant -> Bool
$c== :: FontVariant -> FontVariant -> Bool
Eq)
data FontWeight =
NormalWeight
| BoldWeight
| LightWeight
deriving (Int -> FontWeight -> ShowS
[FontWeight] -> ShowS
FontWeight -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FontWeight] -> ShowS
$cshowList :: [FontWeight] -> ShowS
show :: FontWeight -> String
$cshow :: FontWeight -> String
showsPrec :: Int -> FontWeight -> ShowS
$cshowsPrec :: Int -> FontWeight -> ShowS
Show, FontWeight -> FontWeight -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FontWeight -> FontWeight -> Bool
$c/= :: FontWeight -> FontWeight -> Bool
== :: FontWeight -> FontWeight -> Bool
$c== :: FontWeight -> FontWeight -> Bool
Eq)
data TextDecoration =
NoDecoration
| UnderlineDecoration
deriving (Int -> TextDecoration -> ShowS
[TextDecoration] -> ShowS
TextDecoration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextDecoration] -> ShowS
$cshowList :: [TextDecoration] -> ShowS
show :: TextDecoration -> String
$cshow :: TextDecoration -> String
showsPrec :: Int -> TextDecoration -> ShowS
$cshowsPrec :: Int -> TextDecoration -> ShowS
Show, TextDecoration -> TextDecoration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextDecoration -> TextDecoration -> Bool
$c/= :: TextDecoration -> TextDecoration -> Bool
== :: TextDecoration -> TextDecoration -> Bool
$c== :: TextDecoration -> TextDecoration -> Bool
Eq)
data VerticalAlign =
BaselineAlign
| SupAlign
| SubAlign
deriving (Int -> VerticalAlign -> ShowS
[VerticalAlign] -> ShowS
VerticalAlign -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerticalAlign] -> ShowS
$cshowList :: [VerticalAlign] -> ShowS
show :: VerticalAlign -> String
$cshow :: VerticalAlign -> String
showsPrec :: Int -> VerticalAlign -> ShowS
$cshowsPrec :: Int -> VerticalAlign -> ShowS
Show, VerticalAlign -> VerticalAlign -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerticalAlign -> VerticalAlign -> Bool
$c/= :: VerticalAlign -> VerticalAlign -> Bool
== :: VerticalAlign -> VerticalAlign -> Bool
$c== :: VerticalAlign -> VerticalAlign -> Bool
Eq)
data Element a = Element (ElementType a) Formatting
deriving (Int -> Element a -> ShowS
forall a. Int -> Element a -> ShowS
forall a. [Element a] -> ShowS
forall a. Element a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Element a] -> ShowS
$cshowList :: forall a. [Element a] -> ShowS
show :: Element a -> String
$cshow :: forall a. Element a -> String
showsPrec :: Int -> Element a -> ShowS
$cshowsPrec :: forall a. Int -> Element a -> ShowS
Show, Element a -> Element a -> Bool
forall a. Element a -> Element a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Element a -> Element a -> Bool
$c/= :: forall a. Element a -> Element a -> Bool
== :: Element a -> Element a -> Bool
$c== :: forall a. Element a -> Element a -> Bool
Eq)
data SortDirection =
Ascending
| Descending
deriving (Int -> SortDirection -> ShowS
[SortDirection] -> ShowS
SortDirection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortDirection] -> ShowS
$cshowList :: [SortDirection] -> ShowS
show :: SortDirection -> String
$cshow :: SortDirection -> String
showsPrec :: Int -> SortDirection -> ShowS
$cshowsPrec :: Int -> SortDirection -> ShowS
Show, SortDirection -> SortDirection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortDirection -> SortDirection -> Bool
$c/= :: SortDirection -> SortDirection -> Bool
== :: SortDirection -> SortDirection -> Bool
$c== :: SortDirection -> SortDirection -> Bool
Eq)
data SortKey a =
SortKeyVariable SortDirection Variable
| SortKeyMacro SortDirection [Element a]
deriving (Int -> SortKey a -> ShowS
forall a. Int -> SortKey a -> ShowS
forall a. [SortKey a] -> ShowS
forall a. SortKey a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortKey a] -> ShowS
$cshowList :: forall a. [SortKey a] -> ShowS
show :: SortKey a -> String
$cshow :: forall a. SortKey a -> String
showsPrec :: Int -> SortKey a -> ShowS
$cshowsPrec :: forall a. Int -> SortKey a -> ShowS
Show, SortKey a -> SortKey a -> Bool
forall a. SortKey a -> SortKey a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortKey a -> SortKey a -> Bool
$c/= :: forall a. SortKey a -> SortKey a -> Bool
== :: SortKey a -> SortKey a -> Bool
$c== :: forall a. SortKey a -> SortKey a -> Bool
Eq)
data SortKeyValue =
SortKeyValue SortDirection (Maybe [Text])
deriving (Int -> SortKeyValue -> ShowS
[SortKeyValue] -> ShowS
SortKeyValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SortKeyValue] -> ShowS
$cshowList :: [SortKeyValue] -> ShowS
show :: SortKeyValue -> String
$cshow :: SortKeyValue -> String
showsPrec :: Int -> SortKeyValue -> ShowS
$cshowsPrec :: Int -> SortKeyValue -> ShowS
Show, SortKeyValue -> SortKeyValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SortKeyValue -> SortKeyValue -> Bool
$c/= :: SortKeyValue -> SortKeyValue -> Bool
== :: SortKeyValue -> SortKeyValue -> Bool
$c== :: SortKeyValue -> SortKeyValue -> Bool
Eq)
data Layout a =
Layout
{ forall a. Layout a -> LayoutOptions
layoutOptions :: LayoutOptions
, forall a. Layout a -> Formatting
layoutFormatting :: Formatting
, forall a. Layout a -> [Element a]
layoutElements :: [Element a]
, forall a. Layout a -> [SortKey a]
layoutSortKeys :: [SortKey a]
} deriving (Int -> Layout a -> ShowS
forall a. Int -> Layout a -> ShowS
forall a. [Layout a] -> ShowS
forall a. Layout a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Layout a] -> ShowS
$cshowList :: forall a. [Layout a] -> ShowS
show :: Layout a -> String
$cshow :: forall a. Layout a -> String
showsPrec :: Int -> Layout a -> ShowS
$cshowsPrec :: forall a. Int -> Layout a -> ShowS
Show, Layout a -> Layout a -> Bool
forall a. Layout a -> Layout a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Layout a -> Layout a -> Bool
$c/= :: forall a. Layout a -> Layout a -> Bool
== :: Layout a -> Layout a -> Bool
$c== :: forall a. Layout a -> Layout a -> Bool
Eq)
data LayoutOptions =
LayoutOptions
{ LayoutOptions -> Maybe Collapsing
layoutCollapse :: Maybe Collapsing
, LayoutOptions -> Maybe Text
layoutYearSuffixDelimiter :: Maybe Text
, LayoutOptions -> Maybe Text
layoutAfterCollapseDelimiter :: Maybe Text
} deriving (Int -> LayoutOptions -> ShowS
[LayoutOptions] -> ShowS
LayoutOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LayoutOptions] -> ShowS
$cshowList :: [LayoutOptions] -> ShowS
show :: LayoutOptions -> String
$cshow :: LayoutOptions -> String
showsPrec :: Int -> LayoutOptions -> ShowS
$cshowsPrec :: Int -> LayoutOptions -> ShowS
Show, LayoutOptions -> LayoutOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutOptions -> LayoutOptions -> Bool
$c/= :: LayoutOptions -> LayoutOptions -> Bool
== :: LayoutOptions -> LayoutOptions -> Bool
$c== :: LayoutOptions -> LayoutOptions -> Bool
Eq)
data Collapsing =
CollapseCitationNumber
| CollapseYear
| CollapseYearSuffix
| CollapseYearSuffixRanged
deriving (Int -> Collapsing -> ShowS
[Collapsing] -> ShowS
Collapsing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Collapsing] -> ShowS
$cshowList :: [Collapsing] -> ShowS
show :: Collapsing -> String
$cshow :: Collapsing -> String
showsPrec :: Int -> Collapsing -> ShowS
$cshowsPrec :: Int -> Collapsing -> ShowS
Show, Collapsing -> Collapsing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Collapsing -> Collapsing -> Bool
$c/= :: Collapsing -> Collapsing -> Bool
== :: Collapsing -> Collapsing -> Bool
$c== :: Collapsing -> Collapsing -> Bool
Eq)
data DisambiguationStrategy =
DisambiguationStrategy
{ DisambiguationStrategy -> Bool
disambiguateAddNames :: Bool
, DisambiguationStrategy -> Maybe GivenNameDisambiguationRule
disambiguateAddGivenNames :: Maybe GivenNameDisambiguationRule
, DisambiguationStrategy -> Bool
disambiguateAddYearSuffix :: Bool
} deriving (Int -> DisambiguationStrategy -> ShowS
[DisambiguationStrategy] -> ShowS
DisambiguationStrategy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisambiguationStrategy] -> ShowS
$cshowList :: [DisambiguationStrategy] -> ShowS
show :: DisambiguationStrategy -> String
$cshow :: DisambiguationStrategy -> String
showsPrec :: Int -> DisambiguationStrategy -> ShowS
$cshowsPrec :: Int -> DisambiguationStrategy -> ShowS
Show, DisambiguationStrategy -> DisambiguationStrategy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c/= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
== :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c== :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
Eq, Eq DisambiguationStrategy
DisambiguationStrategy -> DisambiguationStrategy -> Bool
DisambiguationStrategy -> DisambiguationStrategy -> Ordering
DisambiguationStrategy
-> DisambiguationStrategy -> DisambiguationStrategy
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DisambiguationStrategy
-> DisambiguationStrategy -> DisambiguationStrategy
$cmin :: DisambiguationStrategy
-> DisambiguationStrategy -> DisambiguationStrategy
max :: DisambiguationStrategy
-> DisambiguationStrategy -> DisambiguationStrategy
$cmax :: DisambiguationStrategy
-> DisambiguationStrategy -> DisambiguationStrategy
>= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c>= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
> :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c> :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
<= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c<= :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
< :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
$c< :: DisambiguationStrategy -> DisambiguationStrategy -> Bool
compare :: DisambiguationStrategy -> DisambiguationStrategy -> Ordering
$ccompare :: DisambiguationStrategy -> DisambiguationStrategy -> Ordering
Ord)
data GivenNameDisambiguationRule =
AllNames
| AllNamesWithInitials
| PrimaryName
| PrimaryNameWithInitials
| ByCite
deriving (Int -> GivenNameDisambiguationRule -> ShowS
[GivenNameDisambiguationRule] -> ShowS
GivenNameDisambiguationRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GivenNameDisambiguationRule] -> ShowS
$cshowList :: [GivenNameDisambiguationRule] -> ShowS
show :: GivenNameDisambiguationRule -> String
$cshow :: GivenNameDisambiguationRule -> String
showsPrec :: Int -> GivenNameDisambiguationRule -> ShowS
$cshowsPrec :: Int -> GivenNameDisambiguationRule -> ShowS
Show, GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c/= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
== :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c== :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
Eq, Eq GivenNameDisambiguationRule
GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> Ordering
GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> GivenNameDisambiguationRule
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> GivenNameDisambiguationRule
$cmin :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> GivenNameDisambiguationRule
max :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> GivenNameDisambiguationRule
$cmax :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> GivenNameDisambiguationRule
>= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c>= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
> :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c> :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
<= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c<= :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
< :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
$c< :: GivenNameDisambiguationRule -> GivenNameDisambiguationRule -> Bool
compare :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> Ordering
$ccompare :: GivenNameDisambiguationRule
-> GivenNameDisambiguationRule -> Ordering
Ord)
data DemoteNonDroppingParticle =
DemoteDisplayAndSort
| DemoteSortOnly
| DemoteNever
deriving (Int -> DemoteNonDroppingParticle -> ShowS
[DemoteNonDroppingParticle] -> ShowS
DemoteNonDroppingParticle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DemoteNonDroppingParticle] -> ShowS
$cshowList :: [DemoteNonDroppingParticle] -> ShowS
show :: DemoteNonDroppingParticle -> String
$cshow :: DemoteNonDroppingParticle -> String
showsPrec :: Int -> DemoteNonDroppingParticle -> ShowS
$cshowsPrec :: Int -> DemoteNonDroppingParticle -> ShowS
Show, DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool
$c/= :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool
== :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool
$c== :: DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool
Eq)
data StyleOptions =
StyleOptions
{ StyleOptions -> Bool
styleIsNoteStyle :: Bool
, StyleOptions -> Maybe Lang
styleDefaultLocale :: Maybe Lang
, StyleOptions -> DemoteNonDroppingParticle
styleDemoteNonDroppingParticle :: DemoteNonDroppingParticle
, StyleOptions -> Bool
styleInitializeWithHyphen :: Bool
, :: Maybe PageRangeFormat
, :: Maybe Text
, StyleOptions -> DisambiguationStrategy
styleDisambiguation :: DisambiguationStrategy
, StyleOptions -> Maybe Int
styleNearNoteDistance :: Maybe Int
, StyleOptions -> Maybe Text
styleCiteGroupDelimiter :: Maybe Text
, StyleOptions -> Maybe Int
styleLineSpacing :: Maybe Int
, StyleOptions -> Maybe Int
styleEntrySpacing :: Maybe Int
, StyleOptions -> Bool
styleHangingIndent :: Bool
, StyleOptions -> Maybe SecondFieldAlign
styleSecondFieldAlign :: Maybe SecondFieldAlign
, StyleOptions -> Maybe SubsequentAuthorSubstitute
styleSubsequentAuthorSubstitute :: Maybe SubsequentAuthorSubstitute
, StyleOptions -> Bool
styleUsesYearSuffixVariable :: Bool
} deriving (Int -> StyleOptions -> ShowS
[StyleOptions] -> ShowS
StyleOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StyleOptions] -> ShowS
$cshowList :: [StyleOptions] -> ShowS
show :: StyleOptions -> String
$cshow :: StyleOptions -> String
showsPrec :: Int -> StyleOptions -> ShowS
$cshowsPrec :: Int -> StyleOptions -> ShowS
Show, StyleOptions -> StyleOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StyleOptions -> StyleOptions -> Bool
$c/= :: StyleOptions -> StyleOptions -> Bool
== :: StyleOptions -> StyleOptions -> Bool
$c== :: StyleOptions -> StyleOptions -> Bool
Eq)
data SubsequentAuthorSubstitute =
SubsequentAuthorSubstitute Text SubsequentAuthorSubstituteRule
deriving (Int -> SubsequentAuthorSubstitute -> ShowS
[SubsequentAuthorSubstitute] -> ShowS
SubsequentAuthorSubstitute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubsequentAuthorSubstitute] -> ShowS
$cshowList :: [SubsequentAuthorSubstitute] -> ShowS
show :: SubsequentAuthorSubstitute -> String
$cshow :: SubsequentAuthorSubstitute -> String
showsPrec :: Int -> SubsequentAuthorSubstitute -> ShowS
$cshowsPrec :: Int -> SubsequentAuthorSubstitute -> ShowS
Show, SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool
$c/= :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool
== :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool
$c== :: SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool
Eq)
data SubsequentAuthorSubstituteRule =
CompleteAll
| CompleteEach
| PartialEach
| PartialFirst
deriving (Int -> SubsequentAuthorSubstituteRule -> ShowS
[SubsequentAuthorSubstituteRule] -> ShowS
SubsequentAuthorSubstituteRule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubsequentAuthorSubstituteRule] -> ShowS
$cshowList :: [SubsequentAuthorSubstituteRule] -> ShowS
show :: SubsequentAuthorSubstituteRule -> String
$cshow :: SubsequentAuthorSubstituteRule -> String
showsPrec :: Int -> SubsequentAuthorSubstituteRule -> ShowS
$cshowsPrec :: Int -> SubsequentAuthorSubstituteRule -> ShowS
Show, SubsequentAuthorSubstituteRule
-> SubsequentAuthorSubstituteRule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubsequentAuthorSubstituteRule
-> SubsequentAuthorSubstituteRule -> Bool
$c/= :: SubsequentAuthorSubstituteRule
-> SubsequentAuthorSubstituteRule -> Bool
== :: SubsequentAuthorSubstituteRule
-> SubsequentAuthorSubstituteRule -> Bool
$c== :: SubsequentAuthorSubstituteRule
-> SubsequentAuthorSubstituteRule -> Bool
Eq)
data SecondFieldAlign =
SecondFieldAlignFlush
| SecondFieldAlignMargin
deriving (Int -> SecondFieldAlign -> ShowS
[SecondFieldAlign] -> ShowS
SecondFieldAlign -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecondFieldAlign] -> ShowS
$cshowList :: [SecondFieldAlign] -> ShowS
show :: SecondFieldAlign -> String
$cshow :: SecondFieldAlign -> String
showsPrec :: Int -> SecondFieldAlign -> ShowS
$cshowsPrec :: Int -> SecondFieldAlign -> ShowS
Show, SecondFieldAlign -> SecondFieldAlign -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecondFieldAlign -> SecondFieldAlign -> Bool
$c/= :: SecondFieldAlign -> SecondFieldAlign -> Bool
== :: SecondFieldAlign -> SecondFieldAlign -> Bool
$c== :: SecondFieldAlign -> SecondFieldAlign -> Bool
Eq)
data =
|
| PageRangeExpanded
|
|
deriving (Int -> PageRangeFormat -> ShowS
[PageRangeFormat] -> ShowS
PageRangeFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageRangeFormat] -> ShowS
$cshowList :: [PageRangeFormat] -> ShowS
show :: PageRangeFormat -> String
$cshow :: PageRangeFormat -> String
showsPrec :: Int -> PageRangeFormat -> ShowS
$cshowsPrec :: Int -> PageRangeFormat -> ShowS
Show, PageRangeFormat -> PageRangeFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageRangeFormat -> PageRangeFormat -> Bool
$c/= :: PageRangeFormat -> PageRangeFormat -> Bool
== :: PageRangeFormat -> PageRangeFormat -> Bool
$c== :: PageRangeFormat -> PageRangeFormat -> Bool
Eq, Eq PageRangeFormat
PageRangeFormat -> PageRangeFormat -> Bool
PageRangeFormat -> PageRangeFormat -> Ordering
PageRangeFormat -> PageRangeFormat -> PageRangeFormat
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat
$cmin :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat
max :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat
$cmax :: PageRangeFormat -> PageRangeFormat -> PageRangeFormat
>= :: PageRangeFormat -> PageRangeFormat -> Bool
$c>= :: PageRangeFormat -> PageRangeFormat -> Bool
> :: PageRangeFormat -> PageRangeFormat -> Bool
$c> :: PageRangeFormat -> PageRangeFormat -> Bool
<= :: PageRangeFormat -> PageRangeFormat -> Bool
$c<= :: PageRangeFormat -> PageRangeFormat -> Bool
< :: PageRangeFormat -> PageRangeFormat -> Bool
$c< :: PageRangeFormat -> PageRangeFormat -> Bool
compare :: PageRangeFormat -> PageRangeFormat -> Ordering
$ccompare :: PageRangeFormat -> PageRangeFormat -> Ordering
Ord)
data Style a =
Style
{ forall a. Style a -> (Int, Int, Int)
styleCslVersion :: (Int,Int,Int)
, forall a. Style a -> StyleOptions
styleOptions :: StyleOptions
, forall a. Style a -> Layout a
styleCitation :: Layout a
, forall a. Style a -> Maybe (Layout a)
styleBibliography :: Maybe (Layout a)
, forall a. Style a -> [Locale]
styleLocales :: [Locale]
, forall a. Style a -> Maybe Abbreviations
styleAbbreviations :: Maybe Abbreviations
} deriving (Int -> Style a -> ShowS
forall a. Int -> Style a -> ShowS
forall a. [Style a] -> ShowS
forall a. Style a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style a] -> ShowS
$cshowList :: forall a. [Style a] -> ShowS
show :: Style a -> String
$cshow :: forall a. Style a -> String
showsPrec :: Int -> Style a -> ShowS
$cshowsPrec :: forall a. Int -> Style a -> ShowS
Show, Style a -> Style a -> Bool
forall a. Style a -> Style a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style a -> Style a -> Bool
$c/= :: forall a. Style a -> Style a -> Bool
== :: Style a -> Style a -> Bool
$c== :: forall a. Style a -> Style a -> Bool
Eq)
data TermForm =
Long
| Short
| Verb
| VerbShort
| Symbol
deriving (Int -> TermForm -> ShowS
[TermForm] -> ShowS
TermForm -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermForm] -> ShowS
$cshowList :: [TermForm] -> ShowS
show :: TermForm -> String
$cshow :: TermForm -> String
showsPrec :: Int -> TermForm -> ShowS
$cshowsPrec :: Int -> TermForm -> ShowS
Show, Eq TermForm
TermForm -> TermForm -> Bool
TermForm -> TermForm -> Ordering
TermForm -> TermForm -> TermForm
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TermForm -> TermForm -> TermForm
$cmin :: TermForm -> TermForm -> TermForm
max :: TermForm -> TermForm -> TermForm
$cmax :: TermForm -> TermForm -> TermForm
>= :: TermForm -> TermForm -> Bool
$c>= :: TermForm -> TermForm -> Bool
> :: TermForm -> TermForm -> Bool
$c> :: TermForm -> TermForm -> Bool
<= :: TermForm -> TermForm -> Bool
$c<= :: TermForm -> TermForm -> Bool
< :: TermForm -> TermForm -> Bool
$c< :: TermForm -> TermForm -> Bool
compare :: TermForm -> TermForm -> Ordering
$ccompare :: TermForm -> TermForm -> Ordering
Ord, TermForm -> TermForm -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermForm -> TermForm -> Bool
$c/= :: TermForm -> TermForm -> Bool
== :: TermForm -> TermForm -> Bool
$c== :: TermForm -> TermForm -> Bool
Eq)
data TermNumber =
Singular
| Plural
deriving (Int -> TermNumber -> ShowS
[TermNumber] -> ShowS
TermNumber -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermNumber] -> ShowS
$cshowList :: [TermNumber] -> ShowS
show :: TermNumber -> String
$cshow :: TermNumber -> String
showsPrec :: Int -> TermNumber -> ShowS
$cshowsPrec :: Int -> TermNumber -> ShowS
Show, Eq TermNumber
TermNumber -> TermNumber -> Bool
TermNumber -> TermNumber -> Ordering
TermNumber -> TermNumber -> TermNumber
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TermNumber -> TermNumber -> TermNumber
$cmin :: TermNumber -> TermNumber -> TermNumber
max :: TermNumber -> TermNumber -> TermNumber
$cmax :: TermNumber -> TermNumber -> TermNumber
>= :: TermNumber -> TermNumber -> Bool
$c>= :: TermNumber -> TermNumber -> Bool
> :: TermNumber -> TermNumber -> Bool
$c> :: TermNumber -> TermNumber -> Bool
<= :: TermNumber -> TermNumber -> Bool
$c<= :: TermNumber -> TermNumber -> Bool
< :: TermNumber -> TermNumber -> Bool
$c< :: TermNumber -> TermNumber -> Bool
compare :: TermNumber -> TermNumber -> Ordering
$ccompare :: TermNumber -> TermNumber -> Ordering
Ord, TermNumber -> TermNumber -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermNumber -> TermNumber -> Bool
$c/= :: TermNumber -> TermNumber -> Bool
== :: TermNumber -> TermNumber -> Bool
$c== :: TermNumber -> TermNumber -> Bool
Eq)
data TermGender =
Masculine
| Feminine
deriving (Int -> TermGender -> ShowS
[TermGender] -> ShowS
TermGender -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermGender] -> ShowS
$cshowList :: [TermGender] -> ShowS
show :: TermGender -> String
$cshow :: TermGender -> String
showsPrec :: Int -> TermGender -> ShowS
$cshowsPrec :: Int -> TermGender -> ShowS
Show, Eq TermGender
TermGender -> TermGender -> Bool
TermGender -> TermGender -> Ordering
TermGender -> TermGender -> TermGender
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TermGender -> TermGender -> TermGender
$cmin :: TermGender -> TermGender -> TermGender
max :: TermGender -> TermGender -> TermGender
$cmax :: TermGender -> TermGender -> TermGender
>= :: TermGender -> TermGender -> Bool
$c>= :: TermGender -> TermGender -> Bool
> :: TermGender -> TermGender -> Bool
$c> :: TermGender -> TermGender -> Bool
<= :: TermGender -> TermGender -> Bool
$c<= :: TermGender -> TermGender -> Bool
< :: TermGender -> TermGender -> Bool
$c< :: TermGender -> TermGender -> Bool
compare :: TermGender -> TermGender -> Ordering
$ccompare :: TermGender -> TermGender -> Ordering
Ord, TermGender -> TermGender -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermGender -> TermGender -> Bool
$c/= :: TermGender -> TermGender -> Bool
== :: TermGender -> TermGender -> Bool
$c== :: TermGender -> TermGender -> Bool
Eq)
data TermMatch =
LastDigit
| LastTwoDigits
| WholeNumber
deriving (Int -> TermMatch -> ShowS
[TermMatch] -> ShowS
TermMatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermMatch] -> ShowS
$cshowList :: [TermMatch] -> ShowS
show :: TermMatch -> String
$cshow :: TermMatch -> String
showsPrec :: Int -> TermMatch -> ShowS
$cshowsPrec :: Int -> TermMatch -> ShowS
Show, Eq TermMatch
TermMatch -> TermMatch -> Bool
TermMatch -> TermMatch -> Ordering
TermMatch -> TermMatch -> TermMatch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TermMatch -> TermMatch -> TermMatch
$cmin :: TermMatch -> TermMatch -> TermMatch
max :: TermMatch -> TermMatch -> TermMatch
$cmax :: TermMatch -> TermMatch -> TermMatch
>= :: TermMatch -> TermMatch -> Bool
$c>= :: TermMatch -> TermMatch -> Bool
> :: TermMatch -> TermMatch -> Bool
$c> :: TermMatch -> TermMatch -> Bool
<= :: TermMatch -> TermMatch -> Bool
$c<= :: TermMatch -> TermMatch -> Bool
< :: TermMatch -> TermMatch -> Bool
$c< :: TermMatch -> TermMatch -> Bool
compare :: TermMatch -> TermMatch -> Ordering
$ccompare :: TermMatch -> TermMatch -> Ordering
Ord, TermMatch -> TermMatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermMatch -> TermMatch -> Bool
$c/= :: TermMatch -> TermMatch -> Bool
== :: TermMatch -> TermMatch -> Bool
$c== :: TermMatch -> TermMatch -> Bool
Eq)
data Term =
Term
{ Term -> Text
termName :: Text
, Term -> TermForm
termForm :: TermForm
, Term -> Maybe TermNumber
termNumber :: Maybe TermNumber
, Term -> Maybe TermGender
termGender :: Maybe TermGender
, Term -> Maybe TermGender
termGenderForm :: Maybe TermGender
, Term -> Maybe TermMatch
termMatch :: Maybe TermMatch
} deriving (Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Term] -> ShowS
$cshowList :: [Term] -> ShowS
show :: Term -> String
$cshow :: Term -> String
showsPrec :: Int -> Term -> ShowS
$cshowsPrec :: Int -> Term -> ShowS
Show, Term -> Term -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Term -> Term -> Bool
$c/= :: Term -> Term -> Bool
== :: Term -> Term -> Bool
$c== :: Term -> Term -> Bool
Eq)
emptyTerm :: Term
emptyTerm :: Term
emptyTerm = Text
-> TermForm
-> Maybe TermNumber
-> Maybe TermGender
-> Maybe TermGender
-> Maybe TermMatch
-> Term
Term forall a. Monoid a => a
mempty TermForm
Long forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing
instance Ord Term where
<= :: Term -> Term -> Bool
(<=)(Term Text
name1 TermForm
form1 Maybe TermNumber
num1 Maybe TermGender
gen1 Maybe TermGender
gf1 Maybe TermMatch
match1)
(Term Text
name2 TermForm
form2 Maybe TermNumber
num2 Maybe TermGender
gen2 Maybe TermGender
gf2 Maybe TermMatch
match2) =
Text
name1 forall a. Eq a => a -> a -> Bool
== Text
name2 Bool -> Bool -> Bool
&&
TermForm
form1 forall a. Eq a => a -> a -> Bool
== TermForm
form2 Bool -> Bool -> Bool
&&
(forall a. Maybe a -> Bool
isNothing Maybe TermNumber
num1 Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isNothing Maybe TermNumber
num2 Bool -> Bool -> Bool
|| Maybe TermNumber
num1 forall a. Eq a => a -> a -> Bool
== Maybe TermNumber
num2) Bool -> Bool -> Bool
&&
(forall a. Maybe a -> Bool
isNothing Maybe TermGender
gen1 Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isNothing Maybe TermGender
gen2 Bool -> Bool -> Bool
|| Maybe TermGender
gen1 forall a. Eq a => a -> a -> Bool
== Maybe TermGender
gen2) Bool -> Bool -> Bool
&&
(forall a. Maybe a -> Bool
isNothing Maybe TermGender
gf1 Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isNothing Maybe TermGender
gf2 Bool -> Bool -> Bool
|| Maybe TermGender
gf1 forall a. Eq a => a -> a -> Bool
== Maybe TermGender
gf2 ) Bool -> Bool -> Bool
&&
(forall a. Maybe a -> Bool
isNothing Maybe TermMatch
match1 Bool -> Bool -> Bool
|| forall a. Maybe a -> Bool
isNothing Maybe TermMatch
match2 Bool -> Bool -> Bool
|| Maybe TermMatch
match1 forall a. Eq a => a -> a -> Bool
== Maybe TermMatch
match2)
data Locale =
Locale
{ Locale -> Maybe Lang
localeLanguage :: Maybe Lang
, Locale -> Maybe Bool
localePunctuationInQuote :: Maybe Bool
, Locale -> Maybe Bool
localeLimitDayOrdinalsToDay1 :: Maybe Bool
, Locale -> Map DateType (Element Text)
localeDate :: M.Map DateType (Element Text)
, Locale -> Map Text [(Term, Text)]
localeTerms :: M.Map Text [(Term, Text)]
}
deriving (Int -> Locale -> ShowS
[Locale] -> ShowS
Locale -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Locale] -> ShowS
$cshowList :: [Locale] -> ShowS
show :: Locale -> String
$cshow :: Locale -> String
showsPrec :: Int -> Locale -> ShowS
$cshowsPrec :: Int -> Locale -> ShowS
Show, Locale -> Locale -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Locale -> Locale -> Bool
$c/= :: Locale -> Locale -> Bool
== :: Locale -> Locale -> Bool
$c== :: Locale -> Locale -> Bool
Eq)
instance Semigroup Locale where
Locale Maybe Lang
lang1 Maybe Bool
pq1 Maybe Bool
ldo1 Map DateType (Element Text)
date1 Map Text [(Term, Text)]
ts1 <> :: Locale -> Locale -> Locale
<>
Locale Maybe Lang
lang2 Maybe Bool
pq2 Maybe Bool
ldo2 Map DateType (Element Text)
date2 Map Text [(Term, Text)]
ts2 =
Maybe Lang
-> Maybe Bool
-> Maybe Bool
-> Map DateType (Element Text)
-> Map Text [(Term, Text)]
-> Locale
Locale (Maybe Lang
lang1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Lang
lang2)
(Maybe Bool
pq1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Bool
pq2)
(Maybe Bool
ldo1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Bool
ldo2)
(Map DateType (Element Text)
date1 forall a. Semigroup a => a -> a -> a
<> Map DateType (Element Text)
date2)
(forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith forall a. Semigroup a => a -> a -> a
(<>) Map Text [(Term, Text)]
ts1 Map Text [(Term, Text)]
ts2)
instance Monoid Locale where
mempty :: Locale
mempty = Maybe Lang
-> Maybe Bool
-> Maybe Bool
-> Map DateType (Element Text)
-> Map Text [(Term, Text)]
-> Locale
Locale forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Maybe a
Nothing forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty
mappend :: Locale -> Locale -> Locale
mappend = forall a. Semigroup a => a -> a -> a
(<>)
newtype Variable = Variable (CI.CI Text)
deriving (Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Variable] -> ShowS
$cshowList :: [Variable] -> ShowS
show :: Variable -> String
$cshow :: Variable -> String
showsPrec :: Int -> Variable -> ShowS
$cshowsPrec :: Int -> Variable -> ShowS
Show, Eq Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmax :: Variable -> Variable -> Variable
>= :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c< :: Variable -> Variable -> Bool
compare :: Variable -> Variable -> Ordering
$ccompare :: Variable -> Variable -> Ordering
Ord, Variable -> Variable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c== :: Variable -> Variable -> Bool
Eq, String -> Variable
forall a. (String -> a) -> IsString a
fromString :: String -> Variable
$cfromString :: String -> Variable
IsString)
toVariable :: Text -> Variable
toVariable :: Text -> Variable
toVariable = CI Text -> Variable
Variable forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. FoldCase s => s -> CI s
CI.mk
fromVariable :: Variable -> Text
fromVariable :: Variable -> Text
fromVariable (Variable CI Text
x) = forall s. CI s -> s
CI.original CI Text
x
instance Semigroup Variable where
Variable CI Text
x <> :: Variable -> Variable -> Variable
<> Variable CI Text
y = CI Text -> Variable
Variable (CI Text
x forall a. Semigroup a => a -> a -> a
<> CI Text
y)
instance Monoid Variable where
mappend :: Variable -> Variable -> Variable
mappend = forall a. Semigroup a => a -> a -> a
(<>)
mempty :: Variable
mempty = CI Text -> Variable
Variable forall a. Monoid a => a
mempty
instance FromJSON Variable where
parseJSON :: Value -> Parser Variable
parseJSON = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CI Text -> Variable
Variable forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. FoldCase s => s -> CI s
CI.mk) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromJSON a => Value -> Parser a
parseJSON
instance FromJSONKey Variable where
fromJSONKey :: FromJSONKeyFunction Variable
fromJSONKey = forall a. (Text -> a) -> FromJSONKeyFunction a
FromJSONKeyText Text -> Variable
toVariable
instance ToJSON Variable where
toJSON :: Variable -> Value
toJSON (Variable CI Text
v) = forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall s. CI s -> s
CI.original CI Text
v
instance ToJSONKey Variable where
toJSONKey :: ToJSONKeyFunction Variable
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText Variable -> Text
fromVariable
data Reference a =
Reference
{ forall a. Reference a -> ItemId
referenceId :: ItemId
, forall a. Reference a -> Text
referenceType :: Text
, forall a. Reference a -> Maybe DisambiguationData
referenceDisambiguation :: Maybe DisambiguationData
, forall a. Reference a -> Map Variable (Val a)
referenceVariables :: M.Map Variable (Val a)
} deriving (Int -> Reference a -> ShowS
forall a. Show a => Int -> Reference a -> ShowS
forall a. Show a => [Reference a] -> ShowS
forall a. Show a => Reference a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Reference a] -> ShowS
$cshowList :: forall a. Show a => [Reference a] -> ShowS
show :: Reference a -> String
$cshow :: forall a. Show a => Reference a -> String
showsPrec :: Int -> Reference a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Reference a -> ShowS
Show, Reference a -> Reference a -> Bool
Reference a -> Reference a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Reference a)
forall a. Ord a => Reference a -> Reference a -> Bool
forall a. Ord a => Reference a -> Reference a -> Ordering
forall a. Ord a => Reference a -> Reference a -> Reference a
min :: Reference a -> Reference a -> Reference a
$cmin :: forall a. Ord a => Reference a -> Reference a -> Reference a
max :: Reference a -> Reference a -> Reference a
$cmax :: forall a. Ord a => Reference a -> Reference a -> Reference a
>= :: Reference a -> Reference a -> Bool
$c>= :: forall a. Ord a => Reference a -> Reference a -> Bool
> :: Reference a -> Reference a -> Bool
$c> :: forall a. Ord a => Reference a -> Reference a -> Bool
<= :: Reference a -> Reference a -> Bool
$c<= :: forall a. Ord a => Reference a -> Reference a -> Bool
< :: Reference a -> Reference a -> Bool
$c< :: forall a. Ord a => Reference a -> Reference a -> Bool
compare :: Reference a -> Reference a -> Ordering
$ccompare :: forall a. Ord a => Reference a -> Reference a -> Ordering
Ord, Reference a -> Reference a -> Bool
forall a. Eq a => Reference a -> Reference a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Reference a -> Reference a -> Bool
$c/= :: forall a. Eq a => Reference a -> Reference a -> Bool
== :: Reference a -> Reference a -> Bool
$c== :: forall a. Eq a => Reference a -> Reference a -> Bool
Eq, forall a b. a -> Reference b -> Reference a
forall a b. (a -> b) -> Reference a -> Reference b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Reference b -> Reference a
$c<$ :: forall a b. a -> Reference b -> Reference a
fmap :: forall a b. (a -> b) -> Reference a -> Reference b
$cfmap :: forall a b. (a -> b) -> Reference a -> Reference b
Functor, forall a. Eq a => a -> Reference a -> Bool
forall a. Num a => Reference a -> a
forall a. Ord a => Reference a -> a
forall m. Monoid m => Reference m -> m
forall a. Reference a -> Bool
forall a. Reference a -> Int
forall a. Reference a -> [a]
forall a. (a -> a -> a) -> Reference a -> a
forall m a. Monoid m => (a -> m) -> Reference a -> m
forall b a. (b -> a -> b) -> b -> Reference a -> b
forall a b. (a -> b -> b) -> b -> Reference a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Reference a -> a
$cproduct :: forall a. Num a => Reference a -> a
sum :: forall a. Num a => Reference a -> a
$csum :: forall a. Num a => Reference a -> a
minimum :: forall a. Ord a => Reference a -> a
$cminimum :: forall a. Ord a => Reference a -> a
maximum :: forall a. Ord a => Reference a -> a
$cmaximum :: forall a. Ord a => Reference a -> a
elem :: forall a. Eq a => a -> Reference a -> Bool
$celem :: forall a. Eq a => a -> Reference a -> Bool
length :: forall a. Reference a -> Int
$clength :: forall a. Reference a -> Int
null :: forall a. Reference a -> Bool
$cnull :: forall a. Reference a -> Bool
toList :: forall a. Reference a -> [a]
$ctoList :: forall a. Reference a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Reference a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Reference a -> a
foldr1 :: forall a. (a -> a -> a) -> Reference a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Reference a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Reference a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Reference a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Reference a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Reference a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Reference a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Reference a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Reference a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Reference a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Reference a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Reference a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Reference a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Reference a -> m
fold :: forall m. Monoid m => Reference m -> m
$cfold :: forall m. Monoid m => Reference m -> m
Foldable, Functor Reference
Foldable Reference
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
Reference (m a) -> m (Reference a)
forall (f :: * -> *) a.
Applicative f =>
Reference (f a) -> f (Reference a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Reference a -> m (Reference b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Reference a -> f (Reference b)
sequence :: forall (m :: * -> *) a.
Monad m =>
Reference (m a) -> m (Reference a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
Reference (m a) -> m (Reference a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Reference a -> m (Reference b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Reference a -> m (Reference b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Reference (f a) -> f (Reference a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Reference (f a) -> f (Reference a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Reference a -> f (Reference b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Reference a -> f (Reference b)
Traversable)
instance ToJSON a => ToJSON (Reference a) where
toJSON :: Reference a -> Value
toJSON Reference a
r = forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"id" (forall a. Text -> Val a
TextVal forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce (forall a. Reference a -> ItemId
referenceId Reference a
r)) forall a b. (a -> b) -> a -> b
$
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"type" (forall a. Text -> Val a
TextVal forall a b. (a -> b) -> a -> b
$ forall a. Reference a -> Text
referenceType Reference a
r) forall a b. (a -> b) -> a -> b
$
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r
data DisambiguationData =
DisambiguationData
{ DisambiguationData -> Maybe Int
disambYearSuffix :: Maybe Int
, DisambiguationData -> Map Name NameHints
disambNameMap :: M.Map Name NameHints
, DisambiguationData -> Maybe Int
disambEtAlNames :: Maybe Int
, DisambiguationData -> Bool
disambCondition :: Bool
} deriving (Int -> DisambiguationData -> ShowS
[DisambiguationData] -> ShowS
DisambiguationData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisambiguationData] -> ShowS
$cshowList :: [DisambiguationData] -> ShowS
show :: DisambiguationData -> String
$cshow :: DisambiguationData -> String
showsPrec :: Int -> DisambiguationData -> ShowS
$cshowsPrec :: Int -> DisambiguationData -> ShowS
Show, Eq DisambiguationData
DisambiguationData -> DisambiguationData -> Bool
DisambiguationData -> DisambiguationData -> Ordering
DisambiguationData -> DisambiguationData -> DisambiguationData
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DisambiguationData -> DisambiguationData -> DisambiguationData
$cmin :: DisambiguationData -> DisambiguationData -> DisambiguationData
max :: DisambiguationData -> DisambiguationData -> DisambiguationData
$cmax :: DisambiguationData -> DisambiguationData -> DisambiguationData
>= :: DisambiguationData -> DisambiguationData -> Bool
$c>= :: DisambiguationData -> DisambiguationData -> Bool
> :: DisambiguationData -> DisambiguationData -> Bool
$c> :: DisambiguationData -> DisambiguationData -> Bool
<= :: DisambiguationData -> DisambiguationData -> Bool
$c<= :: DisambiguationData -> DisambiguationData -> Bool
< :: DisambiguationData -> DisambiguationData -> Bool
$c< :: DisambiguationData -> DisambiguationData -> Bool
compare :: DisambiguationData -> DisambiguationData -> Ordering
$ccompare :: DisambiguationData -> DisambiguationData -> Ordering
Ord, DisambiguationData -> DisambiguationData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisambiguationData -> DisambiguationData -> Bool
$c/= :: DisambiguationData -> DisambiguationData -> Bool
== :: DisambiguationData -> DisambiguationData -> Bool
$c== :: DisambiguationData -> DisambiguationData -> Bool
Eq)
data NameHints =
AddInitials
| AddGivenName
| AddInitialsIfPrimary
| AddGivenNameIfPrimary
deriving (Int -> NameHints -> ShowS
[NameHints] -> ShowS
NameHints -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NameHints] -> ShowS
$cshowList :: [NameHints] -> ShowS
show :: NameHints -> String
$cshow :: NameHints -> String
showsPrec :: Int -> NameHints -> ShowS
$cshowsPrec :: Int -> NameHints -> ShowS
Show, Eq NameHints
NameHints -> NameHints -> Bool
NameHints -> NameHints -> Ordering
NameHints -> NameHints -> NameHints
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NameHints -> NameHints -> NameHints
$cmin :: NameHints -> NameHints -> NameHints
max :: NameHints -> NameHints -> NameHints
$cmax :: NameHints -> NameHints -> NameHints
>= :: NameHints -> NameHints -> Bool
$c>= :: NameHints -> NameHints -> Bool
> :: NameHints -> NameHints -> Bool
$c> :: NameHints -> NameHints -> Bool
<= :: NameHints -> NameHints -> Bool
$c<= :: NameHints -> NameHints -> Bool
< :: NameHints -> NameHints -> Bool
$c< :: NameHints -> NameHints -> Bool
compare :: NameHints -> NameHints -> Ordering
$ccompare :: NameHints -> NameHints -> Ordering
Ord, NameHints -> NameHints -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NameHints -> NameHints -> Bool
$c/= :: NameHints -> NameHints -> Bool
== :: NameHints -> NameHints -> Bool
$c== :: NameHints -> NameHints -> Bool
Eq)
instance (Eq a, FromJSON a) => FromJSON (Reference a) where
parseJSON :: Value -> Parser (Reference a)
parseJSON Value
v = forall a. FromJSON a => Value -> Parser a
parseJSON Value
v forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. FromJSON a => Map Variable Value -> Parser (Reference a)
parseReference
lookupVariable :: CiteprocOutput a => Variable -> Reference a -> Maybe (Val a)
lookupVariable :: forall a.
CiteprocOutput a =>
Variable -> Reference a -> Maybe (Val a)
lookupVariable Variable
"id" Reference a
r =
case forall a. Reference a -> ItemId
referenceId Reference a
r of
ItemId Text
"" -> forall a. Maybe a
Nothing
ItemId Text
t -> forall a. a -> Maybe a
Just (forall a. Text -> Val a
TextVal Text
t)
lookupVariable Variable
"type" Reference a
r =
case forall a. Reference a -> Text
referenceType Reference a
r of
Text
"" -> forall a. Maybe a
Nothing
Text
t -> forall a. a -> Maybe a
Just (forall a. Text -> Val a
TextVal Text
t)
lookupVariable Variable
"page-first" Reference a
r =
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"page-first" (forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"pages" (forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r) of
Maybe (Val a)
Nothing -> forall a. Maybe a
Nothing
Just (NumVal Int
n) -> forall a. a -> Maybe a
Just (forall a. Int -> Val a
NumVal Int
n)
Just (TextVal Text
t) -> forall a. Int -> Val a
NumVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => String -> Maybe a
readMay (Text -> String
T.unpack (Text -> Text
takeDigits Text
t))
Just (FancyVal a
x) -> forall a. Int -> Val a
NumVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Read a => String -> Maybe a
readMay (Text -> String
T.unpack
(Text -> Text
takeDigits forall a b. (a -> b) -> a -> b
$ forall a. CiteprocOutput a => a -> Text
toText a
x))
Maybe (Val a)
_ -> forall a. Maybe a
Nothing
where
takeDigits :: Text -> Text
takeDigits = (Char -> Bool) -> Text -> Text
T.takeWhile Char -> Bool
isDigit
lookupVariable Variable
v Reference a
r = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
v forall a b. (a -> b) -> a -> b
$ forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r
parseReference :: FromJSON a
=> M.Map Variable Value -> Parser (Reference a)
parseReference :: forall a. FromJSON a => Map Variable Value -> Parser (Reference a)
parseReference Map Variable Value
rawmap =
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM forall {a}.
FromJSON a =>
Reference a -> (Variable, Value) -> Parser (Reference a)
go (forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty forall a. Maybe a
Nothing forall a. Monoid a => a
mempty) (forall k a. Map k a -> [(k, a)]
M.toList Map Variable Value
rawmap)
where
go :: Reference a -> (Variable, Value) -> Parser (Reference a)
go (Reference ItemId
i Text
t Maybe DisambiguationData
d Map Variable (Val a)
m) (Variable
k, Value
v)
| Variable
k forall a. Eq a => a -> a -> Bool
== Variable
"id" = do
ItemId
id' <- Text -> ItemId
ItemId forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
id' Text
t Maybe DisambiguationData
d Map Variable (Val a)
m
| Variable
k forall a. Eq a => a -> a -> Bool
== Variable
"type" = do
Text
type' <- Value -> Parser Text
readString Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i Text
type' Maybe DisambiguationData
d Map Variable (Val a)
m
| Variable
k forall a. Eq a => a -> a -> Bool
== Variable
"journalAbbreviation" Bool -> Bool -> Bool
|| Variable
k forall a. Eq a => a -> a -> Bool
== Variable
"shortTitle" =
Reference a -> (Variable, Value) -> Parser (Reference a)
go (forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i Text
t Maybe DisambiguationData
d Map Variable (Val a)
m) (Variable
"container-title-short", Value
v)
| Variable
k forall a. Eq a => a -> a -> Bool
== Variable
"note" = do
Text
t' <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
let ([(Variable, Text)]
kvs, Text
rest) = Text -> ([(Variable, Text)], Text)
parseNote Text
t'
in (if Text -> Bool
T.null Text
rest
then forall a. a -> a
id
else \(Reference ItemId
i' Text
t'' Maybe DisambiguationData
d' Map Variable (Val a)
m') ->
forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i' Text
t'' Maybe DisambiguationData
d' (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"note" (forall a. Text -> Val a
TextVal Text
rest) Map Variable (Val a)
m'))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldM Reference a -> (Variable, Value) -> Parser (Reference a)
go (forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i Text
t Maybe DisambiguationData
d Map Variable (Val a)
m) ([(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables [(Variable, Text)]
kvs)
| Bool
otherwise = forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i Text
t Maybe DisambiguationData
d forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case Variable -> VariableType
variableType Variable
k of
VariableType
StringVariable -> do
Val a
v' <- forall a. a -> Val a
FancyVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Text -> Val a
TextVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k Val a
v' Map Variable (Val a)
m
VariableType
NumberVariable -> do
Text
v' <- case Value
v of
String{} -> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Number{} -> String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. FromJSON a => Value -> Parser a
parseJSON Value
v :: Parser Int)
Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"String or Number" Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (forall a. Text -> Val a
TextVal Text
v') Map Variable (Val a)
m
VariableType
DateVariable -> do
Date
v' <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (forall a. Date -> Val a
DateVal Date
v') Map Variable (Val a)
m
VariableType
NameVariable -> do
[Name]
v' <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (forall a. [Name] -> Val a
NamesVal [Name]
v') Map Variable (Val a)
m
VariableType
UnknownVariable ->
case Value
v of
String{} -> (\Val a
x -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k Val a
x Map Variable (Val a)
m) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(forall a. a -> Val a
FancyVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Text -> Val a
TextVal forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v)
Number{} -> (\Text
x -> forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (forall a. Text -> Val a
TextVal Text
x) Map Variable (Val a)
m) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
Value
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return Map Variable (Val a)
m
readString :: Value -> Parser Text
readString Value
v =
case Value
v of
String{} -> forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
Number{} -> String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. FromJSON a => Value -> Parser a
parseJSON Value
v :: Parser Int)
Value
_ -> forall a. String -> Value -> Parser a
typeMismatch String
"String or Number" Value
v
consolidateNameVariables :: [(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables :: [(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables [] = []
consolidateNameVariables ((Variable
k,Text
v):[(Variable, Text)]
kvs)
= case Variable -> VariableType
variableType Variable
k of
VariableType
NameVariable
-> (Variable
k, Array -> Value
Array
(forall a. [a] -> Vector a
V.fromList [Text -> Value
String Text
t | (Variable
k',Text
t) <- (Variable
k,Text
v)forall a. a -> [a] -> [a]
:[(Variable, Text)]
kvs, Variable
k' forall a. Eq a => a -> a -> Bool
== Variable
k])) forall a. a -> [a] -> [a]
:
[(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables (forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
/= Variable
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Variable, Text)]
kvs)
VariableType
_ -> (Variable
k, Text -> Value
String Text
v) forall a. a -> [a] -> [a]
: [(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables [(Variable, Text)]
kvs
parseNote :: Text
-> ([(Variable, Text)], Text)
parseNote :: Text -> ([(Variable, Text)], Text)
parseNote Text
t =
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const ([],Text
t)) forall a. a -> a
id forall a b. (a -> b) -> a -> b
$
forall a. Parser a -> Text -> Either String a
P.parseOnly ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
P.many' Parser Text (Variable, Text)
pNoteField forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text
P.takeText) Text
t
where
pNoteField :: Parser Text (Variable, Text)
pNoteField = Parser Text (Variable, Text)
pBracedField forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Text (Variable, Text)
pLineField
pLineField :: Parser Text (Variable, Text)
pLineField = do
Text
name <- Parser Text
pVarname
Char
_ <- Char -> Parser Char
P.char Char
':'
Text
val <- (Char -> Bool) -> Parser Text
P.takeWhile (forall a. Eq a => a -> a -> Bool
/=Char
'\n')
() forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Parser Char
P.char Char
'\n' forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall t. Chunk t => Parser t ()
P.endOfInput
forall (m :: * -> *) a. Monad m => a -> m a
return (CI Text -> Variable
Variable forall a b. (a -> b) -> a -> b
$ forall s. FoldCase s => s -> CI s
CI.mk Text
name, Text -> Text
T.strip Text
val)
pBracedField :: Parser Text (Variable, Text)
pBracedField = do
Text
_ <- Text -> Parser Text
P.string Text
"{:"
Text
name <- Parser Text
pVarname
Char
_ <- Char -> Parser Char
P.char Char
':'
Text
val <- (Char -> Bool) -> Parser Text
P.takeWhile (forall a. Eq a => a -> a -> Bool
/=Char
'}')
Char
_ <- Char -> Parser Char
P.char Char
'}'
forall (m :: * -> *) a. Monad m => a -> m a
return (CI Text -> Variable
Variable forall a b. (a -> b) -> a -> b
$ forall s. FoldCase s => s -> CI s
CI.mk Text
name, Text -> Text
T.strip Text
val)
pVarname :: Parser Text
pVarname = (Char -> Bool) -> Parser Text
P.takeWhile1 (\Char
c -> Char -> Bool
isLetter Char
c Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'-')
data VariableType =
DateVariable
| NameVariable
| NumberVariable
| StringVariable
| UnknownVariable
deriving (Int -> VariableType -> ShowS
[VariableType] -> ShowS
VariableType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VariableType] -> ShowS
$cshowList :: [VariableType] -> ShowS
show :: VariableType -> String
$cshow :: VariableType -> String
showsPrec :: Int -> VariableType -> ShowS
$cshowsPrec :: Int -> VariableType -> ShowS
Show, VariableType -> VariableType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariableType -> VariableType -> Bool
$c/= :: VariableType -> VariableType -> Bool
== :: VariableType -> VariableType -> Bool
$c== :: VariableType -> VariableType -> Bool
Eq)
variableType :: Variable -> VariableType
variableType :: Variable -> VariableType
variableType Variable
"accessed" = VariableType
DateVariable
variableType Variable
"available-date" = VariableType
DateVariable
variableType Variable
"container" = VariableType
DateVariable
variableType Variable
"event-date" = VariableType
DateVariable
variableType Variable
"issued" = VariableType
DateVariable
variableType Variable
"original-date" = VariableType
DateVariable
variableType Variable
"submitted" = VariableType
DateVariable
variableType Variable
"author" = VariableType
NameVariable
variableType Variable
"chair" = VariableType
NameVariable
variableType Variable
"collection-editor" = VariableType
NameVariable
variableType Variable
"composer" = VariableType
NameVariable
variableType Variable
"compiler" = VariableType
NameVariable
variableType Variable
"container-author" = VariableType
NameVariable
variableType Variable
"contributor" = VariableType
NameVariable
variableType Variable
"curator" = VariableType
NameVariable
variableType Variable
"director" = VariableType
NameVariable
variableType Variable
"editor" = VariableType
NameVariable
variableType Variable
"editor-translator" = VariableType
NameVariable
variableType Variable
"editorial-director" = VariableType
NameVariable
variableType Variable
"executive-producer" = VariableType
NameVariable
variableType Variable
"guest" = VariableType
NameVariable
variableType Variable
"host" = VariableType
NameVariable
variableType Variable
"illustrator" = VariableType
NameVariable
variableType Variable
"interviewer" = VariableType
NameVariable
variableType Variable
"narrator" = VariableType
NameVariable
variableType Variable
"original-author" = VariableType
NameVariable
variableType Variable
"organizer" = VariableType
NameVariable
variableType Variable
"performer" = VariableType
NameVariable
variableType Variable
"producer" = VariableType
NameVariable
variableType Variable
"recipient" = VariableType
NameVariable
variableType Variable
"reviewed-author" = VariableType
NameVariable
variableType Variable
"script-writer" = VariableType
NameVariable
variableType Variable
"series-creator" = VariableType
NameVariable
variableType Variable
"translator" = VariableType
NameVariable
variableType Variable
"chapter-number" = VariableType
NumberVariable
variableType Variable
"citation-number" = VariableType
NumberVariable
variableType Variable
"collection-number" = VariableType
NumberVariable
variableType Variable
"edition" = VariableType
NumberVariable
variableType Variable
"first-reference-note-number" = VariableType
NumberVariable
variableType Variable
"issue" = VariableType
NumberVariable
variableType Variable
"locator" = VariableType
NumberVariable
variableType Variable
"number" = VariableType
NumberVariable
variableType Variable
"number-of-pages" = VariableType
NumberVariable
variableType Variable
"number-of-volumes" = VariableType
NumberVariable
variableType Variable
"page" = VariableType
NumberVariable
variableType Variable
"page-first" = VariableType
NumberVariable
variableType Variable
"part-number" = VariableType
NumberVariable
variableType Variable
"printing-number" = VariableType
NumberVariable
variableType Variable
"section" = VariableType
NumberVariable
variableType Variable
"supplement-number" = VariableType
NumberVariable
variableType Variable
"version" = VariableType
NumberVariable
variableType Variable
"volume" = VariableType
NumberVariable
variableType Variable
"abstract" = VariableType
StringVariable
variableType Variable
"annote" = VariableType
StringVariable
variableType Variable
"archive" = VariableType
StringVariable
variableType Variable
"archive_collection" = VariableType
StringVariable
variableType Variable
"archive_location" = VariableType
StringVariable
variableType Variable
"archive-place" = VariableType
StringVariable
variableType Variable
"authority" = VariableType
StringVariable
variableType Variable
"call-number" = VariableType
StringVariable
variableType Variable
"citation-key" = VariableType
StringVariable
variableType Variable
"citation-label" = VariableType
StringVariable
variableType Variable
"collection-title" = VariableType
StringVariable
variableType Variable
"container-title" = VariableType
StringVariable
variableType Variable
"container-title-short" = VariableType
StringVariable
variableType Variable
"dimensions" = VariableType
StringVariable
variableType Variable
"division" = VariableType
StringVariable
variableType Variable
"DOI" = VariableType
StringVariable
variableType Variable
"event" = VariableType
StringVariable
variableType Variable
"event-place" = VariableType
StringVariable
variableType Variable
"event-title" = VariableType
StringVariable
variableType Variable
"genre" = VariableType
StringVariable
variableType Variable
"ISBN" = VariableType
StringVariable
variableType Variable
"ISSN" = VariableType
StringVariable
variableType Variable
"jurisdiction" = VariableType
StringVariable
variableType Variable
"keyword" = VariableType
StringVariable
variableType Variable
"language" = VariableType
StringVariable
variableType Variable
"license" = VariableType
StringVariable
variableType Variable
"medium" = VariableType
StringVariable
variableType Variable
"note" = VariableType
StringVariable
variableType Variable
"original-publisher" = VariableType
StringVariable
variableType Variable
"original-publisher-place" = VariableType
StringVariable
variableType Variable
"original-title" = VariableType
StringVariable
variableType Variable
"part-title" = VariableType
StringVariable
variableType Variable
"PMID" = VariableType
StringVariable
variableType Variable
"PMCID" = VariableType
StringVariable
variableType Variable
"publisher" = VariableType
StringVariable
variableType Variable
"publisher-place" = VariableType
StringVariable
variableType Variable
"references" = VariableType
StringVariable
variableType Variable
"reviewed-genre" = VariableType
StringVariable
variableType Variable
"reviewed-title" = VariableType
StringVariable
variableType Variable
"scale" = VariableType
StringVariable
variableType Variable
"source" = VariableType
StringVariable
variableType Variable
"status" = VariableType
StringVariable
variableType Variable
"title" = VariableType
StringVariable
variableType Variable
"title-short" = VariableType
StringVariable
variableType Variable
"URL" = VariableType
StringVariable
variableType Variable
"volume-title" = VariableType
StringVariable
variableType Variable
"year-suffix" = VariableType
StringVariable
variableType Variable
_ = VariableType
UnknownVariable
newtype (ReferenceMap a) =
ReferenceMap { forall a. ReferenceMap a -> Map ItemId (Reference a)
unReferenceMap :: M.Map ItemId (Reference a) }
deriving (Int -> ReferenceMap a -> ShowS
forall a. Show a => Int -> ReferenceMap a -> ShowS
forall a. Show a => [ReferenceMap a] -> ShowS
forall a. Show a => ReferenceMap a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReferenceMap a] -> ShowS
$cshowList :: forall a. Show a => [ReferenceMap a] -> ShowS
show :: ReferenceMap a -> String
$cshow :: forall a. Show a => ReferenceMap a -> String
showsPrec :: Int -> ReferenceMap a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ReferenceMap a -> ShowS
Show)
makeReferenceMap :: [Reference a] -> ([Reference a], ReferenceMap a)
makeReferenceMap :: forall a. [Reference a] -> ([Reference a], ReferenceMap a)
makeReferenceMap = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {a}.
Reference a
-> (Set ItemId, ([Reference a], ReferenceMap a))
-> (Set ItemId, ([Reference a], ReferenceMap a))
go (forall a. Monoid a => a
mempty, ([], forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap forall a. Monoid a => a
mempty))
where
go :: Reference a
-> (Set ItemId, ([Reference a], ReferenceMap a))
-> (Set ItemId, ([Reference a], ReferenceMap a))
go Reference a
ref (Set ItemId
ids, ([Reference a]
rs, ReferenceMap Map ItemId (Reference a)
refmap)) =
let rid :: ItemId
rid = forall a. Reference a -> ItemId
referenceId Reference a
ref
in if forall a. Ord a => a -> Set a -> Bool
Set.member ItemId
rid Set ItemId
ids
then (Set ItemId
ids, ([Reference a]
rs, forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap Map ItemId (Reference a)
refmap))
else (forall a. Ord a => a -> Set a -> Set a
Set.insert ItemId
rid Set ItemId
ids,
(Reference a
refforall a. a -> [a] -> [a]
:[Reference a]
rs, forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap (forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ItemId
rid Reference a
ref Map ItemId (Reference a)
refmap)))
lookupReference :: ItemId -> ReferenceMap a -> Maybe (Reference a)
lookupReference :: forall a. ItemId -> ReferenceMap a -> Maybe (Reference a)
lookupReference ItemId
ident (ReferenceMap Map ItemId (Reference a)
m) = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ItemId
ident Map ItemId (Reference a)
m
data Val a =
TextVal Text
| FancyVal a
| NumVal Int
| NamesVal [Name]
| DateVal Date
| SubstitutedVal
deriving (Int -> Val a -> ShowS
forall a. Show a => Int -> Val a -> ShowS
forall a. Show a => [Val a] -> ShowS
forall a. Show a => Val a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Val a] -> ShowS
$cshowList :: forall a. Show a => [Val a] -> ShowS
show :: Val a -> String
$cshow :: forall a. Show a => Val a -> String
showsPrec :: Int -> Val a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Val a -> ShowS
Show, Val a -> Val a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (Val a)
forall a. Ord a => Val a -> Val a -> Bool
forall a. Ord a => Val a -> Val a -> Ordering
forall a. Ord a => Val a -> Val a -> Val a
min :: Val a -> Val a -> Val a
$cmin :: forall a. Ord a => Val a -> Val a -> Val a
max :: Val a -> Val a -> Val a
$cmax :: forall a. Ord a => Val a -> Val a -> Val a
>= :: Val a -> Val a -> Bool
$c>= :: forall a. Ord a => Val a -> Val a -> Bool
> :: Val a -> Val a -> Bool
$c> :: forall a. Ord a => Val a -> Val a -> Bool
<= :: Val a -> Val a -> Bool
$c<= :: forall a. Ord a => Val a -> Val a -> Bool
< :: Val a -> Val a -> Bool
$c< :: forall a. Ord a => Val a -> Val a -> Bool
compare :: Val a -> Val a -> Ordering
$ccompare :: forall a. Ord a => Val a -> Val a -> Ordering
Ord, Val a -> Val a -> Bool
forall a. Eq a => Val a -> Val a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Val a -> Val a -> Bool
$c/= :: forall a. Eq a => Val a -> Val a -> Bool
== :: Val a -> Val a -> Bool
$c== :: forall a. Eq a => Val a -> Val a -> Bool
Eq, forall a b. a -> Val b -> Val a
forall a b. (a -> b) -> Val a -> Val b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Val b -> Val a
$c<$ :: forall a b. a -> Val b -> Val a
fmap :: forall a b. (a -> b) -> Val a -> Val b
$cfmap :: forall a b. (a -> b) -> Val a -> Val b
Functor, forall a. Eq a => a -> Val a -> Bool
forall a. Num a => Val a -> a
forall a. Ord a => Val a -> a
forall m. Monoid m => Val m -> m
forall a. Val a -> Bool
forall a. Val a -> Int
forall a. Val a -> [a]
forall a. (a -> a -> a) -> Val a -> a
forall m a. Monoid m => (a -> m) -> Val a -> m
forall b a. (b -> a -> b) -> b -> Val a -> b
forall a b. (a -> b -> b) -> b -> Val a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Val a -> a
$cproduct :: forall a. Num a => Val a -> a
sum :: forall a. Num a => Val a -> a
$csum :: forall a. Num a => Val a -> a
minimum :: forall a. Ord a => Val a -> a
$cminimum :: forall a. Ord a => Val a -> a
maximum :: forall a. Ord a => Val a -> a
$cmaximum :: forall a. Ord a => Val a -> a
elem :: forall a. Eq a => a -> Val a -> Bool
$celem :: forall a. Eq a => a -> Val a -> Bool
length :: forall a. Val a -> Int
$clength :: forall a. Val a -> Int
null :: forall a. Val a -> Bool
$cnull :: forall a. Val a -> Bool
toList :: forall a. Val a -> [a]
$ctoList :: forall a. Val a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Val a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Val a -> a
foldr1 :: forall a. (a -> a -> a) -> Val a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Val a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Val a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Val a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Val a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Val a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Val a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Val a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Val a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Val a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Val a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Val a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Val a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Val a -> m
fold :: forall m. Monoid m => Val m -> m
$cfold :: forall m. Monoid m => Val m -> m
Foldable, Functor Val
Foldable Val
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Val (m a) -> m (Val a)
forall (f :: * -> *) a. Applicative f => Val (f a) -> f (Val a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Val a -> m (Val b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Val a -> f (Val b)
sequence :: forall (m :: * -> *) a. Monad m => Val (m a) -> m (Val a)
$csequence :: forall (m :: * -> *) a. Monad m => Val (m a) -> m (Val a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Val a -> m (Val b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Val a -> m (Val b)
sequenceA :: forall (f :: * -> *) a. Applicative f => Val (f a) -> f (Val a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Val (f a) -> f (Val a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Val a -> f (Val b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Val a -> f (Val b)
Traversable)
instance ToJSON a => ToJSON (Val a) where
toJSON :: Val a -> Value
toJSON (TextVal Text
t) = forall a. ToJSON a => a -> Value
toJSON Text
t
toJSON (FancyVal a
x) = forall a. ToJSON a => a -> Value
toJSON a
x
toJSON (NumVal Int
n) = forall a. ToJSON a => a -> Value
toJSON Int
n
toJSON (NamesVal [Name]
ns) = forall a. ToJSON a => a -> Value
toJSON [Name]
ns
toJSON (DateVal Date
d) = forall a. ToJSON a => a -> Value
toJSON Date
d
toJSON Val a
SubstitutedVal = forall a. ToJSON a => a -> Value
toJSON ()
valToText :: CiteprocOutput a => Val a -> Maybe Text
valToText :: forall a. CiteprocOutput a => Val a -> Maybe Text
valToText (TextVal Text
x) = forall a. a -> Maybe a
Just Text
x
valToText (FancyVal a
x) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. CiteprocOutput a => a -> Text
toText a
x
valToText (NumVal Int
n) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
n
valToText Val a
_ = forall a. Maybe a
Nothing
data Name =
Name
{ Name -> Maybe Text
nameFamily :: Maybe Text
, Name -> Maybe Text
nameGiven :: Maybe Text
, Name -> Maybe Text
nameDroppingParticle :: Maybe Text
, Name -> Maybe Text
nameNonDroppingParticle :: Maybe Text
, Name -> Maybe Text
nameSuffix :: Maybe Text
, Name -> Bool
nameCommaSuffix :: Bool
, Name -> Bool
nameStaticOrdering :: Bool
, Name -> Maybe Text
nameLiteral :: Maybe Text
}
deriving (Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Name] -> ShowS
$cshowList :: [Name] -> ShowS
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> ShowS
$cshowsPrec :: Int -> Name -> ShowS
Show, Name -> Name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq, Eq Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmax :: Name -> Name -> Name
>= :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c< :: Name -> Name -> Bool
compare :: Name -> Name -> Ordering
$ccompare :: Name -> Name -> Ordering
Ord)
instance ToJSON Name where
toJSON :: Name -> Value
toJSON Name
n =
[Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"family", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameFamily Name
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"given", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameGiven Name
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"dropping-particle", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:))
(Name -> Maybe Text
nameDroppingParticle Name
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"non-dropping-particle", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:))
(Name -> Maybe Text
nameNonDroppingParticle Name
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"suffix", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameSuffix Name
n) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Name -> Bool
nameCommaSuffix Name
n
then ((Key
"comma-suffix", forall a. ToJSON a => a -> Value
toJSON Bool
True)forall a. a -> [a] -> [a]
:)
else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(if Name -> Bool
nameStaticOrdering Name
n
then ((Key
"static-ordering", forall a. ToJSON a => a -> Value
toJSON Bool
True)forall a. a -> [a] -> [a]
:)
else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
x -> ((Key
"literal", forall a. ToJSON a => a -> Value
toJSON Text
x)forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameLiteral Name
n) forall a b. (a -> b) -> a -> b
$
[]
fixApos :: Text -> Text
fixApos :: Text -> Text
fixApos = (Char -> Char) -> Text -> Text
T.map Char -> Char
fixAposC
where
fixAposC :: Char -> Char
fixAposC Char
'\'' = Char
'\x2019'
fixAposC Char
c = Char
c
instance FromJSON Name where
parseJSON :: Value -> Parser Name
parseJSON (String Text
t) = Text -> Parser Name
parseCheaterName Text
t
parseJSON Value
x =
Name -> Name
extractParticles forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Name" forall a b. (a -> b) -> a -> b
$ \Object
v -> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Bool
-> Bool
-> Maybe Text
-> Name
Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"family")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"given")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"dropping-particle")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"non-dropping-particle")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"suffix")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"comma-suffix" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Value -> Parser Bool
asBool)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"static-ordering" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Value -> Parser Bool
asBool)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"literal")
) Value
x
extractParticles :: Name -> Name
extractParticles :: Name -> Name
extractParticles =
Name -> Name
extractNonDroppingParticle forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Name
extractDroppingParticle forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Name
extractSuffix
where
extractSuffix :: Name -> Name
extractSuffix Name
name =
case Name -> Maybe Text
nameSuffix Name
name of
Maybe Text
Nothing ->
case Name -> Maybe Text
nameGiven Name
name of
Maybe Text
Nothing -> Name
name
Just Text
t
| Text
"\"" Text -> Text -> Bool
`T.isPrefixOf` Text
t
, Text
"\"" Text -> Text -> Bool
`T.isSuffixOf` Text
t
-> Name
name { nameGiven :: Maybe Text
nameGiven = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.dropEnd Int
1 Text
t }
| Bool
otherwise->
let (Text
a,Text
b) = (Char -> Bool) -> Text -> (Text, Text)
T.break (forall a. Eq a => a -> a -> Bool
==Char
',') Text
t
in if Text -> Bool
T.null Text
a Bool -> Bool -> Bool
|| Text -> Bool
T.null Text
b
then Name
name
else
if Int -> Text -> Text
T.take Int
2 Text
b forall a. Eq a => a -> a -> Bool
== Text
",!"
then Name
name{ nameGiven :: Maybe Text
nameGiven = forall a. a -> Maybe a
Just Text
a
, nameSuffix :: Maybe Text
nameSuffix = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
2 Text
b
, nameCommaSuffix :: Bool
nameCommaSuffix = Bool
True }
else Name
name{ nameGiven :: Maybe Text
nameGiven = forall a. a -> Maybe a
Just Text
a
, nameSuffix :: Maybe Text
nameSuffix = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 Text
b }
Just Text
_ -> Name
name
extractNonDroppingParticle :: Name -> Name
extractNonDroppingParticle Name
name =
case Name -> Maybe Text
nameNonDroppingParticle Name
name of
Maybe Text
Nothing ->
case Name -> Maybe Text
nameFamily Name
name of
Maybe Text
Nothing -> Name
name
Just Text
t
| Text
"\"" Text -> Text -> Bool
`T.isPrefixOf` Text
t
, Text
"\"" Text -> Text -> Bool
`T.isSuffixOf` Text
t
-> Name
name { nameFamily :: Maybe Text
nameFamily = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.dropEnd Int
1 Text
t }
| Bool
otherwise ->
case forall a. (a -> Bool) -> [a] -> ([a], [a])
span ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isParticleChar) (Text -> [Text]
T.words Text
t) of
([],[Text]
_)
-> case (Char -> Bool) -> Text -> [Text]
T.split Char -> Bool
isParticlePunct Text
t of
[Text
x,Text
y] | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isParticleChar Text
x ->
Name
name{ nameFamily :: Maybe Text
nameFamily = forall a. a -> Maybe a
Just Text
y
, nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text
x forall a. Semigroup a => a -> a -> a
<>
Int -> Text -> Text
T.take Int
1
((Char -> Bool) -> Text -> Text
T.dropWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isParticlePunct) Text
t) }
[Text]
_ -> Name
name
([Text]
_,[]) -> Name
name
([Text]
as,[Text]
bs) -> Name
name{ nameFamily :: Maybe Text
nameFamily = forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
bs)
, nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
as) }
Just Text
_ -> Name
name
extractDroppingParticle :: Name -> Name
extractDroppingParticle Name
name =
case Name -> Maybe Text
nameDroppingParticle Name
name of
Just Text
_ -> Name
name
Maybe Text
Nothing ->
case Name -> Maybe Text
nameGiven Name
name of
Maybe Text
Nothing -> Name
name
Just Text
t ->
case forall a. (a -> Bool) -> [a] -> ([a], [a])
break ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isParticleChar) (Text -> [Text]
T.words Text
t) of
([Text]
_,[]) -> Name
name
([],[Text]
_) -> Name
name
([Text]
as,[Text]
bs)
| forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isParticleChar) [Text]
bs
-> Name
name{ nameGiven :: Maybe Text
nameGiven = forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
as)
, nameDroppingParticle :: Maybe Text
nameDroppingParticle = forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
bs) }
| Bool
otherwise -> Name
name
isParticlePunct :: Char -> Bool
isParticlePunct Char
c = Char
c forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'’' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'\x2013' Bool -> Bool -> Bool
||
Char
c forall a. Eq a => a -> a -> Bool
== Char
'.'
isParticleChar :: Char -> Bool
isParticleChar Char
c = Char -> Bool
isLower Char
c Bool -> Bool -> Bool
|| Char -> Bool
isParticlePunct Char
c
parseCheaterName :: Text -> Parser Name
parseCheaterName :: Text -> Parser Name
parseCheaterName Text
t = do
let (Maybe Text
family, Maybe Text
given) = case Text -> Text -> [Text]
T.splitOn Text
"||" Text
t of
(Text
f:Text
g:[Text]
_) -> (forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
f), forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
g))
[Text
f] -> (forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
f), forall a. Maybe a
Nothing)
[] -> (forall a. Maybe a
Nothing, forall a. Maybe a
Nothing)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Name -> Name
extractParticles forall a b. (a -> b) -> a -> b
$
Name
{ nameFamily :: Maybe Text
nameFamily = Maybe Text
family
, nameGiven :: Maybe Text
nameGiven = Maybe Text
given
, nameDroppingParticle :: Maybe Text
nameDroppingParticle = forall a. Maybe a
Nothing
, nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = forall a. Maybe a
Nothing
, nameSuffix :: Maybe Text
nameSuffix = forall a. Maybe a
Nothing
, nameCommaSuffix :: Bool
nameCommaSuffix = Bool
False
, nameStaticOrdering :: Bool
nameStaticOrdering = Bool
False
, nameLiteral :: Maybe Text
nameLiteral = if forall a. Maybe a -> Bool
isNothing Maybe Text
family Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isNothing Maybe Text
given
then forall a. a -> Maybe a
Just Text
t
else forall a. Maybe a
Nothing
}
isByzantineName :: Name -> Bool
isByzantineName :: Name -> Bool
isByzantineName Name
name = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
isByzantine (Name -> Maybe Text
nameFamily Name
name)
isByzantineChar :: Char -> Bool
isByzantineChar :: Char -> Bool
isByzantineChar Char
c = Char
c forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'9') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'z') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'Z') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x0e01' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x0e5b') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x00c0' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x017f') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x0370' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x03ff') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x0400' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x052f') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x0590' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x05d4') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x05d6' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x05ff') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x1f00' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x1fff') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x0600' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x06ff') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x200c' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x200e') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x2018' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x2019') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x021a' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x021b') Bool -> Bool -> Bool
||
(Char
c forall a. Ord a => a -> a -> Bool
>= Char
'\x202a' Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'\x202e')
isByzantine :: Text -> Bool
isByzantine :: Text -> Bool
isByzantine = (Char -> Bool) -> Text -> Bool
T.any Char -> Bool
isByzantineChar
asBool :: Value -> Parser Bool
asBool :: Value -> Parser Bool
asBool (String Text
t) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text
t forall a. Eq a => a -> a -> Bool
== Text
"true"
asBool (Bool Bool
b) = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
b
asBool (Number Scientific
n) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Scientific
n forall a. Eq a => a -> a -> Bool
== Scientific
1
asBool Value
x = forall a. String -> Value -> Parser a
typeMismatch String
"Bool" Value
x
asText :: Value -> Parser Text
asText :: Value -> Parser Text
asText (String Text
t) = forall (m :: * -> *) a. Monad m => a -> m a
return Text
t
asText (Number Scientific
n) = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ case forall r i. (RealFloat r, Integral i) => Scientific -> Either r i
S.floatingOrInteger Scientific
n of
Left Double
r -> String -> Text
T.pack (forall a. Show a => a -> String
show (Double
r :: Double))
Right Int
i -> String -> Text
T.pack (forall a. Show a => a -> String
show (Int
i :: Int))
asText Value
x = forall a. String -> Value -> Parser a
typeMismatch String
"String" Value
x
asInt :: Value -> Parser Int
asInt :: Value -> Parser Int
asInt (String Text
t) =
case Text -> Maybe Int
readAsInt Text
t of
Just Int
x -> forall (m :: * -> *) a. Monad m => a -> m a
return Int
x
Maybe Int
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"not a number"
asInt v :: Value
v@Number{} = forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
asInt Value
v = forall a. String -> Value -> Parser a
typeMismatch String
"Number" Value
v
data Date =
Date
{ Date -> [DateParts]
dateParts :: [DateParts]
, Date -> Bool
dateCirca :: Bool
, Date -> Maybe Int
dateSeason :: Maybe Int
, Date -> Maybe Text
dateLiteral :: Maybe Text
} deriving (Int -> Date -> ShowS
[Date] -> ShowS
Date -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Date] -> ShowS
$cshowList :: [Date] -> ShowS
show :: Date -> String
$cshow :: Date -> String
showsPrec :: Int -> Date -> ShowS
$cshowsPrec :: Int -> Date -> ShowS
Show, Date -> Date -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c== :: Date -> Date -> Bool
Eq, Eq Date
Date -> Date -> Bool
Date -> Date -> Ordering
Date -> Date -> Date
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Date -> Date -> Date
$cmin :: Date -> Date -> Date
max :: Date -> Date -> Date
$cmax :: Date -> Date -> Date
>= :: Date -> Date -> Bool
$c>= :: Date -> Date -> Bool
> :: Date -> Date -> Bool
$c> :: Date -> Date -> Bool
<= :: Date -> Date -> Bool
$c<= :: Date -> Date -> Bool
< :: Date -> Date -> Bool
$c< :: Date -> Date -> Bool
compare :: Date -> Date -> Ordering
$ccompare :: Date -> Date -> Ordering
Ord)
instance ToJSON Date where
toJSON :: Date -> Value
toJSON Date
d =
[Pair] -> Value
object forall a b. (a -> b) -> a -> b
$
(if Date -> Bool
dateCirca Date
d then ((Key
"circa", forall a. ToJSON a => a -> Value
toJSON Bool
True)forall a. a -> [a] -> [a]
:) else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case Date -> Maybe Int
dateSeason Date
d of
Just Int
s -> ((Key
"season", forall a. ToJSON a => a -> Value
toJSON Int
s)forall a. a -> [a] -> [a]
:)
Maybe Int
Nothing -> forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case Date -> Maybe Text
dateLiteral Date
d of
Just Text
l -> ((Key
"literal", forall a. ToJSON a => a -> Value
toJSON Text
l)forall a. a -> [a] -> [a]
:)
Maybe Text
Nothing -> forall a. a -> a
id) forall a b. (a -> b) -> a -> b
$
[ (Key
"date-parts", forall a. ToJSON a => a -> Value
toJSON (Date -> [DateParts]
dateParts Date
d)) ]
instance FromJSON Date where
parseJSON :: Value -> Parser Date
parseJSON (String Text
t) = Text -> Parser Date
rawDate Text
t
parseJSON Value
x = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Date" (\Object
v ->
(Object
vforall a. FromJSON a => Object -> Key -> Parser a
.: Key
"raw" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Parser Date
rawDate)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
([DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date
Date forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"date-parts" forall a. Parser (Maybe a) -> a -> Parser a
.!= []
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"circa" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser Bool
asBool) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"season" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Int
asInt) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"literal")) Value
x
newtype DateParts = DateParts [Int]
deriving (Int -> DateParts -> ShowS
[DateParts] -> ShowS
DateParts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateParts] -> ShowS
$cshowList :: [DateParts] -> ShowS
show :: DateParts -> String
$cshow :: DateParts -> String
showsPrec :: Int -> DateParts -> ShowS
$cshowsPrec :: Int -> DateParts -> ShowS
Show, DateParts -> DateParts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateParts -> DateParts -> Bool
$c/= :: DateParts -> DateParts -> Bool
== :: DateParts -> DateParts -> Bool
$c== :: DateParts -> DateParts -> Bool
Eq, Eq DateParts
DateParts -> DateParts -> Bool
DateParts -> DateParts -> Ordering
DateParts -> DateParts -> DateParts
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DateParts -> DateParts -> DateParts
$cmin :: DateParts -> DateParts -> DateParts
max :: DateParts -> DateParts -> DateParts
$cmax :: DateParts -> DateParts -> DateParts
>= :: DateParts -> DateParts -> Bool
$c>= :: DateParts -> DateParts -> Bool
> :: DateParts -> DateParts -> Bool
$c> :: DateParts -> DateParts -> Bool
<= :: DateParts -> DateParts -> Bool
$c<= :: DateParts -> DateParts -> Bool
< :: DateParts -> DateParts -> Bool
$c< :: DateParts -> DateParts -> Bool
compare :: DateParts -> DateParts -> Ordering
$ccompare :: DateParts -> DateParts -> Ordering
Ord, [DateParts] -> Encoding
[DateParts] -> Value
DateParts -> Encoding
DateParts -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DateParts] -> Encoding
$ctoEncodingList :: [DateParts] -> Encoding
toJSONList :: [DateParts] -> Value
$ctoJSONList :: [DateParts] -> Value
toEncoding :: DateParts -> Encoding
$ctoEncoding :: DateParts -> Encoding
toJSON :: DateParts -> Value
$ctoJSON :: DateParts -> Value
ToJSON)
instance FromJSON DateParts where
parseJSON :: Value -> Parser DateParts
parseJSON Value
v =
[Int] -> DateParts
DateParts forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. FromJSON a => Value -> Parser a
parseJSON Value
v forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Value -> Parser Int
asInt forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Value] -> [Value]
removeEmptyStrings)
rawDate :: Text -> Parser Date
rawDate :: Text -> Parser Date
rawDate Text
t = case Text -> Maybe Date
rawDateEDTF Text
t forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Maybe Date
rawDateOld Text
t of
Just Date
d -> forall (m :: * -> *) a. Monad m => a -> m a
return Date
d
Maybe Date
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Date { dateParts :: [DateParts]
dateParts = []
, dateCirca :: Bool
dateCirca = Bool
False
, dateSeason :: Maybe Int
dateSeason = forall a. Maybe a
Nothing
, dateLiteral :: Maybe Text
dateLiteral = forall a. a -> Maybe a
Just Text
t }
rawDateEDTF :: Text -> Maybe Date
rawDateEDTF :: Text -> Maybe Date
rawDateEDTF = Text -> Maybe Date
rawDateISO forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
handleRanges
where
handleRanges :: Text -> Text
handleRanges Text
t =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
==Char
'/') Text
t of
[Text
x] | (Char -> Bool) -> Text -> Bool
T.any (forall a. Eq a => a -> a -> Bool
== Char
'u') Text
x ->
(Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c forall a. Eq a => a -> a -> Bool
== Char
'u' then Char
'0' else Char
c) Text
x
forall a. Semigroup a => a -> a -> a
<> Text
"/" forall a. Semigroup a => a -> a -> a
<>
(Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c forall a. Eq a => a -> a -> Bool
== Char
'u' then Char
'9' else Char
c) Text
x
[Text
x, Text
"open"] -> Text
x forall a. Semigroup a => a -> a -> a
<> Text
"/"
[Text
x, Text
"unknown"] -> Text
x forall a. Semigroup a => a -> a -> a
<> Text
"/"
[Text]
_ -> Text
t
rawDateISO :: Text -> Maybe Date
rawDateISO :: Text -> Maybe Date
rawDateISO Text
raw = do
let ranges :: [Text]
ranges = forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
T.strip forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
==Char
'/') Text
raw
let circa :: Bool
circa = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Text
"~" Text -> Text -> Bool
`T.isSuffixOf`) [Text]
ranges
let isSpecial :: Char -> Bool
isSpecial Char
'~' = Bool
True
isSpecial Char
'?' = Bool
True
isSpecial Char
'%' = Bool
True
isSpecial Char
'T' = Bool
True
isSpecial Char
_ = Bool
False
let dparts :: Text -> Maybe DateParts
dparts Text
t = do
(Bool
hasY, Text
t') <- if Int -> Text -> Text
T.take Int
1 Text
t forall a. Eq a => a -> a -> Bool
== Text
"y"
then forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Int -> Text -> Text
T.drop Int
1 Text
t)
else forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, Text
t)
(Bool
isNeg, Text
t'') <- if Int -> Text -> Text
T.take Int
1 Text
t' forall a. Eq a => a -> a -> Bool
== Text
"-"
then forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Int -> Text -> Text
T.drop Int
1 Text
t')
else forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
False, Text
t')
let t''' :: Text
t''' = (Char -> Bool) -> Text -> Text
T.takeWhile (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpecial) Text
t''
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
==Char
'-') Text
t''' of
[Text
""] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
0]
[Text
y', Text
m', Text
d'] -> do
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' forall a. Ord a => a -> a -> Bool
>= Int
4
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
m' forall a. Eq a => a -> a -> Bool
== Int
2
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
d' forall a. Eq a => a -> a -> Bool
== Int
2
Int
y <- (if Bool
isNeg
then (\Int
x -> (Int
x forall a. Num a => a -> a -> a
* (-Int
1)) forall a. Num a => a -> a -> a
- Int
1)
else forall a. a -> a
id) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
readAsInt Text
y'
Int
m <- Text -> Maybe Int
readAsInt Text
m'
Int
d <- Text -> Maybe Int
readAsInt Text
d'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m, Int
d]
[Text
y', Text
m'] -> do
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' forall a. Ord a => a -> a -> Bool
>= Int
4
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
m' forall a. Eq a => a -> a -> Bool
== Int
2
Int
y <- (if Bool
isNeg
then (\Int
x -> (Int
x forall a. Num a => a -> a -> a
* (-Int
1)) forall a. Num a => a -> a -> a
- Int
1)
else forall a. a -> a
id) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
readAsInt Text
y'
Int
m <- Text -> Maybe Int
readAsInt Text
m'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m]
[Text
y'] -> do
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' forall a. Ord a => a -> a -> Bool
>= Int
4
Int
y <- (if Bool
isNeg
then (\Int
x -> (Int
x forall a. Num a => a -> a -> a
* (-Int
1)) forall a. Num a => a -> a -> a
- Int
1)
else forall a. a -> a
id) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
readAsInt Text
y'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y]
[Text]
_ -> forall (m :: * -> *) a. MonadPlus m => m a
mzero
[DateParts]
dps <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> Maybe DateParts
dparts [Text]
ranges
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Date
{ dateParts :: [DateParts]
dateParts = [DateParts]
dps
, dateCirca :: Bool
dateCirca = Bool
circa
, dateSeason :: Maybe Int
dateSeason = forall a. Maybe a
Nothing
, dateLiteral :: Maybe Text
dateLiteral = forall a. Maybe a
Nothing
}
rawDateOld :: Text -> Maybe Date
rawDateOld :: Text -> Maybe Date
rawDateOld Text
raw = do
let months :: [Text]
months = [Text
"jan",Text
"feb",Text
"mar",Text
"apr",Text
"may",Text
"jun",Text
"jul",Text
"aug",
Text
"sep",Text
"oct",Text
"nov",Text
"dec"]
let seasons :: [Text]
seasons = [Text
"spr",Text
"sum",Text
"fal",Text
"win"]
let ranges :: [Text]
ranges = (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
==Char
'-') Text
raw
let readTextMonth :: Text -> m Int
readTextMonth Text
t = do
let key :: Text
key = Text -> Text
T.toLower forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.take Int
3 Text
t
case forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
key [Text]
months of
Just Int
n -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nforall a. Num a => a -> a -> a
+Int
1)
Maybe Int
Nothing -> case forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
key [Text]
seasons of
Just Int
n -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nforall a. Num a => a -> a -> a
+Int
13)
Maybe Int
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Improper month"
let dparts :: Text -> Maybe DateParts
dparts Text
t =
case (Char -> Bool) -> Text -> [Text]
T.split (\Char
c -> Char
c forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'/' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
',') forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip Text
t of
[Text
m', Text
d', Text
y'] -> do
Int
y <- Text -> Maybe Int
readAsInt Text
y'
Int
m <- Text -> Maybe Int
readAsInt Text
m' forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall {m :: * -> *}. MonadFail m => Text -> m Int
readTextMonth Text
m'
Int
d <- Text -> Maybe Int
readAsInt Text
d'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m, Int
d]
[Text
m', Text
y'] -> do
Int
y <- Text -> Maybe Int
readAsInt Text
y'
Int
m <- Text -> Maybe Int
readAsInt Text
m' forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall {m :: * -> *}. MonadFail m => Text -> m Int
readTextMonth Text
m'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m]
[Text
y'] -> do
Int
y <- Text -> Maybe Int
readAsInt Text
y'
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y]
[] -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts []
[Text]
_ -> forall (m :: * -> *) a. MonadPlus m => m a
mzero
[DateParts]
dps <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> Maybe DateParts
dparts [Text]
ranges
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Date
{ dateParts :: [DateParts]
dateParts = [DateParts]
dps
, dateCirca :: Bool
dateCirca = Bool
False
, dateSeason :: Maybe Int
dateSeason = forall a. Maybe a
Nothing
, dateLiteral :: Maybe Text
dateLiteral = forall a. Maybe a
Nothing
}
removeEmptyStrings :: [Value] -> [Value]
removeEmptyStrings :: [Value] -> [Value]
removeEmptyStrings = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Bool
isEmptyString)
where
isEmptyString :: Value -> Bool
isEmptyString (String Text
t) = Text -> Bool
T.null Text
t
isEmptyString Value
_ = Bool
False
data Output a =
Formatted Formatting [Output a]
| Linked Text [Output a]
| InNote (Output a)
| Literal a
| Tagged Tag (Output a)
| NullOutput
deriving (Int -> Output a -> ShowS
forall a. Show a => Int -> Output a -> ShowS
forall a. Show a => [Output a] -> ShowS
forall a. Show a => Output a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Output a] -> ShowS
$cshowList :: forall a. Show a => [Output a] -> ShowS
show :: Output a -> String
$cshow :: forall a. Show a => Output a -> String
showsPrec :: Int -> Output a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Output a -> ShowS
Show, Output a -> Output a -> Bool
forall a. Eq a => Output a -> Output a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Output a -> Output a -> Bool
$c/= :: forall a. Eq a => Output a -> Output a -> Bool
== :: Output a -> Output a -> Bool
$c== :: forall a. Eq a => Output a -> Output a -> Bool
Eq)
instance Uniplate (Output a) where
uniplate :: Output a -> (Str (Output a), Str (Output a) -> Output a)
uniplate (Formatted Formatting
f [Output a]
xs) = forall from to. from -> Type from to
plate forall a. Formatting -> [Output a] -> Output a
Formatted forall item from to. Type (item -> from) to -> item -> Type from to
|- Formatting
f forall to from. Type ([to] -> from) to -> [to] -> Type from to
||* [Output a]
xs
uniplate (Linked Text
u [Output a]
xs) = forall from to. from -> Type from to
plate forall a. Text -> [Output a] -> Output a
Linked forall item from to. Type (item -> from) to -> item -> Type from to
|- Text
u forall to from. Type ([to] -> from) to -> [to] -> Type from to
||* [Output a]
xs
uniplate (InNote Output a
x) = forall from to. from -> Type from to
plate forall a. Output a -> Output a
InNote forall to from. Type (to -> from) to -> to -> Type from to
|* Output a
x
uniplate (Literal a
x) = forall from to. from -> Type from to
plate forall a. a -> Output a
Literal forall item from to. Type (item -> from) to -> item -> Type from to
|- a
x
uniplate (Tagged Tag
t Output a
x) = forall from to. from -> Type from to
plate forall a. Tag -> Output a -> Output a
Tagged forall item from to. Type (item -> from) to -> item -> Type from to
|- Tag
t forall to from. Type (to -> from) to -> to -> Type from to
|* Output a
x
uniplate Output a
NullOutput = forall from to. from -> Type from to
plate forall a. Output a
NullOutput
instance Biplate (Output a) (Output a) where
biplate :: Output a -> (Str (Output a), Str (Output a) -> Output a)
biplate = forall to. to -> Type to to
plateSelf
data Identifier =
IdentDOI Text
| IdentPMCID Text
| IdentPMID Text
| IdentURL Text
deriving (Int -> Identifier -> ShowS
[Identifier] -> ShowS
Identifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Identifier] -> ShowS
$cshowList :: [Identifier] -> ShowS
show :: Identifier -> String
$cshow :: Identifier -> String
showsPrec :: Int -> Identifier -> ShowS
$cshowsPrec :: Int -> Identifier -> ShowS
Show, Identifier -> Identifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Identifier -> Identifier -> Bool
$c/= :: Identifier -> Identifier -> Bool
== :: Identifier -> Identifier -> Bool
$c== :: Identifier -> Identifier -> Bool
Eq)
identifierToURL :: Identifier -> Text
identifierToURL :: Identifier -> Text
identifierToURL Identifier
ident =
case Identifier
ident of
IdentDOI Text
t -> Text -> Text -> Text
tolink Text
"https://doi.org/" (Text -> Text
fixShortDOI Text
t)
IdentPMCID Text
t -> Text -> Text -> Text
tolink Text
"https://www.ncbi.nlm.nih.gov/pmc/articles/" Text
t
IdentPMID Text
t -> Text -> Text -> Text
tolink Text
"https://www.ncbi.nlm.nih.gov/pubmed/" Text
t
IdentURL Text
t -> Text -> Text -> Text
tolink Text
"https://" Text
t
where
tolink :: Text -> Text -> Text
tolink Text
pref Text
x = if Text -> Bool
T.null Text
x Bool -> Bool -> Bool
|| (Text
"://" Text -> Text -> Bool
`T.isInfixOf` Text
x)
then Text
x
else Text
pref forall a. Semigroup a => a -> a -> a
<> Text
x
fixShortDOI :: Text -> Text
fixShortDOI :: Text -> Text
fixShortDOI Text
x = if Text
"10/" Text -> Text -> Bool
`T.isPrefixOf` Text
x
then Int -> Text -> Text
T.drop Int
3 Text
x
else Text
x
data Tag =
TagTerm Term
| TagCitationNumber Int
| TagCitationLabel
| TagTitle
| TagItem CitationItemType ItemId
| TagName Name
| TagNames Variable NamesFormat [Name]
| TagDate Date
| TagYearSuffix Int
| TagLocator
| TagPrefix
| TagSuffix
deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tag] -> ShowS
$cshowList :: [Tag] -> ShowS
show :: Tag -> String
$cshow :: Tag -> String
showsPrec :: Int -> Tag -> ShowS
$cshowsPrec :: Int -> Tag -> ShowS
Show, Tag -> Tag -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tag -> Tag -> Bool
$c/= :: Tag -> Tag -> Bool
== :: Tag -> Tag -> Bool
$c== :: Tag -> Tag -> Bool
Eq)
outputToText :: CiteprocOutput a => Output a -> Text
outputToText :: forall a. CiteprocOutput a => Output a -> Text
outputToText Output a
NullOutput = forall a. Monoid a => a
mempty
outputToText (Literal a
x ) = forall a. CiteprocOutput a => a -> Text
toText a
x
outputToText (Tagged Tag
_ Output a
x) = forall a. CiteprocOutput a => Output a -> Text
outputToText Output a
x
outputToText (Formatted Formatting
_ [Output a]
xs) = [Text] -> Text
T.unwords forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. CiteprocOutput a => Output a -> Text
outputToText [Output a]
xs
outputToText (Linked Text
_ [Output a]
xs) = [Text] -> Text
T.unwords forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. CiteprocOutput a => Output a -> Text
outputToText [Output a]
xs
outputToText (InNote Output a
x) = forall a. CiteprocOutput a => Output a -> Text
outputToText Output a
x
renderOutput :: CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput :: forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
_ Output a
NullOutput = forall a. Monoid a => a
mempty
renderOutput CiteprocOptions
_ (Literal a
x) = a
x
renderOutput CiteprocOptions
opts (Tagged (TagItem CitationItemType
itemtype ItemId
ident) Output a
x)
| CiteprocOptions -> Bool
linkCitations CiteprocOptions
opts
, CitationItemType
itemtype forall a. Eq a => a -> a -> Bool
/= CitationItemType
AuthorOnly
= forall a. CiteprocOutput a => Text -> a -> a
addHyperlink (Text
"#ref-" forall a. Semigroup a => a -> a -> a
<> ItemId -> Text
unItemId ItemId
ident) forall a b. (a -> b) -> a -> b
$ forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x
renderOutput CiteprocOptions
opts (Tagged Tag
_ Output a
x) = forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x
renderOutput CiteprocOptions
opts (Formatted Formatting
f [Linked Text
url [Output a]
xs])
| CiteprocOptions -> Bool
linkBibliography CiteprocOptions
opts
, Text
url forall a. Eq a => a -> a -> Bool
== Text
prefix forall a. Semigroup a => a -> a -> a
<> Text
anchor
= forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts forall a b. (a -> b) -> a -> b
$ forall a. Text -> [Output a] -> Output a
Linked Text
url [forall a. Formatting -> [Output a] -> Output a
Formatted Formatting
f [Output a]
xs]
where
anchor :: Text
anchor = forall a. Monoid a => [a] -> a
mconcat (forall a b. (a -> b) -> [a] -> [b]
map forall a. CiteprocOutput a => Output a -> Text
outputToText [Output a]
xs)
prefix :: Text
prefix = forall a. a -> Maybe a -> a
fromMaybe Text
"" (Formatting -> Maybe Text
formatPrefix Formatting
f)
renderOutput CiteprocOptions
opts (Formatted Formatting
formatting [Output a]
xs) =
forall a. CiteprocOutput a => Formatting -> a -> a
addFormatting Formatting
formatting forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. CiteprocOutput a => [a] -> [a]
fixPunct forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case Formatting -> Maybe Text
formatDelimiter Formatting
formatting of
Just Text
d -> forall a. CiteprocOutput a => a -> [a] -> [a]
addDelimiters (forall a. CiteprocOutput a => Text -> a
fromText Text
d)
Maybe Text
Nothing -> forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= forall a. Monoid a => a
mempty) forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts) [Output a]
xs
renderOutput CiteprocOptions
opts (Linked Text
url [Output a]
xs)
= (if CiteprocOptions -> Bool
linkBibliography CiteprocOptions
opts
then forall a. CiteprocOutput a => Text -> a -> a
addHyperlink Text
url
else forall a. a -> a
id) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. CiteprocOutput a => [a] -> [a]
fixPunct forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts) [Output a]
xs
renderOutput CiteprocOptions
opts (InNote Output a
x) = forall {a}. CiteprocOutput a => a -> a
inNote forall a b. (a -> b) -> a -> b
$
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile Char -> Bool
isSpace forall a b. (a -> b) -> a -> b
$
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile (\Char
c -> Char
c forall a. Eq a => a -> a -> Bool
== Char
',' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
':') forall a b. (a -> b) -> a -> b
$
forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x
addDelimiters :: CiteprocOutput a => a -> [a] -> [a]
addDelimiters :: forall a. CiteprocOutput a => a -> [a] -> [a]
addDelimiters a
delim =
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> [a] -> [a]
addDelim []
where
addDelim :: a -> [a] -> [a]
addDelim a
x [] = [a
x]
addDelim a
x (a
a:[a]
as) = case Text -> Maybe (Char, Text)
T.uncons (forall a. CiteprocOutput a => a -> Text
toText a
a) of
Just (Char
c,Text
_)
| Char
c forall a. Eq a => a -> a -> Bool
== Char
',' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'.' -> a
x forall a. a -> [a] -> [a]
: a
a forall a. a -> [a] -> [a]
: [a]
as
Maybe (Char, Text)
_ -> a
x forall a. a -> [a] -> [a]
: a
delim forall a. a -> [a] -> [a]
: a
a forall a. a -> [a] -> [a]
: [a]
as
fixPunct :: CiteprocOutput a => [a] -> [a]
fixPunct :: forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
x:a
y:[a]
zs) =
case (Char
xEnd, Char
yStart) of
(Char
'!',Char
'.') -> [a]
keepFirst
(Char
'!',Char
'?') -> [a]
keepBoth
(Char
'!',Char
':') -> [a]
keepFirst
(Char
'!',Char
',') -> [a]
keepBoth
(Char
'!',Char
';') -> [a]
keepBoth
(Char
'?',Char
'!') -> [a]
keepBoth
(Char
'?',Char
'.') -> [a]
keepFirst
(Char
'?',Char
':') -> [a]
keepFirst
(Char
'?',Char
',') -> [a]
keepBoth
(Char
'?',Char
';') -> [a]
keepBoth
(Char
'.',Char
'!') -> [a]
keepBoth
(Char
'.',Char
'?') -> [a]
keepBoth
(Char
'.',Char
':') -> [a]
keepBoth
(Char
'.',Char
',') -> [a]
keepBoth
(Char
'.',Char
';') -> [a]
keepBoth
(Char
':',Char
'!') -> [a]
keepSecond
(Char
':',Char
'?') -> [a]
keepSecond
(Char
':',Char
'.') -> [a]
keepFirst
(Char
':',Char
',') -> [a]
keepBoth
(Char
':',Char
';') -> [a]
keepBoth
(Char
',',Char
'!') -> [a]
keepBoth
(Char
',',Char
'?') -> [a]
keepBoth
(Char
',',Char
':') -> [a]
keepBoth
(Char
',',Char
'.') -> [a]
keepBoth
(Char
',',Char
';') -> [a]
keepBoth
(Char
';',Char
'!') -> [a]
keepSecond
(Char
';',Char
'?') -> [a]
keepSecond
(Char
';',Char
':') -> [a]
keepFirst
(Char
';',Char
'.') -> [a]
keepFirst
(Char
';',Char
',') -> [a]
keepBoth
(Char
'!',Char
'!') -> [a]
keepFirst
(Char
'?',Char
'?') -> [a]
keepFirst
(Char
'.',Char
'.') -> [a]
keepFirst
(Char
':',Char
':') -> [a]
keepFirst
(Char
';',Char
';') -> [a]
keepFirst
(Char
',',Char
',') -> [a]
keepFirst
(Char
' ',Char
' ') -> [a]
keepSecond
(Char
' ',Char
',') -> [a]
keepSecond
(Char
' ',Char
'.') -> [a]
keepSecond
(Char, Char)
_ -> [a]
keepBoth
where
xText :: Text
xText = forall a. CiteprocOutput a => a -> Text
toText a
x
yText :: Text
yText = forall a. CiteprocOutput a => a -> Text
toText a
y
xEnd :: Char
xEnd = if Text -> Bool
T.null Text
xText then Char
'\xFFFD' else Text -> Char
T.last Text
xText
yStart :: Char
yStart = if Text -> Bool
T.null Text
yText then Char
'\xFFFD' else Text -> Char
T.head Text
yText
xTrimmed :: a
xTrimmed = forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhileEnd (forall a. Eq a => a -> a -> Bool
== Char
xEnd) a
x
yTrimmed :: a
yTrimmed = forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile (forall a. Eq a => a -> a -> Bool
== Char
yStart) a
y
keepFirst :: [a]
keepFirst = if a
yTrimmed forall a. Eq a => a -> a -> Bool
== a
y
then a
x forall a. a -> [a] -> [a]
: forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y forall a. a -> [a] -> [a]
: [a]
zs)
else forall a. CiteprocOutput a => [a] -> [a]
fixPunct forall a b. (a -> b) -> a -> b
$ a
x forall a. a -> [a] -> [a]
: a
yTrimmed forall a. a -> [a] -> [a]
: [a]
zs
keepSecond :: [a]
keepSecond = if a
xTrimmed forall a. Eq a => a -> a -> Bool
== a
x
then a
x forall a. a -> [a] -> [a]
: forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y forall a. a -> [a] -> [a]
: [a]
zs)
else forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
xTrimmed forall a. a -> [a] -> [a]
: a
y forall a. a -> [a] -> [a]
: [a]
zs)
keepBoth :: [a]
keepBoth = a
x forall a. a -> [a] -> [a]
: forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y forall a. a -> [a] -> [a]
: [a]
zs)
fixPunct [a]
zs = [a]
zs
grouped :: [Output a] -> Output a
grouped :: forall a. [Output a] -> Output a
grouped = forall a. Formatting -> [Output a] -> Output a
formatted forall a. Monoid a => a
mempty
formatted :: Formatting -> [Output a] -> Output a
formatted :: forall a. Formatting -> [Output a] -> Output a
formatted Formatting
formatting = forall a. [Output a] -> Output a
grouped' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Output a -> Bool
isNullOutput)
where
isNullOutput :: Output a -> Bool
isNullOutput Output a
NullOutput = Bool
True
isNullOutput Output a
_ = Bool
False
grouped' :: [Output a] -> Output a
grouped' [] = forall a. Output a
NullOutput
grouped' [Output a
x] | Formatting
formatting forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = Output a
x
grouped' [Output a]
xs = forall a. Formatting -> [Output a] -> Output a
Formatted Formatting
formatting [Output a]
xs
readAsInt :: Text -> Maybe Int
readAsInt :: Text -> Maybe Int
readAsInt Text
t =
case forall a. Integral a => Reader a
TR.decimal Text
t of
Right (Int
x,Text
t') | Text -> Bool
T.null Text
t' -> forall a. a -> Maybe a
Just Int
x
Either String (Int, Text)
_ -> forall a. Maybe a
Nothing
newtype Abbreviations =
Abbreviations (M.Map Variable (M.Map Variable Text))
deriving (Int -> Abbreviations -> ShowS
[Abbreviations] -> ShowS
Abbreviations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Abbreviations] -> ShowS
$cshowList :: [Abbreviations] -> ShowS
show :: Abbreviations -> String
$cshow :: Abbreviations -> String
showsPrec :: Int -> Abbreviations -> ShowS
$cshowsPrec :: Int -> Abbreviations -> ShowS
Show, Abbreviations -> Abbreviations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Abbreviations -> Abbreviations -> Bool
$c/= :: Abbreviations -> Abbreviations -> Bool
== :: Abbreviations -> Abbreviations -> Bool
$c== :: Abbreviations -> Abbreviations -> Bool
Eq, Eq Abbreviations
Abbreviations -> Abbreviations -> Bool
Abbreviations -> Abbreviations -> Ordering
Abbreviations -> Abbreviations -> Abbreviations
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Abbreviations -> Abbreviations -> Abbreviations
$cmin :: Abbreviations -> Abbreviations -> Abbreviations
max :: Abbreviations -> Abbreviations -> Abbreviations
$cmax :: Abbreviations -> Abbreviations -> Abbreviations
>= :: Abbreviations -> Abbreviations -> Bool
$c>= :: Abbreviations -> Abbreviations -> Bool
> :: Abbreviations -> Abbreviations -> Bool
$c> :: Abbreviations -> Abbreviations -> Bool
<= :: Abbreviations -> Abbreviations -> Bool
$c<= :: Abbreviations -> Abbreviations -> Bool
< :: Abbreviations -> Abbreviations -> Bool
$c< :: Abbreviations -> Abbreviations -> Bool
compare :: Abbreviations -> Abbreviations -> Ordering
$ccompare :: Abbreviations -> Abbreviations -> Ordering
Ord)
instance FromJSON Abbreviations where
parseJSON :: Value -> Parser Abbreviations
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Abbreviations" forall a b. (a -> b) -> a -> b
$ \Object
v ->
Map Variable (Map Variable Text) -> Abbreviations
Abbreviations forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"default"
instance ToJSON Abbreviations where
toJSON :: Abbreviations -> Value
toJSON (Abbreviations Map Variable (Map Variable Text)
m) =
[Pair] -> Value
object [(Key
"default", forall a. ToJSON a => a -> Value
toJSON Map Variable (Map Variable Text)
m)]
lookupAbbreviation :: CiteprocOutput a
=> Variable -> Val a -> Abbreviations -> Maybe (Val a)
lookupAbbreviation :: forall a.
CiteprocOutput a =>
Variable -> Val a -> Abbreviations -> Maybe (Val a)
lookupAbbreviation Variable
var Val a
val (Abbreviations Map Variable (Map Variable Text)
abbrevmap) = do
Map Variable Text
abbrvs <- forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (if Variable -> VariableType
variableType Variable
var forall a. Eq a => a -> a -> Bool
== VariableType
NumberVariable
then Variable
"number"
else Variable
var) Map Variable (Map Variable Text)
abbrevmap
case Val a
val of
TextVal Text
t -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall (m :: * -> *) a. MonadPlus m => m a
mzero (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Text -> Val a
TextVal)
forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Variable
toVariable Text
t) Map Variable Text
abbrvs
FancyVal a
x -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall (m :: * -> *) a. MonadPlus m => m a
mzero (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Text -> Val a
TextVal)
forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Variable
toVariable (forall a. CiteprocOutput a => a -> Text
toText a
x)) Map Variable Text
abbrvs
NumVal Int
n -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall (m :: * -> *) a. MonadPlus m => m a
mzero (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Text -> Val a
TextVal)
forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Variable
toVariable (String -> Text
T.pack (forall a. Show a => a -> String
show Int
n))) Map Variable Text
abbrvs
Val a
_ -> forall (m :: * -> *) a. MonadPlus m => m a
mzero
data Result a =
Result
{ forall a. Result a -> [a]
resultCitations :: [a]
, forall a. Result a -> [(Text, a)]
resultBibliography :: [(Text, a)]
, forall a. Result a -> [Text]
resultWarnings :: [Text]
} deriving (Int -> Result a -> ShowS
forall a. Show a => Int -> Result a -> ShowS
forall a. Show a => [Result a] -> ShowS
forall a. Show a => Result a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Result a] -> ShowS
$cshowList :: forall a. Show a => [Result a] -> ShowS
show :: Result a -> String
$cshow :: forall a. Show a => Result a -> String
showsPrec :: Int -> Result a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Result a -> ShowS
Show, forall a b. a -> Result b -> Result a
forall a b. (a -> b) -> Result a -> Result b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Result b -> Result a
$c<$ :: forall a b. a -> Result b -> Result a
fmap :: forall a b. (a -> b) -> Result a -> Result b
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
Functor, Functor Result
Foldable Result
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Result (m a) -> m (Result a)
forall (f :: * -> *) a.
Applicative f =>
Result (f a) -> f (Result a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Result a -> m (Result b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Result a -> f (Result b)
sequence :: forall (m :: * -> *) a. Monad m => Result (m a) -> m (Result a)
$csequence :: forall (m :: * -> *) a. Monad m => Result (m a) -> m (Result a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Result a -> m (Result b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Result a -> m (Result b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Result (f a) -> f (Result a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Result (f a) -> f (Result a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Result a -> f (Result b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Result a -> f (Result b)
Traversable, forall a. Eq a => a -> Result a -> Bool
forall a. Num a => Result a -> a
forall a. Ord a => Result a -> a
forall m. Monoid m => Result m -> m
forall a. Result a -> Bool
forall a. Result a -> Int
forall a. Result a -> [a]
forall a. (a -> a -> a) -> Result a -> a
forall m a. Monoid m => (a -> m) -> Result a -> m
forall b a. (b -> a -> b) -> b -> Result a -> b
forall a b. (a -> b -> b) -> b -> Result a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => Result a -> a
$cproduct :: forall a. Num a => Result a -> a
sum :: forall a. Num a => Result a -> a
$csum :: forall a. Num a => Result a -> a
minimum :: forall a. Ord a => Result a -> a
$cminimum :: forall a. Ord a => Result a -> a
maximum :: forall a. Ord a => Result a -> a
$cmaximum :: forall a. Ord a => Result a -> a
elem :: forall a. Eq a => a -> Result a -> Bool
$celem :: forall a. Eq a => a -> Result a -> Bool
length :: forall a. Result a -> Int
$clength :: forall a. Result a -> Int
null :: forall a. Result a -> Bool
$cnull :: forall a. Result a -> Bool
toList :: forall a. Result a -> [a]
$ctoList :: forall a. Result a -> [a]
foldl1 :: forall a. (a -> a -> a) -> Result a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Result a -> a
foldr1 :: forall a. (a -> a -> a) -> Result a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Result a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> Result a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Result a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Result a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Result a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Result a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Result a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Result a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Result a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> Result a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Result a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Result a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Result a -> m
fold :: forall m. Monoid m => Result m -> m
$cfold :: forall m. Monoid m => Result m -> m
Foldable)
instance ToJSON a => ToJSON (Result a) where
toJSON :: Result a -> Value
toJSON Result a
res = [Pair] -> Value
object
[ (Key
"citations", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Result a -> [a]
resultCitations Result a
res)
, (Key
"bibliography", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Result a -> [(Text, a)]
resultBibliography Result a
res)
, (Key
"warnings", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Result a -> [Text]
resultWarnings Result a
res)
]
instance FromJSON a => FromJSON (Result a) where
parseJSON :: Value -> Parser (Result a)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Result" forall a b. (a -> b) -> a -> b
$ \Object
v ->
forall a. [a] -> [(Text, a)] -> [Text] -> Result a
Result forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"citations"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"bibliography"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"warnings"
data Inputs a =
Inputs
{ forall a. Inputs a -> Maybe [Citation a]
inputsCitations :: Maybe [Citation a]
, forall a. Inputs a -> Maybe [Reference a]
inputsReferences :: Maybe [Reference a]
, forall a. Inputs a -> Maybe Text
inputsStyle :: Maybe Text
, forall a. Inputs a -> Maybe Abbreviations
inputsAbbreviations :: Maybe Abbreviations
, forall a. Inputs a -> Maybe Lang
inputsLang :: Maybe Lang
} deriving (Int -> Inputs a -> ShowS
forall a. Show a => Int -> Inputs a -> ShowS
forall a. Show a => [Inputs a] -> ShowS
forall a. Show a => Inputs a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Inputs a] -> ShowS
$cshowList :: forall a. Show a => [Inputs a] -> ShowS
show :: Inputs a -> String
$cshow :: forall a. Show a => Inputs a -> String
showsPrec :: Int -> Inputs a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Inputs a -> ShowS
Show)
instance ToJSON a => ToJSON (Inputs a) where
toJSON :: Inputs a -> Value
toJSON Inputs a
inp = [Pair] -> Value
object
[ (Key
"citations", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Inputs a -> Maybe [Citation a]
inputsCitations Inputs a
inp)
, (Key
"references", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Inputs a -> Maybe [Reference a]
inputsReferences Inputs a
inp)
, (Key
"style", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Inputs a -> Maybe Text
inputsStyle Inputs a
inp)
, (Key
"abbreviations", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ forall a. Inputs a -> Maybe Abbreviations
inputsAbbreviations Inputs a
inp)
, (Key
"lang", forall a. ToJSON a => a -> Value
toJSON forall a b. (a -> b) -> a -> b
$ Lang -> Text
renderLang forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Inputs a -> Maybe Lang
inputsLang Inputs a
inp)
]
instance (FromJSON a, Eq a) => FromJSON (Inputs a) where
parseJSON :: Value -> Parser (Inputs a)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Inputs" forall a b. (a -> b) -> a -> b
$ \Object
v ->
forall a.
Maybe [Citation a]
-> Maybe [Reference a]
-> Maybe Text
-> Maybe Abbreviations
-> Maybe Lang
-> Inputs a
Inputs forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"citations"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"references"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"style"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"abbreviations"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (do Maybe Text
mbl <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"lang"
case Maybe Text
mbl of
Maybe Text
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Just Text
l ->
case Text -> Either String Lang
parseLang Text
l of
Left String
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
Right Lang
lang -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just Lang
lang)