{-# 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(..)
  , 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)

-- import Debug.Trace
--
-- traceShowIdLabeled :: Show a => String -> a -> a
-- traceShowIdLabeled label x =
--   trace (label ++ ": " ++ show x) x

-- import Text.Show.Pretty (ppShow)
--
-- ppTrace :: Show a => a -> a
-- ppTrace x = trace (ppShow x) x

-- | Options affecting the output in ways that go beyond
-- what can be specified in styles.
newtype CiteprocOptions =
  CiteprocOptions
  { CiteprocOptions -> Bool
linkCitations :: Bool
    -- ^ Create hyperlinks from citations to bibliography entries
  }
  deriving (Int -> CiteprocOptions -> ShowS
[CiteprocOptions] -> ShowS
CiteprocOptions -> String
(Int -> CiteprocOptions -> ShowS)
-> (CiteprocOptions -> String)
-> ([CiteprocOptions] -> ShowS)
-> Show CiteprocOptions
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
(CiteprocOptions -> CiteprocOptions -> Bool)
-> (CiteprocOptions -> CiteprocOptions -> Bool)
-> Eq CiteprocOptions
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 :: Bool -> CiteprocOptions
CiteprocOptions
  { linkCitations :: Bool
linkCitations = Bool
False }

data CiteprocError =
    CiteprocXMLError Text
  | CiteprocParseError Text
  | CiteprocLocaleNotFound Text
  deriving (Int -> CiteprocError -> ShowS
[CiteprocError] -> ShowS
CiteprocError -> String
(Int -> CiteprocError -> ShowS)
-> (CiteprocError -> String)
-> ([CiteprocError] -> ShowS)
-> Show CiteprocError
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
(CiteprocError -> CiteprocError -> Bool)
-> (CiteprocError -> CiteprocError -> Bool) -> Eq CiteprocError
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: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
prettyCiteprocError (CiteprocParseError Text
t) =
  Text
"CiteprocParseError: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t
prettyCiteprocError (CiteprocLocaleNotFound Text
t) =
  Text
"CiteprocLocaleNotFound: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t

-- | CSL styles require certain formatting transformations to
-- be defined.  These are defined in the 'CiteprocOutput' class.
-- The library may be used with any structured format that defines
-- these operations.  See the 'Citeproc.CslJson' module for an instance
-- that corresponds to the markup allowed in CSL JSON. See
-- the 'Citeproc.Pandoc' module for an instance for Pandoc 'Inlines'.
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

addFormatting :: CiteprocOutput a => Formatting -> a -> a
addFormatting :: Formatting -> a -> a
addFormatting Formatting
f a
x =
  if Text -> Bool
T.null (a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x)  -- TODO inefficient
     then a
forall a. Monoid a => a
mempty
     else
       (a -> a)
-> (DisplayStyle -> a -> a) -> Maybe DisplayStyle -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id DisplayStyle -> a -> a
forall a. CiteprocOutput a => DisplayStyle -> a -> a
addDisplay (Formatting -> Maybe DisplayStyle
formatDisplay Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (if Bool
affixesInside then a -> a
forall a. a -> a
id else a -> a
forall p. CiteprocOutput p => p -> p
addPrefix (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall p. CiteprocOutput p => p -> p
addSuffix) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (if Formatting -> Bool
formatQuotes Formatting
f then a -> a
forall p. CiteprocOutput p => p -> p
addQuotes else a -> a
forall a. a -> a
id) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a)
-> (VerticalAlign -> a -> a) -> Maybe VerticalAlign -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id VerticalAlign -> a -> a
forall a. CiteprocOutput a => VerticalAlign -> a -> a
addVerticalAlign (Formatting -> Maybe VerticalAlign
formatVerticalAlign Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a)
-> (TextDecoration -> a -> a) -> Maybe TextDecoration -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id TextDecoration -> a -> a
forall a. CiteprocOutput a => TextDecoration -> a -> a
addTextDecoration (Formatting -> Maybe TextDecoration
formatTextDecoration Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a) -> (FontWeight -> a -> a) -> Maybe FontWeight -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id FontWeight -> a -> a
forall a. CiteprocOutput a => FontWeight -> a -> a
addFontWeight (Formatting -> Maybe FontWeight
formatFontWeight Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a) -> (FontVariant -> a -> a) -> Maybe FontVariant -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id FontVariant -> a -> a
forall a. CiteprocOutput a => FontVariant -> a -> a
addFontVariant (Formatting -> Maybe FontVariant
formatFontVariant Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a) -> (TextCase -> a -> a) -> Maybe TextCase -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id (Maybe Lang -> TextCase -> a -> a
forall a. CiteprocOutput a => Maybe Lang -> TextCase -> a -> a
addTextCase (Formatting -> Maybe Lang
formatLang Formatting
f)) (Formatting -> Maybe TextCase
formatTextCase Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (a -> a) -> (FontStyle -> a -> a) -> Maybe FontStyle -> a -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a -> a
forall a. a -> a
id FontStyle -> a -> a
forall a. CiteprocOutput a => FontStyle -> a -> a
addFontStyle (Formatting -> Maybe FontStyle
formatFontStyle Formatting
f) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (if Bool
affixesInside then a -> a
forall p. CiteprocOutput p => p -> p
addPrefix (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall p. CiteprocOutput p => p -> p
addSuffix else a -> a
forall a. a -> a
id) (a -> a) -> (a -> a) -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
       (if Formatting -> Bool
formatStripPeriods Formatting
f then (Text -> Text) -> a -> a
forall a. CiteprocOutput a => (Text -> Text) -> a -> a
mapText ((Char -> Bool) -> Text -> Text
T.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'.')) else a -> a
forall a. a -> a
id)
       (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ a
x
 where
  addPrefix :: p -> p
addPrefix p
z = case Formatting -> Maybe Text
formatPrefix Formatting
f of
                  Just Text
s   -> [p] -> p
forall a. Monoid a => [a] -> a
mconcat ([p] -> p) -> [p] -> p
forall a b. (a -> b) -> a -> b
$ [p] -> [p]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct [Text -> p
forall a. CiteprocOutput a => Text -> a
fromText Text
s, p
z]
                  Maybe Text
Nothing  -> p
z
  addSuffix :: p -> p
addSuffix p
z = case Formatting -> Maybe Text
formatSuffix Formatting
f of
                  Just Text
s   -> [p] -> p
forall a. Monoid a => [a] -> a
mconcat ([p] -> p) -> [p] -> p
forall a b. (a -> b) -> a -> b
$ [p] -> [p]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct [p
z, Text -> p
forall a. CiteprocOutput a => Text -> a
fromText Text
s]
                  Maybe Text
Nothing  -> p
z
  affixesInside :: Bool
affixesInside = Formatting -> Bool
formatAffixesInside Formatting
f

-- | The identifier used to identify a work in a bibliographic
-- database.
newtype ItemId = ItemId { ItemId -> Text
unItemId :: Text }
  deriving (Int -> ItemId -> ShowS
[ItemId] -> ShowS
ItemId -> String
(Int -> ItemId -> ShowS)
-> (ItemId -> String) -> ([ItemId] -> ShowS) -> Show ItemId
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
(ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> Bool) -> Eq ItemId
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
Eq ItemId
-> (ItemId -> ItemId -> Ordering)
-> (ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> Bool)
-> (ItemId -> ItemId -> ItemId)
-> (ItemId -> ItemId -> ItemId)
-> Ord 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
$cp1Ord :: Eq ItemId
Ord, b -> ItemId -> ItemId
NonEmpty ItemId -> ItemId
ItemId -> ItemId -> ItemId
(ItemId -> ItemId -> ItemId)
-> (NonEmpty ItemId -> ItemId)
-> (forall b. Integral b => b -> ItemId -> ItemId)
-> Semigroup 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 :: 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
Semigroup ItemId
-> ItemId
-> (ItemId -> ItemId -> ItemId)
-> ([ItemId] -> ItemId)
-> Monoid 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
$cp1Monoid :: Semigroup ItemId
Monoid, [ItemId] -> Encoding
[ItemId] -> Value
ItemId -> Encoding
ItemId -> Value
(ItemId -> Value)
-> (ItemId -> Encoding)
-> ([ItemId] -> Value)
-> ([ItemId] -> Encoding)
-> ToJSON ItemId
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
(Value -> Parser ItemId)
-> (Value -> Parser [ItemId]) -> FromJSON 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      -- ^ e.g., Smith
  | SuppressAuthor  -- ^ e.g., (2000, p. 30)
  | NormalCite      -- ^ e.g., (Smith 2000, p. 30)
  deriving (Int -> CitationItemType -> ShowS
[CitationItemType] -> ShowS
CitationItemType -> String
(Int -> CitationItemType -> ShowS)
-> (CitationItemType -> String)
-> ([CitationItemType] -> ShowS)
-> Show CitationItemType
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
(CitationItemType -> CitationItemType -> Bool)
-> (CitationItemType -> CitationItemType -> Bool)
-> Eq CitationItemType
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
Eq CitationItemType
-> (CitationItemType -> CitationItemType -> Ordering)
-> (CitationItemType -> CitationItemType -> Bool)
-> (CitationItemType -> CitationItemType -> Bool)
-> (CitationItemType -> CitationItemType -> Bool)
-> (CitationItemType -> CitationItemType -> Bool)
-> (CitationItemType -> CitationItemType -> CitationItemType)
-> (CitationItemType -> CitationItemType -> CitationItemType)
-> Ord 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
$cp1Ord :: Eq CitationItemType
Ord)

instance FromJSON CitationItemType where
  parseJSON :: Value -> Parser CitationItemType
parseJSON Value
x = Value -> Parser String
forall a. FromJSON a => Value -> Parser a
parseJSON Value
x Parser String
-> (String -> Parser CitationItemType) -> Parser CitationItemType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
    \case
      String
"author-only"     -> CitationItemType -> Parser CitationItemType
forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
AuthorOnly
      String
"suppress-author" -> CitationItemType -> Parser CitationItemType
forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
SuppressAuthor
      String
"normal-cite"     -> CitationItemType -> Parser CitationItemType
forall (f :: * -> *) a. Applicative f => a -> f a
pure CitationItemType
NormalCite
      String
t                 -> String -> Parser CitationItemType
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser CitationItemType)
-> String -> Parser CitationItemType
forall a b. (a -> b) -> a -> b
$ String
"Unknown type " String -> ShowS
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"

-- | The part of a citation corresponding to a single work,
-- possibly including a label, locator, prefix and suffix.
data CitationItem a =
  CitationItem
  { CitationItem a -> ItemId
citationItemId             :: ItemId
  , CitationItem a -> Maybe Text
citationItemLabel          :: Maybe Text
  , CitationItem a -> Maybe Text
citationItemLocator        :: Maybe Text
  , CitationItem a -> CitationItemType
citationItemType           :: CitationItemType
  , CitationItem a -> Maybe a
citationItemPrefix         :: Maybe a
  , CitationItem a -> Maybe a
citationItemSuffix         :: Maybe a
  } deriving (Int -> CitationItem a -> ShowS
[CitationItem a] -> ShowS
CitationItem a -> String
(Int -> CitationItem a -> ShowS)
-> (CitationItem a -> String)
-> ([CitationItem a] -> ShowS)
-> Show (CitationItem a)
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
(CitationItem a -> CitationItem a -> Bool)
-> (CitationItem a -> CitationItem a -> Bool)
-> Eq (CitationItem a)
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, Eq (CitationItem a)
Eq (CitationItem a)
-> (CitationItem a -> CitationItem a -> Ordering)
-> (CitationItem a -> CitationItem a -> Bool)
-> (CitationItem a -> CitationItem a -> Bool)
-> (CitationItem a -> CitationItem a -> Bool)
-> (CitationItem a -> CitationItem a -> Bool)
-> (CitationItem a -> CitationItem a -> CitationItem a)
-> (CitationItem a -> CitationItem a -> CitationItem a)
-> Ord (CitationItem a)
CitationItem a -> CitationItem a -> Bool
CitationItem a -> CitationItem a -> Ordering
CitationItem a -> CitationItem a -> CitationItem a
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
$cp1Ord :: forall a. Ord a => Eq (CitationItem a)
Ord)

instance FromJSON a => FromJSON (CitationItem a) where
  parseJSON :: Value -> Parser (CitationItem a)
parseJSON = String
-> (Object -> Parser (CitationItem a))
-> Value
-> Parser (CitationItem a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CitationItem" ((Object -> Parser (CitationItem a))
 -> Value -> Parser (CitationItem a))
-> (Object -> Parser (CitationItem a))
-> Value
-> Parser (CitationItem a)
forall a b. (a -> b) -> a -> b
$ \Object
v -> ItemId
-> Maybe Text
-> Maybe Text
-> CitationItemType
-> Maybe a
-> Maybe a
-> CitationItem a
forall a.
ItemId
-> Maybe Text
-> Maybe Text
-> CitationItemType
-> Maybe a
-> Maybe a
-> CitationItem a
CitationItem
    (ItemId
 -> Maybe Text
 -> Maybe Text
 -> CitationItemType
 -> Maybe a
 -> Maybe a
 -> CitationItem a)
-> Parser ItemId
-> Parser
     (Maybe Text
      -> Maybe Text
      -> CitationItemType
      -> Maybe a
      -> Maybe a
      -> CitationItem a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"id" Parser Value -> (Value -> Parser ItemId) -> Parser ItemId
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Text -> ItemId) -> Parser Text -> Parser ItemId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ItemId
ItemId (Parser Text -> Parser ItemId)
-> (Value -> Parser Text) -> Value -> Parser ItemId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Text
asText)
    Parser
  (Maybe Text
   -> Maybe Text
   -> CitationItemType
   -> Maybe a
   -> Maybe a
   -> CitationItem a)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> CitationItemType -> Maybe a -> Maybe a -> CitationItem a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"label"
    Parser
  (Maybe Text
   -> CitationItemType -> Maybe a -> Maybe a -> CitationItem a)
-> Parser (Maybe Text)
-> Parser
     (CitationItemType -> Maybe a -> Maybe a -> CitationItem a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text -> Parser (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"locator" Parser Value -> (Value -> Parser Text) -> Parser Text
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser Text
asText)
    Parser (CitationItemType -> Maybe a -> Maybe a -> CitationItem a)
-> Parser CitationItemType
-> Parser (Maybe a -> Maybe a -> CitationItem a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ( (Object
v Object -> Text -> Parser CitationItemType
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type")
        Parser CitationItemType
-> Parser CitationItemType -> Parser CitationItemType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do Maybe Bool
suppressAuth <- Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"suppress-author"
                Maybe Bool
authorOnly <- Object
v Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"author-only"
                CitationItemType -> Parser CitationItemType
forall (m :: * -> *) a. Monad m => a -> m a
return (CitationItemType -> Parser CitationItemType)
-> CitationItemType -> Parser CitationItemType
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) )
    Parser (Maybe a -> Maybe a -> CitationItem a)
-> Parser (Maybe a) -> Parser (Maybe a -> CitationItem a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"prefix"
    Parser (Maybe a -> CitationItem a)
-> Parser (Maybe a) -> Parser (CitationItem a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe a)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"suffix"

instance ToJSON a => ToJSON (CitationItem a) where
  toJSON :: CitationItem a -> Value
toJSON CitationItem a
i = [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
    [ ( Text
"id", ItemId -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItem a -> ItemId
forall a. CitationItem a -> ItemId
citationItemId CitationItem a
i) )
    , (Text
"type", CitationItemType -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItemType -> Value) -> CitationItemType -> Value
forall a b. (a -> b) -> a -> b
$ CitationItem a -> CitationItemType
forall a. CitationItem a -> CitationItemType
citationItemType CitationItem a
i) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
    [ ( Text
"label", Maybe Text -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItem a -> Maybe Text
forall a. CitationItem a -> Maybe Text
citationItemLabel CitationItem a
i) )
                  | Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (CitationItem a -> Maybe Text
forall a. CitationItem a -> Maybe Text
citationItemLabel CitationItem a
i) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
    [ (Text
"locator", Maybe Text -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItem a -> Maybe Text
forall a. CitationItem a -> Maybe Text
citationItemLocator CitationItem a
i) )
                  | Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (CitationItem a -> Maybe Text
forall a. CitationItem a -> Maybe Text
citationItemLocator CitationItem a
i) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
    [ (Text
"prefix", Maybe a -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItem a -> Maybe a
forall a. CitationItem a -> Maybe a
citationItemPrefix CitationItem a
i))
                 | Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (CitationItem a -> Maybe a
forall a. CitationItem a -> Maybe a
citationItemPrefix CitationItem a
i) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
    [ (Text
"suffix", Maybe a -> Value
forall a. ToJSON a => a -> Value
toJSON (CitationItem a -> Maybe a
forall a. CitationItem a -> Maybe a
citationItemSuffix CitationItem a
i))
                 | Maybe a -> Bool
forall a. Maybe a -> Bool
isJust (CitationItem a -> Maybe a
forall a. CitationItem a -> Maybe a
citationItemSuffix CitationItem a
i) ]


-- | A citation (which may include several items, e.g.
-- in @(Smith 2000; Jones 2010, p. 30)@).
data Citation a =
  Citation { Citation a -> Maybe Text
citationId         :: Maybe Text
           , Citation a -> Maybe Int
citationNoteNumber :: Maybe Int
           , Citation a -> [CitationItem a]
citationItems      :: [CitationItem a] }
  deriving (Int -> Citation a -> ShowS
[Citation a] -> ShowS
Citation a -> String
(Int -> Citation a -> ShowS)
-> (Citation a -> String)
-> ([Citation a] -> ShowS)
-> Show (Citation a)
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
(Citation a -> Citation a -> Bool)
-> (Citation a -> Citation a -> Bool) -> Eq (Citation a)
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, Eq (Citation a)
Eq (Citation a)
-> (Citation a -> Citation a -> Ordering)
-> (Citation a -> Citation a -> Bool)
-> (Citation a -> Citation a -> Bool)
-> (Citation a -> Citation a -> Bool)
-> (Citation a -> Citation a -> Bool)
-> (Citation a -> Citation a -> Citation a)
-> (Citation a -> Citation a -> Citation a)
-> Ord (Citation a)
Citation a -> Citation a -> Bool
Citation a -> Citation a -> Ordering
Citation a -> Citation a -> Citation a
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
$cp1Ord :: forall a. Ord a => Eq (Citation a)
Ord)

instance FromJSON a => FromJSON (Citation a) where
 parseJSON :: Value -> Parser (Citation a)
parseJSON Value
v =
   String
-> (Array -> Parser (Citation a)) -> Value -> Parser (Citation a)
forall a. String -> (Array -> Parser a) -> Value -> Parser a
withArray String
"Citation"
     (\Array
ary ->
       case Array
ary Array -> Int -> Maybe Value
forall a. Vector a -> Int -> Maybe a
V.!? Int
0 of
         Just Value
v' -> (String
-> (Object -> Parser (Citation a)) -> Value -> Parser (Citation a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Citation" ((Object -> Parser (Citation a)) -> Value -> Parser (Citation a))
-> (Object -> Parser (Citation a)) -> Value -> Parser (Citation a)
forall a b. (a -> b) -> a -> b
$ \Object
o
                      -> Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation (Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a)
-> Parser (Maybe Text)
-> Parser (Maybe Int -> [CitationItem a] -> Citation a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"citationID"
                                  Parser (Maybe Int -> [CitationItem a] -> Citation a)
-> Parser (Maybe Int) -> Parser ([CitationItem a] -> Citation a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
o Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"properties"
                                             Parser Object
-> (Object -> Parser (Maybe Int)) -> Parser (Maybe Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"noteIndex"))
                                      Parser (Maybe Int) -> Parser (Maybe Int) -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Int
forall a. Maybe a
Nothing)
                                  Parser ([CitationItem a] -> Citation a)
-> Parser [CitationItem a] -> Parser (Citation a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [CitationItem a]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"citationItems") Value
v'
                  Parser (Citation a) -> Parser (Citation a) -> Parser (Citation a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation Maybe Text
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing ([CitationItem a] -> Citation a)
-> Parser [CitationItem a] -> Parser (Citation a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [CitationItem a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v'
         Maybe Value
Nothing -> String -> Parser (Citation a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Empty array") Value
v
   Parser (Citation a) -> Parser (Citation a) -> Parser (Citation a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
   String
-> (Object -> Parser (Citation a)) -> Value -> Parser (Citation a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Citation"
     (\Object
o -> Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation (Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a)
-> Parser (Maybe Text)
-> Parser (Maybe Int -> [CitationItem a] -> Citation a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"citationID"
                     Parser (Maybe Int -> [CitationItem a] -> Citation a)
-> Parser (Maybe Int) -> Parser ([CitationItem a] -> Citation a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"citationNoteNumber"
                     Parser ([CitationItem a] -> Citation a)
-> Parser [CitationItem a] -> Parser (Citation a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Text -> Parser [CitationItem a]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"citationItems") Value
v
   Parser (Citation a) -> Parser (Citation a) -> Parser (Citation a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
   (Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
forall a. Maybe Text -> Maybe Int -> [CitationItem a] -> Citation a
Citation Maybe Text
forall a. Maybe a
Nothing Maybe Int
forall a. Maybe a
Nothing ([CitationItem a] -> Citation a)
-> Parser [CitationItem a] -> Parser (Citation a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [CitationItem a]
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 ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
     [ (Text
"citationID", Maybe Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe Text -> Value) -> Maybe Text -> Value
forall a b. (a -> b) -> a -> b
$ Citation a -> Maybe Text
forall a. Citation a -> Maybe Text
citationId Citation a
c) | Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust (Citation a -> Maybe Text
forall a. Citation a -> Maybe Text
citationId Citation a
c) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
     [ (Text
"citationItems" , [CitationItem a] -> Value
forall a. ToJSON a => a -> Value
toJSON ([CitationItem a] -> Value) -> [CitationItem a] -> Value
forall a b. (a -> b) -> a -> b
$ Citation a -> [CitationItem a]
forall a. Citation a -> [CitationItem a]
citationItems Citation a
c) ] [Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++
     case Citation a -> Maybe Int
forall a. Citation a -> Maybe Int
citationNoteNumber Citation a
c of
           Maybe Int
Nothing -> []
           Just Int
n  -> [ (Text
"citationNoteNumber", Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
n) ]

data Match =
    MatchAll
  | MatchAny
  | MatchNone
  deriving (Int -> Match -> ShowS
[Match] -> ShowS
Match -> String
(Int -> Match -> ShowS)
-> (Match -> String) -> ([Match] -> ShowS) -> Show Match
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
(Match -> Match -> Bool) -> (Match -> Match -> Bool) -> Eq Match
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
(Int -> Condition -> ShowS)
-> (Condition -> String)
-> ([Condition] -> ShowS)
-> Show Condition
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
(Condition -> Condition -> Bool)
-> (Condition -> Condition -> Bool) -> Eq Condition
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
(Int -> Position -> ShowS)
-> (Position -> String) -> ([Position] -> ShowS) -> Show Position
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
(Position -> Position -> Bool)
-> (Position -> Position -> Bool) -> Eq Position
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
Eq Position
-> (Position -> Position -> Ordering)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Bool)
-> (Position -> Position -> Position)
-> (Position -> Position -> Position)
-> Ord 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
$cp1Ord :: Eq Position
Ord)

data DateType =
    LocalizedNumeric
  | LocalizedText
  | NonLocalized
  deriving (Int -> DateType -> ShowS
[DateType] -> ShowS
DateType -> String
(Int -> DateType -> ShowS)
-> (DateType -> String) -> ([DateType] -> ShowS) -> Show DateType
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
(DateType -> DateType -> Bool)
-> (DateType -> DateType -> Bool) -> Eq DateType
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
Eq DateType
-> (DateType -> DateType -> Ordering)
-> (DateType -> DateType -> Bool)
-> (DateType -> DateType -> Bool)
-> (DateType -> DateType -> Bool)
-> (DateType -> DateType -> Bool)
-> (DateType -> DateType -> DateType)
-> (DateType -> DateType -> DateType)
-> Ord 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
$cp1Ord :: Eq DateType
Ord)

data ShowDateParts =
    YearMonthDay
  | YearMonth
  | Year
  deriving (Int -> ShowDateParts -> ShowS
[ShowDateParts] -> ShowS
ShowDateParts -> String
(Int -> ShowDateParts -> ShowS)
-> (ShowDateParts -> String)
-> ([ShowDateParts] -> ShowS)
-> Show ShowDateParts
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
(ShowDateParts -> ShowDateParts -> Bool)
-> (ShowDateParts -> ShowDateParts -> Bool) -> Eq ShowDateParts
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
(Int -> DPName -> ShowS)
-> (DPName -> String) -> ([DPName] -> ShowS) -> Show DPName
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
(DPName -> DPName -> Bool)
-> (DPName -> DPName -> Bool) -> Eq DPName
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
Eq DPName
-> (DPName -> DPName -> Ordering)
-> (DPName -> DPName -> Bool)
-> (DPName -> DPName -> Bool)
-> (DPName -> DPName -> Bool)
-> (DPName -> DPName -> Bool)
-> (DPName -> DPName -> DPName)
-> (DPName -> DPName -> DPName)
-> Ord 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
$cp1Ord :: Eq DPName
Ord)

data DPForm =
    DPNumeric
  | DPNumericLeadingZeros
  | DPOrdinal
  | DPLong
  | DPShort
  deriving (Int -> DPForm -> ShowS
[DPForm] -> ShowS
DPForm -> String
(Int -> DPForm -> ShowS)
-> (DPForm -> String) -> ([DPForm] -> ShowS) -> Show DPForm
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
(DPForm -> DPForm -> Bool)
-> (DPForm -> DPForm -> Bool) -> Eq DPForm
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
(Int -> DP -> ShowS)
-> (DP -> String) -> ([DP] -> ShowS) -> Show DP
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
(DP -> DP -> Bool) -> (DP -> DP -> Bool) -> Eq DP
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
(Int -> VariableForm -> ShowS)
-> (VariableForm -> String)
-> ([VariableForm] -> ShowS)
-> Show VariableForm
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
(VariableForm -> VariableForm -> Bool)
-> (VariableForm -> VariableForm -> Bool) -> Eq VariableForm
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
(Int -> TextType -> ShowS)
-> (TextType -> String) -> ([TextType] -> ShowS) -> Show TextType
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
(TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool) -> Eq TextType
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
(Int -> NumberForm -> ShowS)
-> (NumberForm -> String)
-> ([NumberForm] -> ShowS)
-> Show NumberForm
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
(NumberForm -> NumberForm -> Bool)
-> (NumberForm -> NumberForm -> Bool) -> Eq NumberForm
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
(Int -> Pluralize -> ShowS)
-> (Pluralize -> String)
-> ([Pluralize] -> ShowS)
-> Show Pluralize
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
(Pluralize -> Pluralize -> Bool)
-> (Pluralize -> Pluralize -> Bool) -> Eq Pluralize
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
(Int -> NamesFormat -> ShowS)
-> (NamesFormat -> String)
-> ([NamesFormat] -> ShowS)
-> Show NamesFormat
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
(NamesFormat -> NamesFormat -> Bool)
-> (NamesFormat -> NamesFormat -> Bool) -> Eq NamesFormat
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
(Int -> DelimiterPrecedes -> ShowS)
-> (DelimiterPrecedes -> String)
-> ([DelimiterPrecedes] -> ShowS)
-> Show DelimiterPrecedes
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
(DelimiterPrecedes -> DelimiterPrecedes -> Bool)
-> (DelimiterPrecedes -> DelimiterPrecedes -> Bool)
-> Eq DelimiterPrecedes
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
(Int -> NameForm -> ShowS)
-> (NameForm -> String) -> ([NameForm] -> ShowS) -> Show NameForm
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
(NameForm -> NameForm -> Bool)
-> (NameForm -> NameForm -> Bool) -> Eq NameForm
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
(Int -> NameFormat -> ShowS)
-> (NameFormat -> String)
-> ([NameFormat] -> ShowS)
-> Show NameFormat
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
(NameFormat -> NameFormat -> Bool)
-> (NameFormat -> NameFormat -> Bool) -> Eq NameFormat
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 :: Maybe Formatting
-> Maybe Formatting
-> Maybe TermForm
-> Text
-> DelimiterPrecedes
-> DelimiterPrecedes
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Bool
-> NameForm
-> Bool
-> Maybe Text
-> Maybe NameAsSortOrder
-> Text
-> NameFormat
NameFormat
  { nameGivenFormatting :: Maybe Formatting
nameGivenFormatting          = Maybe Formatting
forall a. Maybe a
Nothing
  , nameFamilyFormatting :: Maybe Formatting
nameFamilyFormatting         =  Maybe Formatting
forall a. Maybe a
Nothing
  , nameAndStyle :: Maybe TermForm
nameAndStyle                 = Maybe TermForm
forall a. Maybe a
Nothing
  , nameDelimiter :: Text
nameDelimiter                = Text
", "
  , nameDelimiterPrecedesEtAl :: DelimiterPrecedes
nameDelimiterPrecedesEtAl    = DelimiterPrecedes
PrecedesContextual
  , nameDelimiterPrecedesLast :: DelimiterPrecedes
nameDelimiterPrecedesLast    = DelimiterPrecedes
PrecedesContextual
  , nameEtAlMin :: Maybe Int
nameEtAlMin                  = Maybe Int
forall a. Maybe a
Nothing
  , nameEtAlUseFirst :: Maybe Int
nameEtAlUseFirst             = Maybe Int
forall a. Maybe a
Nothing
  , nameEtAlSubsequentUseFirst :: Maybe Int
nameEtAlSubsequentUseFirst   = Maybe Int
forall a. Maybe a
Nothing
  , nameEtAlSubsequentMin :: Maybe Int
nameEtAlSubsequentMin        = Maybe Int
forall a. Maybe a
Nothing
  , nameEtAlUseLast :: Bool
nameEtAlUseLast              = Bool
False
  , nameForm :: NameForm
nameForm                     = NameForm
LongName
  , nameInitialize :: Bool
nameInitialize               = Bool
True
  , nameInitializeWith :: Maybe Text
nameInitializeWith           = Maybe Text
forall a. Maybe a
Nothing
  , nameAsSortOrder :: Maybe NameAsSortOrder
nameAsSortOrder              = Maybe NameAsSortOrder
forall a. Maybe a
Nothing
  , nameSortSeparator :: Text
nameSortSeparator            = Text
", "
  }

data NameAsSortOrder =
     NameAsSortOrderFirst
   | NameAsSortOrderAll
   deriving (Int -> NameAsSortOrder -> ShowS
[NameAsSortOrder] -> ShowS
NameAsSortOrder -> String
(Int -> NameAsSortOrder -> ShowS)
-> (NameAsSortOrder -> String)
-> ([NameAsSortOrder] -> ShowS)
-> Show NameAsSortOrder
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
(NameAsSortOrder -> NameAsSortOrder -> Bool)
-> (NameAsSortOrder -> NameAsSortOrder -> Bool)
-> Eq NameAsSortOrder
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] -- last part is substitutes if any
  | ELabel Variable TermForm Pluralize
  | EGroup Bool [Element a]  -- Bool is true if it's an expanded macro
  | EChoose [(Match, [Condition], [Element a])]
    -- 'else' can be represented by a final trivial match condition
  deriving (Int -> ElementType a -> ShowS
[ElementType a] -> ShowS
ElementType a -> String
(Int -> ElementType a -> ShowS)
-> (ElementType a -> String)
-> ([ElementType a] -> ShowS)
-> Show (ElementType a)
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
(ElementType a -> ElementType a -> Bool)
-> (ElementType a -> ElementType a -> Bool) -> Eq (ElementType a)
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  -- put affixes inside other formatting
  } deriving (Int -> Formatting -> ShowS
[Formatting] -> ShowS
Formatting -> String
(Int -> Formatting -> ShowS)
-> (Formatting -> String)
-> ([Formatting] -> ShowS)
-> Show Formatting
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
(Formatting -> Formatting -> Bool)
-> (Formatting -> Formatting -> Bool) -> Eq Formatting
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 Maybe Lang
forall a. Maybe a
Nothing Maybe FontStyle
forall a. Maybe a
Nothing Maybe FontVariant
forall a. Maybe a
Nothing Maybe FontWeight
forall a. Maybe a
Nothing Maybe TextDecoration
forall a. Maybe a
Nothing
  Maybe VerticalAlign
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe DisplayStyle
forall a. Maybe a
Nothing Maybe TextCase
forall a. Maybe a
Nothing Maybe Text
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 Maybe Lang -> Maybe Lang -> Maybe Lang
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Lang
la2) (Maybe FontStyle
a1 Maybe FontStyle -> Maybe FontStyle -> Maybe FontStyle
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontStyle
a2) (Maybe FontVariant
b1 Maybe FontVariant -> Maybe FontVariant -> Maybe FontVariant
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontVariant
b2) (Maybe FontWeight
c1 Maybe FontWeight -> Maybe FontWeight -> Maybe FontWeight
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FontWeight
c2)
                (Maybe TextDecoration
d1 Maybe TextDecoration
-> Maybe TextDecoration -> Maybe TextDecoration
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe TextDecoration
d2) (Maybe VerticalAlign
e1 Maybe VerticalAlign -> Maybe VerticalAlign -> Maybe VerticalAlign
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe VerticalAlign
e2) (Maybe Text
f1 Maybe Text -> Maybe Text -> Maybe Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
f2)
                (Maybe Text
g1 Maybe Text -> Maybe Text -> Maybe Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Text
g2) (Maybe DisplayStyle
h1 Maybe DisplayStyle -> Maybe DisplayStyle -> Maybe DisplayStyle
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe DisplayStyle
h2) (Maybe TextCase
i1 Maybe TextCase -> Maybe TextCase -> Maybe TextCase
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe TextCase
i2)
                (Maybe Text
j1 Maybe Text -> Maybe Text -> Maybe Text
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 = Formatting -> Formatting -> Formatting
forall a. Semigroup a => a -> a -> a
(<>)

data TextCase =
     Lowercase
   | Uppercase
   | CapitalizeFirst
   | CapitalizeAll
   | SentenceCase
   | TitleCase
   deriving (Int -> TextCase -> ShowS
[TextCase] -> ShowS
TextCase -> String
(Int -> TextCase -> ShowS)
-> (TextCase -> String) -> ([TextCase] -> ShowS) -> Show TextCase
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
(TextCase -> TextCase -> Bool)
-> (TextCase -> TextCase -> Bool) -> Eq TextCase
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
(Int -> DisplayStyle -> ShowS)
-> (DisplayStyle -> String)
-> ([DisplayStyle] -> ShowS)
-> Show DisplayStyle
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
(DisplayStyle -> DisplayStyle -> Bool)
-> (DisplayStyle -> DisplayStyle -> Bool) -> Eq DisplayStyle
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
(Int -> FontStyle -> ShowS)
-> (FontStyle -> String)
-> ([FontStyle] -> ShowS)
-> Show FontStyle
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
(FontStyle -> FontStyle -> Bool)
-> (FontStyle -> FontStyle -> Bool) -> Eq FontStyle
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
(Int -> FontVariant -> ShowS)
-> (FontVariant -> String)
-> ([FontVariant] -> ShowS)
-> Show FontVariant
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
(FontVariant -> FontVariant -> Bool)
-> (FontVariant -> FontVariant -> Bool) -> Eq FontVariant
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
(Int -> FontWeight -> ShowS)
-> (FontWeight -> String)
-> ([FontWeight] -> ShowS)
-> Show FontWeight
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
(FontWeight -> FontWeight -> Bool)
-> (FontWeight -> FontWeight -> Bool) -> Eq FontWeight
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
(Int -> TextDecoration -> ShowS)
-> (TextDecoration -> String)
-> ([TextDecoration] -> ShowS)
-> Show TextDecoration
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
(TextDecoration -> TextDecoration -> Bool)
-> (TextDecoration -> TextDecoration -> Bool) -> Eq TextDecoration
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
(Int -> VerticalAlign -> ShowS)
-> (VerticalAlign -> String)
-> ([VerticalAlign] -> ShowS)
-> Show VerticalAlign
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
(VerticalAlign -> VerticalAlign -> Bool)
-> (VerticalAlign -> VerticalAlign -> Bool) -> Eq VerticalAlign
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
[Element a] -> ShowS
Element a -> String
(Int -> Element a -> ShowS)
-> (Element a -> String)
-> ([Element a] -> ShowS)
-> Show (Element a)
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
(Element a -> Element a -> Bool)
-> (Element a -> Element a -> Bool) -> Eq (Element a)
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
(Int -> SortDirection -> ShowS)
-> (SortDirection -> String)
-> ([SortDirection] -> ShowS)
-> Show SortDirection
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
(SortDirection -> SortDirection -> Bool)
-> (SortDirection -> SortDirection -> Bool) -> Eq SortDirection
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
[SortKey a] -> ShowS
SortKey a -> String
(Int -> SortKey a -> ShowS)
-> (SortKey a -> String)
-> ([SortKey a] -> ShowS)
-> Show (SortKey a)
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
(SortKey a -> SortKey a -> Bool)
-> (SortKey a -> SortKey a -> Bool) -> Eq (SortKey a)
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
(Int -> SortKeyValue -> ShowS)
-> (SortKeyValue -> String)
-> ([SortKeyValue] -> ShowS)
-> Show SortKeyValue
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
(SortKeyValue -> SortKeyValue -> Bool)
-> (SortKeyValue -> SortKeyValue -> Bool) -> Eq SortKeyValue
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
  { Layout a -> LayoutOptions
layoutOptions        :: LayoutOptions
  , Layout a -> Formatting
layoutFormatting     :: Formatting
  , Layout a -> [Element a]
layoutElements       :: [Element a]
  , Layout a -> [SortKey a]
layoutSortKeys       :: [SortKey a]
  } deriving (Int -> Layout a -> ShowS
[Layout a] -> ShowS
Layout a -> String
(Int -> Layout a -> ShowS)
-> (Layout a -> String) -> ([Layout a] -> ShowS) -> Show (Layout a)
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
(Layout a -> Layout a -> Bool)
-> (Layout a -> Layout a -> Bool) -> Eq (Layout a)
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
(Int -> LayoutOptions -> ShowS)
-> (LayoutOptions -> String)
-> ([LayoutOptions] -> ShowS)
-> Show LayoutOptions
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
(LayoutOptions -> LayoutOptions -> Bool)
-> (LayoutOptions -> LayoutOptions -> Bool) -> Eq LayoutOptions
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
(Int -> Collapsing -> ShowS)
-> (Collapsing -> String)
-> ([Collapsing] -> ShowS)
-> Show Collapsing
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
(Collapsing -> Collapsing -> Bool)
-> (Collapsing -> Collapsing -> Bool) -> Eq Collapsing
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
(Int -> DisambiguationStrategy -> ShowS)
-> (DisambiguationStrategy -> String)
-> ([DisambiguationStrategy] -> ShowS)
-> Show DisambiguationStrategy
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
(DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> (DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> Eq DisambiguationStrategy
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
Eq DisambiguationStrategy
-> (DisambiguationStrategy -> DisambiguationStrategy -> Ordering)
-> (DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> (DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> (DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> (DisambiguationStrategy -> DisambiguationStrategy -> Bool)
-> (DisambiguationStrategy
    -> DisambiguationStrategy -> DisambiguationStrategy)
-> (DisambiguationStrategy
    -> DisambiguationStrategy -> DisambiguationStrategy)
-> Ord 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
$cp1Ord :: Eq DisambiguationStrategy
Ord)

data GivenNameDisambiguationRule =
    AllNames
  | AllNamesWithInitials
  | PrimaryName
  | PrimaryNameWithInitials
  | ByCite
  deriving (Int -> GivenNameDisambiguationRule -> ShowS
[GivenNameDisambiguationRule] -> ShowS
GivenNameDisambiguationRule -> String
(Int -> GivenNameDisambiguationRule -> ShowS)
-> (GivenNameDisambiguationRule -> String)
-> ([GivenNameDisambiguationRule] -> ShowS)
-> Show GivenNameDisambiguationRule
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
(GivenNameDisambiguationRule
 -> GivenNameDisambiguationRule -> Bool)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Bool)
-> Eq GivenNameDisambiguationRule
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
Eq GivenNameDisambiguationRule
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Ordering)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Bool)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Bool)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Bool)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> Bool)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> GivenNameDisambiguationRule)
-> (GivenNameDisambiguationRule
    -> GivenNameDisambiguationRule -> GivenNameDisambiguationRule)
-> Ord 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
$cp1Ord :: Eq GivenNameDisambiguationRule
Ord)

data DemoteNonDroppingParticle =
     DemoteDisplayAndSort
   | DemoteSortOnly
   | DemoteNever
   deriving (Int -> DemoteNonDroppingParticle -> ShowS
[DemoteNonDroppingParticle] -> ShowS
DemoteNonDroppingParticle -> String
(Int -> DemoteNonDroppingParticle -> ShowS)
-> (DemoteNonDroppingParticle -> String)
-> ([DemoteNonDroppingParticle] -> ShowS)
-> Show DemoteNonDroppingParticle
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
(DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool)
-> (DemoteNonDroppingParticle -> DemoteNonDroppingParticle -> Bool)
-> Eq DemoteNonDroppingParticle
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
  , StyleOptions -> Maybe PageRangeFormat
stylePageRangeFormat            :: Maybe PageRangeFormat
  , StyleOptions -> Maybe Text
stylePageRangeDelimiter         :: 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
(Int -> StyleOptions -> ShowS)
-> (StyleOptions -> String)
-> ([StyleOptions] -> ShowS)
-> Show StyleOptions
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
(StyleOptions -> StyleOptions -> Bool)
-> (StyleOptions -> StyleOptions -> Bool) -> Eq StyleOptions
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
(Int -> SubsequentAuthorSubstitute -> ShowS)
-> (SubsequentAuthorSubstitute -> String)
-> ([SubsequentAuthorSubstitute] -> ShowS)
-> Show SubsequentAuthorSubstitute
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
(SubsequentAuthorSubstitute -> SubsequentAuthorSubstitute -> Bool)
-> (SubsequentAuthorSubstitute
    -> SubsequentAuthorSubstitute -> Bool)
-> Eq SubsequentAuthorSubstitute
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
(Int -> SubsequentAuthorSubstituteRule -> ShowS)
-> (SubsequentAuthorSubstituteRule -> String)
-> ([SubsequentAuthorSubstituteRule] -> ShowS)
-> Show SubsequentAuthorSubstituteRule
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
(SubsequentAuthorSubstituteRule
 -> SubsequentAuthorSubstituteRule -> Bool)
-> (SubsequentAuthorSubstituteRule
    -> SubsequentAuthorSubstituteRule -> Bool)
-> Eq SubsequentAuthorSubstituteRule
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
(Int -> SecondFieldAlign -> ShowS)
-> (SecondFieldAlign -> String)
-> ([SecondFieldAlign] -> ShowS)
-> Show SecondFieldAlign
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
(SecondFieldAlign -> SecondFieldAlign -> Bool)
-> (SecondFieldAlign -> SecondFieldAlign -> Bool)
-> Eq SecondFieldAlign
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 PageRangeFormat =
    PageRangeChicago
  | PageRangeExpanded
  | PageRangeMinimal
  | PageRangeMinimalTwo
  deriving (Int -> PageRangeFormat -> ShowS
[PageRangeFormat] -> ShowS
PageRangeFormat -> String
(Int -> PageRangeFormat -> ShowS)
-> (PageRangeFormat -> String)
-> ([PageRangeFormat] -> ShowS)
-> Show PageRangeFormat
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
(PageRangeFormat -> PageRangeFormat -> Bool)
-> (PageRangeFormat -> PageRangeFormat -> Bool)
-> Eq PageRangeFormat
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
Eq PageRangeFormat
-> (PageRangeFormat -> PageRangeFormat -> Ordering)
-> (PageRangeFormat -> PageRangeFormat -> Bool)
-> (PageRangeFormat -> PageRangeFormat -> Bool)
-> (PageRangeFormat -> PageRangeFormat -> Bool)
-> (PageRangeFormat -> PageRangeFormat -> Bool)
-> (PageRangeFormat -> PageRangeFormat -> PageRangeFormat)
-> (PageRangeFormat -> PageRangeFormat -> PageRangeFormat)
-> Ord 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
$cp1Ord :: Eq PageRangeFormat
Ord)

data Style a =
  Style
  { Style a -> (Int, Int, Int)
styleCslVersion    :: (Int,Int,Int)
  , Style a -> StyleOptions
styleOptions       :: StyleOptions
  , Style a -> Layout a
styleCitation      :: Layout a
  , Style a -> Maybe (Layout a)
styleBibliography  :: Maybe (Layout a)
  , Style a -> [Locale]
styleLocales       :: [Locale]
  , Style a -> Maybe Abbreviations
styleAbbreviations :: Maybe Abbreviations
  } deriving (Int -> Style a -> ShowS
[Style a] -> ShowS
Style a -> String
(Int -> Style a -> ShowS)
-> (Style a -> String) -> ([Style a] -> ShowS) -> Show (Style a)
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
(Style a -> Style a -> Bool)
-> (Style a -> Style a -> Bool) -> Eq (Style a)
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)
-- Note: no macros section, because we
-- expand these after parsing the CSL.

data TermForm =
    Long
  | Short
  | Verb
  | VerbShort
  | Symbol
  deriving (Int -> TermForm -> ShowS
[TermForm] -> ShowS
TermForm -> String
(Int -> TermForm -> ShowS)
-> (TermForm -> String) -> ([TermForm] -> ShowS) -> Show TermForm
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
Eq TermForm
-> (TermForm -> TermForm -> Ordering)
-> (TermForm -> TermForm -> Bool)
-> (TermForm -> TermForm -> Bool)
-> (TermForm -> TermForm -> Bool)
-> (TermForm -> TermForm -> Bool)
-> (TermForm -> TermForm -> TermForm)
-> (TermForm -> TermForm -> TermForm)
-> Ord 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
$cp1Ord :: Eq TermForm
Ord, TermForm -> TermForm -> Bool
(TermForm -> TermForm -> Bool)
-> (TermForm -> TermForm -> Bool) -> Eq TermForm
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
(Int -> TermNumber -> ShowS)
-> (TermNumber -> String)
-> ([TermNumber] -> ShowS)
-> Show TermNumber
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
Eq TermNumber
-> (TermNumber -> TermNumber -> Ordering)
-> (TermNumber -> TermNumber -> Bool)
-> (TermNumber -> TermNumber -> Bool)
-> (TermNumber -> TermNumber -> Bool)
-> (TermNumber -> TermNumber -> Bool)
-> (TermNumber -> TermNumber -> TermNumber)
-> (TermNumber -> TermNumber -> TermNumber)
-> Ord 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
$cp1Ord :: Eq TermNumber
Ord, TermNumber -> TermNumber -> Bool
(TermNumber -> TermNumber -> Bool)
-> (TermNumber -> TermNumber -> Bool) -> Eq TermNumber
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
(Int -> TermGender -> ShowS)
-> (TermGender -> String)
-> ([TermGender] -> ShowS)
-> Show TermGender
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
Eq TermGender
-> (TermGender -> TermGender -> Ordering)
-> (TermGender -> TermGender -> Bool)
-> (TermGender -> TermGender -> Bool)
-> (TermGender -> TermGender -> Bool)
-> (TermGender -> TermGender -> Bool)
-> (TermGender -> TermGender -> TermGender)
-> (TermGender -> TermGender -> TermGender)
-> Ord 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
$cp1Ord :: Eq TermGender
Ord, TermGender -> TermGender -> Bool
(TermGender -> TermGender -> Bool)
-> (TermGender -> TermGender -> Bool) -> Eq TermGender
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
(Int -> TermMatch -> ShowS)
-> (TermMatch -> String)
-> ([TermMatch] -> ShowS)
-> Show TermMatch
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
Eq TermMatch
-> (TermMatch -> TermMatch -> Ordering)
-> (TermMatch -> TermMatch -> Bool)
-> (TermMatch -> TermMatch -> Bool)
-> (TermMatch -> TermMatch -> Bool)
-> (TermMatch -> TermMatch -> Bool)
-> (TermMatch -> TermMatch -> TermMatch)
-> (TermMatch -> TermMatch -> TermMatch)
-> Ord 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
$cp1Ord :: Eq TermMatch
Ord, TermMatch -> TermMatch -> Bool
(TermMatch -> TermMatch -> Bool)
-> (TermMatch -> TermMatch -> Bool) -> Eq TermMatch
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
(Int -> Term -> ShowS)
-> (Term -> String) -> ([Term] -> ShowS) -> Show Term
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
(Term -> Term -> Bool) -> (Term -> Term -> Bool) -> Eq Term
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 Text
forall a. Monoid a => a
mempty TermForm
Long Maybe TermNumber
forall a. Maybe a
Nothing Maybe TermGender
forall a. Maybe a
Nothing Maybe TermGender
forall a. Maybe a
Nothing Maybe TermMatch
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 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
name2 Bool -> Bool -> Bool
&&
     TermForm
form1 TermForm -> TermForm -> Bool
forall a. Eq a => a -> a -> Bool
== TermForm
form2 Bool -> Bool -> Bool
&&
     (Maybe TermNumber -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermNumber
num1   Bool -> Bool -> Bool
|| Maybe TermNumber -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermNumber
num2   Bool -> Bool -> Bool
|| Maybe TermNumber
num1 Maybe TermNumber -> Maybe TermNumber -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe TermNumber
num2) Bool -> Bool -> Bool
&&
     (Maybe TermGender -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermGender
gen1   Bool -> Bool -> Bool
|| Maybe TermGender -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermGender
gen2   Bool -> Bool -> Bool
|| Maybe TermGender
gen1 Maybe TermGender -> Maybe TermGender -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe TermGender
gen2) Bool -> Bool -> Bool
&&
     (Maybe TermGender -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermGender
gf1    Bool -> Bool -> Bool
|| Maybe TermGender -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermGender
gf2    Bool -> Bool -> Bool
|| Maybe TermGender
gf1  Maybe TermGender -> Maybe TermGender -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe TermGender
gf2 ) Bool -> Bool -> Bool
&&
     (Maybe TermMatch -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermMatch
match1 Bool -> Bool -> Bool
|| Maybe TermMatch -> Bool
forall a. Maybe a -> Bool
isNothing Maybe TermMatch
match2 Bool -> Bool -> Bool
|| Maybe TermMatch
match1 Maybe TermMatch -> Maybe TermMatch -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe TermMatch
match2)

-- | Defines locale-specific terms, punctuation styles, and date
-- formats.
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
(Int -> Locale -> ShowS)
-> (Locale -> String) -> ([Locale] -> ShowS) -> Show Locale
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
(Locale -> Locale -> Bool)
-> (Locale -> Locale -> Bool) -> Eq Locale
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)

-- in x <> y, x values take precedence
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 Maybe Lang -> Maybe Lang -> Maybe Lang
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Lang
lang2)
          (Maybe Bool
pq1 Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Bool
pq2)
          (Maybe Bool
ldo1 Maybe Bool -> Maybe Bool -> Maybe Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Bool
ldo2)
          (Map DateType (Element Text)
date1 Map DateType (Element Text)
-> Map DateType (Element Text) -> Map DateType (Element Text)
forall a. Semigroup a => a -> a -> a
<> Map DateType (Element Text)
date2)
          (([(Term, Text)] -> [(Term, Text)] -> [(Term, Text)])
-> Map Text [(Term, Text)]
-> Map Text [(Term, Text)]
-> Map Text [(Term, Text)]
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
M.unionWith [(Term, Text)] -> [(Term, Text)] -> [(Term, Text)]
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 Maybe Lang
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Map DateType (Element Text)
forall a. Monoid a => a
mempty Map Text [(Term, Text)]
forall a. Monoid a => a
mempty
 mappend :: Locale -> Locale -> Locale
mappend = Locale -> Locale -> Locale
forall a. Semigroup a => a -> a -> a
(<>)

newtype Variable = Variable (CI.CI Text)
  deriving (Int -> Variable -> ShowS
[Variable] -> ShowS
Variable -> String
(Int -> Variable -> ShowS)
-> (Variable -> String) -> ([Variable] -> ShowS) -> Show Variable
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
Eq Variable
-> (Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord 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
$cp1Ord :: Eq Variable
Ord, Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
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
(String -> Variable) -> IsString 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 (CI Text -> Variable) -> (Text -> CI Text) -> Text -> Variable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CI Text
forall s. FoldCase s => s -> CI s
CI.mk

fromVariable :: Variable -> Text
fromVariable :: Variable -> Text
fromVariable (Variable CI Text
x) = CI Text -> Text
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 CI Text -> CI Text -> CI Text
forall a. Semigroup a => a -> a -> a
<> CI Text
y)

instance Monoid Variable where
  mappend :: Variable -> Variable -> Variable
mappend = Variable -> Variable -> Variable
forall a. Semigroup a => a -> a -> a
(<>)
  mempty :: Variable
mempty = CI Text -> Variable
Variable CI Text
forall a. Monoid a => a
mempty

instance FromJSON Variable where
  parseJSON :: Value -> Parser Variable
parseJSON = (Text -> Variable) -> Parser Text -> Parser Variable
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (CI Text -> Variable
Variable (CI Text -> Variable) -> (Text -> CI Text) -> Text -> Variable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CI Text
forall s. FoldCase s => s -> CI s
CI.mk) (Parser Text -> Parser Variable)
-> (Value -> Parser Text) -> Value -> Parser Variable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON

instance FromJSONKey Variable where
  fromJSONKey :: FromJSONKeyFunction Variable
fromJSONKey = (Text -> Variable) -> FromJSONKeyFunction Variable
forall a. (Text -> a) -> FromJSONKeyFunction a
FromJSONKeyText Text -> Variable
toVariable

instance ToJSON Variable where
  toJSON :: Variable -> Value
toJSON (Variable CI Text
v) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ CI Text -> Text
forall s. CI s -> s
CI.original CI Text
v

instance ToJSONKey Variable where
  toJSONKey :: ToJSONKeyFunction Variable
toJSONKey = (Variable -> Text) -> ToJSONKeyFunction Variable
forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText Variable -> Text
fromVariable

-- | Encodes bibliographic data for a single work.
data Reference a =
  Reference
  { Reference a -> ItemId
referenceId             :: ItemId
  , Reference a -> Text
referenceType           :: Text
  , Reference a -> Maybe DisambiguationData
referenceDisambiguation :: Maybe DisambiguationData
           -- ^ This is added in processing; if you are constructing
           -- a Reference, set to Nothing
  , Reference a -> Map Variable (Val a)
referenceVariables      :: M.Map Variable (Val a)
  } deriving (Int -> Reference a -> ShowS
[Reference a] -> ShowS
Reference a -> String
(Int -> Reference a -> ShowS)
-> (Reference a -> String)
-> ([Reference a] -> ShowS)
-> Show (Reference a)
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, a -> Reference b -> Reference a
(a -> b) -> Reference a -> Reference b
(forall a b. (a -> b) -> Reference a -> Reference b)
-> (forall a b. a -> Reference b -> Reference a)
-> Functor Reference
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
<$ :: a -> Reference b -> Reference a
$c<$ :: forall a b. a -> Reference b -> Reference a
fmap :: (a -> b) -> Reference a -> Reference b
$cfmap :: forall a b. (a -> b) -> Reference a -> Reference b
Functor, Reference a -> Bool
(a -> m) -> Reference a -> m
(a -> b -> b) -> b -> Reference a -> b
(forall m. Monoid m => Reference m -> m)
-> (forall m a. Monoid m => (a -> m) -> Reference a -> m)
-> (forall m a. Monoid m => (a -> m) -> Reference a -> m)
-> (forall a b. (a -> b -> b) -> b -> Reference a -> b)
-> (forall a b. (a -> b -> b) -> b -> Reference a -> b)
-> (forall b a. (b -> a -> b) -> b -> Reference a -> b)
-> (forall b a. (b -> a -> b) -> b -> Reference a -> b)
-> (forall a. (a -> a -> a) -> Reference a -> a)
-> (forall a. (a -> a -> a) -> Reference a -> a)
-> (forall a. Reference a -> [a])
-> (forall a. Reference a -> Bool)
-> (forall a. Reference a -> Int)
-> (forall a. Eq a => a -> Reference a -> Bool)
-> (forall a. Ord a => Reference a -> a)
-> (forall a. Ord a => Reference a -> a)
-> (forall a. Num a => Reference a -> a)
-> (forall a. Num a => Reference a -> a)
-> Foldable Reference
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 :: Reference a -> a
$cproduct :: forall a. Num a => Reference a -> a
sum :: Reference a -> a
$csum :: forall a. Num a => Reference a -> a
minimum :: Reference a -> a
$cminimum :: forall a. Ord a => Reference a -> a
maximum :: Reference a -> a
$cmaximum :: forall a. Ord a => Reference a -> a
elem :: a -> Reference a -> Bool
$celem :: forall a. Eq a => a -> Reference a -> Bool
length :: Reference a -> Int
$clength :: forall a. Reference a -> Int
null :: Reference a -> Bool
$cnull :: forall a. Reference a -> Bool
toList :: Reference a -> [a]
$ctoList :: forall a. Reference a -> [a]
foldl1 :: (a -> a -> a) -> Reference a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Reference a -> a
foldr1 :: (a -> a -> a) -> Reference a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Reference a -> a
foldl' :: (b -> a -> b) -> b -> Reference a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Reference a -> b
foldl :: (b -> a -> b) -> b -> Reference a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Reference a -> b
foldr' :: (a -> b -> b) -> b -> Reference a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Reference a -> b
foldr :: (a -> b -> b) -> b -> Reference a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Reference a -> b
foldMap' :: (a -> m) -> Reference a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Reference a -> m
foldMap :: (a -> m) -> Reference a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Reference a -> m
fold :: Reference m -> m
$cfold :: forall m. Monoid m => Reference m -> m
Foldable, Functor Reference
Foldable Reference
Functor Reference
-> Foldable Reference
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Reference a -> f (Reference b))
-> (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 (m :: * -> *) a.
    Monad m =>
    Reference (m a) -> m (Reference a))
-> Traversable Reference
(a -> f b) -> Reference a -> f (Reference b)
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 :: Reference (m a) -> m (Reference a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
Reference (m a) -> m (Reference a)
mapM :: (a -> m b) -> Reference a -> m (Reference b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Reference a -> m (Reference b)
sequenceA :: Reference (f a) -> f (Reference a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Reference (f a) -> f (Reference a)
traverse :: (a -> f b) -> Reference a -> f (Reference b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Reference a -> f (Reference b)
$cp2Traversable :: Foldable Reference
$cp1Traversable :: Functor Reference
Traversable)

instance ToJSON a => ToJSON (Reference a) where
  toJSON :: Reference a -> Value
toJSON Reference a
r = Map Variable (Val a) -> Value
forall a. ToJSON a => a -> Value
toJSON (Map Variable (Val a) -> Value) -> Map Variable (Val a) -> Value
forall a b. (a -> b) -> a -> b
$
               Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"id" (Text -> Val a
forall a. Text -> Val a
TextVal (Text -> Val a) -> Text -> Val a
forall a b. (a -> b) -> a -> b
$ ItemId -> Text
coerce (Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
r)) (Map Variable (Val a) -> Map Variable (Val a))
-> Map Variable (Val a) -> Map Variable (Val a)
forall a b. (a -> b) -> a -> b
$
               Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"type" (Text -> Val a
forall a. Text -> Val a
TextVal (Text -> Val a) -> Text -> Val a
forall a b. (a -> b) -> a -> b
$ Reference a -> Text
forall a. Reference a -> Text
referenceType Reference a
r) (Map Variable (Val a) -> Map Variable (Val a))
-> Map Variable (Val a) -> Map Variable (Val a)
forall a b. (a -> b) -> a -> b
$
               Reference a -> Map Variable (Val a)
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
(Int -> DisambiguationData -> ShowS)
-> (DisambiguationData -> String)
-> ([DisambiguationData] -> ShowS)
-> Show DisambiguationData
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)

data NameHints =
    AddInitials
  | AddGivenName
  | AddInitialsIfPrimary
  | AddGivenNameIfPrimary
  deriving (Int -> NameHints -> ShowS
[NameHints] -> ShowS
NameHints -> String
(Int -> NameHints -> ShowS)
-> (NameHints -> String)
-> ([NameHints] -> ShowS)
-> Show NameHints
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)

instance (Eq a, FromJSON a)  => FromJSON (Reference a) where
  parseJSON :: Value -> Parser (Reference a)
parseJSON Value
v = Value -> Parser (Map Variable Value)
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Map Variable Value)
-> (Map Variable Value -> Parser (Reference a))
-> Parser (Reference a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Map Variable Value -> Parser (Reference a)
forall a. FromJSON a => Map Variable Value -> Parser (Reference a)
parseReference

lookupVariable :: CiteprocOutput a => Variable -> Reference a -> Maybe (Val a)
lookupVariable :: Variable -> Reference a -> Maybe (Val a)
lookupVariable Variable
"id" Reference a
r =
  case Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
r of
    ItemId Text
"" -> Maybe (Val a)
forall a. Maybe a
Nothing
    ItemId Text
t  -> Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just (Text -> Val a
forall a. Text -> Val a
TextVal Text
t)
lookupVariable Variable
"type" Reference a
r =
  case Reference a -> Text
forall a. Reference a -> Text
referenceType Reference a
r of
    Text
"" -> Maybe (Val a)
forall a. Maybe a
Nothing
    Text
t  -> Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just (Text -> Val a
forall a. Text -> Val a
TextVal Text
t)
lookupVariable Variable
"page-first" Reference a
r =  -- compute "page-first" if not set
  Variable -> Map Variable (Val a) -> Maybe (Val a)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"page-first" (Reference a -> Map Variable (Val a)
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r) Maybe (Val a) -> Maybe (Val a) -> Maybe (Val a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    case Variable -> Map Variable (Val a) -> Maybe (Val a)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"pages" (Reference a -> Map Variable (Val a)
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r) of
      Maybe (Val a)
Nothing           -> Maybe (Val a)
forall a. Maybe a
Nothing
      Just (NumVal Int
n)   -> Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just (Int -> Val a
forall a. Int -> Val a
NumVal Int
n)
      Just (TextVal Text
t)  -> Int -> Val a
forall a. Int -> Val a
NumVal (Int -> Val a) -> Maybe Int -> Maybe (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Int
forall a. Read a => String -> Maybe a
readMay (Text -> String
T.unpack (Text -> Text
takeDigits Text
t))
      Just (FancyVal a
x) -> Int -> Val a
forall a. Int -> Val a
NumVal (Int -> Val a) -> Maybe Int -> Maybe (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Maybe Int
forall a. Read a => String -> Maybe a
readMay (Text -> String
T.unpack
                                           (Text -> Text
takeDigits (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x))
      Maybe (Val a)
_                 -> 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 = Variable -> Map Variable (Val a) -> Maybe (Val a)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
v (Map Variable (Val a) -> Maybe (Val a))
-> Map Variable (Val a) -> Maybe (Val a)
forall a b. (a -> b) -> a -> b
$ Reference a -> Map Variable (Val a)
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference a
r

parseReference :: FromJSON a
               => M.Map Variable Value -> Parser (Reference a)
parseReference :: Map Variable Value -> Parser (Reference a)
parseReference Map Variable Value
rawmap =
  (Reference a -> (Variable, Value) -> Parser (Reference a))
-> Reference a -> [(Variable, Value)] -> Parser (Reference a)
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)
forall a.
FromJSON a =>
Reference a -> (Variable, Value) -> Parser (Reference a)
go (ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
forall a. Monoid a => a
mempty Text
forall a. Monoid a => a
mempty Maybe DisambiguationData
forall a. Maybe a
Nothing Map Variable (Val a)
forall a. Monoid a => a
mempty) (Map Variable Value -> [(Variable, Value)]
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 Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
"id"   = do
        ItemId
id' <- Text -> ItemId
ItemId (Text -> ItemId) -> Parser Text -> Parser ItemId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
        Reference a -> Parser (Reference a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Reference a -> Parser (Reference a))
-> Reference a -> Parser (Reference a)
forall a b. (a -> b) -> a -> b
$ ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
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 Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
"type" = do
        Text
type' <- Value -> Parser Text
readString Value
v
        Reference a -> Parser (Reference a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Reference a -> Parser (Reference a))
-> Reference a -> Parser (Reference a)
forall a b. (a -> b) -> a -> b
$ ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
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 Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
"journalAbbreviation" Bool -> Bool -> Bool
|| Variable
k Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
"shortTitle" = -- legacy citeproc-js
      Reference a -> (Variable, Value) -> Parser (Reference a)
go (ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
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 Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
"note" = do
        Text
t' <- Value -> Parser Text
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 Reference a -> Reference a
forall a. a -> a
id
                else \(Reference ItemId
i' Text
t'' Maybe DisambiguationData
d' Map Variable (Val a)
m') ->
                       ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i' Text
t'' Maybe DisambiguationData
d' (Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
"note" (Text -> Val a
forall a. Text -> Val a
TextVal Text
rest) Map Variable (Val a)
m'))
             (Reference a -> Reference a)
-> Parser (Reference a) -> Parser (Reference a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Reference a -> (Variable, Value) -> Parser (Reference a))
-> Reference a -> [(Variable, Value)] -> Parser (Reference a)
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 (ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
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   = ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
forall a.
ItemId
-> Text
-> Maybe DisambiguationData
-> Map Variable (Val a)
-> Reference a
Reference ItemId
i Text
t Maybe DisambiguationData
d (Map Variable (Val a) -> Reference a)
-> Parser (Map Variable (Val a)) -> Parser (Reference a)
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' <- a -> Val a
forall a. a -> Val a
FancyVal (a -> Val a) -> Parser a -> Parser (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Val a) -> Parser (Val a) -> Parser (Val a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Val a
forall a. Text -> Val a
TextVal (Text -> Val a) -> Parser Text -> Parser (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
            Map Variable (Val a) -> Parser (Map Variable (Val a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Variable (Val a) -> Parser (Map Variable (Val a)))
-> Map Variable (Val a) -> Parser (Map Variable (Val a))
forall a b. (a -> b) -> a -> b
$ Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
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{} -> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
                    Number{} -> String -> Text
T.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> Text) -> Parser Int -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v :: Parser Int)
                    Value
_        -> String -> Value -> Parser Text
forall a. String -> Value -> Parser a
typeMismatch String
"String or Number" Value
v
            Map Variable (Val a) -> Parser (Map Variable (Val a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Variable (Val a) -> Parser (Map Variable (Val a)))
-> Map Variable (Val a) -> Parser (Map Variable (Val a))
forall a b. (a -> b) -> a -> b
$ Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (Text -> Val a
forall a. Text -> Val a
TextVal Text
v') Map Variable (Val a)
m
          VariableType
DateVariable -> do
            Date
v' <- Value -> Parser Date
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
            Map Variable (Val a) -> Parser (Map Variable (Val a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Variable (Val a) -> Parser (Map Variable (Val a)))
-> Map Variable (Val a) -> Parser (Map Variable (Val a))
forall a b. (a -> b) -> a -> b
$ Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (Date -> Val a
forall a. Date -> Val a
DateVal Date
v') Map Variable (Val a)
m
          VariableType
NameVariable -> do
            [Name]
v' <- Value -> Parser [Name]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
            Map Variable (Val a) -> Parser (Map Variable (Val a))
forall (m :: * -> *) a. Monad m => a -> m a
return (Map Variable (Val a) -> Parser (Map Variable (Val a)))
-> Map Variable (Val a) -> Parser (Map Variable (Val a))
forall a b. (a -> b) -> a -> b
$ Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k ([Name] -> Val a
forall a. [Name] -> Val a
NamesVal [Name]
v') Map Variable (Val a)
m
          VariableType
UnknownVariable -> -- treat as string variable if possible
            case Value
v of
              String{}  -> (\Val a
x -> Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
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) (Val a -> Map Variable (Val a))
-> Parser (Val a) -> Parser (Map Variable (Val a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                    (a -> Val a
forall a. a -> Val a
FancyVal (a -> Val a) -> Parser a -> Parser (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (Val a) -> Parser (Val a) -> Parser (Val a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Val a
forall a. Text -> Val a
TextVal (Text -> Val a) -> Parser Text -> Parser (Val a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v)
              Number{}  -> (\Text
x -> Variable -> Val a -> Map Variable (Val a) -> Map Variable (Val a)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Variable
k (Text -> Val a
forall a. Text -> Val a
TextVal Text
x) Map Variable (Val a)
m) (Text -> Map Variable (Val a))
-> Parser Text -> Parser (Map Variable (Val a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
readString Value
v
              Value
_         -> Map Variable (Val a) -> Parser (Map Variable (Val a))
forall (m :: * -> *) a. Monad m => a -> m a
return Map Variable (Val a)
m -- silently ignore
  readString :: Value -> Parser Text
readString Value
v =
    case Value
v of
       String{} -> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
       Number{} -> String -> Text
T.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> Text) -> Parser Int -> Parser Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v :: Parser Int)
       Value
_        -> String -> Value -> Parser Text
forall a. String -> Value -> Parser a
typeMismatch String
"String or Number" Value
v

-- name variables are cumulative and should be packed into an array
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
                 ([Value] -> Array
forall a. [a] -> Vector a
V.fromList [Text -> Value
String Text
t | (Variable
k',Text
t) <- (Variable
k,Text
v)(Variable, Text) -> [(Variable, Text)] -> [(Variable, Text)]
forall a. a -> [a] -> [a]
:[(Variable, Text)]
kvs, Variable
k' Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
== Variable
k])) (Variable, Value) -> [(Variable, Value)] -> [(Variable, Value)]
forall a. a -> [a] -> [a]
:
            [(Variable, Text)] -> [(Variable, Value)]
consolidateNameVariables (((Variable, Text) -> Bool)
-> [(Variable, Text)] -> [(Variable, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Variable -> Variable -> Bool
forall a. Eq a => a -> a -> Bool
/= Variable
k) (Variable -> Bool)
-> ((Variable, Text) -> Variable) -> (Variable, Text) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Variable, Text) -> Variable
forall a b. (a, b) -> a
fst) [(Variable, Text)]
kvs)
      VariableType
_ -> (Variable
k, Text -> Value
String Text
v) (Variable, Value) -> [(Variable, Value)] -> [(Variable, Value)]
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 =
  (String -> ([(Variable, Text)], Text))
-> (([(Variable, Text)], Text) -> ([(Variable, Text)], Text))
-> Either String ([(Variable, Text)], Text)
-> ([(Variable, Text)], Text)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (([(Variable, Text)], Text) -> String -> ([(Variable, Text)], Text)
forall a b. a -> b -> a
const ([],Text
t)) ([(Variable, Text)], Text) -> ([(Variable, Text)], Text)
forall a. a -> a
id (Either String ([(Variable, Text)], Text)
 -> ([(Variable, Text)], Text))
-> Either String ([(Variable, Text)], Text)
-> ([(Variable, Text)], Text)
forall a b. (a -> b) -> a -> b
$
    Parser ([(Variable, Text)], Text)
-> Text -> Either String ([(Variable, Text)], Text)
forall a. Parser a -> Text -> Either String a
P.parseOnly ((,) ([(Variable, Text)] -> Text -> ([(Variable, Text)], Text))
-> Parser Text [(Variable, Text)]
-> Parser Text (Text -> ([(Variable, Text)], Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text (Variable, Text) -> Parser Text [(Variable, Text)]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
P.many' Parser Text (Variable, Text)
pNoteField Parser Text (Text -> ([(Variable, Text)], Text))
-> Parser Text Text -> Parser ([(Variable, Text)], Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Text Text
P.takeText) Text
t
 where
  pNoteField :: Parser Text (Variable, Text)
pNoteField = Parser Text (Variable, Text)
pBracedField Parser Text (Variable, Text)
-> Parser Text (Variable, Text) -> Parser Text (Variable, Text)
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 Text
pVarname
    Char
_ <- Char -> Parser Char
P.char Char
':'
    Text
val <- (Char -> Bool) -> Parser Text Text
P.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'\n')
    () () -> Parser Char -> Parser Text ()
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Parser Char
P.char Char
'\n' Parser Text () -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser Text ()
forall t. Chunk t => Parser t ()
P.endOfInput
    (Variable, Text) -> Parser Text (Variable, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (CI Text -> Variable
Variable (CI Text -> Variable) -> CI Text -> Variable
forall a b. (a -> b) -> a -> b
$ Text -> CI Text
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 Text
P.string Text
"{:"
    Text
name <- Parser Text Text
pVarname
    Char
_ <- Char -> Parser Char
P.char Char
':'
    Text
val <- (Char -> Bool) -> Parser Text Text
P.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'}')
    Char
_ <- Char -> Parser Char
P.char Char
'}'
    (Variable, Text) -> Parser Text (Variable, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (CI Text -> Variable
Variable (CI Text -> Variable) -> CI Text -> Variable
forall a b. (a -> b) -> a -> b
$ Text -> CI Text
forall s. FoldCase s => s -> CI s
CI.mk Text
name, Text -> Text
T.strip Text
val)
  pVarname :: Parser Text Text
pVarname = (Char -> Bool) -> Parser Text Text
P.takeWhile1 (\Char
c -> Char -> Bool
isLetter Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')

data VariableType =
    DateVariable
  | NameVariable
  | NumberVariable
  | StringVariable
  | UnknownVariable
  deriving (Int -> VariableType -> ShowS
[VariableType] -> ShowS
VariableType -> String
(Int -> VariableType -> ShowS)
-> (VariableType -> String)
-> ([VariableType] -> ShowS)
-> Show VariableType
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
(VariableType -> VariableType -> Bool)
-> (VariableType -> VariableType -> Bool) -> Eq VariableType
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 --(new name for "event" to avoid confusion with new "event" type) 
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 { ReferenceMap a -> Map ItemId (Reference a)
unReferenceMap :: M.Map ItemId (Reference a) }
  deriving (Int -> ReferenceMap a -> ShowS
[ReferenceMap a] -> ShowS
ReferenceMap a -> String
(Int -> ReferenceMap a -> ShowS)
-> (ReferenceMap a -> String)
-> ([ReferenceMap a] -> ShowS)
-> Show (ReferenceMap a)
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)

-- | Returns a pair consisting of the cleaned up list of
-- references and a reference map.  If the original reference
-- list contains items with the same id, then the one that
-- occurs last in the list is retained, and the others are
-- omittedfrom the cleaned-up list.
makeReferenceMap :: [Reference a] -> ([Reference a], ReferenceMap a)
makeReferenceMap :: [Reference a] -> ([Reference a], ReferenceMap a)
makeReferenceMap = (Set ItemId, ([Reference a], ReferenceMap a))
-> ([Reference a], ReferenceMap a)
forall a b. (a, b) -> b
snd ((Set ItemId, ([Reference a], ReferenceMap a))
 -> ([Reference a], ReferenceMap a))
-> ([Reference a] -> (Set ItemId, ([Reference a], ReferenceMap a)))
-> [Reference a]
-> ([Reference a], ReferenceMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Reference a
 -> (Set ItemId, ([Reference a], ReferenceMap a))
 -> (Set ItemId, ([Reference a], ReferenceMap a)))
-> (Set ItemId, ([Reference a], ReferenceMap a))
-> [Reference a]
-> (Set ItemId, ([Reference a], ReferenceMap a))
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Reference a
-> (Set ItemId, ([Reference a], ReferenceMap a))
-> (Set ItemId, ([Reference a], ReferenceMap a))
forall a.
Reference a
-> (Set ItemId, ([Reference a], ReferenceMap a))
-> (Set ItemId, ([Reference a], ReferenceMap a))
go (Set ItemId
forall a. Monoid a => a
mempty, ([], Map ItemId (Reference a) -> ReferenceMap a
forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap Map ItemId (Reference a)
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 = Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
ref
      in if ItemId -> Set ItemId -> Bool
forall a. Ord a => a -> Set a -> Bool
Set.member ItemId
rid Set ItemId
ids
            then (Set ItemId
ids, ([Reference a]
rs, Map ItemId (Reference a) -> ReferenceMap a
forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap Map ItemId (Reference a)
refmap))
            else (ItemId -> Set ItemId -> Set ItemId
forall a. Ord a => a -> Set a -> Set a
Set.insert ItemId
rid Set ItemId
ids,
                   (Reference a
refReference a -> [Reference a] -> [Reference a]
forall a. a -> [a] -> [a]
:[Reference a]
rs, Map ItemId (Reference a) -> ReferenceMap a
forall a. Map ItemId (Reference a) -> ReferenceMap a
ReferenceMap (ItemId
-> Reference a
-> Map ItemId (Reference a)
-> Map ItemId (Reference a)
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 :: ItemId -> ReferenceMap a -> Maybe (Reference a)
lookupReference ItemId
ident (ReferenceMap Map ItemId (Reference a)
m) = ItemId -> Map ItemId (Reference a) -> Maybe (Reference a)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup ItemId
ident Map ItemId (Reference a)
m

-- | Value associated with a certain variable in a bibliographic
-- entry.
data Val a =
    TextVal Text      -- ^ Plain text value
  | FancyVal a        -- ^ Formatted value with parameterized type
  | NumVal  Int       -- ^ Numerical value
  | NamesVal [Name]    -- ^ Structured names
  | DateVal Date       -- ^ Structured date
  deriving (Int -> Val a -> ShowS
[Val a] -> ShowS
Val a -> String
(Int -> Val a -> ShowS)
-> (Val a -> String) -> ([Val a] -> ShowS) -> Show (Val a)
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 -> Bool
(Val a -> Val a -> Bool) -> (Val a -> Val a -> Bool) -> Eq (Val a)
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, a -> Val b -> Val a
(a -> b) -> Val a -> Val b
(forall a b. (a -> b) -> Val a -> Val b)
-> (forall a b. a -> Val b -> Val a) -> Functor Val
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
<$ :: a -> Val b -> Val a
$c<$ :: forall a b. a -> Val b -> Val a
fmap :: (a -> b) -> Val a -> Val b
$cfmap :: forall a b. (a -> b) -> Val a -> Val b
Functor, Val a -> Bool
(a -> m) -> Val a -> m
(a -> b -> b) -> b -> Val a -> b
(forall m. Monoid m => Val m -> m)
-> (forall m a. Monoid m => (a -> m) -> Val a -> m)
-> (forall m a. Monoid m => (a -> m) -> Val a -> m)
-> (forall a b. (a -> b -> b) -> b -> Val a -> b)
-> (forall a b. (a -> b -> b) -> b -> Val a -> b)
-> (forall b a. (b -> a -> b) -> b -> Val a -> b)
-> (forall b a. (b -> a -> b) -> b -> Val a -> b)
-> (forall a. (a -> a -> a) -> Val a -> a)
-> (forall a. (a -> a -> a) -> Val a -> a)
-> (forall a. Val a -> [a])
-> (forall a. Val a -> Bool)
-> (forall a. Val a -> Int)
-> (forall a. Eq a => a -> Val a -> Bool)
-> (forall a. Ord a => Val a -> a)
-> (forall a. Ord a => Val a -> a)
-> (forall a. Num a => Val a -> a)
-> (forall a. Num a => Val a -> a)
-> Foldable Val
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 :: Val a -> a
$cproduct :: forall a. Num a => Val a -> a
sum :: Val a -> a
$csum :: forall a. Num a => Val a -> a
minimum :: Val a -> a
$cminimum :: forall a. Ord a => Val a -> a
maximum :: Val a -> a
$cmaximum :: forall a. Ord a => Val a -> a
elem :: a -> Val a -> Bool
$celem :: forall a. Eq a => a -> Val a -> Bool
length :: Val a -> Int
$clength :: forall a. Val a -> Int
null :: Val a -> Bool
$cnull :: forall a. Val a -> Bool
toList :: Val a -> [a]
$ctoList :: forall a. Val a -> [a]
foldl1 :: (a -> a -> a) -> Val a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Val a -> a
foldr1 :: (a -> a -> a) -> Val a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Val a -> a
foldl' :: (b -> a -> b) -> b -> Val a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Val a -> b
foldl :: (b -> a -> b) -> b -> Val a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Val a -> b
foldr' :: (a -> b -> b) -> b -> Val a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Val a -> b
foldr :: (a -> b -> b) -> b -> Val a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Val a -> b
foldMap' :: (a -> m) -> Val a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Val a -> m
foldMap :: (a -> m) -> Val a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Val a -> m
fold :: Val m -> m
$cfold :: forall m. Monoid m => Val m -> m
Foldable, Functor Val
Foldable Val
Functor Val
-> Foldable Val
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Val a -> f (Val b))
-> (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 (m :: * -> *) a. Monad m => Val (m a) -> m (Val a))
-> Traversable Val
(a -> f b) -> Val a -> f (Val b)
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 :: Val (m a) -> m (Val a)
$csequence :: forall (m :: * -> *) a. Monad m => Val (m a) -> m (Val a)
mapM :: (a -> m b) -> Val a -> m (Val b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Val a -> m (Val b)
sequenceA :: Val (f a) -> f (Val a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Val (f a) -> f (Val a)
traverse :: (a -> f b) -> Val a -> f (Val b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Val a -> f (Val b)
$cp2Traversable :: Foldable Val
$cp1Traversable :: Functor Val
Traversable)

instance ToJSON a => ToJSON (Val a) where
  toJSON :: Val a -> Value
toJSON (TextVal Text
t) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
  toJSON (FancyVal a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x
  toJSON (NumVal Int
n) = Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
n
  toJSON (NamesVal [Name]
ns) = [Name] -> Value
forall a. ToJSON a => a -> Value
toJSON [Name]
ns
  toJSON (DateVal Date
d) = Date -> Value
forall a. ToJSON a => a -> Value
toJSON Date
d

valToText :: CiteprocOutput a => Val a -> Maybe Text
valToText :: Val a -> Maybe Text
valToText (TextVal Text
x)  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
x
valToText (FancyVal a
x) = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x
valToText (NumVal Int
n)   = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
n
valToText Val a
_            = Maybe Text
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
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
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
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
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
Eq Name
-> (Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord 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
$cp1Ord :: Eq Name
Ord)

instance ToJSON Name where
  toJSON :: Name -> Value
toJSON Name
n =
    [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"family", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameFamily Name
n) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"given", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameGiven Name
n) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"dropping-particle", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:))
         (Name -> Maybe Text
nameDroppingParticle Name
n) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"non-dropping-particle", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:))
         (Name -> Maybe Text
nameNonDroppingParticle Name
n) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"suffix", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameSuffix Name
n) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      (if Name -> Bool
nameCommaSuffix Name
n
          then ((Text
"comma-suffix", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)
          else [Pair] -> [Pair]
forall a. a -> a
id) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      (if Name -> Bool
nameStaticOrdering Name
n
          then ((Text
"static-ordering", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)
          else [Pair] -> [Pair]
forall a. a -> a
id) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      ([Pair] -> [Pair])
-> (Text -> [Pair] -> [Pair]) -> Maybe Text -> [Pair] -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Pair] -> [Pair]
forall a. a -> a
id (\Text
x -> ((Text
"literal", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
x)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)) (Name -> Maybe Text
nameLiteral Name
n) ([Pair] -> [Pair]) -> [Pair] -> [Pair]
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 (Name -> Name) -> Parser Name -> Parser Name
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
     (String -> (Object -> Parser Name) -> Value -> Parser Name
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Name" ((Object -> Parser Name) -> Value -> Parser Name)
-> (Object -> Parser Name) -> Value -> Parser 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
      (Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Bool
 -> Bool
 -> Maybe Text
 -> Name)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Bool
      -> Bool
      -> Maybe Text
      -> Name)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"family")
      Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Bool
   -> Bool
   -> Maybe Text
   -> Name)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text -> Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"given")
      Parser
  (Maybe Text
   -> Maybe Text -> Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text -> Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"dropping-particle")
      Parser
  (Maybe Text -> Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
-> Parser (Maybe Text)
-> Parser (Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"non-dropping-particle")
      Parser (Maybe Text -> Bool -> Bool -> Maybe Text -> Name)
-> Parser (Maybe Text)
-> Parser (Bool -> Bool -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"suffix")
      Parser (Bool -> Bool -> Maybe Text -> Name)
-> Parser Bool -> Parser (Bool -> Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"comma-suffix" Parser (Maybe Value) -> (Maybe Value -> Parser Bool) -> Parser Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Parser Bool -> (Value -> Parser Bool) -> Maybe Value -> Parser Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> Parser Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Value -> Parser Bool
asBool)
      Parser (Bool -> Maybe Text -> Name)
-> Parser Bool -> Parser (Maybe Text -> Name)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Object
v Object -> Text -> Parser (Maybe Value)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"static-ordering" Parser (Maybe Value) -> (Maybe Value -> Parser Bool) -> Parser Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Parser Bool -> (Value -> Parser Bool) -> Maybe Value -> Parser Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> Parser Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False) Value -> Parser Bool
asBool)
      Parser (Maybe Text -> Name) -> Parser (Maybe Text) -> Parser Name
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Text
fixApos (Maybe Text -> Maybe Text)
-> Parser (Maybe Text) -> Parser (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"literal")
     ) Value
x

-- "lowercase elements before the family name are treated as “non-dropping”
-- particles, and lowercase elements following the given name as “dropping”
-- particles"
extractParticles :: Name -> Name
extractParticles :: Name -> Name
extractParticles =
  Name -> Name
extractNonDroppingParticle (Name -> Name) -> (Name -> Name) -> Name -> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name -> Name
extractDroppingParticle (Name -> Name) -> (Name -> Name) -> Name -> Name
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
            -- in CSL JSON you can put double quotes around something
            -- to make it a unit (not subject to splitting).
            | Text
"\"" Text -> Text -> Bool
`T.isPrefixOf` Text
t
            , Text
"\"" Text -> Text -> Bool
`T.isSuffixOf` Text
t
            -> Name
name { nameGiven :: Maybe Text
nameGiven = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> Text -> Text
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 (Char -> Char -> Bool
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 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
",!"
                        then Name
name{ nameGiven :: Maybe Text
nameGiven  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
a
                                 , nameSuffix :: Maybe Text
nameSuffix = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text) -> Text -> Text
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  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
a
                                 , nameSuffix :: Maybe Text
nameSuffix = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.strip (Text -> Text) -> Text -> Text
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 = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.drop Int
1 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.dropEnd Int
1 Text
t }
            | Bool
otherwise ->
              case (Text -> Bool) -> [Text] -> ([Text], [Text])
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 = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
y
                                  , nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
                                      Int -> Text -> Text
T.take Int
1
                                      ((Char -> Bool) -> Text -> Text
T.dropWhile (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
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 = Text -> Maybe Text
forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
bs)
                               , nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = Text -> Maybe Text
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 (Text -> Bool) -> [Text] -> ([Text], [Text])
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)
                | (Text -> Bool) -> [Text] -> Bool
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 = Text -> Maybe Text
forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
as)
                             , nameDroppingParticle :: Maybe Text
nameDroppingParticle = Text -> Maybe Text
forall a. a -> Maybe a
Just ([Text] -> Text
T.unwords [Text]
bs) }
                | Bool
otherwise -> Name
name
  isParticlePunct :: Char -> Bool
isParticlePunct Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\'' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'’' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\x2013' Bool -> Bool -> Bool
||
                      Char
c Char -> Char -> Bool
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

-- cheater syntax for name: used in parsing note:
--  editor: Thompson || Hunter S.
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]
_) -> (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
f), Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
g))
                           [Text
f]     -> (Text -> Maybe Text
forall a. a -> Maybe a
Just (Text -> Text
T.strip Text
f), Maybe Text
forall a. Maybe a
Nothing)
                           []      -> (Maybe Text
forall a. Maybe a
Nothing, Maybe Text
forall a. Maybe a
Nothing)
  Name -> Parser Name
forall (m :: * -> *) a. Monad m => a -> m a
return (Name -> Parser Name) -> Name -> Parser Name
forall a b. (a -> b) -> a -> b
$ Name -> Name
extractParticles (Name -> Name) -> Name -> Name
forall a b. (a -> b) -> a -> b
$
      Name :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Bool
-> Bool
-> Maybe Text
-> Name
Name
      { nameFamily :: Maybe Text
nameFamily              = Maybe Text
family
      , nameGiven :: Maybe Text
nameGiven               = Maybe Text
given
      , nameDroppingParticle :: Maybe Text
nameDroppingParticle    = Maybe Text
forall a. Maybe a
Nothing
      , nameNonDroppingParticle :: Maybe Text
nameNonDroppingParticle = Maybe Text
forall a. Maybe a
Nothing
      , nameSuffix :: Maybe Text
nameSuffix              = Maybe Text
forall a. Maybe a
Nothing
      , nameCommaSuffix :: Bool
nameCommaSuffix         = Bool
False
      , nameStaticOrdering :: Bool
nameStaticOrdering      = Bool
False
      , nameLiteral :: Maybe Text
nameLiteral             = if Maybe Text -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Text
family Bool -> Bool -> Bool
&& Maybe Text -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Text
given
                                     then Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
                                     else Maybe Text
forall a. Maybe a
Nothing
      }

isByzantineName :: Name -> Bool
isByzantineName :: Name -> Bool
isByzantineName Name
name = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Text -> Bool
isByzantine (Name -> Maybe Text
nameFamily Name
name)

-- detect latin/cyrillic names
-- see src/load.js ROMANESQUE_REGEX in citeproc-js:
-- /[-0-9a-zA-Z\u0e01-\u0e5b\u00c0-\u017f\u0370-\u03ff\u0400-\u052f\u0590-\u05d4\u05d6-\u05ff\u1f00-\u1fff\u0600-\u06ff\u200c\u200d\u200e\u0218\u0219\u021a\u021b\u202a-\u202e]/
isByzantineChar :: Char -> Bool
isByzantineChar :: Char -> Bool
isByzantineChar Char
c = Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'z') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'A' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'Z') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x0e01' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x0e5b') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x00c0' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x017f') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x0370' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x03ff') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x0400' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x052f') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x0590' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x05d4') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x05d6' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x05ff') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x1f00' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x1fff') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x0600' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x06ff') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x200c' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x200e') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x2018' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x2019') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x021a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x021b') Bool -> Bool -> Bool
||
                (Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'\x202a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
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) = Bool -> Parser Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Parser Bool) -> Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"true"
asBool (Bool Bool
b)   = Bool -> Parser Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
b
asBool (Number Scientific
n) = Bool -> Parser Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> Parser Bool) -> Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$ Scientific
n Scientific -> Scientific -> Bool
forall a. Eq a => a -> a -> Bool
== Scientific
1
asBool Value
x          = String -> Value -> Parser Bool
forall a. String -> Value -> Parser a
typeMismatch String
"Bool" Value
x

asText :: Value -> Parser Text
asText :: Value -> Parser Text
asText (String Text
t)   = Text -> Parser Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
t
asText (Number Scientific
n)   = Text -> Parser Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Parser Text) -> Text -> Parser Text
forall a b. (a -> b) -> a -> b
$ case Scientific -> Either Double Int
forall r i. (RealFloat r, Integral i) => Scientific -> Either r i
S.floatingOrInteger Scientific
n of
                                 Left Double
r -> String -> Text
T.pack (Double -> String
forall a. Show a => a -> String
show (Double
r :: Double))
                                 Right Int
i -> String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show (Int
i :: Int))
asText Value
x            = String -> Value -> Parser Text
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  -> Int -> Parser Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
x
    Maybe Int
Nothing -> String -> Parser Int
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"not a number"
asInt v :: Value
v@Number{} = Value -> Parser Int
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
asInt Value
v = String -> Value -> Parser Int
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
(Int -> Date -> ShowS)
-> (Date -> String) -> ([Date] -> ShowS) -> Show Date
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
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
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
Eq Date
-> (Date -> Date -> Ordering)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Bool)
-> (Date -> Date -> Date)
-> (Date -> Date -> Date)
-> Ord 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
$cp1Ord :: Eq Date
Ord)

instance ToJSON Date where
  toJSON :: Date -> Value
toJSON Date
d =
    [Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
      (if Date -> Bool
dateCirca Date
d then ((Text
"circa", Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
True)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:) else [Pair] -> [Pair]
forall a. a -> a
id) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      (case Date -> Maybe Int
dateSeason Date
d of
        Just Int
s -> ((Text
"season", Int -> Value
forall a. ToJSON a => a -> Value
toJSON Int
s)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)
        Maybe Int
Nothing -> [Pair] -> [Pair]
forall a. a -> a
id) ([Pair] -> [Pair]) -> ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      (case Date -> Maybe Text
dateLiteral Date
d of
        Just Text
l -> ((Text
"literal", Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
l)Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
:)
        Maybe Text
Nothing -> [Pair] -> [Pair]
forall a. a -> a
id) ([Pair] -> [Pair]) -> [Pair] -> [Pair]
forall a b. (a -> b) -> a -> b
$
      [ (Text
"date-parts", [DateParts] -> Value
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  -- cheater dates
 parseJSON Value
x = String -> (Object -> Parser Date) -> Value -> Parser Date
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Date" (\Object
v ->
   (Object
vObject -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"raw" Parser Text -> (Text -> Parser Date) -> Parser Date
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Parser Date
rawDate)
   Parser Date -> Parser Date -> Parser Date
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
   ([DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date
Date ([DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date)
-> Parser [DateParts]
-> Parser (Bool -> Maybe Int -> Maybe Text -> Date)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe [DateParts])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"date-parts" Parser (Maybe [DateParts]) -> [DateParts] -> Parser [DateParts]
forall a. Parser (Maybe a) -> a -> Parser a
.!= []
         Parser (Bool -> Maybe Int -> Maybe Text -> Date)
-> Parser Bool -> Parser (Maybe Int -> Maybe Text -> Date)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"circa" Parser Value -> (Value -> Parser Bool) -> Parser Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Value -> Parser Bool
asBool) Parser Bool -> Parser Bool -> Parser Bool
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Bool -> Parser Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
False)
         Parser (Maybe Int -> Maybe Text -> Date)
-> Parser (Maybe Int) -> Parser (Maybe Text -> Date)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"season" Parser Value -> (Value -> Parser (Maybe Int)) -> Parser (Maybe Int)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Int -> Maybe Int) -> Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Maybe Int
forall a. a -> Maybe a
Just (Parser Int -> Parser (Maybe Int))
-> (Value -> Parser Int) -> Value -> Parser (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Int
asInt) Parser (Maybe Int) -> Parser (Maybe Int) -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Int
forall a. Maybe a
Nothing)
         Parser (Maybe Text -> Date) -> Parser (Maybe Text) -> Parser Date
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"literal")) Value
x

newtype DateParts = DateParts [Int]
  deriving (Int -> DateParts -> ShowS
[DateParts] -> ShowS
DateParts -> String
(Int -> DateParts -> ShowS)
-> (DateParts -> String)
-> ([DateParts] -> ShowS)
-> Show DateParts
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
(DateParts -> DateParts -> Bool)
-> (DateParts -> DateParts -> Bool) -> Eq DateParts
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
Eq DateParts
-> (DateParts -> DateParts -> Ordering)
-> (DateParts -> DateParts -> Bool)
-> (DateParts -> DateParts -> Bool)
-> (DateParts -> DateParts -> Bool)
-> (DateParts -> DateParts -> Bool)
-> (DateParts -> DateParts -> DateParts)
-> (DateParts -> DateParts -> DateParts)
-> Ord 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
$cp1Ord :: Eq DateParts
Ord, [DateParts] -> Encoding
[DateParts] -> Value
DateParts -> Encoding
DateParts -> Value
(DateParts -> Value)
-> (DateParts -> Encoding)
-> ([DateParts] -> Value)
-> ([DateParts] -> Encoding)
-> ToJSON DateParts
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 ([Int] -> DateParts) -> Parser [Int] -> Parser DateParts
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value -> Parser [Value]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser [Value] -> ([Value] -> Parser [Int]) -> Parser [Int]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Value -> Parser Int) -> [Value] -> Parser [Int]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Value -> Parser Int
asInt ([Value] -> Parser [Int])
-> ([Value] -> [Value]) -> [Value] -> Parser [Int]
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 Maybe Date -> Maybe Date -> Maybe Date
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Maybe Date
rawDateOld Text
t of
              Just Date
d  -> Date -> Parser Date
forall (m :: * -> *) a. Monad m => a -> m a
return Date
d
              Maybe Date
Nothing -> Date -> Parser Date
forall (m :: * -> *) a. Monad m => a -> m a
return (Date -> Parser Date) -> Date -> Parser Date
forall a b. (a -> b) -> a -> b
$ Date :: [DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date
Date { dateParts :: [DateParts]
dateParts = []
                                       , dateCirca :: Bool
dateCirca = Bool
False
                                       , dateSeason :: Maybe Int
dateSeason = Maybe Int
forall a. Maybe a
Nothing
                                       , dateLiteral :: Maybe Text
dateLiteral = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t }

rawDateEDTF :: Text -> Maybe Date
rawDateEDTF :: Text -> Maybe Date
rawDateEDTF = Text -> Maybe Date
rawDateISO (Text -> Maybe Date) -> (Text -> Text) -> Text -> Maybe Date
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 (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') Text
t of
         -- 199u EDTF format for a range
         [Text
x] | (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'u') Text
x ->
               (Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'u' then Char
'0' else Char
c) Text
x
               Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
               (Char -> Char) -> Text -> Text
T.map (\Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'u' then Char
'9' else Char
c) Text
x
         [Text
x, Text
"open"] -> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/"    -- EDTF
         [Text
x, Text
"unknown"] -> Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/" -- EDTF
         [Text]
_  -> Text
t

rawDateISO :: Text -> Maybe Date
rawDateISO :: Text -> Maybe Date
rawDateISO Text
raw = do
  let ranges :: [Text]
ranges = (Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Text
T.strip ([Text] -> [Text]) -> [Text] -> [Text]
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'/') Text
raw
  let circa :: Bool
circa = (Text -> Bool) -> [Text] -> Bool
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 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"y"
                         then (Bool, Text) -> Maybe (Bool, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Int -> Text -> Text
T.drop Int
1 Text
t)
                         else (Bool, Text) -> Maybe (Bool, Text)
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' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"-"
                           then (Bool, Text) -> Maybe (Bool, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
True, Int -> Text -> Text
T.drop Int
1 Text
t')
                           else (Bool, Text) -> Maybe (Bool, Text)
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 (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpecial) Text
t''
        case (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
'-') Text
t''' of
          [Text
""]         -> DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
0]
          [Text
y', Text
m', Text
d'] -> do
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
4
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
m' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
d' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2
            Int
y <- (if Bool
isNeg
                     then (\Int
x -> (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
* (-Int
1)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) -- 0 = 1 BC
                     else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Maybe Int -> Maybe Int
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'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m, Int
d]
          [Text
y', Text
m'] -> do
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
4
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
m' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2
            Int
y <- (if Bool
isNeg
                     then (\Int
x -> (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
* (-Int
1)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) -- 0 = 1 BC
                     else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Maybe Int -> Maybe Int
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'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y, Int
m]
          [Text
y'] -> do
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Bool
hasY Bool -> Bool -> Bool
&& Text -> Int
T.length Text
y' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
4
            Int
y <- (if Bool
isNeg
                     then (\Int
x -> (Int
x Int -> Int -> Int
forall a. Num a => a -> a -> a
* (-Int
1)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) -- 0 = 1 BC
                     else Int -> Int
forall a. a -> a
id) (Int -> Int) -> Maybe Int -> Maybe Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe Int
readAsInt Text
y'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y]
          [Text]
_ -> Maybe DateParts
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  [DateParts]
dps <- (Text -> Maybe DateParts) -> [Text] -> Maybe [DateParts]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> Maybe DateParts
dparts [Text]
ranges
  Date -> Maybe Date
forall (m :: * -> *) a. Monad m => a -> m a
return (Date -> Maybe Date) -> Date -> Maybe Date
forall a b. (a -> b) -> a -> b
$ Date :: [DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date
Date
    { dateParts :: [DateParts]
dateParts     = [DateParts]
dps
    , dateCirca :: Bool
dateCirca     = Bool
circa
    , dateSeason :: Maybe Int
dateSeason    = Maybe Int
forall a. Maybe a
Nothing
    , dateLiteral :: Maybe Text
dateLiteral   = Maybe Text
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 (Char -> Char -> Bool
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.take Int
3 Text
t
        case Text -> [Text] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
key [Text]
months of
             Just Int
n  -> Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
             Maybe Int
Nothing -> case Text -> [Text] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
key [Text]
seasons of
                          Just Int
n -> Int -> m Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
13)
                          Maybe Int
Nothing -> String -> m Int
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 Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'/' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',') (Text -> [Text]) -> Text -> [Text]
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' Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Maybe Int
forall (m :: * -> *). MonadFail m => Text -> m Int
readTextMonth Text
m'
            Int
d <- Text -> Maybe Int
readAsInt Text
d'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
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' Maybe Int -> Maybe Int -> Maybe Int
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> Maybe Int
forall (m :: * -> *). MonadFail m => Text -> m Int
readTextMonth Text
m'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
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'
            DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts [Int
y]
          []           -> DateParts -> Maybe DateParts
forall (m :: * -> *) a. Monad m => a -> m a
return (DateParts -> Maybe DateParts) -> DateParts -> Maybe DateParts
forall a b. (a -> b) -> a -> b
$ [Int] -> DateParts
DateParts []
          [Text]
_            -> Maybe DateParts
forall (m :: * -> *) a. MonadPlus m => m a
mzero
  [DateParts]
dps <- (Text -> Maybe DateParts) -> [Text] -> Maybe [DateParts]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> Maybe DateParts
dparts [Text]
ranges
  Date -> Maybe Date
forall (m :: * -> *) a. Monad m => a -> m a
return (Date -> Maybe Date) -> Date -> Maybe Date
forall a b. (a -> b) -> a -> b
$ Date :: [DateParts] -> Bool -> Maybe Int -> Maybe Text -> Date
Date
    { dateParts :: [DateParts]
dateParts     = [DateParts]
dps
    , dateCirca :: Bool
dateCirca     = Bool
False
    , dateSeason :: Maybe Int
dateSeason    = Maybe Int
forall a. Maybe a
Nothing
    , dateLiteral :: Maybe Text
dateLiteral   = Maybe Text
forall a. Maybe a
Nothing
    }



removeEmptyStrings :: [Value] -> [Value]
removeEmptyStrings :: [Value] -> [Value]
removeEmptyStrings = (Value -> Bool) -> [Value] -> [Value]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Value -> Bool) -> Value -> Bool
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]
  | InNote (Output a)
  | Literal a
  | Tagged Tag (Output a)
  | NullOutput
  deriving (Int -> Output a -> ShowS
[Output a] -> ShowS
Output a -> String
(Int -> Output a -> ShowS)
-> (Output a -> String) -> ([Output a] -> ShowS) -> Show (Output a)
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
(Output a -> Output a -> Bool)
-> (Output a -> Output a -> Bool) -> Eq (Output a)
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) = (Formatting -> [Output a] -> Output a)
-> Type (Formatting -> [Output a] -> Output a) (Output a)
forall from to. from -> Type from to
plate Formatting -> [Output a] -> Output a
forall a. Formatting -> [Output a] -> Output a
Formatted Type (Formatting -> [Output a] -> Output a) (Output a)
-> Formatting -> Type ([Output a] -> Output a) (Output a)
forall item from to. Type (item -> from) to -> item -> Type from to
|- Formatting
f Type ([Output a] -> Output a) (Output a)
-> [Output a] -> (Str (Output a), Str (Output a) -> Output a)
forall to from. Type ([to] -> from) to -> [to] -> Type from to
||* [Output a]
xs
  uniplate (InNote Output a
x)       = (Output a -> Output a) -> Type (Output a -> Output a) (Output a)
forall from to. from -> Type from to
plate Output a -> Output a
forall a. Output a -> Output a
InNote Type (Output a -> Output a) (Output a)
-> Output a -> (Str (Output a), Str (Output a) -> Output a)
forall to from. Type (to -> from) to -> to -> Type from to
|* Output a
x
  uniplate (Literal a
x)      = (a -> Output a) -> Type (a -> Output a) (Output a)
forall from to. from -> Type from to
plate a -> Output a
forall a. a -> Output a
Literal Type (a -> Output a) (Output a)
-> a -> (Str (Output a), Str (Output a) -> Output a)
forall item from to. Type (item -> from) to -> item -> Type from to
|- a
x
  uniplate (Tagged Tag
t Output a
x)     = (Tag -> Output a -> Output a)
-> Type (Tag -> Output a -> Output a) (Output a)
forall from to. from -> Type from to
plate Tag -> Output a -> Output a
forall a. Tag -> Output a -> Output a
Tagged Type (Tag -> Output a -> Output a) (Output a)
-> Tag -> Type (Output a -> Output a) (Output a)
forall item from to. Type (item -> from) to -> item -> Type from to
|- Tag
t Type (Output a -> Output a) (Output a)
-> Output a -> (Str (Output a), Str (Output a) -> Output a)
forall to from. Type (to -> from) to -> to -> Type from to
|* Output a
x
  uniplate Output a
NullOutput       = Output a -> (Str (Output a), Str (Output a) -> Output a)
forall from to. from -> Type from to
plate Output a
forall a. Output a
NullOutput

instance Biplate (Output a) (Output a) where
  biplate :: Output a -> (Str (Output a), Str (Output a) -> Output a)
biplate = Output a -> (Str (Output a), Str (Output a) -> Output a)
forall to. to -> Type to to
plateSelf

data Tag =
      TagTerm
    | TagCitationNumber Int
    | TagCitationLabel
    | TagItem CitationItemType ItemId
    | TagName Name
    | TagNames Variable NamesFormat [Name]
    | TagDate Date
    | TagYearSuffix Int
    | TagLocator
  deriving (Int -> Tag -> ShowS
[Tag] -> ShowS
Tag -> String
(Int -> Tag -> ShowS)
-> (Tag -> String) -> ([Tag] -> ShowS) -> Show Tag
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
(Tag -> Tag -> Bool) -> (Tag -> Tag -> Bool) -> Eq Tag
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 :: Output a -> Text
outputToText Output a
NullOutput = Text
forall a. Monoid a => a
mempty
outputToText (Literal a
x ) = a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x
outputToText (Tagged Tag
_ Output a
x) = Output a -> Text
forall a. CiteprocOutput a => Output a -> Text
outputToText Output a
x
outputToText (Formatted Formatting
_ [Output a]
xs) = [Text] -> Text
T.unwords ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Output a -> Text) -> [Output a] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Output a -> Text
forall a. CiteprocOutput a => Output a -> Text
outputToText [Output a]
xs
outputToText (InNote Output a
x)   = Output a -> Text
forall a. CiteprocOutput a => Output a -> Text
outputToText Output a
x

renderOutput :: CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput :: CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
_ Output a
NullOutput = a
forall a. Monoid a => a
mempty
renderOutput CiteprocOptions
_ (Literal a
x) = a
x
renderOutput CiteprocOptions
opts (Tagged (TagItem CitationItemType
_ ItemId
ident) Output a
x)
  | CiteprocOptions -> Bool
linkCitations CiteprocOptions
opts
  = Text -> a -> a
forall a. CiteprocOutput a => Text -> a -> a
addHyperlink (Text
"#ref-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ItemId -> Text
unItemId ItemId
ident) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ CiteprocOptions -> Output a -> a
forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x
renderOutput CiteprocOptions
opts (Tagged Tag
_ Output a
x) = CiteprocOptions -> Output a -> a
forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x
renderOutput CiteprocOptions
opts (Formatted Formatting
formatting [Output a]
xs) =
  Formatting -> a -> a
forall a. CiteprocOutput a => Formatting -> a -> a
addFormatting Formatting
formatting (a -> a) -> ([a] -> a) -> [a] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> a
forall a. Monoid a => [a] -> a
mconcat ([a] -> a) -> ([a] -> [a]) -> [a] -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
    (case Formatting -> Maybe Text
formatDelimiter Formatting
formatting of
       Just Text
d  -> a -> [a] -> [a]
forall a. CiteprocOutput a => a -> [a] -> [a]
addDelimiters (Text -> a
forall a. CiteprocOutput a => Text -> a
fromText Text
d)
       Maybe Text
Nothing -> [a] -> [a]
forall a. a -> a
id) ([a] -> [a]) -> ([a] -> [a]) -> [a] -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter (a -> a -> Bool
forall a. Eq a => a -> a -> Bool
/= a
forall a. Monoid a => a
mempty) ([a] -> a) -> [a] -> a
forall a b. (a -> b) -> a -> b
$ (Output a -> a) -> [Output a] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map (CiteprocOptions -> Output a -> a
forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts) [Output a]
xs
renderOutput CiteprocOptions
opts (InNote Output a
x) = a -> a
forall p. CiteprocOutput p => p -> p
inNote (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$
  (Char -> Bool) -> a -> a
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile Char -> Bool
isSpace (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$
  (Char -> Bool) -> a -> a
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$
  CiteprocOptions -> Output a -> a
forall a. CiteprocOutput a => CiteprocOptions -> Output a -> a
renderOutput CiteprocOptions
opts Output a
x

addDelimiters :: CiteprocOutput a => a -> [a] -> [a]
addDelimiters :: a -> [a] -> [a]
addDelimiters a
delim =
  (a -> [a] -> [a]) -> [a] -> [a] -> [a]
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 (a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
a) of
                         Just (Char
c,Text
_)
                           | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
',' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
';' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.' -> a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
as
                         Maybe (Char, Text)
_ -> a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
delim a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
a a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
as

fixPunct :: CiteprocOutput a => [a] -> [a]
fixPunct :: [a] -> [a]
fixPunct (a
x:a
y:[a]
zs) =
  case (Char
xEnd, Char
yStart) of
    -- https://github.com/Juris-M/citeproc-js/blob/master/src/queue.js#L724
    (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 = a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x
  yText :: Text
yText = a -> Text
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 = (Char -> Bool) -> a -> a
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
xEnd) a
x
  yTrimmed :: a
yTrimmed = (Char -> Bool) -> a -> a
forall a. CiteprocOutput a => (Char -> Bool) -> a -> a
dropTextWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
yStart) a
y
  keepFirst :: [a]
keepFirst = if a
yTrimmed a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
y -- see #49
                 then a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs)
                 else [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
yTrimmed a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs
  keepSecond :: [a]
keepSecond = if a
xTrimmed a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
x -- see #49
                  then a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs)
                  else [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
xTrimmed a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs)
  keepBoth :: [a]
keepBoth = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
forall a. CiteprocOutput a => [a] -> [a]
fixPunct (a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs)
fixPunct [a]
zs = [a]
zs


grouped :: [Output a] -> Output a
grouped :: [Output a] -> Output a
grouped = Formatting -> [Output a] -> Output a
forall a. Formatting -> [Output a] -> Output a
formatted Formatting
forall a. Monoid a => a
mempty

formatted :: Formatting -> [Output a] -> Output a
formatted :: Formatting -> [Output a] -> Output a
formatted Formatting
formatting = [Output a] -> Output a
forall a. [Output a] -> Output a
grouped' ([Output a] -> Output a)
-> ([Output a] -> [Output a]) -> [Output a] -> Output a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Output a -> Bool) -> [Output a] -> [Output a]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Output a -> Bool) -> Output a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Output a -> Bool
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' []  = Output a
forall a. Output a
NullOutput
  grouped' [Output a
x] | Formatting
formatting Formatting -> Formatting -> Bool
forall a. Eq a => a -> a -> Bool
== Formatting
forall a. Monoid a => a
mempty = Output a
x
  grouped' [Output a]
xs  = Formatting -> [Output a] -> Output a
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 Reader Int
forall a. Integral a => Reader a
TR.decimal Text
t of
      Right (Int
x,Text
t') | Text -> Bool
T.null Text
t' -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
x
      Either String (Int, Text)
_                        -> Maybe Int
forall a. Maybe a
Nothing

-- | An abbreviations map.  These are typically stored in a JSON
-- serialization: for examples of the format, see
-- <https://github.com/citation-style-language/abbreviations>.
-- Abbreviations are substituted in the output when the variable
-- and its content are matched by something in the abbreviations map.
newtype Abbreviations =
  Abbreviations (M.Map Variable (M.Map Variable Text))
  deriving (Int -> Abbreviations -> ShowS
[Abbreviations] -> ShowS
Abbreviations -> String
(Int -> Abbreviations -> ShowS)
-> (Abbreviations -> String)
-> ([Abbreviations] -> ShowS)
-> Show Abbreviations
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
(Abbreviations -> Abbreviations -> Bool)
-> (Abbreviations -> Abbreviations -> Bool) -> Eq Abbreviations
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
Eq Abbreviations
-> (Abbreviations -> Abbreviations -> Ordering)
-> (Abbreviations -> Abbreviations -> Bool)
-> (Abbreviations -> Abbreviations -> Bool)
-> (Abbreviations -> Abbreviations -> Bool)
-> (Abbreviations -> Abbreviations -> Bool)
-> (Abbreviations -> Abbreviations -> Abbreviations)
-> (Abbreviations -> Abbreviations -> Abbreviations)
-> Ord 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
$cp1Ord :: Eq Abbreviations
Ord)
-- NOTE: We use 'Variable' in the second map for the contents of the
-- variable, because we want it to be treated case-insensitively,
-- and we need a wrapper around 'CI' that has To/FromJSON instances.

instance FromJSON Abbreviations where
  parseJSON :: Value -> Parser Abbreviations
parseJSON = String
-> (Object -> Parser Abbreviations)
-> Value
-> Parser Abbreviations
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Abbreviations" ((Object -> Parser Abbreviations) -> Value -> Parser Abbreviations)
-> (Object -> Parser Abbreviations)
-> Value
-> Parser Abbreviations
forall a b. (a -> b) -> a -> b
$ \Object
v ->
    Map Variable (Map Variable Text) -> Abbreviations
Abbreviations (Map Variable (Map Variable Text) -> Abbreviations)
-> Parser (Map Variable (Map Variable Text))
-> Parser Abbreviations
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Map Variable (Map Variable Text))
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"default"

instance ToJSON Abbreviations where
  toJSON :: Abbreviations -> Value
toJSON (Abbreviations Map Variable (Map Variable Text)
m) =
    [Pair] -> Value
object [(Text
"default", Map Variable (Map Variable Text) -> Value
forall a. ToJSON a => a -> Value
toJSON Map Variable (Map Variable Text)
m)]

-- | Returns an abbreviation if the variable and its value match
-- something in the abbreviations map.
lookupAbbreviation :: CiteprocOutput a
                   => Variable -> Val a -> Abbreviations -> Maybe (Val a)
lookupAbbreviation :: 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 <- Variable
-> Map Variable (Map Variable Text) -> Maybe (Map Variable Text)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (if Variable -> VariableType
variableType Variable
var VariableType -> VariableType -> Bool
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  -> Maybe (Val a)
-> (Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe (Val a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Val a -> Maybe (Val a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Val a -> Maybe (Val a))
-> (Text -> Val a) -> Text -> Maybe (Val a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Val a
forall a. Text -> Val a
TextVal)
                         (Maybe Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall a b. (a -> b) -> a -> b
$ Variable -> Map Variable Text -> Maybe Text
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 -> Maybe (Val a)
-> (Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe (Val a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Val a -> Maybe (Val a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Val a -> Maybe (Val a))
-> (Text -> Val a) -> Text -> Maybe (Val a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Val a
forall a. Text -> Val a
TextVal)
                         (Maybe Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall a b. (a -> b) -> a -> b
$ Variable -> Map Variable Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Variable
toVariable (a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x)) Map Variable Text
abbrvs
    NumVal Int
n   -> Maybe (Val a)
-> (Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Maybe (Val a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero (Val a -> Maybe (Val a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Val a -> Maybe (Val a))
-> (Text -> Val a) -> Text -> Maybe (Val a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Val a
forall a. Text -> Val a
TextVal)
                         (Maybe Text -> Maybe (Val a)) -> Maybe Text -> Maybe (Val a)
forall a b. (a -> b) -> a -> b
$ Variable -> Map Variable Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text -> Variable
toVariable (String -> Text
T.pack (Int -> String
forall a. Show a => a -> String
show Int
n))) Map Variable Text
abbrvs
    Val a
_          -> Maybe (Val a)
forall (m :: * -> *) a. MonadPlus m => m a
mzero

-- | Result of citation processing.
data Result a =
  Result
  { Result a -> [a]
resultCitations     :: [a]          -- ^ List of formatted citations
                    -- corresponding to the citations given to 'citeproc'
  , Result a -> [(Text, a)]
resultBibliography  :: [(Text, a)]  -- ^ List of formatted bibliography
                    -- entries (if the style calls for a bibliography),
                    -- each a pair consisting of the item identifier and
                    -- the formatted entry
  , Result a -> [Text]
resultWarnings      :: [Text]       -- ^ Warnings from citation processing
  } deriving (Int -> Result a -> ShowS
[Result a] -> ShowS
Result a -> String
(Int -> Result a -> ShowS)
-> (Result a -> String) -> ([Result a] -> ShowS) -> Show (Result a)
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, a -> Result b -> Result a
(a -> b) -> Result a -> Result b
(forall a b. (a -> b) -> Result a -> Result b)
-> (forall a b. a -> Result b -> Result a) -> Functor Result
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
<$ :: a -> Result b -> Result a
$c<$ :: forall a b. a -> Result b -> Result a
fmap :: (a -> b) -> Result a -> Result b
$cfmap :: forall a b. (a -> b) -> Result a -> Result b
Functor, Functor Result
Foldable Result
Functor Result
-> Foldable Result
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Result a -> f (Result b))
-> (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 (m :: * -> *) a.
    Monad m =>
    Result (m a) -> m (Result a))
-> Traversable Result
(a -> f b) -> Result a -> f (Result b)
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 :: Result (m a) -> m (Result a)
$csequence :: forall (m :: * -> *) a. Monad m => Result (m a) -> m (Result a)
mapM :: (a -> m b) -> Result a -> m (Result b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Result a -> m (Result b)
sequenceA :: Result (f a) -> f (Result a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Result (f a) -> f (Result a)
traverse :: (a -> f b) -> Result a -> f (Result b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Result a -> f (Result b)
$cp2Traversable :: Foldable Result
$cp1Traversable :: Functor Result
Traversable, Result a -> Bool
(a -> m) -> Result a -> m
(a -> b -> b) -> b -> Result a -> b
(forall m. Monoid m => Result m -> m)
-> (forall m a. Monoid m => (a -> m) -> Result a -> m)
-> (forall m a. Monoid m => (a -> m) -> Result a -> m)
-> (forall a b. (a -> b -> b) -> b -> Result a -> b)
-> (forall a b. (a -> b -> b) -> b -> Result a -> b)
-> (forall b a. (b -> a -> b) -> b -> Result a -> b)
-> (forall b a. (b -> a -> b) -> b -> Result a -> b)
-> (forall a. (a -> a -> a) -> Result a -> a)
-> (forall a. (a -> a -> a) -> Result a -> a)
-> (forall a. Result a -> [a])
-> (forall a. Result a -> Bool)
-> (forall a. Result a -> Int)
-> (forall a. Eq a => a -> Result a -> Bool)
-> (forall a. Ord a => Result a -> a)
-> (forall a. Ord a => Result a -> a)
-> (forall a. Num a => Result a -> a)
-> (forall a. Num a => Result a -> a)
-> Foldable Result
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 :: Result a -> a
$cproduct :: forall a. Num a => Result a -> a
sum :: Result a -> a
$csum :: forall a. Num a => Result a -> a
minimum :: Result a -> a
$cminimum :: forall a. Ord a => Result a -> a
maximum :: Result a -> a
$cmaximum :: forall a. Ord a => Result a -> a
elem :: a -> Result a -> Bool
$celem :: forall a. Eq a => a -> Result a -> Bool
length :: Result a -> Int
$clength :: forall a. Result a -> Int
null :: Result a -> Bool
$cnull :: forall a. Result a -> Bool
toList :: Result a -> [a]
$ctoList :: forall a. Result a -> [a]
foldl1 :: (a -> a -> a) -> Result a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Result a -> a
foldr1 :: (a -> a -> a) -> Result a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Result a -> a
foldl' :: (b -> a -> b) -> b -> Result a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Result a -> b
foldl :: (b -> a -> b) -> b -> Result a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Result a -> b
foldr' :: (a -> b -> b) -> b -> Result a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Result a -> b
foldr :: (a -> b -> b) -> b -> Result a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Result a -> b
foldMap' :: (a -> m) -> Result a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Result a -> m
foldMap :: (a -> m) -> Result a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Result a -> m
fold :: 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
    [ (Text
"citations", [a] -> Value
forall a. ToJSON a => a -> Value
toJSON ([a] -> Value) -> [a] -> Value
forall a b. (a -> b) -> a -> b
$ Result a -> [a]
forall a. Result a -> [a]
resultCitations Result a
res)
    , (Text
"bibliography", [(Text, a)] -> Value
forall a. ToJSON a => a -> Value
toJSON ([(Text, a)] -> Value) -> [(Text, a)] -> Value
forall a b. (a -> b) -> a -> b
$ Result a -> [(Text, a)]
forall a. Result a -> [(Text, a)]
resultBibliography Result a
res)
    , (Text
"warnings", [Text] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Text] -> Value) -> [Text] -> Value
forall a b. (a -> b) -> a -> b
$ Result a -> [Text]
forall a. Result a -> [Text]
resultWarnings Result a
res)
    ]

instance FromJSON a => FromJSON (Result a) where
  parseJSON :: Value -> Parser (Result a)
parseJSON = String
-> (Object -> Parser (Result a)) -> Value -> Parser (Result a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Result" ((Object -> Parser (Result a)) -> Value -> Parser (Result a))
-> (Object -> Parser (Result a)) -> Value -> Parser (Result a)
forall a b. (a -> b) -> a -> b
$ \Object
v ->
    [a] -> [(Text, a)] -> [Text] -> Result a
forall a. [a] -> [(Text, a)] -> [Text] -> Result a
Result ([a] -> [(Text, a)] -> [Text] -> Result a)
-> Parser [a] -> Parser ([(Text, a)] -> [Text] -> Result a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser [a]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"citations"
           Parser ([(Text, a)] -> [Text] -> Result a)
-> Parser [(Text, a)] -> Parser ([Text] -> Result a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [(Text, a)]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"bibliography"
           Parser ([Text] -> Result a) -> Parser [Text] -> Parser (Result a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"warnings"

-- | Inputs for citation processing.
data Inputs a =
  Inputs
  { Inputs a -> Maybe [Citation a]
inputsCitations     :: Maybe [Citation a]
  , Inputs a -> Maybe [Reference a]
inputsReferences    :: Maybe [Reference a]
  , Inputs a -> Maybe Text
inputsStyle         :: Maybe Text
  , Inputs a -> Maybe Abbreviations
inputsAbbreviations :: Maybe Abbreviations
  , Inputs a -> Maybe Lang
inputsLang          :: Maybe Lang
  } deriving (Int -> Inputs a -> ShowS
[Inputs a] -> ShowS
Inputs a -> String
(Int -> Inputs a -> ShowS)
-> (Inputs a -> String) -> ([Inputs a] -> ShowS) -> Show (Inputs a)
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
    [ (Text
"citations",     Maybe [Citation a] -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe [Citation a] -> Value) -> Maybe [Citation a] -> Value
forall a b. (a -> b) -> a -> b
$ Inputs a -> Maybe [Citation a]
forall a. Inputs a -> Maybe [Citation a]
inputsCitations Inputs a
inp)
    , (Text
"references",    Maybe [Reference a] -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe [Reference a] -> Value) -> Maybe [Reference a] -> Value
forall a b. (a -> b) -> a -> b
$ Inputs a -> Maybe [Reference a]
forall a. Inputs a -> Maybe [Reference a]
inputsReferences Inputs a
inp)
    , (Text
"style",         Maybe Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe Text -> Value) -> Maybe Text -> Value
forall a b. (a -> b) -> a -> b
$ Inputs a -> Maybe Text
forall a. Inputs a -> Maybe Text
inputsStyle Inputs a
inp)
    , (Text
"abbreviations", Maybe Abbreviations -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe Abbreviations -> Value) -> Maybe Abbreviations -> Value
forall a b. (a -> b) -> a -> b
$ Inputs a -> Maybe Abbreviations
forall a. Inputs a -> Maybe Abbreviations
inputsAbbreviations Inputs a
inp)
    , (Text
"lang",          Maybe Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe Text -> Value) -> Maybe Text -> Value
forall a b. (a -> b) -> a -> b
$ Lang -> Text
renderLang (Lang -> Text) -> Maybe Lang -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inputs a -> Maybe Lang
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 = String
-> (Object -> Parser (Inputs a)) -> Value -> Parser (Inputs a)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Inputs" ((Object -> Parser (Inputs a)) -> Value -> Parser (Inputs a))
-> (Object -> Parser (Inputs a)) -> Value -> Parser (Inputs a)
forall a b. (a -> b) -> a -> b
$ \Object
v ->
    Maybe [Citation a]
-> Maybe [Reference a]
-> Maybe Text
-> Maybe Abbreviations
-> Maybe Lang
-> Inputs a
forall a.
Maybe [Citation a]
-> Maybe [Reference a]
-> Maybe Text
-> Maybe Abbreviations
-> Maybe Lang
-> Inputs a
Inputs (Maybe [Citation a]
 -> Maybe [Reference a]
 -> Maybe Text
 -> Maybe Abbreviations
 -> Maybe Lang
 -> Inputs a)
-> Parser (Maybe [Citation a])
-> Parser
     (Maybe [Reference a]
      -> Maybe Text -> Maybe Abbreviations -> Maybe Lang -> Inputs a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser (Maybe [Citation a])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"citations"
           Parser
  (Maybe [Reference a]
   -> Maybe Text -> Maybe Abbreviations -> Maybe Lang -> Inputs a)
-> Parser (Maybe [Reference a])
-> Parser
     (Maybe Text -> Maybe Abbreviations -> Maybe Lang -> Inputs a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe [Reference a])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"references"
           Parser
  (Maybe Text -> Maybe Abbreviations -> Maybe Lang -> Inputs a)
-> Parser (Maybe Text)
-> Parser (Maybe Abbreviations -> Maybe Lang -> Inputs a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"style"
           Parser (Maybe Abbreviations -> Maybe Lang -> Inputs a)
-> Parser (Maybe Abbreviations) -> Parser (Maybe Lang -> Inputs a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Text -> Parser (Maybe Abbreviations)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"abbreviations"
           Parser (Maybe Lang -> Inputs a)
-> Parser (Maybe Lang) -> Parser (Inputs a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (do Maybe Text
mbl <- Object
v Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? Text
"lang"
                   case Maybe Text
mbl of
                     Maybe Text
Nothing -> Maybe Lang -> Parser (Maybe Lang)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Lang
forall a. Maybe a
Nothing
                     Just Text
l  ->
                       case Text -> Either String Lang
parseLang Text
l of
                         Left String
_     -> Maybe Lang -> Parser (Maybe Lang)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Lang
forall a. Maybe a
Nothing
                         Right Lang
lang -> Maybe Lang -> Parser (Maybe Lang)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Lang -> Parser (Maybe Lang))
-> Maybe Lang -> Parser (Maybe Lang)
forall a b. (a -> b) -> a -> b
$ Lang -> Maybe Lang
forall a. a -> Maybe a
Just Lang
lang)