{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.Pandoc.Readers.Djot
( readDjot
)
where
import Text.Pandoc.Class
import Text.Pandoc.Sources
import Text.Parsec.Pos (newPos)
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Text.Pandoc.Shared (addPandocAttributes, tshow)
import qualified Text.Pandoc.UTF8 as UTF8
import Djot (ParseOptions(..), SourcePosOption(..), parseDoc, Pos(..))
import qualified Djot.AST as D
import Text.Pandoc.Error (PandocError(..))
import Control.Monad.Except (throwError)
import qualified Data.Text as T
import Text.Pandoc.Builder
import Text.Pandoc.Logging
import Text.Pandoc.Emoji (emojiToInline)
import Control.Monad.Reader
import qualified Data.Foldable as F
import Data.List (foldl')
import Data.ByteString (ByteString)
readDjot :: (PandocMonad m, ToSources a) => ReaderOptions -> a -> m Pandoc
readDjot :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readDjot ReaderOptions
opts a
inp = do
let sources :: Sources
sources = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
inp
case ParseOptions -> ByteString -> Either String Doc
parseDoc ParseOptions{ sourcePositions :: SourcePosOption
sourcePositions =
if Extension -> ReaderOptions -> Bool
forall a. HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled Extension
Ext_sourcepos ReaderOptions
opts
then SourcePosOption
AllSourcePos
else SourcePosOption
NoSourcePos }
(Text -> ByteString
UTF8.fromText (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ Sources -> Text
sourcesToText Sources
sources) of
Left String
e -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> String
forall a. Show a => a -> String
show String
e
Right Doc
d ->
ReaderT Env m Pandoc -> Env -> m Pandoc
forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (Blocks -> Pandoc
doc (Blocks -> Pandoc) -> ReaderT Env m Blocks -> ReaderT Env m Pandoc
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks (Doc -> Blocks
D.docBlocks Doc
d))
Env{ references :: ReferenceMap
references = Doc -> ReferenceMap
D.docReferences Doc
d ReferenceMap -> ReferenceMap -> ReferenceMap
forall a. Semigroup a => a -> a -> a
<> Doc -> ReferenceMap
D.docAutoReferences Doc
d
, footnotes :: NoteMap
footnotes = Doc -> NoteMap
D.docFootnotes Doc
d
}
data Env =
Env{ Env -> ReferenceMap
references :: D.ReferenceMap
, :: D.NoteMap
}
deriving (Int -> Env -> String -> String
[Env] -> String -> String
Env -> String
(Int -> Env -> String -> String)
-> (Env -> String) -> ([Env] -> String -> String) -> Show Env
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Env -> String -> String
showsPrec :: Int -> Env -> String -> String
$cshow :: Env -> String
show :: Env -> String
$cshowList :: [Env] -> String -> String
showList :: [Env] -> String -> String
Show, Eq Env
Eq Env =>
(Env -> Env -> Ordering)
-> (Env -> Env -> Bool)
-> (Env -> Env -> Bool)
-> (Env -> Env -> Bool)
-> (Env -> Env -> Bool)
-> (Env -> Env -> Env)
-> (Env -> Env -> Env)
-> Ord Env
Env -> Env -> Bool
Env -> Env -> Ordering
Env -> Env -> Env
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
$ccompare :: Env -> Env -> Ordering
compare :: Env -> Env -> Ordering
$c< :: Env -> Env -> Bool
< :: Env -> Env -> Bool
$c<= :: Env -> Env -> Bool
<= :: Env -> Env -> Bool
$c> :: Env -> Env -> Bool
> :: Env -> Env -> Bool
$c>= :: Env -> Env -> Bool
>= :: Env -> Env -> Bool
$cmax :: Env -> Env -> Env
max :: Env -> Env -> Env
$cmin :: Env -> Env -> Env
min :: Env -> Env -> Env
Ord, Env -> Env -> Bool
(Env -> Env -> Bool) -> (Env -> Env -> Bool) -> Eq Env
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Env -> Env -> Bool
== :: Env -> Env -> Bool
$c/= :: Env -> Env -> Bool
/= :: Env -> Env -> Bool
Eq)
convertBlocks :: PandocMonad m => D.Blocks -> ReaderT Env m Blocks
convertBlocks :: forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks = ([Blocks] -> Blocks)
-> ReaderT Env m [Blocks] -> ReaderT Env m Blocks
forall a b. (a -> b) -> ReaderT Env m a -> ReaderT Env m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat (ReaderT Env m [Blocks] -> ReaderT Env m Blocks)
-> (Blocks -> ReaderT Env m [Blocks])
-> Blocks
-> ReaderT Env m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node Block -> ReaderT Env m Blocks)
-> [Node Block] -> ReaderT Env m [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Node Block -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Node Block -> ReaderT Env m Blocks
convertBlock ([Node Block] -> ReaderT Env m [Blocks])
-> (Blocks -> [Node Block]) -> Blocks -> ReaderT Env m [Blocks]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq (Node Block) -> [Node Block]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList (Seq (Node Block) -> [Node Block])
-> (Blocks -> Seq (Node Block)) -> Blocks -> [Node Block]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> Seq (Node Block)
forall a. Many a -> Seq a
D.unMany
convertBlock :: PandocMonad m => D.Node D.Block -> ReaderT Env m Blocks
convertBlock :: forall (m :: * -> *).
PandocMonad m =>
Node Block -> ReaderT Env m Blocks
convertBlock (D.Node Pos
pos Attr
attr Block
bl) = Pos -> Attr -> Blocks -> Blocks
addAttrToBlock Pos
pos Attr
attr (Blocks -> Blocks) -> ReaderT Env m Blocks -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case Block
bl of
D.Para Inlines
ils -> Inlines -> Blocks
para (Inlines -> Blocks)
-> ReaderT Env m Inlines -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Section Blocks
bls -> Attr -> Blocks -> Blocks
divWith (Text
"",[Text
"section"],[]) (Blocks -> Blocks) -> ReaderT Env m Blocks -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls
D.Heading Int
lev Inlines
ils -> Int -> Inlines -> Blocks
header Int
lev (Inlines -> Blocks)
-> ReaderT Env m Inlines -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.BlockQuote Blocks
bls -> Blocks -> Blocks
blockQuote (Blocks -> Blocks) -> ReaderT Env m Blocks -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls
D.CodeBlock ByteString
lang ByteString
bs -> Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> ReaderT Env m Blocks) -> Blocks -> ReaderT Env m Blocks
forall a b. (a -> b) -> a -> b
$
Attr -> Text -> Blocks
codeBlockWith (Text
"", [ByteString -> Text
UTF8.toText ByteString
lang], []) (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
UTF8.toText ByteString
bs
D.Div Blocks
bls -> Attr -> Blocks -> Blocks
divWith Attr
nullAttr (Blocks -> Blocks) -> ReaderT Env m Blocks -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls
D.OrderedList OrderedListAttributes
olattr ListSpacing
listSpacing [Blocks]
items ->
ListAttributes -> [Blocks] -> Blocks
orderedListWith ListAttributes
olattr' ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case ListSpacing
listSpacing of
ListSpacing
D.Tight -> (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Blocks
toTight
ListSpacing
D.Loose -> [Blocks] -> [Blocks]
forall a. a -> a
id) ([Blocks] -> Blocks)
-> ReaderT Env m [Blocks] -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Blocks -> ReaderT Env m Blocks)
-> [Blocks] -> ReaderT Env m [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks [Blocks]
items
where
olattr' :: ListAttributes
olattr' = ( OrderedListAttributes -> Int
D.orderedListStart OrderedListAttributes
olattr
, case OrderedListAttributes -> OrderedListStyle
D.orderedListStyle OrderedListAttributes
olattr of
OrderedListStyle
D.Decimal -> ListNumberStyle
Decimal
OrderedListStyle
D.LetterUpper -> ListNumberStyle
UpperAlpha
OrderedListStyle
D.LetterLower -> ListNumberStyle
LowerAlpha
OrderedListStyle
D.RomanUpper -> ListNumberStyle
UpperRoman
OrderedListStyle
D.RomanLower -> ListNumberStyle
LowerRoman
, case OrderedListAttributes -> OrderedListDelim
D.orderedListDelim OrderedListAttributes
olattr of
OrderedListDelim
D.RightPeriod -> ListNumberDelim
Period
OrderedListDelim
D.RightParen -> ListNumberDelim
OneParen
OrderedListDelim
D.LeftRightParen -> ListNumberDelim
TwoParens
)
D.BulletList ListSpacing
listSpacing [Blocks]
items ->
[Blocks] -> Blocks
bulletList ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case ListSpacing
listSpacing of
ListSpacing
D.Tight -> (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Blocks
toTight
ListSpacing
D.Loose -> [Blocks] -> [Blocks]
forall a. a -> a
id) ([Blocks] -> Blocks)
-> ReaderT Env m [Blocks] -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Blocks -> ReaderT Env m Blocks)
-> [Blocks] -> ReaderT Env m [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks [Blocks]
items
D.TaskList ListSpacing
listSpacing [(TaskStatus, Blocks)]
items ->
[Blocks] -> Blocks
bulletList ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case ListSpacing
listSpacing of
ListSpacing
D.Tight -> (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Blocks
toTight
ListSpacing
D.Loose -> [Blocks] -> [Blocks]
forall a. a -> a
id) ([Blocks] -> Blocks)
-> ReaderT Env m [Blocks] -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((TaskStatus, Blocks) -> ReaderT Env m Blocks)
-> [(TaskStatus, Blocks)] -> ReaderT Env m [Blocks]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (TaskStatus, Blocks) -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
(TaskStatus, Blocks) -> ReaderT Env m Blocks
toTaskListItem [(TaskStatus, Blocks)]
items
D.DefinitionList ListSpacing
listSpacing [(Inlines, Blocks)]
items ->
[(Inlines, [Blocks])] -> Blocks
definitionList ([(Inlines, [Blocks])] -> Blocks)
-> ([(Inlines, [Blocks])] -> [(Inlines, [Blocks])])
-> [(Inlines, [Blocks])]
-> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
(case ListSpacing
listSpacing of
ListSpacing
D.Tight -> ((Inlines, [Blocks]) -> (Inlines, [Blocks]))
-> [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
forall a b. (a -> b) -> [a] -> [b]
map (\(Inlines
t,[Blocks]
d) -> (Inlines
t, (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map Blocks -> Blocks
toTight [Blocks]
d))
ListSpacing
D.Loose -> [(Inlines, [Blocks])] -> [(Inlines, [Blocks])]
forall a. a -> a
id) ([(Inlines, [Blocks])] -> Blocks)
-> ReaderT Env m [(Inlines, [Blocks])] -> ReaderT Env m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((Inlines, Blocks) -> ReaderT Env m (Inlines, [Blocks]))
-> [(Inlines, Blocks)] -> ReaderT Env m [(Inlines, [Blocks])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (Inlines, Blocks) -> ReaderT Env m (Inlines, [Blocks])
forall {m :: * -> *}.
PandocMonad m =>
(Inlines, Blocks) -> ReaderT Env m (Inlines, [Blocks])
toDlItem [(Inlines, Blocks)]
items
where
toDlItem :: (Inlines, Blocks) -> ReaderT Env m (Inlines, [Blocks])
toDlItem (Inlines
ils,Blocks
bls) = (,) (Inlines -> [Blocks] -> (Inlines, [Blocks]))
-> ReaderT Env m Inlines
-> ReaderT Env m ([Blocks] -> (Inlines, [Blocks]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
ReaderT Env m ([Blocks] -> (Inlines, [Blocks]))
-> ReaderT Env m [Blocks] -> ReaderT Env m (Inlines, [Blocks])
forall a b.
ReaderT Env m (a -> b) -> ReaderT Env m a -> ReaderT Env m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
:[]) (Blocks -> [Blocks])
-> ReaderT Env m Blocks -> ReaderT Env m [Blocks]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls)
Block
D.ThematicBreak -> Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule
D.Table Maybe Caption
mbCaption [[Cell]]
rows -> do
Caption
capt <- case Maybe Caption
mbCaption of
Just (D.Caption Blocks
bls') ->
Maybe ShortCaption -> [Block] -> Caption
Caption Maybe ShortCaption
forall a. Maybe a
Nothing ([Block] -> Caption) -> (Blocks -> [Block]) -> Blocks -> Caption
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blocks -> [Block]
forall a. Many a -> [a]
toList (Blocks -> Caption)
-> ReaderT Env m Blocks -> ReaderT Env m Caption
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls'
Maybe Caption
Nothing -> Caption -> ReaderT Env m Caption
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Caption -> ReaderT Env m Caption)
-> Caption -> ReaderT Env m Caption
forall a b. (a -> b) -> a -> b
$ Maybe ShortCaption -> [Block] -> Caption
Caption Maybe ShortCaption
forall a. Maybe a
Nothing [Block]
forall a. Monoid a => a
mempty
let toAlign :: Align -> Alignment
toAlign Align
D.AlignLeft = Alignment
AlignLeft
toAlign Align
D.AlignRight = Alignment
AlignRight
toAlign Align
D.AlignCenter = Alignment
AlignCenter
toAlign Align
D.AlignDefault = Alignment
AlignDefault
let toColSpec :: Cell -> (Alignment, ColWidth)
toColSpec (D.Cell CellType
_ Align
align Inlines
_) = (Align -> Alignment
toAlign Align
align, ColWidth
ColWidthDefault)
let colspecs :: [(Alignment, ColWidth)]
colspecs = case [[Cell]]
rows of
[] -> []
([Cell]
cells:[[Cell]]
_) -> (Cell -> (Alignment, ColWidth))
-> [Cell] -> [(Alignment, ColWidth)]
forall a b. (a -> b) -> [a] -> [b]
map Cell -> (Alignment, ColWidth)
toColSpec [Cell]
cells
let ([Cell]
headrow, [[Cell]]
rest) =
case [[Cell]]
rows of
(r :: [Cell]
r@(D.Cell CellType
D.HeadCell Align
_ Inlines
_ : [Cell]
_) : [[Cell]]
rs) -> ([Cell]
r, [[Cell]]
rs)
[[Cell]]
_ -> ([],[[Cell]]
rows)
let getBody :: [([[Cell]], [[Cell]])] -> [Cell] -> [([[Cell]], [[Cell]])]
getBody [([[Cell]], [[Cell]])]
bods [Cell]
row =
case [Cell]
row of
(D.Cell CellType
D.HeadCell Align
_ Inlines
_ : [Cell]
_) ->
case [([[Cell]], [[Cell]])]
bods of
[] -> [([[Cell]
row],[])]
([],[[Cell]]
_):[([[Cell]], [[Cell]])]
_ -> (([[Cell]
row],[])([[Cell]], [[Cell]])
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a. a -> [a] -> [a]
:[([[Cell]], [[Cell]])]
bods)
([[Cell]]
hs,[[Cell]]
bs):[([[Cell]], [[Cell]])]
rs -> ([[Cell]]
hs,[Cell]
row[Cell] -> [[Cell]] -> [[Cell]]
forall a. a -> [a] -> [a]
:[[Cell]]
bs)([[Cell]], [[Cell]])
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a. a -> [a] -> [a]
:[([[Cell]], [[Cell]])]
rs
[Cell]
_ -> case [([[Cell]], [[Cell]])]
bods of
([[Cell]]
hs,[[Cell]]
bs):[([[Cell]], [[Cell]])]
rs -> ([[Cell]]
hs,[Cell]
row[Cell] -> [[Cell]] -> [[Cell]]
forall a. a -> [a] -> [a]
:[[Cell]]
bs)([[Cell]], [[Cell]])
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a. a -> [a] -> [a]
:[([[Cell]], [[Cell]])]
rs
[] -> [([],[[Cell]
row])]
let reverseSnd :: (a, [a]) -> (a, [a])
reverseSnd (a
as,[a]
bs) = (a
as,[a] -> [a]
forall a. [a] -> [a]
reverse [a]
bs)
let bodies :: [([[Cell]], [[Cell]])]
bodies = [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a. [a] -> [a]
reverse ([([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])])
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a b. (a -> b) -> a -> b
$ (([[Cell]], [[Cell]]) -> ([[Cell]], [[Cell]]))
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a b. (a -> b) -> [a] -> [b]
map ([[Cell]], [[Cell]]) -> ([[Cell]], [[Cell]])
forall {a} {a}. (a, [a]) -> (a, [a])
reverseSnd ([([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])])
-> [([[Cell]], [[Cell]])] -> [([[Cell]], [[Cell]])]
forall a b. (a -> b) -> a -> b
$ ([([[Cell]], [[Cell]])] -> [Cell] -> [([[Cell]], [[Cell]])])
-> [([[Cell]], [[Cell]])] -> [[Cell]] -> [([[Cell]], [[Cell]])]
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' [([[Cell]], [[Cell]])] -> [Cell] -> [([[Cell]], [[Cell]])]
getBody [] [[Cell]]
rest
let toCell :: Cell -> ReaderT Env m Cell
toCell (D.Cell CellType
_ Align
al Inlines
ils) =
Attr -> Alignment -> RowSpan -> ColSpan -> [Block] -> Cell
Cell Attr
nullAttr (Align -> Alignment
toAlign Align
al) (Int -> RowSpan
RowSpan Int
1) (Int -> ColSpan
ColSpan Int
1)
([Block] -> Cell) -> (Inlines -> [Block]) -> Inlines -> Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Inlines
is -> [ShortCaption -> Block
Para (ShortCaption -> Block) -> ShortCaption -> Block
forall a b. (a -> b) -> a -> b
$ Inlines -> ShortCaption
forall a. Many a -> [a]
toList Inlines
is]) (Inlines -> Cell) -> ReaderT Env m Inlines -> ReaderT Env m Cell
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
let toRow :: [Cell] -> ReaderT Env m Row
toRow = ([Cell] -> Row) -> ReaderT Env m [Cell] -> ReaderT Env m Row
forall a b. (a -> b) -> ReaderT Env m a -> ReaderT Env m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> [Cell] -> Row
Row Attr
nullAttr) (ReaderT Env m [Cell] -> ReaderT Env m Row)
-> ([Cell] -> ReaderT Env m [Cell]) -> [Cell] -> ReaderT Env m Row
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Cell -> ReaderT Env m Cell) -> [Cell] -> ReaderT Env m [Cell]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Cell -> ReaderT Env m Cell
forall {m :: * -> *}. PandocMonad m => Cell -> ReaderT Env m Cell
toCell
TableHead
thead <- Attr -> [Row] -> TableHead
TableHead Attr
forall a. Monoid a => a
mempty ([Row] -> TableHead)
-> ReaderT Env m [Row] -> ReaderT Env m TableHead
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Cell] -> ReaderT Env m Row) -> [[Cell]] -> ReaderT Env m [Row]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Cell] -> ReaderT Env m Row
toRow [[Cell]
headrow]
let toTableBody :: ([[Cell]], [[Cell]]) -> ReaderT Env m TableBody
toTableBody ([[Cell]]
hs, [[Cell]]
rs) =
Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
forall a. Monoid a => a
mempty (Int -> RowHeadColumns
RowHeadColumns Int
0) ([Row] -> [Row] -> TableBody)
-> ReaderT Env m [Row] -> ReaderT Env m ([Row] -> TableBody)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
([Cell] -> ReaderT Env m Row) -> [[Cell]] -> ReaderT Env m [Row]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Cell] -> ReaderT Env m Row
toRow [[Cell]]
hs ReaderT Env m ([Row] -> TableBody)
-> ReaderT Env m [Row] -> ReaderT Env m TableBody
forall a b.
ReaderT Env m (a -> b) -> ReaderT Env m a -> ReaderT Env m b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Cell] -> ReaderT Env m Row) -> [[Cell]] -> ReaderT Env m [Row]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM [Cell] -> ReaderT Env m Row
toRow [[Cell]]
rs
[TableBody]
tbodies <- (([[Cell]], [[Cell]]) -> ReaderT Env m TableBody)
-> [([[Cell]], [[Cell]])] -> ReaderT Env m [TableBody]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ([[Cell]], [[Cell]]) -> ReaderT Env m TableBody
toTableBody [([[Cell]], [[Cell]])]
bodies
let tfoot :: TableFoot
tfoot = Attr -> [Row] -> TableFoot
TableFoot Attr
forall a. Monoid a => a
mempty []
Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> ReaderT Env m Blocks) -> Blocks -> ReaderT Env m Blocks
forall a b. (a -> b) -> a -> b
$ Block -> Blocks
forall a. a -> Many a
singleton (Block -> Blocks) -> Block -> Blocks
forall a b. (a -> b) -> a -> b
$ Attr
-> Caption
-> [(Alignment, ColWidth)]
-> TableHead
-> [TableBody]
-> TableFoot
-> Block
Table Attr
forall a. Monoid a => a
mempty Caption
capt [(Alignment, ColWidth)]
colspecs TableHead
thead [TableBody]
tbodies TableFoot
tfoot
D.RawBlock (D.Format ByteString
fmt) ByteString
bs -> Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> ReaderT Env m Blocks) -> Blocks -> ReaderT Env m Blocks
forall a b. (a -> b) -> a -> b
$
Text -> Text -> Blocks
rawBlock (ByteString -> Text
UTF8.toText ByteString
fmt) (ByteString -> Text
UTF8.toText ByteString
bs)
addAttrToBlock :: Pos -> D.Attr -> Blocks -> Blocks
addAttrToBlock :: Pos -> Attr -> Blocks -> Blocks
addAttrToBlock Pos
pos (D.Attr [(ByteString, ByteString)]
as) =
[(Text, Text)] -> Blocks -> Blocks
forall b. HasAttributes (Cm () b) => [(Text, Text)] -> b -> b
addPandocAttributes ([(Text, Text)] -> Blocks -> Blocks)
-> [(Text, Text)] -> Blocks -> Blocks
forall a b. (a -> b) -> a -> b
$
case Pos
pos of
Pos
NoPos -> [(Text, Text)]
textkvs
Pos Int
sl Int
sc Int
el Int
ec ->
(Text
"data-pos", Int -> Text
forall a. Show a => a -> Text
tshow Int
sl Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
sc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
el Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
ec) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
textkvs
where
textkvs :: [(Text, Text)]
textkvs = (((ByteString, ByteString) -> (Text, Text))
-> [(ByteString, ByteString)] -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (\(ByteString
k,ByteString
v) -> (ByteString -> Text
UTF8.toText ByteString
k, ByteString -> Text
UTF8.toText ByteString
v))
(((ByteString, ByteString) -> Bool)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((ByteString, ByteString) -> Bool)
-> (ByteString, ByteString)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString, ByteString) -> Bool
internalAttribute) [(ByteString, ByteString)]
as))
addAttrToInline :: Pos -> D.Attr -> Inlines -> Inlines
addAttrToInline :: Pos -> Attr -> Inlines -> Inlines
addAttrToInline Pos
pos (D.Attr [(ByteString, ByteString)]
as) =
[(Text, Text)] -> Inlines -> Inlines
forall b. HasAttributes (Cm () b) => [(Text, Text)] -> b -> b
addPandocAttributes ([(Text, Text)] -> Inlines -> Inlines)
-> [(Text, Text)] -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$
case Pos
pos of
Pos
NoPos -> [(Text, Text)]
textkvs
Pos Int
sl Int
sc Int
el Int
ec ->
(Text
"data-pos", Int -> Text
forall a. Show a => a -> Text
tshow Int
sl Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
sc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
el Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text
forall a. Show a => a -> Text
tshow Int
ec) (Text, Text) -> [(Text, Text)] -> [(Text, Text)]
forall a. a -> [a] -> [a]
: [(Text, Text)]
textkvs
where
textkvs :: [(Text, Text)]
textkvs = (((ByteString, ByteString) -> (Text, Text))
-> [(ByteString, ByteString)] -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map (\(ByteString
k,ByteString
v) -> (ByteString -> Text
UTF8.toText ByteString
k, ByteString -> Text
UTF8.toText ByteString
v))
(((ByteString, ByteString) -> Bool)
-> [(ByteString, ByteString)] -> [(ByteString, ByteString)]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((ByteString, ByteString) -> Bool)
-> (ByteString, ByteString)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString, ByteString) -> Bool
internalAttribute) [(ByteString, ByteString)]
as))
convertInlines :: PandocMonad m => D.Inlines -> ReaderT Env m Inlines
convertInlines :: forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines = ([Inlines] -> Inlines)
-> ReaderT Env m [Inlines] -> ReaderT Env m Inlines
forall a b. (a -> b) -> ReaderT Env m a -> ReaderT Env m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat (ReaderT Env m [Inlines] -> ReaderT Env m Inlines)
-> (Inlines -> ReaderT Env m [Inlines])
-> Inlines
-> ReaderT Env m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Node Inline -> ReaderT Env m Inlines)
-> [Node Inline] -> ReaderT Env m [Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM Node Inline -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Node Inline -> ReaderT Env m Inlines
convertInline ([Node Inline] -> ReaderT Env m [Inlines])
-> (Inlines -> [Node Inline]) -> Inlines -> ReaderT Env m [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seq (Node Inline) -> [Node Inline]
forall a. Seq a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList (Seq (Node Inline) -> [Node Inline])
-> (Inlines -> Seq (Node Inline)) -> Inlines -> [Node Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Seq (Node Inline)
forall a. Many a -> Seq a
D.unMany
convertInline :: PandocMonad m => D.Node D.Inline -> ReaderT Env m Inlines
convertInline :: forall (m :: * -> *).
PandocMonad m =>
Node Inline -> ReaderT Env m Inlines
convertInline (D.Node Pos
pos Attr
attr Inline
il) = Pos -> Attr -> Inlines -> Inlines
addAttrToInline Pos
pos Attr
attr (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
case Inline
il of
D.Str ByteString
bs -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str (ByteString -> Text
UTF8.toText ByteString
bs)
D.Emph Inlines
ils -> Inlines -> Inlines
emph (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Strong Inlines
ils -> Inlines -> Inlines
strong (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Highlight Inlines
ils -> Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"highlighted"],[]) (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Insert Inlines
ils -> Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"inserted"],[]) (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Delete Inlines
ils -> Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"deleted"],[]) (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Subscript Inlines
ils -> Inlines -> Inlines
subscript (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Superscript Inlines
ils -> Inlines -> Inlines
superscript (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Span Inlines
ils -> Attr -> Inlines -> Inlines
spanWith Attr
nullAttr (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Quoted QuoteType
D.DoubleQuotes Inlines
ils -> Inlines -> Inlines
doubleQuoted (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Quoted QuoteType
D.SingleQuotes Inlines
ils -> Inlines -> Inlines
singleQuoted (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Verbatim ByteString
bs -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
code (ByteString -> Text
UTF8.toText ByteString
bs)
D.Symbol ByteString
bs -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$
let s :: Text
s = ByteString -> Text
UTF8.toText ByteString
bs
in Inlines -> (Inline -> Inlines) -> Maybe Inline -> Inlines
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"symbol"],[]) (Text -> Inlines
str Text
s)) Inline -> Inlines
forall a. a -> Many a
singleton (Maybe Inline -> Inlines) -> Maybe Inline -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Inline
emojiToInline Text
s
D.Math MathStyle
sty ByteString
bs -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$
(case MathStyle
sty of
MathStyle
D.DisplayMath -> Text -> Inlines
displayMath
MathStyle
D.InlineMath -> Text -> Inlines
math) (ByteString -> Text
UTF8.toText ByteString
bs)
D.Link Inlines
ils Target
target ->
case Target
target of
D.Direct ByteString
url -> Text -> Text -> Inlines -> Inlines
link (ByteString -> Text
UTF8.toText ByteString
url) Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Reference ByteString
label -> do
ReferenceMap
refs <- (Env -> ReferenceMap) -> ReaderT Env m ReferenceMap
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks Env -> ReferenceMap
references
case ByteString -> ReferenceMap -> Maybe (ByteString, Attr)
D.lookupReference ByteString
label ReferenceMap
refs of
Just (ByteString
url, Attr
lattr) ->
Pos -> Attr -> Inlines -> Inlines
addAttrToInline Pos
pos Attr
lattr (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Inlines -> Inlines
link (ByteString -> Text
UTF8.toText ByteString
url) Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
Maybe (ByteString, Attr)
Nothing -> do
LogMessage -> ReaderT Env m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT Env m ()) -> LogMessage -> ReaderT Env m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
ReferenceNotFound (ByteString -> Text
UTF8.toText ByteString
label) (String -> Int -> Int -> SourcePos
newPos String
"" Int
0 Int
0)
Text -> Text -> Inlines -> Inlines
link Text
"" Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Image Inlines
ils Target
target ->
case Target
target of
D.Direct ByteString
url -> Text -> Text -> Inlines -> Inlines
image (ByteString -> Text
UTF8.toText ByteString
url) Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.Reference ByteString
label -> do
ReferenceMap
refs <- (Env -> ReferenceMap) -> ReaderT Env m ReferenceMap
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks Env -> ReferenceMap
references
case ByteString -> ReferenceMap -> Maybe (ByteString, Attr)
D.lookupReference ByteString
label ReferenceMap
refs of
Just (ByteString
url, Attr
lattr) ->
Pos -> Attr -> Inlines -> Inlines
addAttrToInline Pos
pos Attr
lattr (Inlines -> Inlines) -> (Inlines -> Inlines) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Text -> Text -> Inlines -> Inlines
image (ByteString -> Text
UTF8.toText ByteString
url) Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
Maybe (ByteString, Attr)
Nothing -> do
LogMessage -> ReaderT Env m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT Env m ()) -> LogMessage -> ReaderT Env m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
ReferenceNotFound (ByteString -> Text
UTF8.toText ByteString
label) (String -> Int -> Int -> SourcePos
newPos String
"" Int
0 Int
0)
Text -> Text -> Inlines -> Inlines
image Text
"" Text
"" (Inlines -> Inlines)
-> ReaderT Env m Inlines -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Inlines -> ReaderT Env m Inlines
forall (m :: * -> *).
PandocMonad m =>
Inlines -> ReaderT Env m Inlines
convertInlines Inlines
ils
D.FootnoteReference ByteString
bs -> do
NoteMap
notes <- (Env -> NoteMap) -> ReaderT Env m NoteMap
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks Env -> NoteMap
footnotes
case ByteString -> NoteMap -> Maybe Blocks
D.lookupNote ByteString
bs NoteMap
notes of
Just Blocks
bls -> Blocks -> Inlines
note (Blocks -> Inlines)
-> ReaderT Env m Blocks -> ReaderT Env m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls
Maybe Blocks
Nothing -> do
LogMessage -> ReaderT Env m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ReaderT Env m ()) -> LogMessage -> ReaderT Env m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
IgnoredElement (Text
"Undefined footnote reference " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ByteString -> Text
forall a. Show a => a -> Text
tshow ByteString
bs)
Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
forall a. Monoid a => a
mempty
D.UrlLink ByteString
bs -> do
let url :: Text
url = ByteString -> Text
UTF8.toText ByteString
bs
Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
linkWith (Text
"",[Text
"uri"],[]) Text
url Text
"" (Text -> Inlines
str Text
url)
D.EmailLink ByteString
bs -> do
let email :: Text
email = ByteString -> Text
UTF8.toText ByteString
bs
Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
linkWith (Text
"",[Text
"email"],[]) (Text
"mailto:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
email) Text
"" (Text -> Inlines
str Text
email)
D.RawInline (D.Format ByteString
fbs) ByteString
bs -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$
Text -> Text -> Inlines
rawInline (ByteString -> Text
UTF8.toText ByteString
fbs) (ByteString -> Text
UTF8.toText ByteString
bs)
Inline
D.NonBreakingSpace -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> ReaderT Env m Inlines)
-> Inlines -> ReaderT Env m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
"\160"
Inline
D.SoftBreak -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
softbreak
Inline
D.HardBreak -> Inlines -> ReaderT Env m Inlines
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Inlines
linebreak
internalAttribute :: (ByteString, ByteString) -> Bool
internalAttribute :: (ByteString, ByteString) -> Bool
internalAttribute (ByteString
"_implicit",ByteString
_) = Bool
True
internalAttribute (ByteString
"_autogen",ByteString
_) = Bool
True
internalAttribute (ByteString, ByteString)
_ = Bool
False
toTight :: Blocks -> Blocks
toTight :: Blocks -> Blocks
toTight (Many Seq Block
bls) = Seq Block -> Blocks
forall a. Seq a -> Many a
Many (Seq Block -> Blocks) -> Seq Block -> Blocks
forall a b. (a -> b) -> a -> b
$ Block -> Block
paraToPlain (Block -> Block) -> Seq Block -> Seq Block
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Seq Block
bls
where
paraToPlain :: Block -> Block
paraToPlain (Para ShortCaption
ils) = ShortCaption -> Block
Plain ShortCaption
ils
paraToPlain Block
x = Block
x
toTaskListItem :: PandocMonad m
=> (D.TaskStatus, D.Blocks) -> ReaderT Env m Blocks
toTaskListItem :: forall (m :: * -> *).
PandocMonad m =>
(TaskStatus, Blocks) -> ReaderT Env m Blocks
toTaskListItem (TaskStatus
status, Blocks
bls) = do
Blocks
bls' <- Blocks -> ReaderT Env m Blocks
forall (m :: * -> *).
PandocMonad m =>
Blocks -> ReaderT Env m Blocks
convertBlocks Blocks
bls
case Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
bls' of
(Para ShortCaption
ils : [Block]
rest) -> Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> ReaderT Env m Blocks) -> Blocks -> ReaderT Env m Blocks
forall a b. (a -> b) -> a -> b
$
[Block] -> Blocks
forall a. [a] -> Many a
fromList ([Block] -> Blocks) -> [Block] -> Blocks
forall a b. (a -> b) -> a -> b
$ ShortCaption -> Block
Para (Text -> Inline
Str Text
taskmarker Inline -> ShortCaption -> ShortCaption
forall a. a -> [a] -> [a]
: Inline
Space Inline -> ShortCaption -> ShortCaption
forall a. a -> [a] -> [a]
: ShortCaption
ils) Block -> [Block] -> [Block]
forall a. a -> [a] -> [a]
: [Block]
rest
[Block]
_ -> Blocks -> ReaderT Env m Blocks
forall a. a -> ReaderT Env m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Blocks -> ReaderT Env m Blocks) -> Blocks -> ReaderT Env m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
para (Text -> Inlines
str Text
taskmarker) Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
bls'
where
taskmarker :: Text
taskmarker
| TaskStatus
status TaskStatus -> TaskStatus -> Bool
forall a. Eq a => a -> a -> Bool
== TaskStatus
D.Complete = Text
"[X]"
| Bool
otherwise = Text
"[ ]"