{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Citeproc.Pandoc
()
where
import Text.Pandoc.Definition
import Text.Pandoc.Builder as B
import Text.Pandoc.Walk
import qualified Data.Text as T
import qualified Data.Sequence as Seq
import Data.Text (Text)
import Citeproc.Types
import Citeproc.CaseTransform
import Control.Monad.Trans.State.Strict as S
import Control.Monad (unless, when)
import Data.Functor.Reverse
import Data.Char (isSpace, isAscii, isPunctuation, isAlphaNum)
instance CiteprocOutput Inlines where
toText :: Inlines -> Text
toText = Inlines -> Text
forall a. Walkable Inline a => a -> Text
stringify
fromText :: Text -> Inlines
fromText Text
t = (if Text
" " Text -> Text -> Bool
`T.isPrefixOf` Text
t
then Inlines
B.space
else Inlines
forall a. Monoid a => a
mempty) Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
Text -> Inlines
B.text Text
t Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
(if Text
" " Text -> Text -> Bool
`T.isSuffixOf` Text
t
then Inlines
B.space
else Inlines
forall a. Monoid a => a
mempty)
dropTextWhile :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhile = (Char -> Bool) -> Inlines -> Inlines
dropTextWhile'
dropTextWhileEnd :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhileEnd = (Char -> Bool) -> Inlines -> Inlines
dropTextWhileEnd'
addFontVariant :: FontVariant -> Inlines -> Inlines
addFontVariant FontVariant
x =
case FontVariant
x of
FontVariant
NormalVariant -> Inlines -> Inlines
forall a. a -> a
id
FontVariant
SmallCapsVariant -> Inlines -> Inlines
B.smallcaps
addFontStyle :: FontStyle -> Inlines -> Inlines
addFontStyle FontStyle
x =
case FontStyle
x of
FontStyle
NormalFont -> Inlines -> Inlines
forall a. a -> a
id
FontStyle
ItalicFont -> Inlines -> Inlines
B.emph
FontStyle
ObliqueFont -> Inlines -> Inlines
B.emph
addFontWeight :: FontWeight -> Inlines -> Inlines
addFontWeight FontWeight
x =
case FontWeight
x of
FontWeight
NormalWeight -> Inlines -> Inlines
forall a. a -> a
id
FontWeight
LightWeight -> Inlines -> Inlines
forall a. a -> a
id
FontWeight
BoldWeight -> Inlines -> Inlines
B.strong
addTextDecoration :: TextDecoration -> Inlines -> Inlines
addTextDecoration TextDecoration
x =
case TextDecoration
x of
TextDecoration
NoDecoration -> Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"nodecoration"],[])
TextDecoration
UnderlineDecoration -> Inlines -> Inlines
B.underline
addVerticalAlign :: VerticalAlign -> Inlines -> Inlines
addVerticalAlign VerticalAlign
x =
case VerticalAlign
x of
VerticalAlign
BaselineAlign -> Inlines -> Inlines
forall a. a -> a
id
VerticalAlign
SubAlign -> Inlines -> Inlines
B.subscript
VerticalAlign
SupAlign -> Inlines -> Inlines
B.superscript
addTextCase :: Maybe Lang -> TextCase -> Inlines -> Inlines
addTextCase Maybe Lang
mblang TextCase
x =
case TextCase
x of
TextCase
Lowercase -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withLowercaseAll
TextCase
Uppercase -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withUppercaseAll
TextCase
CapitalizeFirst -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withCapitalizeFirst
TextCase
CapitalizeAll -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withCapitalizeWords
TextCase
SentenceCase -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withSentenceCase
TextCase
TitleCase -> Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
withTitleCase
addDisplay :: DisplayStyle -> Inlines -> Inlines
addDisplay DisplayStyle
x =
case DisplayStyle
x of
DisplayStyle
DisplayBlock -> Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"csl-block"],[])
DisplayStyle
DisplayLeftMargin -> Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"csl-left-margin"],[])
DisplayStyle
DisplayRightInline -> Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"csl-right-inline"],[])
DisplayStyle
DisplayIndent -> Attr -> Inlines -> Inlines
B.spanWith (Text
"",[Text
"csl-indent"],[])
addQuotes :: Inlines -> Inlines
addQuotes = Inlines -> Inlines
B.doubleQuoted (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QuoteType -> Inlines -> Inlines
flipFlopQuotes QuoteType
DoubleQuote
inNote :: Inlines -> Inlines
inNote = Blocks -> Inlines
B.note (Blocks -> Inlines) -> (Inlines -> Blocks) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Blocks
B.para
movePunctuationInsideQuotes :: Inlines -> Inlines
movePunctuationInsideQuotes
= Inlines -> Inlines
punctuationInsideQuotes
mapText :: (Text -> Text) -> Inlines -> Inlines
mapText Text -> Text
f = (Inline -> Inline) -> Inlines -> Inlines
forall a b. Walkable a b => (a -> a) -> b -> b
walk Inline -> Inline
go
where go :: Inline -> Inline
go (Str Text
t) = Text -> Inline
Str (Text -> Text
f Text
t)
go Inline
x = Inline
x
addHyperlink :: Text -> Inlines -> Inlines
addHyperlink Text
t = Text -> Text -> Inlines -> Inlines
B.link Text
t Text
""
flipFlopQuotes :: QuoteType -> Inlines -> Inlines
flipFlopQuotes :: QuoteType -> Inlines -> Inlines
flipFlopQuotes QuoteType
qt = [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList ([Inline] -> Inlines)
-> (Inlines -> [Inline]) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
qt) ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
B.toList
where
go :: QuoteType -> Inline -> Inline
go :: QuoteType -> Inline -> Inline
go QuoteType
q (Quoted QuoteType
_ [Inline]
zs) =
let q' :: QuoteType
q' = case QuoteType
q of
QuoteType
SingleQuote -> QuoteType
DoubleQuote
QuoteType
DoubleQuote -> QuoteType
SingleQuote
in QuoteType -> [Inline] -> Inline
Quoted QuoteType
q' ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q') [Inline]
zs)
go QuoteType
q (SmallCaps [Inline]
zs) = [Inline] -> Inline
SmallCaps ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Superscript [Inline]
zs) = [Inline] -> Inline
Superscript ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Subscript [Inline]
zs) = [Inline] -> Inline
Subscript ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Span Attr
attr [Inline]
zs) = Attr -> [Inline] -> Inline
Span Attr
attr ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Emph [Inline]
zs) = [Inline] -> Inline
Emph ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Underline [Inline]
zs) = [Inline] -> Inline
Underline ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Strong [Inline]
zs) = [Inline] -> Inline
Strong ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Strikeout [Inline]
zs) = [Inline] -> Inline
Strikeout ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Cite [Citation]
cs [Inline]
zs) = [Citation] -> [Inline] -> Inline
Cite [Citation]
cs ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs)
go QuoteType
q (Link Attr
attr [Inline]
zs (Text, Text)
t) = Attr -> [Inline] -> (Text, Text) -> Inline
Link Attr
attr ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs) (Text, Text)
t
go QuoteType
q (Image Attr
attr [Inline]
zs (Text, Text)
t) = Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr ((Inline -> Inline) -> [Inline] -> [Inline]
forall a b. (a -> b) -> [a] -> [b]
map (QuoteType -> Inline -> Inline
go QuoteType
q) [Inline]
zs) (Text, Text)
t
go QuoteType
_ Inline
x = Inline
x
punctuationInsideQuotes :: Inlines -> Inlines
punctuationInsideQuotes :: Inlines -> Inlines
punctuationInsideQuotes = [Inline] -> Inlines
forall a. [a] -> Many a
B.fromList ([Inline] -> Inlines)
-> (Inlines -> [Inline]) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> [Inline]
go ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Inline] -> [Inline]) -> [Inline] -> [Inline]
forall a b. Walkable a b => (a -> a) -> b -> b
walk [Inline] -> [Inline]
go ([Inline] -> [Inline])
-> (Inlines -> [Inline]) -> Inlines -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
B.toList
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 :: [Inline] -> [Inline]
go [] = []
go (Quoted QuoteType
qt [Inline]
xs : Str Text
t : [Inline]
rest)
| Text -> Bool
startsWithMovable Text
t
= QuoteType -> [Inline] -> Inline
Quoted QuoteType
qt ([Inline]
xs [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str (Int -> Text -> Text
T.take Int
1 Text
t) | Bool -> Bool
not (Bool -> [Inline] -> Bool
endWithPunct Bool
True [Inline]
xs)]) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
:
if Text -> Int
T.length Text
t Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
then [Inline] -> [Inline]
go [Inline]
rest
else Text -> Inline
Str (Int -> Text -> Text
T.drop Int
1 Text
t) Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
go [Inline]
rest
go (Inline
x:[Inline]
xs) = Inline
x Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline] -> [Inline]
go [Inline]
xs
endWithPunct :: Bool -> [Inline] -> Bool
endWithPunct :: Bool -> [Inline] -> Bool
endWithPunct Bool
_ [] = Bool
False
endWithPunct Bool
onlyFinal xs :: [Inline]
xs@(Inline
_:[Inline]
_) =
case [Char] -> [Char]
forall a. [a] -> [a]
reverse (Text -> [Char]
T.unpack (Text -> [Char]) -> Text -> [Char]
forall a b. (a -> b) -> a -> b
$ [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify [Inline]
xs) of
[] -> Bool
True
(Char
d:Char
c:[Char]
_) | Char -> Bool
isPunctuation Char
d
Bool -> Bool -> Bool
&& Bool -> Bool
not Bool
onlyFinal
Bool -> Bool -> Bool
&& Char -> Bool
isEndPunct Char
c -> Bool
True
(Char
c:[Char]
_) | Char -> Bool
isEndPunct Char
c -> Bool
True
| Bool
otherwise -> Bool
False
where isEndPunct :: Char -> Bool
isEndPunct Char
c = Char
c Char -> [Char] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` ([Char]
".,;:!?" :: String)
dropTextWhile' :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhile' :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhile' Char -> Bool
f Inlines
ils = State Bool Inlines -> Bool -> Inlines
forall s a. State s a -> s -> a
evalState ((Inline -> StateT Bool Identity Inline)
-> Inlines -> State Bool Inlines
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> StateT Bool Identity Inline
forall (m :: * -> *). Monad m => Inline -> StateT Bool m Inline
go Inlines
ils) Bool
True
where
go :: Inline -> StateT Bool m Inline
go Inline
x = do
Bool
atStart <- StateT Bool m Bool
forall (m :: * -> *) s. Monad m => StateT s m s
get
if Bool
atStart
then
case Inline
x of
Str Text
t -> do
let t' :: Text
t' = (Char -> Bool) -> Text -> Text
T.dropWhile Char -> Bool
f Text
t
Bool -> StateT Bool m () -> StateT Bool m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
t') (StateT Bool m () -> StateT Bool m ())
-> StateT Bool m () -> StateT Bool m ()
forall a b. (a -> b) -> a -> b
$
Bool -> StateT Bool m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put Bool
False
Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> StateT Bool m Inline) -> Inline -> StateT Bool m Inline
forall a b. (a -> b) -> a -> b
$ Text -> Inline
Str Text
t'
Inline
Space ->
if Char -> Bool
f Char
' '
then Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> StateT Bool m Inline) -> Inline -> StateT Bool m Inline
forall a b. (a -> b) -> a -> b
$ Text -> Inline
Str Text
""
else do
Bool -> StateT Bool m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put Bool
False
Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
Space
Inline
_ -> Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x
else Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x
dropTextWhileEnd' :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhileEnd' :: (Char -> Bool) -> Inlines -> Inlines
dropTextWhileEnd' Char -> Bool
f Inlines
ils =
Reverse Many Inline -> Inlines
forall k (f :: k -> *) (a :: k). Reverse f a -> f a
getReverse (Reverse Many Inline -> Inlines) -> Reverse Many Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ State Bool (Reverse Many Inline) -> Bool -> Reverse Many Inline
forall s a. State s a -> s -> a
evalState ((Inline -> StateT Bool Identity Inline)
-> Reverse Many Inline -> State Bool (Reverse Many Inline)
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM Inline -> StateT Bool Identity Inline
forall (m :: * -> *). Monad m => Inline -> StateT Bool m Inline
go (Reverse Many Inline -> State Bool (Reverse Many Inline))
-> Reverse Many Inline -> State Bool (Reverse Many Inline)
forall a b. (a -> b) -> a -> b
$ Inlines -> Reverse Many Inline
forall k (f :: k -> *) (a :: k). f a -> Reverse f a
Reverse Inlines
ils) Bool
True
where
go :: Inline -> StateT Bool m Inline
go Inline
x = do
Bool
atEnd <- StateT Bool m Bool
forall (m :: * -> *) s. Monad m => StateT s m s
get
if Bool
atEnd
then
case Inline
x of
Str Text
t -> do
let t' :: Text
t' = (Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
f Text
t
Bool -> StateT Bool m () -> StateT Bool m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
T.null Text
t') (StateT Bool m () -> StateT Bool m ())
-> StateT Bool m () -> StateT Bool m ()
forall a b. (a -> b) -> a -> b
$
Bool -> StateT Bool m ()
forall (m :: * -> *) s. Monad m => s -> StateT s m ()
put Bool
False
Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> StateT Bool m Inline) -> Inline -> StateT Bool m Inline
forall a b. (a -> b) -> a -> b
$ Text -> Inline
Str Text
t'
Inline
Space | Char -> Bool
f Char
' ' -> Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> StateT Bool m Inline) -> Inline -> StateT Bool m Inline
forall a b. (a -> b) -> a -> b
$ Text -> Inline
Str Text
""
Inline
_ -> Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x
else Inline -> StateT Bool m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x
stringify :: Walkable Inline a => a -> T.Text
stringify :: a -> Text
stringify = (Inline -> Text) -> a -> Text
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> Text
go (a -> Text) -> (a -> a) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inline -> Inline) -> a -> a
forall a b. Walkable a b => (a -> a) -> b -> b
walk (Inline -> Inline
unNote (Inline -> Inline) -> (Inline -> Inline) -> Inline -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inline -> Inline
unQuote)
where
go :: Inline -> T.Text
go :: Inline -> Text
go Inline
Space = Text
" "
go Inline
SoftBreak = Text
" "
go (Str Text
x) = Text
x
go (Code Attr
_ Text
x) = Text
x
go (Math MathType
_ Text
x) = Text
x
go (RawInline (Format Text
"html") (Text -> [Char]
T.unpack -> (Char
'<':Char
'b':Char
'r':[Char]
_)))
= Text
" "
go Inline
LineBreak = Text
" "
go Inline
_ = Text
""
unNote :: Inline -> Inline
unNote :: Inline -> Inline
unNote (Note [Block]
_) = Text -> Inline
Str Text
""
unNote Inline
x = Inline
x
unQuote :: Inline -> Inline
unQuote :: Inline -> Inline
unQuote (Quoted QuoteType
SingleQuote [Inline]
xs) =
Attr -> [Inline] -> Inline
Span (Text
"",[],[]) (Text -> Inline
Str Text
"\8216" Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
xs [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"\8217"])
unQuote (Quoted QuoteType
DoubleQuote [Inline]
xs) =
Attr -> [Inline] -> Inline
Span (Text
"",[],[]) (Text -> Inline
Str Text
"\8220" Inline -> [Inline] -> [Inline]
forall a. a -> [a] -> [a]
: [Inline]
xs [Inline] -> [Inline] -> [Inline]
forall a. [a] -> [a] -> [a]
++ [Text -> Inline
Str Text
"\8221"])
unQuote Inline
x = Inline
x
caseTransform :: Maybe Lang
-> CaseTransformer
-> Inlines
-> Inlines
caseTransform :: Maybe Lang -> CaseTransformer -> Inlines -> Inlines
caseTransform Maybe Lang
mblang CaseTransformer
f Inlines
x =
State CaseTransformState Inlines -> CaseTransformState -> Inlines
forall s a. State s a -> s -> a
evalState ((CaseTransformState -> Text -> Text)
-> Inlines -> State CaseTransformState Inlines
caseTransform' (CaseTransformer -> Maybe Lang -> CaseTransformState -> Text -> Text
unCaseTransformer CaseTransformer
f Maybe Lang
mblang) Inlines
x) CaseTransformState
Start
caseTransform' :: (CaseTransformState -> Text -> Text)
-> Inlines
-> State CaseTransformState Inlines
caseTransform' :: (CaseTransformState -> Text -> Text)
-> Inlines -> State CaseTransformState Inlines
caseTransform' CaseTransformState -> Text -> Text
f Inlines
ils =
case Seq Inline -> ViewR Inline
forall a. Seq a -> ViewR a
Seq.viewr (Inlines -> Seq Inline
forall a. Many a -> Seq a
unMany Inlines
ils) of
Seq Inline
xs Seq.:> Str Text
t | Bool -> Bool
not (Seq Inline -> Bool
forall a. Seq a -> Bool
Seq.null Seq Inline
xs)
, Bool -> Bool
not (Text -> Bool
hasWordBreak Text
t) -> do
Seq Inline
xs' <- (Inline -> StateT CaseTransformState Identity Inline)
-> Seq Inline -> StateT CaseTransformState Identity (Seq Inline)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go Seq Inline
xs
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 (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
Inline
x' <- Inline -> StateT CaseTransformState Identity Inline
go (Text -> Inline
Str Text
t)
Inlines -> State CaseTransformState Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> State CaseTransformState Inlines)
-> Inlines -> State CaseTransformState Inlines
forall a b. (a -> b) -> a -> b
$ Seq Inline -> Inlines
forall a. Seq a -> Many a
Many (Seq Inline -> Inlines) -> Seq Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Seq Inline
xs' Seq Inline -> Inline -> Seq Inline
forall a. Seq a -> a -> Seq a
Seq.|> Inline
x'
ViewR Inline
_ -> (Inline -> StateT CaseTransformState Identity Inline)
-> Inlines -> State CaseTransformState Inlines
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go Inlines
ils
where
go :: Inline -> StateT CaseTransformState Identity Inline
go (Str Text
t) = Text -> Inline
Str (Text -> Inline) -> ([Text] -> Text) -> [Text] -> Inline
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Inline)
-> StateT CaseTransformState Identity [Text]
-> StateT CaseTransformState Identity Inline
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
t)
go Inline
Space = Inline
Space Inline
-> StateT CaseTransformState Identity Text
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> StateT CaseTransformState Identity Text
g Text
" "
go (SmallCaps [Inline]
zs) = Inline -> StateT CaseTransformState Identity Inline
forall b.
Walkable Inline b =>
b -> StateT CaseTransformState Identity b
return' (Inline -> StateT CaseTransformState Identity Inline)
-> Inline -> StateT CaseTransformState Identity Inline
forall a b. (a -> b) -> a -> b
$ [Inline] -> Inline
SmallCaps [Inline]
zs
go (Superscript [Inline]
zs) = Inline -> StateT CaseTransformState Identity Inline
forall b.
Walkable Inline b =>
b -> StateT CaseTransformState Identity b
return' (Inline -> StateT CaseTransformState Identity Inline)
-> Inline -> StateT CaseTransformState Identity Inline
forall a b. (a -> b) -> a -> b
$ [Inline] -> Inline
Superscript [Inline]
zs
go (Subscript [Inline]
zs) = Inline -> StateT CaseTransformState Identity Inline
forall b.
Walkable Inline b =>
b -> StateT CaseTransformState Identity b
return' (Inline -> StateT CaseTransformState Identity Inline)
-> Inline -> StateT CaseTransformState Identity Inline
forall a b. (a -> b) -> a -> b
$ [Inline] -> Inline
Subscript [Inline]
zs
go (Span attr :: Attr
attr@(Text
_,[Text]
classes,[(Text, Text)]
_) [Inline]
zs)
| Text
"nocase" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes = do
CaseTransformState
st <- StateT CaseTransformState Identity CaseTransformState
forall (m :: * -> *) s. Monad m => StateT s m s
get
case CaseTransformState
st of
CaseTransformState
AfterWordChar | [Text]
classes [Text] -> [Text] -> Bool
forall a. Eq a => a -> a -> Bool
== [Text
"nocase"]
-> Inline -> StateT CaseTransformState Identity Inline
forall b.
Walkable Inline b =>
b -> StateT CaseTransformState Identity b
return' (Inline -> StateT CaseTransformState Identity Inline)
-> Inline -> StateT CaseTransformState Identity Inline
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> Inline
Span Attr
nullAttr [Inline]
zs
CaseTransformState
_ -> Inline -> StateT CaseTransformState Identity Inline
forall b.
Walkable Inline b =>
b -> StateT CaseTransformState Identity b
return' (Inline -> StateT CaseTransformState Identity Inline)
-> Inline -> StateT CaseTransformState Identity Inline
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> Inline
Span Attr
attr [Inline]
zs
| Bool
otherwise = Attr -> [Inline] -> Inline
Span Attr
attr ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Emph [Inline]
zs) = [Inline] -> Inline
Emph ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Underline [Inline]
zs) = [Inline] -> Inline
Underline ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Strong [Inline]
zs) = [Inline] -> Inline
Strong ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Strikeout [Inline]
zs) = [Inline] -> Inline
Strikeout ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Quoted QuoteType
qt [Inline]
zs) = QuoteType -> [Inline] -> Inline
Quoted QuoteType
qt ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Cite [Citation]
cs [Inline]
zs) = [Citation] -> [Inline] -> Inline
Cite [Citation]
cs ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Link Attr
attr [Inline]
zs (Text, Text)
t) = (\[Inline]
x -> Attr -> [Inline] -> (Text, Text) -> Inline
Link Attr
attr [Inline]
x (Text, Text)
t) ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go (Image Attr
attr [Inline]
zs (Text, Text)
t) = (\[Inline]
x -> Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr [Inline]
x (Text, Text)
t) ([Inline] -> Inline)
-> StateT CaseTransformState Identity [Inline]
-> StateT CaseTransformState Identity Inline
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Inline -> StateT CaseTransformState Identity Inline)
-> [Inline] -> StateT CaseTransformState Identity [Inline]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Inline -> StateT CaseTransformState Identity Inline
go [Inline]
zs
go Inline
x = Inline -> StateT CaseTransformState Identity Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x
return' :: b -> StateT CaseTransformState Identity b
return' b
x = b
x b
-> StateT CaseTransformState Identity Text
-> StateT CaseTransformState Identity b
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> StateT CaseTransformState Identity Text
g ((Inline -> Text) -> b -> Text
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Inline -> Text
fromStr b
x)
fromStr :: Inline -> Text
fromStr (Str Text
t) = Text
t
fromStr Inline
_ = Text
forall a. Monoid a => a
mempty
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 :: Text -> Bool
hasWordBreak = (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)