{-# LANGUAGE StrictData #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveTraversable #-}
module Citeproc.CslJson
( CslJson(..)
, cslJsonToJson
, renderCslJson
, parseCslJson
)
where
import Citeproc.Types
import Citeproc.CaseTransform
import Data.Ord ()
import Data.Char (isAlphaNum, isSpace, isAscii)
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import qualified Data.Text as T
import qualified Data.Map as M
import Data.Functor.Identity
import Data.Attoparsec.Text as P
import Data.Aeson (FromJSON(..), ToJSON(..), Value(..), object)
import Control.Monad.Trans.State
import Control.Monad (guard, when)
import Control.Applicative ((<|>))
import Data.Generics.Uniplate.Direct
data CslJson a =
CslText a
| CslEmpty
| CslConcat (CslJson a) (CslJson a)
| CslQuoted (CslJson a)
| CslItalic (CslJson a)
| CslNormal (CslJson a)
| CslBold (CslJson a)
| CslUnderline (CslJson a)
| CslNoDecoration (CslJson a)
| CslSmallCaps (CslJson a)
| CslBaseline (CslJson a)
| CslSup (CslJson a)
| CslSub (CslJson a)
| CslNoCase (CslJson a)
| CslDiv Text (CslJson a)
deriving (Int -> CslJson a -> ShowS
[CslJson a] -> ShowS
CslJson a -> String
(Int -> CslJson a -> ShowS)
-> (CslJson a -> String)
-> ([CslJson a] -> ShowS)
-> Show (CslJson a)
forall a. Show a => Int -> CslJson a -> ShowS
forall a. Show a => [CslJson a] -> ShowS
forall a. Show a => CslJson a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CslJson a] -> ShowS
$cshowList :: forall a. Show a => [CslJson a] -> ShowS
show :: CslJson a -> String
$cshow :: forall a. Show a => CslJson a -> String
showsPrec :: Int -> CslJson a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> CslJson a -> ShowS
Show, CslJson a -> CslJson a -> Bool
(CslJson a -> CslJson a -> Bool)
-> (CslJson a -> CslJson a -> Bool) -> Eq (CslJson a)
forall a. Eq a => CslJson a -> CslJson a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CslJson a -> CslJson a -> Bool
$c/= :: forall a. Eq a => CslJson a -> CslJson a -> Bool
== :: CslJson a -> CslJson a -> Bool
$c== :: forall a. Eq a => CslJson a -> CslJson a -> Bool
Eq, Eq (CslJson a)
Eq (CslJson a)
-> (CslJson a -> CslJson a -> Ordering)
-> (CslJson a -> CslJson a -> Bool)
-> (CslJson a -> CslJson a -> Bool)
-> (CslJson a -> CslJson a -> Bool)
-> (CslJson a -> CslJson a -> Bool)
-> (CslJson a -> CslJson a -> CslJson a)
-> (CslJson a -> CslJson a -> CslJson a)
-> Ord (CslJson a)
CslJson a -> CslJson a -> Bool
CslJson a -> CslJson a -> Ordering
CslJson a -> CslJson a -> CslJson 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 (CslJson a)
forall a. Ord a => CslJson a -> CslJson a -> Bool
forall a. Ord a => CslJson a -> CslJson a -> Ordering
forall a. Ord a => CslJson a -> CslJson a -> CslJson a
min :: CslJson a -> CslJson a -> CslJson a
$cmin :: forall a. Ord a => CslJson a -> CslJson a -> CslJson a
max :: CslJson a -> CslJson a -> CslJson a
$cmax :: forall a. Ord a => CslJson a -> CslJson a -> CslJson a
>= :: CslJson a -> CslJson a -> Bool
$c>= :: forall a. Ord a => CslJson a -> CslJson a -> Bool
> :: CslJson a -> CslJson a -> Bool
$c> :: forall a. Ord a => CslJson a -> CslJson a -> Bool
<= :: CslJson a -> CslJson a -> Bool
$c<= :: forall a. Ord a => CslJson a -> CslJson a -> Bool
< :: CslJson a -> CslJson a -> Bool
$c< :: forall a. Ord a => CslJson a -> CslJson a -> Bool
compare :: CslJson a -> CslJson a -> Ordering
$ccompare :: forall a. Ord a => CslJson a -> CslJson a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (CslJson a)
Ord, a -> CslJson b -> CslJson a
(a -> b) -> CslJson a -> CslJson b
(forall a b. (a -> b) -> CslJson a -> CslJson b)
-> (forall a b. a -> CslJson b -> CslJson a) -> Functor CslJson
forall a b. a -> CslJson b -> CslJson a
forall a b. (a -> b) -> CslJson a -> CslJson b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CslJson b -> CslJson a
$c<$ :: forall a b. a -> CslJson b -> CslJson a
fmap :: (a -> b) -> CslJson a -> CslJson b
$cfmap :: forall a b. (a -> b) -> CslJson a -> CslJson b
Functor, CslJson a -> Bool
(a -> m) -> CslJson a -> m
(a -> b -> b) -> b -> CslJson a -> b
(forall m. Monoid m => CslJson m -> m)
-> (forall m a. Monoid m => (a -> m) -> CslJson a -> m)
-> (forall m a. Monoid m => (a -> m) -> CslJson a -> m)
-> (forall a b. (a -> b -> b) -> b -> CslJson a -> b)
-> (forall a b. (a -> b -> b) -> b -> CslJson a -> b)
-> (forall b a. (b -> a -> b) -> b -> CslJson a -> b)
-> (forall b a. (b -> a -> b) -> b -> CslJson a -> b)
-> (forall a. (a -> a -> a) -> CslJson a -> a)
-> (forall a. (a -> a -> a) -> CslJson a -> a)
-> (forall a. CslJson a -> [a])
-> (forall a. CslJson a -> Bool)
-> (forall a. CslJson a -> Int)
-> (forall a. Eq a => a -> CslJson a -> Bool)
-> (forall a. Ord a => CslJson a -> a)
-> (forall a. Ord a => CslJson a -> a)
-> (forall a. Num a => CslJson a -> a)
-> (forall a. Num a => CslJson a -> a)
-> Foldable CslJson
forall a. Eq a => a -> CslJson a -> Bool
forall a. Num a => CslJson a -> a
forall a. Ord a => CslJson a -> a
forall m. Monoid m => CslJson m -> m
forall a. CslJson a -> Bool
forall a. CslJson a -> Int
forall a. CslJson a -> [a]
forall a. (a -> a -> a) -> CslJson a -> a
forall m a. Monoid m => (a -> m) -> CslJson a -> m
forall b a. (b -> a -> b) -> b -> CslJson a -> b
forall a b. (a -> b -> b) -> b -> CslJson 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 :: CslJson a -> a
$cproduct :: forall a. Num a => CslJson a -> a
sum :: CslJson a -> a
$csum :: forall a. Num a => CslJson a -> a
minimum :: CslJson a -> a
$cminimum :: forall a. Ord a => CslJson a -> a
maximum :: CslJson a -> a
$cmaximum :: forall a. Ord a => CslJson a -> a
elem :: a -> CslJson a -> Bool
$celem :: forall a. Eq a => a -> CslJson a -> Bool
length :: CslJson a -> Int
$clength :: forall a. CslJson a -> Int
null :: CslJson a -> Bool
$cnull :: forall a. CslJson a -> Bool
toList :: CslJson a -> [a]
$ctoList :: forall a. CslJson a -> [a]
foldl1 :: (a -> a -> a) -> CslJson a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> CslJson a -> a
foldr1 :: (a -> a -> a) -> CslJson a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> CslJson a -> a
foldl' :: (b -> a -> b) -> b -> CslJson a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> CslJson a -> b
foldl :: (b -> a -> b) -> b -> CslJson a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> CslJson a -> b
foldr' :: (a -> b -> b) -> b -> CslJson a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> CslJson a -> b
foldr :: (a -> b -> b) -> b -> CslJson a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> CslJson a -> b
foldMap' :: (a -> m) -> CslJson a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> CslJson a -> m
foldMap :: (a -> m) -> CslJson a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> CslJson a -> m
fold :: CslJson m -> m
$cfold :: forall m. Monoid m => CslJson m -> m
Foldable, Functor CslJson
Foldable CslJson
Functor CslJson
-> Foldable CslJson
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CslJson a -> f (CslJson b))
-> (forall (f :: * -> *) a.
Applicative f =>
CslJson (f a) -> f (CslJson a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CslJson a -> m (CslJson b))
-> (forall (m :: * -> *) a.
Monad m =>
CslJson (m a) -> m (CslJson a))
-> Traversable CslJson
(a -> f b) -> CslJson a -> f (CslJson 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 => CslJson (m a) -> m (CslJson a)
forall (f :: * -> *) a.
Applicative f =>
CslJson (f a) -> f (CslJson a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CslJson a -> m (CslJson b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CslJson a -> f (CslJson b)
sequence :: CslJson (m a) -> m (CslJson a)
$csequence :: forall (m :: * -> *) a. Monad m => CslJson (m a) -> m (CslJson a)
mapM :: (a -> m b) -> CslJson a -> m (CslJson b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CslJson a -> m (CslJson b)
sequenceA :: CslJson (f a) -> f (CslJson a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
CslJson (f a) -> f (CslJson a)
traverse :: (a -> f b) -> CslJson a -> f (CslJson b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CslJson a -> f (CslJson b)
$cp2Traversable :: Foldable CslJson
$cp1Traversable :: Functor CslJson
Traversable)
instance Semigroup (CslJson a) where
(CslConcat CslJson a
x CslJson a
y) <> :: CslJson a -> CslJson a -> CslJson a
<> CslJson a
z = CslJson a
x CslJson a -> CslJson a -> CslJson a
forall a. Semigroup a => a -> a -> a
<> (CslJson a
y CslJson a -> CslJson a -> CslJson a
forall a. Semigroup a => a -> a -> a
<> CslJson a
z)
CslJson a
CslEmpty <> CslJson a
x = CslJson a
x
CslJson a
x <> CslJson a
CslEmpty = CslJson a
x
CslJson a
x <> CslJson a
y = CslJson a -> CslJson a -> CslJson a
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson a
x CslJson a
y
instance Monoid (CslJson a) where
mempty :: CslJson a
mempty = CslJson a
forall a. CslJson a
CslEmpty
mappend :: CslJson a -> CslJson a -> CslJson a
mappend = CslJson a -> CslJson a -> CslJson a
forall a. Semigroup a => a -> a -> a
(<>)
instance FromJSON (CslJson Text) where
parseJSON :: Value -> Parser (CslJson Text)
parseJSON = (Text -> CslJson Text) -> Parser Text -> Parser (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Locale -> Text -> CslJson Text
parseCslJson Locale
forall a. Monoid a => a
mempty) (Parser Text -> Parser (CslJson Text))
-> (Value -> Parser Text) -> Value -> Parser (CslJson Text)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON
instance ToJSON (CslJson Text) where
toJSON :: CslJson Text -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (CslJson Text -> Text) -> CslJson Text -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Locale -> CslJson Text -> Text
renderCslJson Bool
False Locale
forall a. Monoid a => a
mempty
instance Uniplate (CslJson a) where
uniplate :: CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
uniplate (CslText a
x) = (a -> CslJson a) -> Type (a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate a -> CslJson a
forall a. a -> CslJson a
CslText Type (a -> CslJson a) (CslJson a)
-> a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall item from to. Type (item -> from) to -> item -> Type from to
|- a
x
uniplate (CslJson a
CslEmpty) = CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall from to. from -> Type from to
plate CslJson a
forall a. CslJson a
CslEmpty
uniplate (CslConcat CslJson a
x CslJson a
y) = (CslJson a -> CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a -> CslJson a
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat Type (CslJson a -> CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> Type (CslJson a -> CslJson a) (CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
y
uniplate (CslQuoted CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslQuoted Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslItalic CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslItalic Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslNormal CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslNormal Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslBold CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslBold Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslUnderline CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslUnderline Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslNoDecoration CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslNoDecoration Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslSmallCaps CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslSmallCaps Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslBaseline CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslBaseline Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslSup CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslSup Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslSub CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslSub Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslNoCase CslJson a
x) = (CslJson a -> CslJson a)
-> Type (CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate CslJson a -> CslJson a
forall a. CslJson a -> CslJson a
CslNoCase Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
uniplate (CslDiv Text
t CslJson a
x) = (Text -> CslJson a -> CslJson a)
-> Type (Text -> CslJson a -> CslJson a) (CslJson a)
forall from to. from -> Type from to
plate Text -> CslJson a -> CslJson a
forall a. Text -> CslJson a -> CslJson a
CslDiv Type (Text -> CslJson a -> CslJson a) (CslJson a)
-> Text -> Type (CslJson a -> CslJson a) (CslJson a)
forall item from to. Type (item -> from) to -> item -> Type from to
|- Text
t Type (CslJson a -> CslJson a) (CslJson a)
-> CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to from. Type (to -> from) to -> to -> Type from to
|* CslJson a
x
instance Biplate (CslJson a) (CslJson a) where
biplate :: CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
biplate = CslJson a -> (Str (CslJson a), Str (CslJson a) -> CslJson a)
forall to. to -> Type to to
plateSelf
instance CiteprocOutput (CslJson Text) where
toText :: CslJson Text -> Text
toText = (Text -> Text) -> CslJson Text -> Text
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Text -> Text
forall a. a -> a
id
fromText :: Text -> CslJson Text
fromText = Locale -> Text -> CslJson Text
parseCslJson Locale
forall a. Monoid a => a
mempty
dropTextWhile :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhile = (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhile'
dropTextWhileEnd :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd = (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd'
addFontVariant :: FontVariant -> CslJson Text -> CslJson Text
addFontVariant FontVariant
x =
case FontVariant
x of
FontVariant
NormalVariant -> CslJson Text -> CslJson Text
forall a. a -> a
id
FontVariant
SmallCapsVariant -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSmallCaps
addFontStyle :: FontStyle -> CslJson Text -> CslJson Text
addFontStyle FontStyle
x =
case FontStyle
x of
FontStyle
NormalFont -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNormal
FontStyle
ItalicFont -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic
FontStyle
ObliqueFont -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic
addFontWeight :: FontWeight -> CslJson Text -> CslJson Text
addFontWeight FontWeight
x =
case FontWeight
x of
FontWeight
NormalWeight -> CslJson Text -> CslJson Text
forall a. a -> a
id
FontWeight
LightWeight -> CslJson Text -> CslJson Text
forall a. a -> a
id
FontWeight
BoldWeight -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBold
addTextDecoration :: TextDecoration -> CslJson Text -> CslJson Text
addTextDecoration TextDecoration
x =
case TextDecoration
x of
TextDecoration
NoDecoration -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoDecoration
TextDecoration
UnderlineDecoration -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslUnderline
addVerticalAlign :: VerticalAlign -> CslJson Text -> CslJson Text
addVerticalAlign VerticalAlign
x =
case VerticalAlign
x of
VerticalAlign
BaselineAlign -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBaseline
VerticalAlign
SubAlign -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSub
VerticalAlign
SupAlign -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup
addTextCase :: Maybe Lang -> TextCase -> CslJson Text -> CslJson Text
addTextCase Maybe Lang
mblang TextCase
x =
case TextCase
x of
TextCase
Lowercase -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withLowercaseAll
TextCase
Uppercase -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withUppercaseAll
TextCase
CapitalizeFirst -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withCapitalizeFirst
TextCase
CapitalizeAll -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withCapitalizeWords
TextCase
SentenceCase -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withSentenceCase
TextCase
TitleCase -> Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
withTitleCase
addDisplay :: DisplayStyle -> CslJson Text -> CslJson Text
addDisplay DisplayStyle
x =
case DisplayStyle
x of
DisplayStyle
DisplayBlock -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
"block"
DisplayStyle
DisplayLeftMargin -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
"left-margin"
DisplayStyle
DisplayRightInline -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
"right-inline"
DisplayStyle
DisplayIndent -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
"indent"
addQuotes :: CslJson Text -> CslJson Text
addQuotes = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted
inNote :: CslJson Text -> CslJson Text
inNote = CslJson Text -> CslJson Text
forall a. a -> a
id
movePunctuationInsideQuotes :: CslJson Text -> CslJson Text
movePunctuationInsideQuotes
= CslJson Text -> CslJson Text
punctuationInsideQuotes
mapText :: (Text -> Text) -> CslJson Text -> CslJson Text
mapText Text -> Text
f = Identity (CslJson Text) -> CslJson Text
forall a. Identity a -> a
runIdentity (Identity (CslJson Text) -> CslJson Text)
-> (CslJson Text -> Identity (CslJson Text))
-> CslJson Text
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Identity Text) -> CslJson Text -> Identity (CslJson Text)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Text -> Identity Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Identity Text) -> (Text -> Text) -> Text -> Identity Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
f)
addHyperlink :: Text -> CslJson Text -> CslJson Text
addHyperlink Text
_ = CslJson Text -> CslJson Text
forall a. a -> a
id
dropTextWhile' :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhile' :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhile' Char -> Bool
f CslJson Text
x = State Bool (CslJson Text) -> Bool -> CslJson Text
forall s a. State s a -> s -> a
evalState ((Text -> StateT Bool Identity Text)
-> CslJson Text -> State Bool (CslJson Text)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Text -> StateT Bool Identity Text
forall (m :: * -> *). Monad m => Text -> StateT Bool m Text
g CslJson Text
x) Bool
False
where
g :: Text -> StateT Bool m Text
g Text
t = do
Bool
pastFirst <- StateT Bool m Bool
forall (m :: * -> *) s. Monad m => StateT s m s
get
if Bool
pastFirst
then Text -> StateT Bool m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
t
else do
Bool -> StateT Bool m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put Bool
True
Text -> StateT Bool m Text
forall (m :: * -> *) a. Monad m => a -> m a
return ((Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
f Text
t)
dropTextWhileEnd' :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' :: (Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
el =
case CslJson Text
el of
CslJson Text
CslEmpty -> CslJson Text
forall a. CslJson a
CslEmpty
CslText Text
t -> Text -> CslJson Text
forall a. a -> CslJson a
CslText ((Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
f Text
t)
CslConcat CslJson Text
x CslJson Text
y -> CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
x ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
y)
CslQuoted CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslItalic CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslNormal CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNormal ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslBold CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBold ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslUnderline CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslUnderline ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslNoDecoration CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoDecoration ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslSmallCaps CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSmallCaps ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslBaseline CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBaseline ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslSub CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSub ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslSup CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslNoCase CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoCase ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
CslDiv Text
t CslJson Text
x -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
t ((Char -> Bool) -> CslJson Text -> CslJson Text
dropTextWhileEnd' Char -> Bool
f CslJson Text
x)
parseCslJson :: Locale -> Text -> CslJson Text
parseCslJson :: Locale -> Text -> CslJson Text
parseCslJson Locale
locale Text
t =
case Parser [CslJson Text] -> Text -> Either String [CslJson Text]
forall a. Parser a -> Text -> Either String a
P.parseOnly
(Parser Text (CslJson Text) -> Parser [CslJson Text]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
P.many' (Locale -> Parser Text (CslJson Text)
pCslJson Locale
locale) Parser [CslJson Text] -> Parser Text () -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text ()
forall t. Chunk t => Parser t ()
P.endOfInput) Text
t of
Left String
_ -> Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
t
Right [CslJson Text]
xs -> [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat [CslJson Text]
xs
pCslJson :: Locale -> P.Parser (CslJson Text)
pCslJson :: Locale -> Parser Text (CslJson Text)
pCslJson Locale
locale = [Parser Text (CslJson Text)] -> Parser Text (CslJson Text)
forall (f :: * -> *) a. Alternative f => [f a] -> f a
P.choice
[ Parser Text (CslJson Text)
pCslText
, Parser Text (CslJson Text)
pCslQuoted
, Parser Text (CslJson Text)
pCslItalic
, Parser Text (CslJson Text)
pCslBold
, Parser Text (CslJson Text)
pCslUnderline
, Parser Text (CslJson Text)
pCslNoDecoration
, Parser Text (CslJson Text)
pCslSmallCaps
, Parser Text (CslJson Text)
pCslSup
, Parser Text (CslJson Text)
pCslSub
, Parser Text (CslJson Text)
pCslBaseline
, Parser Text (CslJson Text)
pCslNoCase
, Parser Text (CslJson Text)
pCslSymbol
]
where
((Text
outerOpenQuote, Text
outerCloseQuote), (Text
innerOpenQuote, Text
innerCloseQuote)) =
((Text, Text), (Text, Text))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a. a -> Maybe a -> a
fromMaybe ((Text
"\x201C",Text
"\x201D"),(Text
"\x2018",Text
"\x2019")) (Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text)))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a b. (a -> b) -> a -> b
$ Locale -> Maybe ((Text, Text), (Text, Text))
lookupQuotes Locale
locale
isSpecialChar :: Char -> Bool
isSpecialChar 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
'"' Bool -> Bool -> Bool
||
Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'’' Bool -> Bool -> Bool
|| (Bool -> Bool
not (Char -> Bool
isAscii Char
c) Bool -> Bool -> Bool
&& (Char -> Bool
isSuperscriptChar Char
c Bool -> Bool -> Bool
|| Char -> Bool
isQuoteChar Char
c))
isQuoteChar :: Char -> Bool
isQuoteChar = String -> Char -> Bool
P.inClass
(Text -> String
T.unpack (Text
outerOpenQuote Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
outerCloseQuote Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
innerOpenQuote Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
innerCloseQuote))
isSuperscriptChar :: Char -> Bool
isSuperscriptChar = String -> Char -> Bool
P.inClass String
superscriptChars
isApostrophe :: Char -> Bool
isApostrophe Char
'\'' = Bool
True
isApostrophe Char
'’' = Bool
True
isApostrophe Char
_ = Bool
False
pCsl :: Parser Text (CslJson Text)
pCsl = Locale -> Parser Text (CslJson Text)
pCslJson Locale
locale
notFollowedBySpace :: Parser Text ()
notFollowedBySpace =
Parser Char
P.peekChar' Parser Char -> (Char -> Parser Text ()) -> Parser Text ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Bool -> Parser Text ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Parser Text ())
-> (Char -> Bool) -> Char -> Parser Text ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpaceChar
isSpaceChar :: Char -> Bool
isSpaceChar = String -> Char -> Bool
P.inClass [Char
' ',Char
'\t',Char
'\n',Char
'\r']
pOpenQuote :: Parser Text Text
pOpenQuote = ((Text
"\"" Text -> Parser Char -> Parser Text Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Parser Char
P.char Char
'"')
Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text
"'" Text -> Parser Char -> Parser Text Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> Parser Char
P.char Char
'\'')
Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text
outerCloseQuote Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser Text Text
P.string Text
outerOpenQuote)
Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Text
innerCloseQuote Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> Parser Text Text
P.string Text
innerOpenQuote))
Parser Text Text -> Parser Text () -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser Text ()
notFollowedBySpace
pSpace :: Parser Text ()
pSpace = (Char -> Bool) -> Parser Text ()
P.skipWhile Char -> Bool
isSpaceChar
pCslText :: Parser Text (CslJson Text)
pCslText = Text -> CslJson Text
forall a. a -> CslJson a
CslText (Text -> CslJson Text) -> (Text -> Text) -> Text -> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
addNarrowSpace (Text -> CslJson Text)
-> Parser Text Text -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
( do Text
t <- (Char -> Bool) -> Parser Text Text
P.takeWhile1 (\Char
c -> Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isSpecialChar Char
c))
Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => a -> f a -> f a
P.option Text
t (Parser Text Text -> Parser Text Text)
-> Parser Text Text -> Parser Text Text
forall a b. (a -> b) -> a -> b
$ do Char
_ <- (Char -> Bool) -> Parser Char
P.satisfy Char -> Bool
isApostrophe
Text
t' <- (Char -> Bool) -> Parser Text Text
P.takeWhile1 Char -> Bool
isAlphaNum
Text -> Parser Text Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"’" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t')
Parser Text Text -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
((Char -> Bool) -> Parser Text Text
P.takeWhile1 (\Char
c -> Bool -> Bool
not (Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char -> Bool
isSpecialChar Char
c))) )
pCslQuoted :: Parser Text (CslJson Text)
pCslQuoted = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted (CslJson Text -> CslJson Text)
-> Parser Text (CslJson Text) -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
do Text
cl <- Parser Text Text
pOpenQuote
Maybe Char
mbc <- Parser (Maybe Char)
peekChar
case Maybe Char
mbc of
Just Char
c | Char -> Text
T.singleton Char
c Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
cl -> String -> Parser Text ()
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"unexpected close quote"
Maybe Char
_ -> () -> Parser Text ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
[CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
cl)
pCslSymbol :: Parser Text (CslJson Text)
pCslSymbol = do
Char
c <- (Char -> Bool) -> Parser Char
P.satisfy Char -> Bool
isSpecialChar
CslJson Text -> Parser Text (CslJson Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (CslJson Text -> Parser Text (CslJson Text))
-> CslJson Text -> Parser Text (CslJson Text)
forall a b. (a -> b) -> a -> b
$
if Char -> Bool
isApostrophe Char
c
then Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"’"
else Char -> CslJson Text
charToSup Char
c
pCslItalic :: Parser Text (CslJson Text)
pCslItalic = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<i>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</i>"))
pCslBold :: Parser Text (CslJson Text)
pCslBold = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBold (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<b>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</b>"))
pCslUnderline :: Parser Text (CslJson Text)
pCslUnderline = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslUnderline (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<u>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</u>"))
pCslNoDecoration :: Parser Text (CslJson Text)
pCslNoDecoration = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoDecoration (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<span" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Text -> Parser Text Text
P.string Text
"class=\"nodecor\"" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Char -> Parser Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> Parser Char
P.char Char
'>' Parser Char -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</span>"))
pCslSup :: Parser Text (CslJson Text)
pCslSup = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<sup>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</sup>"))
pCslSub :: Parser Text (CslJson Text)
pCslSub = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSub (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<sub>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</sub>"))
pCslBaseline :: Parser Text (CslJson Text)
pCslBaseline = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBaseline (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<span" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> Parser Text Text
P.string Text
"style=\"baseline\">" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</span>"))
pCslSmallCaps :: Parser Text (CslJson Text)
pCslSmallCaps = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSmallCaps (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
((Text -> Parser Text Text
P.string Text
"<span" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Text -> Parser Text Text
P.string Text
"style=\"font-variant:" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Text -> Parser Text Text
P.string Text
"small-caps;" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Char -> Parser Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> Parser Char
P.char Char
'"' Parser Char -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Parser Text ()
pSpace Parser Text () -> Parser Char -> Parser Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> Parser Char
P.char Char
'>' Parser Char -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</span>"))
Parser [CslJson Text]
-> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(Text -> Parser Text Text
P.string Text
"<sc>" Parser Text Text -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</sc>")))
pCslNoCase :: Parser Text (CslJson Text)
pCslNoCase = CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoCase (CslJson Text -> CslJson Text)
-> ([CslJson Text] -> CslJson Text)
-> [CslJson Text]
-> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [CslJson Text] -> CslJson Text
forall a. Monoid a => [a] -> a
mconcat ([CslJson Text] -> CslJson Text)
-> Parser [CslJson Text] -> Parser Text (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(Text -> Parser Text Text
P.string Text
"<span" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Text Text -> Parser Text Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Text -> Parser Text Text
P.string Text
"class=\"nocase\"" Parser Text Text -> Parser Text () -> Parser Text ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser Text ()
pSpace Parser Text () -> Parser Char -> Parser Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Char -> Parser Char
P.char Char
'>' Parser Char -> Parser [CslJson Text] -> Parser [CslJson Text]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
Parser Text (CslJson Text)
-> Parser Text Text -> Parser [CslJson Text]
forall (m :: * -> *) a b. MonadPlus m => m a -> m b -> m [a]
P.manyTill' Parser Text (CslJson Text)
pCsl (Text -> Parser Text Text
P.string Text
"</span>"))
addNarrowSpace :: Text -> Text
addNarrowSpace =
Text -> Text -> Text -> Text
T.replace Text
" ;" Text
"\x202F;" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
" ?" Text
"\x202F?" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
" !" Text
"\x202F!" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
" »" Text
"\x202F»" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"« " Text
"«\x202F"
data RenderContext =
RenderContext
{ RenderContext -> Bool
useOuterQuotes :: Bool
, RenderContext -> Bool
useItalics :: Bool
, RenderContext -> Bool
useBold :: Bool
, RenderContext -> Bool
useSmallCaps :: Bool
} deriving (Int -> RenderContext -> ShowS
[RenderContext] -> ShowS
RenderContext -> String
(Int -> RenderContext -> ShowS)
-> (RenderContext -> String)
-> ([RenderContext] -> ShowS)
-> Show RenderContext
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RenderContext] -> ShowS
$cshowList :: [RenderContext] -> ShowS
show :: RenderContext -> String
$cshow :: RenderContext -> String
showsPrec :: Int -> RenderContext -> ShowS
$cshowsPrec :: Int -> RenderContext -> ShowS
Show, RenderContext -> RenderContext -> Bool
(RenderContext -> RenderContext -> Bool)
-> (RenderContext -> RenderContext -> Bool) -> Eq RenderContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RenderContext -> RenderContext -> Bool
$c/= :: RenderContext -> RenderContext -> Bool
== :: RenderContext -> RenderContext -> Bool
$c== :: RenderContext -> RenderContext -> Bool
Eq)
lookupTerm :: Locale -> Text -> Maybe Text
lookupTerm :: Locale -> Text -> Maybe Text
lookupTerm Locale
locale Text
termname = do
let terms :: Map Text [(Term, Text)]
terms = Locale -> Map Text [(Term, Text)]
localeTerms Locale
locale
case Text -> Map Text [(Term, Text)] -> Maybe [(Term, Text)]
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
termname Map Text [(Term, Text)]
terms of
Just ((Term
_,Text
t):[(Term, Text)]
_) -> Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t
Maybe [(Term, Text)]
_ -> Maybe Text
forall a. Maybe a
Nothing
lookupQuotes :: Locale -> Maybe ((Text, Text), (Text, Text))
lookupQuotes :: Locale -> Maybe ((Text, Text), (Text, Text))
lookupQuotes Locale
locale = do
(Text, Text)
outerQuotes <- (,) (Text -> Text -> (Text, Text))
-> Maybe Text -> Maybe (Text -> (Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Locale -> Text -> Maybe Text
lookupTerm Locale
locale Text
"open-quote"
Maybe (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Locale -> Text -> Maybe Text
lookupTerm Locale
locale Text
"close-quote"
(Text, Text)
innerQuotes <- (,) (Text -> Text -> (Text, Text))
-> Maybe Text -> Maybe (Text -> (Text, Text))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Locale -> Text -> Maybe Text
lookupTerm Locale
locale Text
"open-inner-quote"
Maybe (Text -> (Text, Text)) -> Maybe Text -> Maybe (Text, Text)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Locale -> Text -> Maybe Text
lookupTerm Locale
locale Text
"close-inner-quote"
((Text, Text), (Text, Text)) -> Maybe ((Text, Text), (Text, Text))
forall (m :: * -> *) a. Monad m => a -> m a
return ((Text, Text)
outerQuotes, (Text, Text)
innerQuotes)
renderCslJson :: Bool
-> Locale
-> CslJson Text
-> Text
renderCslJson :: Bool -> Locale -> CslJson Text -> Text
renderCslJson Bool
useEntities Locale
locale =
RenderContext -> CslJson Text -> Text
go (Bool -> Bool -> Bool -> Bool -> RenderContext
RenderContext Bool
True Bool
True Bool
True Bool
True)
where
((Text, Text)
outerQuotes, (Text, Text)
innerQuotes) = ((Text, Text), (Text, Text))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a. a -> Maybe a -> a
fromMaybe ((Text
"\"",Text
"\""),(Text
"'",Text
"'"))
(Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text)))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a b. (a -> b) -> a -> b
$ Locale -> Maybe ((Text, Text), (Text, Text))
lookupQuotes Locale
locale
go :: RenderContext -> CslJson Text -> Text
go :: RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
el =
case CslJson Text
el of
CslText Text
t -> Text -> Text
escape Text
t
CslJson Text
CslEmpty -> Text
forall a. Monoid a => a
mempty
CslConcat CslJson Text
x CslJson Text
y -> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
y
CslQuoted CslJson Text
x
| RenderContext -> Bool
useOuterQuotes RenderContext
ctx
-> (Text, Text) -> Text
forall a b. (a, b) -> a
fst (Text, Text)
outerQuotes Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useOuterQuotes :: Bool
useOuterQuotes = Bool
False } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(Text, Text) -> Text
forall a b. (a, b) -> b
snd (Text, Text)
outerQuotes
| Bool
otherwise
-> (Text, Text) -> Text
forall a b. (a, b) -> a
fst (Text, Text)
innerQuotes Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useOuterQuotes :: Bool
useOuterQuotes = Bool
True } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(Text, Text) -> Text
forall a b. (a, b) -> b
snd (Text, Text)
innerQuotes
CslNormal CslJson Text
x
| RenderContext -> Bool
useItalics RenderContext
ctx -> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x
| Bool
otherwise -> Text
"<span style=\"font-style:normal;\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslItalic CslJson Text
x
| RenderContext -> Bool
useItalics RenderContext
ctx -> Text
"<i>" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useItalics :: Bool
useItalics = Bool
False } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</i>"
| Bool
otherwise -> Text
"<span style=\"font-style:normal;\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useItalics :: Bool
useItalics = Bool
True } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslBold CslJson Text
x
| RenderContext -> Bool
useBold RenderContext
ctx -> Text
"<b>" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useBold :: Bool
useBold = Bool
False } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</b>"
| Bool
otherwise -> Text
"<span style=\"font-weight:normal;\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useBold :: Bool
useBold = Bool
True } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslUnderline CslJson Text
x -> Text
"<u>" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</u>"
CslNoDecoration CslJson Text
x -> Text
"<span style=\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(if RenderContext -> Bool
useSmallCaps RenderContext
ctx
then Text
""
else Text
"font-variant:normal;") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(if RenderContext -> Bool
useBold RenderContext
ctx
then Text
""
else Text
"font-weight:normal;") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
(if RenderContext -> Bool
useItalics RenderContext
ctx
then Text
""
else Text
"font-style:normal;") Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslSmallCaps CslJson Text
x
| RenderContext -> Bool
useSmallCaps RenderContext
ctx -> Text
"<span style=\"font-variant:small-caps;\">"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useSmallCaps :: Bool
useSmallCaps = Bool
False } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"</span>"
| Bool
otherwise -> Text
"<span style=\"font-variant:normal;\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> Text
go RenderContext
ctx{ useSmallCaps :: Bool
useSmallCaps = Bool
True } CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslSup CslJson Text
x -> Text
"<sup>" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</sup>"
CslSub CslJson Text
x -> Text
"<sub>" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</sub>"
CslBaseline CslJson Text
x -> Text
"<span style=\"baseline\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</span>"
CslDiv Text
t CslJson Text
x -> Text
"<div class=\"csl-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\">" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"</div>"
CslNoCase CslJson Text
x -> RenderContext -> CslJson Text -> Text
go RenderContext
ctx CslJson Text
x
escape :: Text -> Text
escape Text
t
| Bool
useEntities
= case (Char -> Bool) -> Text -> Maybe Int
T.findIndex (\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
t of
Just Int
_ -> Text -> Text -> Text -> Text
T.replace Text
"<" Text
"<" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
">" Text
">" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Text -> Text
T.replace Text
"&" Text
"&" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
t
Maybe Int
Nothing -> Text
t
| Bool
otherwise = Text
t
cslJsonToJson :: Locale -> CslJson Text -> [Value]
cslJsonToJson :: Locale -> CslJson Text -> [Value]
cslJsonToJson Locale
locale = RenderContext -> CslJson Text -> [Value]
go (Bool -> Bool -> Bool -> Bool -> RenderContext
RenderContext Bool
True Bool
True Bool
True Bool
True)
where
((Text, Text)
outerQuotes, (Text, Text)
innerQuotes) = ((Text, Text), (Text, Text))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a. a -> Maybe a -> a
fromMaybe
((Text
"\"",Text
"\""),(Text
"'",Text
"'")) (Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text)))
-> Maybe ((Text, Text), (Text, Text))
-> ((Text, Text), (Text, Text))
forall a b. (a -> b) -> a -> b
$ Locale -> Maybe ((Text, Text), (Text, Text))
lookupQuotes Locale
locale
isString :: Value -> Bool
isString (String Text
_) = Bool
True
isString Value
_ = Bool
False
consolidateStrings :: [Value] -> [Value]
consolidateStrings :: [Value] -> [Value]
consolidateStrings [] = []
consolidateStrings (String Text
t : [Value]
rest) =
let ([Value]
xs,[Value]
ys) = (Value -> Bool) -> [Value] -> ([Value], [Value])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span Value -> Bool
isString [Value]
rest
in Text -> Value
String (Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
t' | String Text
t' <- [Value]
xs]) Value -> [Value] -> [Value]
forall a. a -> [a] -> [a]
:
[Value] -> [Value]
consolidateStrings [Value]
ys
consolidateStrings (Value
x : [Value]
rest) =
Value
x Value -> [Value] -> [Value]
forall a. a -> [a] -> [a]
: [Value] -> [Value]
consolidateStrings [Value]
rest
go :: RenderContext -> CslJson Text -> [Value]
go :: RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
el = [Value] -> [Value]
consolidateStrings ([Value] -> [Value]) -> [Value] -> [Value]
forall a b. (a -> b) -> a -> b
$
case CslJson Text
el of
CslText Text
t -> [Text -> Value
String Text
t]
CslJson Text
CslEmpty -> []
CslConcat CslJson Text
x CslJson Text
CslEmpty -> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x
CslConcat (CslConcat CslJson Text
x CslJson Text
y) CslJson Text
z -> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx (CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
x (CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
y CslJson Text
z))
CslConcat CslJson Text
x CslJson Text
y -> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x [Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
y
CslQuoted CslJson Text
x
| RenderContext -> Bool
useOuterQuotes RenderContext
ctx
-> [Text -> Value
String ((Text, Text) -> Text
forall a b. (a, b) -> a
fst (Text, Text)
outerQuotes)] [Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useOuterQuotes :: Bool
useOuterQuotes = Bool
False } CslJson Text
x [Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<>
[Text -> Value
String ((Text, Text) -> Text
forall a b. (a, b) -> b
snd (Text, Text)
outerQuotes)]
| Bool
otherwise
-> [Text -> Value
String ((Text, Text) -> Text
forall a b. (a, b) -> a
fst (Text, Text)
innerQuotes)] [Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<>
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useOuterQuotes :: Bool
useOuterQuotes = Bool
True } CslJson Text
x [Value] -> [Value] -> [Value]
forall a. Semigroup a => a -> a -> a
<>
[Text -> Value
String ((Text, Text) -> Text
forall a b. (a, b) -> b
snd (Text, Text)
innerQuotes)]
CslNormal CslJson Text
x
| RenderContext -> Bool
useItalics RenderContext
ctx -> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x
| Bool
otherwise -> [ [Pair] -> Value
object
[ (Text
"format", Value
"no-italics")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslItalic CslJson Text
x
| RenderContext -> Bool
useItalics RenderContext
ctx -> [ [Pair] -> Value
object
[ (Text
"format", Value
"italics")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useItalics :: Bool
useItalics = Bool
False } CslJson Text
x)
]
]
| Bool
otherwise -> [ [Pair] -> Value
object
[ (Text
"format", Value
"no-italics")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useItalics :: Bool
useItalics = Bool
False } CslJson Text
x)
]
]
CslBold CslJson Text
x
| RenderContext -> Bool
useItalics RenderContext
ctx -> [ [Pair] -> Value
object
[ (Text
"format", Value
"bold")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useBold :: Bool
useBold = Bool
False } CslJson Text
x)
]
]
| Bool
otherwise -> [ [Pair] -> Value
object
[ (Text
"format", Value
"no-bold")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useBold :: Bool
useBold = Bool
False } CslJson Text
x)
]
]
CslUnderline CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"underline")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslNoDecoration CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"no-decoration")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslSmallCaps CslJson Text
x
| RenderContext -> Bool
useSmallCaps RenderContext
ctx -> [ [Pair] -> Value
object
[ (Text
"format", Value
"small-caps")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useSmallCaps :: Bool
useSmallCaps = Bool
False } CslJson Text
x)
]
]
| Bool
otherwise -> [ [Pair] -> Value
object
[ (Text
"format", Value
"no-small-caps")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$
RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx{ useSmallCaps :: Bool
useSmallCaps = Bool
False } CslJson Text
x)
]
]
CslSup CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"superscript")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslSub CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"subscript")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslBaseline CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"baseline")
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslDiv Text
t CslJson Text
x -> [ [Pair] -> Value
object
[ (Text
"format", Value
"div")
, (Text
"class", Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ Text
"csl-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t)
, (Text
"contents", [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ([Value] -> Value) -> [Value] -> Value
forall a b. (a -> b) -> a -> b
$ RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x)
]
]
CslNoCase CslJson Text
x -> RenderContext -> CslJson Text -> [Value]
go RenderContext
ctx CslJson Text
x
caseTransform' :: (CaseTransformState -> Text -> Text)
-> Int
-> CslJson Text
-> State CaseTransformState (CslJson Text)
caseTransform' :: (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f Int
lev CslJson Text
el =
case CslJson Text
el of
CslText Text
x -> Text -> CslJson Text
forall a. a -> CslJson a
CslText (Text -> CslJson Text)
-> ([Text] -> Text) -> [Text] -> CslJson Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> CslJson Text)
-> StateT CaseTransformState Identity [Text]
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> StateT CaseTransformState Identity Text)
-> [Text] -> StateT CaseTransformState Identity [Text]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Text -> StateT CaseTransformState Identity Text
g (Text -> [Text]
splitUp Text
x)
CslConcat CslJson Text
x CslJson Text
y -> do
CslJson Text
x' <- (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f Int
lev CslJson Text
x
let lastWord :: Bool
lastWord = Int
lev Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 Bool -> Bool -> Bool
&& Bool -> Bool
not (CslJson Text -> Bool
hasWordBreak CslJson Text
y)
CaseTransformState
st <- StateT CaseTransformState Identity CaseTransformState
forall (m :: * -> *) s. Monad m => StateT s m s
get
Bool
-> StateT CaseTransformState Identity ()
-> StateT CaseTransformState Identity ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
lastWord Bool -> Bool -> Bool
&&
(CaseTransformState
st CaseTransformState -> CaseTransformState -> Bool
forall a. Eq a => a -> a -> Bool
== CaseTransformState
AfterWordEnd Bool -> Bool -> Bool
|| CaseTransformState
st CaseTransformState -> CaseTransformState -> Bool
forall a. Eq a => a -> a -> Bool
== CaseTransformState
StartSentence Bool -> Bool -> Bool
|| CaseTransformState
st CaseTransformState -> CaseTransformState -> Bool
forall a. Eq a => a -> a -> Bool
== CaseTransformState
Start)) (StateT CaseTransformState Identity ()
-> StateT CaseTransformState Identity ())
-> StateT CaseTransformState Identity ()
-> StateT CaseTransformState Identity ()
forall a b. (a -> b) -> a -> b
$
CaseTransformState -> StateT CaseTransformState Identity ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put CaseTransformState
BeforeLastWord
CslJson Text
y' <- (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f Int
lev CslJson Text
y
CslJson Text -> State CaseTransformState (CslJson Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (CslJson Text -> State CaseTransformState (CslJson Text))
-> CslJson Text -> State CaseTransformState (CslJson Text)
forall a b. (a -> b) -> a -> b
$ CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
x' CslJson Text
y'
CslQuoted CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted (CslJson Text -> CslJson Text)
-> State CaseTransformState (CslJson Text)
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) CslJson Text
x
CslItalic CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic (CslJson Text -> CslJson Text)
-> State CaseTransformState (CslJson Text)
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) CslJson Text
x
CslNormal CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNormal (CslJson Text -> CslJson Text)
-> State CaseTransformState (CslJson Text)
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) CslJson Text
x
CslBold CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBold (CslJson Text -> CslJson Text)
-> State CaseTransformState (CslJson Text)
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) CslJson Text
x
CslUnderline CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslUnderline (CslJson Text -> CslJson Text)
-> State CaseTransformState (CslJson Text)
-> State CaseTransformState (CslJson Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' CaseTransformState -> Text -> Text
f (Int
lev Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) CslJson Text
x
CslNoDecoration CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslSmallCaps CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslBaseline CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslSub CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslSup CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslNoCase CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslDiv Text
_ CslJson Text
_ -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
CslJson Text
CslEmpty -> CslJson Text -> State CaseTransformState (CslJson Text)
forall a.
CiteprocOutput a =>
a -> StateT CaseTransformState Identity a
return' CslJson Text
el
where
return' :: a -> StateT CaseTransformState Identity a
return' a
x = a
x a
-> StateT CaseTransformState Identity Text
-> StateT CaseTransformState Identity a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> StateT CaseTransformState Identity Text
g (a -> Text
forall a. CiteprocOutput a => a -> Text
toText a
x)
g :: Text -> State CaseTransformState Text
g :: Text -> StateT CaseTransformState Identity Text
g Text
t = do
CaseTransformState
st <- StateT CaseTransformState Identity CaseTransformState
forall (m :: * -> *) s. Monad m => StateT s m s
get
CaseTransformState -> StateT CaseTransformState Identity ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put (CaseTransformState -> StateT CaseTransformState Identity ())
-> CaseTransformState -> StateT CaseTransformState Identity ()
forall a b. (a -> b) -> a -> b
$ case Text -> Maybe (Text, Char)
T.unsnoc Text
t of
Maybe (Text, Char)
Nothing -> CaseTransformState
st
Just (Text
_,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
':' ->
CaseTransformState
AfterSentenceEndingPunctuation
| Char -> Bool
isAlphaNum Char
c -> CaseTransformState
AfterWordChar
| Char -> Bool
isSpace Char
c
, CaseTransformState
st CaseTransformState -> CaseTransformState -> Bool
forall a. Eq a => a -> a -> Bool
== CaseTransformState
AfterSentenceEndingPunctuation -> CaseTransformState
StartSentence
| Char -> Bool
isWordBreak Char
c -> CaseTransformState
AfterWordEnd
| Bool
otherwise -> CaseTransformState
st
Text -> StateT CaseTransformState Identity Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> StateT CaseTransformState Identity Text)
-> Text -> StateT CaseTransformState Identity Text
forall a b. (a -> b) -> a -> b
$
if (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isAlphaNum Text
t
then CaseTransformState -> Text -> Text
f CaseTransformState
st Text
t
else Text
t
isWordBreak :: Char -> Bool
isWordBreak Char
'-' = Bool
True
isWordBreak Char
'/' = Bool
True
isWordBreak Char
'\x2013' = Bool
True
isWordBreak Char
'\x2014' = Bool
True
isWordBreak Char
c = Char -> Bool
isSpace Char
c
hasWordBreak :: CslJson Text -> Bool
hasWordBreak = (Text -> Bool) -> CslJson Text -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Char -> Bool) -> Text -> Bool
T.any Char -> Bool
isWordBreak)
splitUp :: Text -> [Text]
splitUp = (Char -> Char -> Bool) -> Text -> [Text]
T.groupBy Char -> Char -> Bool
sameType
sameType :: Char -> Char -> Bool
sameType Char
c Char
d =
(Char -> Bool
isAscii Char
c Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
&& Char -> Bool
isAscii Char
d Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
d) Bool -> Bool -> Bool
||
(Bool -> Bool
not (Char -> Bool
isAscii Char
c) Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isAscii Char
d) Bool -> Bool -> Bool
&& Char -> Bool
isAlphaNum Char
d) Bool -> Bool -> Bool
||
(Char -> Bool
isSpace Char
c Bool -> Bool -> Bool
&& Char -> Bool
isSpace Char
d)
caseTransform :: Maybe Lang
-> CaseTransformer
-> CslJson Text
-> CslJson Text
caseTransform :: Maybe Lang -> CaseTransformer -> CslJson Text -> CslJson Text
caseTransform Maybe Lang
mblang CaseTransformer
f CslJson Text
x =
State CaseTransformState (CslJson Text)
-> CaseTransformState -> CslJson Text
forall s a. State s a -> s -> a
evalState ((CaseTransformState -> Text -> Text)
-> Int -> CslJson Text -> State CaseTransformState (CslJson Text)
caseTransform' (CaseTransformer -> Maybe Lang -> CaseTransformState -> Text -> Text
unCaseTransformer CaseTransformer
f Maybe Lang
mblang) Int
0 CslJson Text
x) CaseTransformState
Start
punctuationInsideQuotes :: CslJson Text -> CslJson Text
punctuationInsideQuotes :: CslJson Text -> CslJson Text
punctuationInsideQuotes = CslJson Text -> CslJson Text
go
where
startsWithMovable :: Text -> Bool
startsWithMovable Text
t =
case Text -> Maybe (Char, Text)
T.uncons Text
t 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
'!' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'?'
Maybe (Char, Text)
Nothing -> Bool
False
go :: CslJson Text -> CslJson Text
go CslJson Text
el =
case CslJson Text
el of
CslConcat CslJson Text
CslEmpty CslJson Text
x -> CslJson Text -> CslJson Text
go CslJson Text
x
CslConcat CslJson Text
x CslJson Text
CslEmpty -> CslJson Text -> CslJson Text
go CslJson Text
x
CslConcat (CslQuoted CslJson Text
x) CslJson Text
y ->
case CslJson Text -> CslJson Text
go CslJson Text
y of
(CslText Text
t) | Text -> Bool
startsWithMovable Text
t
-> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted (CslJson Text -> CslJson Text
go (CslJson Text
x CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> Text -> CslJson Text
forall a. a -> CslJson a
CslText (Int -> Text -> Text
T.take Int
1 Text
t)))
CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> Text -> CslJson Text
forall a. a -> CslJson a
CslText (Int -> Text -> Text
T.drop Int
1 Text
t)
(CslConcat (CslText Text
t) CslJson Text
z) | Text -> Bool
startsWithMovable Text
t
-> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted (CslJson Text -> CslJson Text
go (CslJson Text
x CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> Text -> CslJson Text
forall a. a -> CslJson a
CslText (Int -> Text -> Text
T.take Int
1 Text
t))) CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<>
Text -> CslJson Text
forall a. a -> CslJson a
CslText (Int -> Text -> Text
T.drop Int
1 Text
t) CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> CslJson Text
z
CslJson Text
z -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted CslJson Text
x CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> CslJson Text
z
CslConcat (CslConcat CslJson Text
x CslJson Text
y) CslJson Text
z -> CslJson Text -> CslJson Text
go (CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
x (CslJson Text -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a -> CslJson a
CslConcat CslJson Text
y CslJson Text
z))
CslConcat CslJson Text
x CslJson Text
y -> CslJson Text -> CslJson Text
go CslJson Text
x CslJson Text -> CslJson Text -> CslJson Text
forall a. Semigroup a => a -> a -> a
<> CslJson Text -> CslJson Text
go CslJson Text
y
CslQuoted CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslQuoted (CslJson Text -> CslJson Text
go CslJson Text
x)
CslItalic CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslItalic (CslJson Text -> CslJson Text
go CslJson Text
x)
CslNormal CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNormal (CslJson Text -> CslJson Text
go CslJson Text
x)
CslBold CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBold (CslJson Text -> CslJson Text
go CslJson Text
x)
CslUnderline CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslUnderline (CslJson Text -> CslJson Text
go CslJson Text
x)
CslNoDecoration CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoDecoration (CslJson Text -> CslJson Text
go CslJson Text
x)
CslSmallCaps CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSmallCaps (CslJson Text -> CslJson Text
go CslJson Text
x)
CslSup CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (CslJson Text -> CslJson Text
go CslJson Text
x)
CslSub CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSub (CslJson Text -> CslJson Text
go CslJson Text
x)
CslBaseline CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslBaseline (CslJson Text -> CslJson Text
go CslJson Text
x)
CslNoCase CslJson Text
x -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslNoCase (CslJson Text -> CslJson Text
go CslJson Text
x)
CslDiv Text
t CslJson Text
x -> Text -> CslJson Text -> CslJson Text
forall a. Text -> CslJson a -> CslJson a
CslDiv Text
t (CslJson Text -> CslJson Text
go CslJson Text
x)
CslText Text
t -> Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
t
CslJson Text
CslEmpty -> CslJson Text
forall a. CslJson a
CslEmpty
superscriptChars :: [Char]
superscriptChars :: String
superscriptChars =
[ Char
'\x00AA'
, Char
'\x00B2'
, Char
'\x00B3'
, Char
'\x00B9'
, Char
'\x00BA'
, Char
'\x02B0'
, Char
'\x02B1'
, Char
'\x02B2'
, Char
'\x02B3'
, Char
'\x02B4'
, Char
'\x02B5'
, Char
'\x02B6'
, Char
'\x02B7'
, Char
'\x02B8'
, Char
'\x02E0'
, Char
'\x02E1'
, Char
'\x02E2'
, Char
'\x02E3'
, Char
'\x02E4'
, Char
'\x1D2C'
, Char
'\x1D2D'
, Char
'\x1D2E'
, Char
'\x1D30'
, Char
'\x1D31'
, Char
'\x1D32'
, Char
'\x1D33'
, Char
'\x1D34'
, Char
'\x1D35'
, Char
'\x1D36'
, Char
'\x1D37'
, Char
'\x1D38'
, Char
'\x1D39'
, Char
'\x1D3A'
, Char
'\x1D3C'
, Char
'\x1D3D'
, Char
'\x1D3E'
, Char
'\x1D3F'
, Char
'\x1D40'
, Char
'\x1D41'
, Char
'\x1D42'
, Char
'\x1D43'
, Char
'\x1D44'
, Char
'\x1D45'
, Char
'\x1D46'
, Char
'\x1D47'
, Char
'\x1D48'
, Char
'\x1D49'
, Char
'\x1D4A'
, Char
'\x1D4B'
, Char
'\x1D4C'
, Char
'\x1D4D'
, Char
'\x1D4F'
, Char
'\x1D50'
, Char
'\x1D51'
, Char
'\x1D52'
, Char
'\x1D53'
, Char
'\x1D54'
, Char
'\x1D55'
, Char
'\x1D56'
, Char
'\x1D57'
, Char
'\x1D58'
, Char
'\x1D59'
, Char
'\x1D5A'
, Char
'\x1D5B'
, Char
'\x1D5C'
, Char
'\x1D5D'
, Char
'\x1D5E'
, Char
'\x1D5F'
, Char
'\x1D60'
, Char
'\x1D61'
, Char
'\x2070'
, Char
'\x2071'
, Char
'\x2074'
, Char
'\x2075'
, Char
'\x2076'
, Char
'\x2077'
, Char
'\x2078'
, Char
'\x2079'
, Char
'\x207A'
, Char
'\x207B'
, Char
'\x207C'
, Char
'\x207D'
, Char
'\x207E'
, Char
'\x207F'
, Char
'\x2120'
, Char
'\x2122'
, Char
'\x3192'
, Char
'\x3193'
, Char
'\x3194'
, Char
'\x3195'
, Char
'\x3196'
, Char
'\x3197'
, Char
'\x3198'
, Char
'\x3199'
, Char
'\x319A'
, Char
'\x319B'
, Char
'\x319C'
, Char
'\x319D'
, Char
'\x319E'
, Char
'\x319F'
, Char
'\x02C0'
, Char
'\x02C1'
, Char
'\x06E5'
, Char
'\x06E6'
]
charToSup :: Char -> CslJson Text
charToSup :: Char -> CslJson Text
charToSup Char
c =
case Char
c of
Char
'\x00AA' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0061")
Char
'\x00B2' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0032")
Char
'\x00B3' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0033")
Char
'\x00B9' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0031")
Char
'\x00BA' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006F")
Char
'\x02B0' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0068")
Char
'\x02B1' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0266")
Char
'\x02B2' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006A")
Char
'\x02B3' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0072")
Char
'\x02B4' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0279")
Char
'\x02B5' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x027B")
Char
'\x02B6' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0281")
Char
'\x02B7' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0077")
Char
'\x02B8' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0079")
Char
'\x02E0' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0263")
Char
'\x02E1' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006C")
Char
'\x02E2' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0073")
Char
'\x02E3' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0078")
Char
'\x02E4' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0295")
Char
'\x1D2C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0041")
Char
'\x1D2D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x00C6")
Char
'\x1D2E' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0042")
Char
'\x1D30' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0044")
Char
'\x1D31' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0045")
Char
'\x1D32' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x018E")
Char
'\x1D33' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0047")
Char
'\x1D34' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0048")
Char
'\x1D35' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0049")
Char
'\x1D36' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004A")
Char
'\x1D37' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004B")
Char
'\x1D38' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004C")
Char
'\x1D39' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004D")
Char
'\x1D3A' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004E")
Char
'\x1D3C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x004F")
Char
'\x1D3D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0222")
Char
'\x1D3E' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0050")
Char
'\x1D3F' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0052")
Char
'\x1D40' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0054")
Char
'\x1D41' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0055")
Char
'\x1D42' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0057")
Char
'\x1D43' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0061")
Char
'\x1D44' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0250")
Char
'\x1D45' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0251")
Char
'\x1D46' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x1D02")
Char
'\x1D47' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0062")
Char
'\x1D48' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0064")
Char
'\x1D49' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0065")
Char
'\x1D4A' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0259")
Char
'\x1D4B' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x025B")
Char
'\x1D4C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x025C")
Char
'\x1D4D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0067")
Char
'\x1D4F' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006B")
Char
'\x1D50' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006D")
Char
'\x1D51' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x014B")
Char
'\x1D52' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006F")
Char
'\x1D53' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0254")
Char
'\x1D54' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x1D16")
Char
'\x1D55' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x1D17")
Char
'\x1D56' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0070")
Char
'\x1D57' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0074")
Char
'\x1D58' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0075")
Char
'\x1D59' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x1D1D")
Char
'\x1D5A' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x026F")
Char
'\x1D5B' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0076")
Char
'\x1D5C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x1D25")
Char
'\x1D5D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x03B2")
Char
'\x1D5E' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x03B3")
Char
'\x1D5F' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x03B4")
Char
'\x1D60' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x03C6")
Char
'\x1D61' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x03C7")
Char
'\x2070' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0030")
Char
'\x2071' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0069")
Char
'\x2074' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0034")
Char
'\x2075' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0035")
Char
'\x2076' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0036")
Char
'\x2077' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0037")
Char
'\x2078' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0038")
Char
'\x2079' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0039")
Char
'\x207A' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x002B")
Char
'\x207B' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x2212")
Char
'\x207C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x003D")
Char
'\x207D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0028")
Char
'\x207E' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0029")
Char
'\x207F' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x006E")
Char
'\x2120' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0053\x004D")
Char
'\x2122' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0054\x004D")
Char
'\x3192' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E00")
Char
'\x3193' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E8C")
Char
'\x3194' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E09")
Char
'\x3195' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x56DB")
Char
'\x3196' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E0A")
Char
'\x3197' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E2D")
Char
'\x3198' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E0B")
Char
'\x3199' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x7532")
Char
'\x319A' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E59")
Char
'\x319B' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E19")
Char
'\x319C' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4E01")
Char
'\x319D' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x5929")
Char
'\x319E' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x5730")
Char
'\x319F' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x4EBA")
Char
'\x02C0' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0294")
Char
'\x02C1' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0295")
Char
'\x06E5' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x0648")
Char
'\x06E6' -> CslJson Text -> CslJson Text
forall a. CslJson a -> CslJson a
CslSup (Text -> CslJson Text
forall a. a -> CslJson a
CslText Text
"\x064A")
Char
_ -> Text -> CslJson Text
forall a. a -> CslJson a
CslText (Text -> CslJson Text) -> Text -> CslJson Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
c