{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Pandoc.Readers.DocBook ( readDocBook ) where
import Control.Monad (MonadPlus(mplus))
import Control.Monad.State.Strict
    ( MonadTrans(lift),
      StateT(runStateT),
      MonadState(get),
      gets,
      modify )
import Data.ByteString (ByteString)
import Data.FileEmbed
import Data.Char (isSpace, isLetter, chr)
import Data.Default
import Data.Either (rights)
import Data.Foldable (asum)
import Data.Generics
import Data.List (intersperse,elemIndex)
import qualified Data.Set as Set
import Data.List.NonEmpty (nonEmpty)
import Data.Maybe (catMaybes,fromMaybe,mapMaybe,maybeToList)
import Data.Text (Text)
import Data.Text.Read as TR
import Data.Text.Encoding (decodeUtf8)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Control.Monad.Except (throwError)
import Text.Pandoc.XML (lookupEntity)
import Text.Pandoc.Error (PandocError(..))
import Text.Pandoc.Builder
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
import Text.Pandoc.Options
import Text.Pandoc.Logging (LogMessage(..))
import Text.Pandoc.Shared (safeRead, extractSpaces)
import Text.Pandoc.Sources (ToSources(..), sourcesToText)
import Text.Pandoc.Transforms (headerShift)
import Text.TeXMath (readMathML, writeTeX)
import qualified Data.Map as M
import Text.Pandoc.XML.Light
import Text.Pandoc.Walk (query)
type DB m = StateT DBState m
data DBState = DBState{ DBState -> Int
dbSectionLevel :: Int
                      , DBState -> QuoteType
dbQuoteType    :: QuoteType
                      , DBState -> Meta
dbMeta         :: Meta
                      , DBState -> Bool
dbBook         :: Bool
                      , DBState -> [Content]
dbContent      :: [Content]
                      } deriving Int -> DBState -> ShowS
[DBState] -> ShowS
DBState -> String
(Int -> DBState -> ShowS)
-> (DBState -> String) -> ([DBState] -> ShowS) -> Show DBState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DBState -> ShowS
showsPrec :: Int -> DBState -> ShowS
$cshow :: DBState -> String
show :: DBState -> String
$cshowList :: [DBState] -> ShowS
showList :: [DBState] -> ShowS
Show
instance Default DBState where
  def :: DBState
def = DBState{ dbSectionLevel :: Int
dbSectionLevel = Int
0
               , dbQuoteType :: QuoteType
dbQuoteType = QuoteType
DoubleQuote
               , dbMeta :: Meta
dbMeta = Meta
forall a. Monoid a => a
mempty
               , dbBook :: Bool
dbBook = Bool
False
               , dbContent :: [Content]
dbContent = [] }
readDocBook :: (PandocMonad m, ToSources a)
            => ReaderOptions
            -> a
            -> m Pandoc
readDocBook :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readDocBook ReaderOptions
_ a
inp = do
  let sources :: Sources
sources = a -> Sources
forall a. ToSources a => a -> Sources
toSources a
inp
  [Content]
tree <- (Text -> m [Content])
-> ([Content] -> m [Content])
-> Either Text [Content]
-> m [Content]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (PandocError -> m [Content]
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m [Content])
-> (Text -> PandocError) -> Text -> m [Content]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> PandocError
PandocXMLError Text
"") [Content] -> m [Content]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text [Content] -> m [Content])
-> Either Text [Content] -> m [Content]
forall a b. (a -> b) -> a -> b
$
            Map Text Text -> Text -> Either Text [Content]
parseXMLContentsWithEntities
            Map Text Text
docbookEntityMap
              (Text -> Text
TL.fromStrict (Text -> Text) -> (Sources -> Text) -> Sources -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
handleInstructions (Text -> Text) -> (Sources -> Text) -> Sources -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sources -> Text
sourcesToText (Sources -> Text) -> Sources -> Text
forall a b. (a -> b) -> a -> b
$ Sources
sources)
  ([Blocks]
bs, DBState
st') <- (StateT DBState m [Blocks] -> DBState -> m ([Blocks], DBState))
-> DBState -> StateT DBState m [Blocks] -> m ([Blocks], DBState)
forall a b c. (a -> b -> c) -> b -> a -> c
flip StateT DBState m [Blocks] -> DBState -> m ([Blocks], DBState)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (DBState
forall a. Default a => a
def{ dbContent = tree }) (StateT DBState m [Blocks] -> m ([Blocks], DBState))
-> StateT DBState m [Blocks] -> m ([Blocks], DBState)
forall a b. (a -> b) -> a -> b
$ (Content -> StateT DBState m Blocks)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Content -> DB m Blocks
parseBlock [Content]
tree
  let headerLevel :: Block -> [Int]
headerLevel (Header Int
n Attr
_ [Inline]
_) = [Int
n]
      headerLevel Block
_              = []
  let bottomLevel :: Int
bottomLevel = Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
1 NonEmpty Int -> Int
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum (Maybe (NonEmpty Int) -> Int) -> Maybe (NonEmpty Int) -> Int
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty ([Int] -> Maybe (NonEmpty Int)) -> [Int] -> Maybe (NonEmpty Int)
forall a b. (a -> b) -> a -> b
$ (Block -> [Int]) -> [Blocks] -> [Int]
forall c. Monoid c => (Block -> c) -> [Blocks] -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query Block -> [Int]
headerLevel [Blocks]
bs
  Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$
    
    (if Int
bottomLevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1
        then Int -> Pandoc -> Pandoc
headerShift (Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
bottomLevel)
        else Pandoc -> Pandoc
forall a. a -> a
id) (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$ Meta -> [Block] -> Pandoc
Pandoc (DBState -> Meta
dbMeta DBState
st') ([Block] -> Pandoc) -> [Block] -> Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
toList (Blocks -> [Block]) -> Blocks -> [Block]
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
bs
handleInstructions :: Text -> Text
handleInstructions :: Text -> Text
handleInstructions Text
t =
  let (Text
x,Text
y) = HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOn Text
"<?" Text
t
   in if Text -> Bool
T.null Text
y
         then Text
x
         else
           let (Text
w,Text
z) = HasCallStack => Text -> Text -> (Text, Text)
Text -> Text -> (Text, Text)
T.breakOn Text
"?>" Text
y
            in (if (Char -> Bool) -> Text -> Text
T.takeWhile (\Char
c -> Char -> Bool
isLetter Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
                    (Int -> Text -> Text
T.drop Int
2 Text
w) Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"asciidoc-br", Text
"dbfo"]
                   then Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"<pi-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.drop Int
2 Text
w Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"/>"
                   else Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
w Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.take Int
2 Text
z) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
               Text -> Text
handleInstructions (Int -> Text -> Text
T.drop Int
2 Text
z)
getFigure :: PandocMonad m => Element -> DB m Blocks
getFigure :: forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getFigure Element
e = do
  Inlines
tit <- case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title") Element
e of
              Just Element
t  -> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
t
              Maybe Element
Nothing -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
  Blocks
contents <- Element -> DB m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
  let contents' :: Blocks
contents' =
        case Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
contents of
          [Para [img :: Inline
img@Image{}]] -> Inlines -> Blocks
plain ([Inline] -> Inlines
forall a. [a] -> Many a
fromList [Inline
img])
          [Block]
_ -> Blocks
contents
  Blocks -> DB m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DB m Blocks) -> Blocks -> DB m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Caption -> Blocks -> Blocks
figureWith
             (Text -> Element -> Text
attrValue Text
"id" Element
e, [], [])
             (Blocks -> Caption
simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
plain Inlines
tit)
             Blocks
contents'
attrValue :: Text -> Element -> Text
attrValue :: Text -> Element -> Text
attrValue Text
attr Element
elt =
  Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" ((QName -> Bool) -> [Attr] -> Maybe Text
lookupAttrBy (\QName
x -> QName -> Text
qName QName
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
attr) (Element -> [Attr]
elAttribs Element
elt))
named :: Text -> Element -> Bool
named :: Text -> Element -> Bool
named Text
s Element
e = QName -> Text
qName (Element -> QName
elName Element
e) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
s
addMetadataFromElement :: PandocMonad m => Element -> DB m Blocks
addMetadataFromElement :: forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e =
  Blocks
forall a. Monoid a => a
mempty Blocks -> StateT DBState m () -> StateT DBState m Blocks
forall a b. a -> StateT DBState m b -> StateT DBState m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (Element -> StateT DBState m ())
-> [Element] -> StateT DBState m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Element -> StateT DBState m ()
handleMetadataElement
                  ((Element -> Bool) -> Element -> [Element]
filterChildren ((Text -> Bool
forall {a}. (Eq a, IsString a) => a -> Bool
isMetadataField (Text -> Bool) -> (Element -> Text) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName (QName -> Text) -> (Element -> QName) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName)) Element
e)
 where
  handleMetadataElement :: Element -> StateT DBState m ()
handleMetadataElement Element
elt =
    case QName -> Text
qName (Element -> QName
elName Element
elt) of
      Text
"title" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"title" Element
elt
      Text
"subtitle" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"subtitle" Element
elt
      Text
"abstract" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"abstract" Element
elt
      Text
"date" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"date" Element
elt
      Text
"release" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"release" Element
elt
      Text
"releaseinfo" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"releaseinfo" Element
elt
      Text
"address" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"address" Element
elt
      Text
"copyright" -> Text -> Element -> StateT DBState m ()
forall {m :: * -> *}.
PandocMonad m =>
Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
"copyright" Element
elt
      Text
"author" -> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
fromAuthor Element
elt StateT DBState m Inlines
-> (Inlines -> StateT DBState m ()) -> StateT DBState m ()
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> StateT DBState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> DB m ()
addMeta Text
"author"
      Text
"authorgroup" ->
        (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
fromAuthor ((Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"author") Element
elt) StateT DBState m [Inlines]
-> ([Inlines] -> StateT DBState m ()) -> StateT DBState m ()
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> [Inlines] -> StateT DBState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> DB m ()
addMeta Text
"author"
      Text
_ -> LogMessage -> StateT DBState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> StateT DBState m ())
-> (Element -> LogMessage) -> Element -> StateT DBState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LogMessage
IgnoredElement (Text -> LogMessage) -> (Element -> Text) -> Element -> LogMessage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName (QName -> Text) -> (Element -> QName) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName (Element -> StateT DBState m ()) -> Element -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ Element
elt
  fromAuthor :: Element -> StateT DBState m Inlines
fromAuthor Element
elt =
    [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse Inlines
space ([Inlines] -> [Inlines])
-> ([Inlines] -> [Inlines]) -> [Inlines] -> [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> Bool) -> [Inlines] -> [Inlines]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (Inlines -> Bool) -> Inlines -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Bool
forall a. Many a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null)
      ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines (Element -> [Element]
elChildren Element
elt)
  addContentsToMetadata :: Text -> Element -> StateT DBState m ()
addContentsToMetadata Text
fieldname Element
elt =
    if (Element -> Bool) -> [Element] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any ((Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
blockTags) (Text -> Bool) -> (Element -> Text) -> Element -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QName -> Text
qName (QName -> Text) -> (Element -> QName) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> QName
elName) (Element -> [Element]
elChildren Element
elt)
       then Element -> DB m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
elt DB m Blocks
-> (Blocks -> StateT DBState m ()) -> StateT DBState m ()
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Blocks -> StateT DBState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> DB m ()
addMeta Text
fieldname
       else Element -> DB m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
elt DB m Inlines
-> (Inlines -> StateT DBState m ()) -> StateT DBState m ()
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> StateT DBState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> DB m ()
addMeta Text
fieldname
  isMetadataField :: a -> Bool
isMetadataField a
"abstract" = Bool
True
  isMetadataField a
"address" = Bool
True
  isMetadataField a
"annotation" = Bool
True
  isMetadataField a
"artpagenums" = Bool
True
  isMetadataField a
"author" = Bool
True
  isMetadataField a
"authorgroup" = Bool
True
  isMetadataField a
"authorinitials" = Bool
True
  isMetadataField a
"bibliocoverage" = Bool
True
  isMetadataField a
"biblioid" = Bool
True
  isMetadataField a
"bibliomisc" = Bool
True
  isMetadataField a
"bibliomset" = Bool
True
  isMetadataField a
"bibliorelation" = Bool
True
  isMetadataField a
"biblioset" = Bool
True
  isMetadataField a
"bibliosource" = Bool
True
  isMetadataField a
"collab" = Bool
True
  isMetadataField a
"confgroup" = Bool
True
  isMetadataField a
"contractnum" = Bool
True
  isMetadataField a
"contractsponsor" = Bool
True
  isMetadataField a
"copyright" = Bool
True
  isMetadataField a
"cover" = Bool
True
  isMetadataField a
"date" = Bool
True
  isMetadataField a
"edition" = Bool
True
  isMetadataField a
"editor" = Bool
True
  isMetadataField a
"extendedlink" = Bool
True
  isMetadataField a
"issuenum" = Bool
True
  isMetadataField a
"itermset" = Bool
True
  isMetadataField a
"keywordset" = Bool
True
  isMetadataField a
"legalnotice" = Bool
True
  isMetadataField a
"mediaobject" = Bool
True
  isMetadataField a
"org" = Bool
True
  isMetadataField a
"orgname" = Bool
True
  isMetadataField a
"othercredit" = Bool
True
  isMetadataField a
"pagenums" = Bool
True
  isMetadataField a
"printhistory" = Bool
True
  isMetadataField a
"productname" = Bool
True
  isMetadataField a
"productnumber" = Bool
True
  isMetadataField a
"pubdate" = Bool
True
  isMetadataField a
"publisher" = Bool
True
  isMetadataField a
"publishername" = Bool
True
  isMetadataField a
"releaseinfo" = Bool
True
  isMetadataField a
"revhistory" = Bool
True
  isMetadataField a
"seriesvolnums" = Bool
True
  isMetadataField a
"subjectset" = Bool
True
  isMetadataField a
"subtitle" = Bool
True
  isMetadataField a
"title" = Bool
True
  isMetadataField a
"titleabbrev" = Bool
True
  isMetadataField a
"volumenum" = Bool
True
  isMetadataField a
_ = Bool
False
addMeta :: PandocMonad m => ToMetaValue a => Text -> a -> DB m ()
addMeta :: forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> DB m ()
addMeta Text
field a
val = (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (Text -> a -> DBState -> DBState
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> DBState -> DBState
setMeta Text
field a
val)
instance HasMeta DBState where
  setMeta :: forall b. ToMetaValue b => Text -> b -> DBState -> DBState
setMeta Text
field b
v DBState
s =  DBState
s {dbMeta = setMeta field v (dbMeta s)}
  deleteMeta :: Text -> DBState -> DBState
deleteMeta Text
field DBState
s = DBState
s {dbMeta = deleteMeta field (dbMeta s)}
isBlockElement :: Content -> Bool
isBlockElement :: Content -> Bool
isBlockElement (Elem Element
e) = QName -> Text
qName (Element -> QName
elName Element
e) Text -> Set Text -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set Text
blockTags
isBlockElement Content
_ = Bool
False
blockTags :: Set.Set Text
blockTags :: Set Text
blockTags = [Text] -> Set Text
forall a. Ord a => [a] -> Set a
Set.fromList ([Text] -> Set Text) -> [Text] -> Set Text
forall a b. (a -> b) -> a -> b
$
  [ Text
"abstract"
  , Text
"ackno"
  , Text
"answer"
  , Text
"appendix"
  , Text
"appendixinfo"
  , Text
"area"
  , Text
"areaset"
  , Text
"areaspec"
  , Text
"article"
  , Text
"articleinfo"
  , Text
"attribution"
  , Text
"authorinitials"
  , Text
"bibliodiv"
  , Text
"biblioentry"
  , Text
"bibliography"
  , Text
"bibliomisc"
  , Text
"bibliomixed"
  , Text
"blockquote"
  , Text
"book"
  , Text
"bookinfo"
  , Text
"bridgehead"
  , Text
"calloutlist"
  , Text
"caption"
  , Text
"chapter"
  , Text
"chapterinfo"
  , Text
"epigraph"
  , Text
"example"
  , Text
"figure"
  , Text
"formalpara"
  , Text
"glossary"
  , Text
"glossaryinfo"
  , Text
"glossdiv"
  , Text
"glossee"
  , Text
"glosseealso"
  , Text
"glosslist"
  , Text
"glosssee"
  , Text
"glossseealso"
  , Text
"index"
  , Text
"info"
  , Text
"informalexample"
  , Text
"informalfigure"
  , Text
"informaltable"
  , Text
"itemizedlist"
  , Text
"linegroup"
  , Text
"literallayout"
  , Text
"mediaobject"
  , Text
"orderedlist"
  , Text
"para"
  , Text
"part"
  , Text
"partinfo"
  , Text
"preface"
  , Text
"procedure"
  , Text
"programlisting"
  , Text
"qandadiv"
  , Text
"question"
  , Text
"refsect1"
  , Text
"refsect1info"
  , Text
"refsect2"
  , Text
"refsect2info"
  , Text
"refsect3"
  , Text
"refsect3info"
  , Text
"refsection"
  , Text
"refsectioninfo"
  , Text
"screen"
  , Text
"sect1"
  , Text
"sect1info"
  , Text
"sect2"
  , Text
"sect2info"
  , Text
"sect3"
  , Text
"sect3info"
  , Text
"sect4"
  , Text
"sect4info"
  , Text
"sect5"
  , Text
"sect5info"
  , Text
"section"
  , Text
"sectioninfo"
  , Text
"simpara"
  , Text
"simplesect"
  , Text
"substeps"
  , Text
"subtitle"
  , Text
"table"
  , Text
"title"
  , Text
"titleabbrev"
  , Text
"toc"
  , Text
"variablelist"
  ] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text]
admonitionTags
admonitionTags :: [Text]
admonitionTags :: [Text]
admonitionTags = [Text
"caution",Text
"danger",Text
"important",Text
"note",Text
"tip",Text
"warning"]
titledBlockElements :: [Text]
titledBlockElements :: [Text]
titledBlockElements = [Text
"example", Text
"formalpara", Text
"sidebar"]
trimNl :: Text -> Text
trimNl :: Text -> Text
trimNl = (Char -> Bool) -> Text -> Text
T.dropAround (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n')
addToStart :: Inlines -> Blocks -> Blocks
addToStart :: Inlines -> Blocks -> Blocks
addToStart Inlines
toadd Blocks
bs =
  case Blocks -> [Block]
forall a. Many a -> [a]
toList Blocks
bs of
    (Para [Inline]
xs : [Block]
rest) -> Inlines -> Blocks
para (Inlines
toadd Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> [Inline] -> Inlines
forall a. [a] -> Many a
fromList [Inline]
xs) Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> [Block] -> Blocks
forall a. [a] -> Many a
fromList [Block]
rest
    [Block]
_                -> Blocks
bs
getMediaobject :: PandocMonad m => Element -> DB m Inlines
getMediaobject :: forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getMediaobject Element
e = do
  let (Text
imageUrl, Text
tit, Attr
attr) =
        case (Element -> Bool) -> Element -> [Element]
filterElements (Text -> Element -> Bool
named Text
"imageobject") Element
e of
          []  -> (Text
forall a. Monoid a => a
mempty, Text
forall a. Monoid a => a
mempty, Attr
nullAttr)
          (Element
z:[Element]
_) ->
            let tit' :: Text
tit' = Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" Element -> Text
strContent (Maybe Element -> Text) -> Maybe Element -> Text
forall a b. (a -> b) -> a -> b
$
                         (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"objectinfo") Element
z Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                         (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title")
                (Text
imageUrl', Attr
attr') =
                  case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"imagedata") Element
z of
                        Maybe Element
Nothing -> (Text
forall a. Monoid a => a
mempty, Attr
nullAttr)
                        Just Element
i  -> let atVal :: Text -> Text
atVal Text
a = Text -> Element -> Text
attrValue Text
a Element
i
                                       w :: [(Text, Text)]
w = case Text -> Text
atVal Text
"width" of
                                             Text
"" -> []
                                             Text
d  -> [(Text
"width", Text
d)]
                                       h :: [(Text, Text)]
h = case Text -> Text
atVal Text
"depth" of
                                             Text
"" -> []
                                             Text
d  -> [(Text
"height", Text
d)]
                                       id' :: Text
id' = Text -> Text
atVal Text
"id"
                                       cs :: [Text]
cs = Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Text
atVal Text
"role"
                                       atr :: Attr
atr = (Text
id', [Text]
cs, [(Text, Text)]
w [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. [a] -> [a] -> [a]
++ [(Text, Text)]
h)
                                   in  (Text -> Text
atVal Text
"fileref", Attr
atr)
            in  (Text
imageUrl', Text
tit', Attr
attr')
  let capt :: DB m Inlines
capt = case (Element -> Bool) -> Element -> Maybe Element
filterChild (\Element
x -> Text -> Element -> Bool
named Text
"caption" Element
x
                                            Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"textobject" Element
x
                                            Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"alt" Element
x) Element
e of
                        Maybe Element
Nothing -> Inlines -> DB m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
                        Just Element
z  -> Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> DB m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                                         (Content -> DB m Inlines)
-> [Content] -> StateT DBState 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 Content -> DB m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Element -> [Content]
elContent Element
z)
  (Inlines -> Inlines) -> DB m Inlines -> DB m Inlines
forall a b. (a -> b) -> StateT DBState m a -> StateT DBState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Attr -> Text -> Text -> Inlines -> Inlines
imageWith Attr
attr Text
imageUrl Text
tit) DB m Inlines
capt
getBlocks :: PandocMonad m => Element -> DB m Blocks
getBlocks :: forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e =  [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                 (Content -> StateT DBState m Blocks)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Content -> DB m Blocks
parseBlock (Element -> [Content]
elContent Element
e)
parseBlock :: PandocMonad m => Content -> DB m Blocks
parseBlock :: forall (m :: * -> *). PandocMonad m => Content -> DB m Blocks
parseBlock (Text (CData CDataKind
CDataRaw Text
_ Maybe Line
_)) = Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty 
parseBlock (Text (CData CDataKind
_ Text
s Maybe Line
_)) = if (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isSpace Text
s
                                     then Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
                                     else Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
plain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
trimInlines (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
s
parseBlock (CRef Text
x) = Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
plain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toUpper Text
x
parseBlock (Elem Element
e) =
  case QName -> Text
qName (Element -> QName
elName Element
e) of
        Text
"toc"   -> StateT DBState m Blocks
skip 
        Text
"index" -> StateT DBState m Blocks
skip 
        Text
"para"  -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"simpara"  -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"ackno"  -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"epigraph" -> StateT DBState m Blocks
parseBlockquote
        Text
"blockquote" -> StateT DBState m Blocks -> StateT DBState m Blocks
withOptionalTitle StateT DBState m Blocks
parseBlockquote
        Text
"attribution" -> StateT DBState m Blocks
skip
        Text
"titleabbrev" -> StateT DBState m Blocks
skip
        Text
"authorinitials" -> StateT DBState m Blocks
skip
        Text
"bibliography" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
0
        Text
"bibliodiv" ->
          case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title") Element
e of
            Just Element
_  -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
1
            Maybe Element
Nothing -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
        Text
"biblioentry" -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"bibliomisc" -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"bibliomixed" -> (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
para (Element -> [Content]
elContent Element
e)
        Text
"equation"         -> Inlines -> Blocks
para (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> (Text -> Inlines) -> StateT DBState m Inlines
forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
displayMath
        Text
"informalequation" -> Attr -> Blocks -> Blocks
divWith (Text -> Element -> Text
attrValue Text
"id" Element
e,[Text
"informalequation"],[]) (Blocks -> Blocks) -> (Inlines -> Blocks) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              Inlines -> Blocks
para (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> (Text -> Inlines) -> StateT DBState m Inlines
forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
displayMath
        Text
"glosssee" -> Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Inlines
ils -> Text -> Inlines
text Text
"See " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ils Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
".")
                         (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e
        Text
"glossseealso" -> Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\Inlines
ils -> Text -> Inlines
text Text
"See also " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
ils Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
".")
                         (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e
        Text
"glossary" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
0
        Text
"glossdiv" -> [(Inlines, [Blocks])] -> Blocks
definitionList ([(Inlines, [Blocks])] -> Blocks)
-> StateT DBState m [(Inlines, [Blocks])]
-> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                  (Element -> StateT DBState m (Inlines, [Blocks]))
-> [Element] -> StateT DBState 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 Element -> StateT DBState m (Inlines, [Blocks])
forall {m :: * -> *}.
PandocMonad m =>
Element -> StateT DBState m (Inlines, [Blocks])
parseGlossEntry ((Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"glossentry") Element
e)
        Text
"glosslist" -> [(Inlines, [Blocks])] -> Blocks
definitionList ([(Inlines, [Blocks])] -> Blocks)
-> StateT DBState m [(Inlines, [Blocks])]
-> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                  (Element -> StateT DBState m (Inlines, [Blocks]))
-> [Element] -> StateT DBState 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 Element -> StateT DBState m (Inlines, [Blocks])
forall {m :: * -> *}.
PandocMonad m =>
Element -> StateT DBState m (Inlines, [Blocks])
parseGlossEntry ((Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"glossentry") Element
e)
        Text
"chapter" -> (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DBState
st -> DBState
st{ dbBook = True}) StateT DBState m ()
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
0
        Text
"part" -> (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DBState
st -> DBState
st{ dbBook = True}) StateT DBState m ()
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect (-Int
1)
        Text
"appendix" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
0
        Text
"preface" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
0
        Text
"bridgehead" -> Inlines -> Blocks
para (Inlines -> Blocks) -> (Inlines -> Inlines) -> Inlines -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> Inlines
strong (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e
        Text
"sect1" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
1
        Text
"sect2" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
2
        Text
"sect3" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
3
        Text
"sect4" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
4
        Text
"sect5" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
5
        Text
"section" -> (DBState -> Int) -> StateT DBState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> Int
dbSectionLevel StateT DBState m Int
-> (Int -> StateT DBState m Blocks) -> StateT DBState m Blocks
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect (Int -> StateT DBState m Blocks)
-> (Int -> Int) -> Int -> StateT DBState m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        Text
"simplesect" ->
          (DBState -> Int) -> StateT DBState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> Int
dbSectionLevel StateT DBState m Int
-> (Int -> StateT DBState m Blocks) -> StateT DBState m Blocks
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
          Text -> [Text] -> [(Text, Text)] -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Text -> [Text] -> [(Text, Text)] -> Int -> StateT DBState m Blocks
sectWith(Text -> Element -> Text
attrValue Text
"id" Element
e) [Text
"unnumbered"] [] (Int -> StateT DBState m Blocks)
-> (Int -> Int) -> Int -> StateT DBState m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        Text
"refsect1" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
1
        Text
"refsect2" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
2
        Text
"refsect3" -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect Int
3
        Text
"refsection" -> (DBState -> Int) -> StateT DBState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> Int
dbSectionLevel StateT DBState m Int
-> (Int -> StateT DBState m Blocks) -> StateT DBState m Blocks
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect (Int -> StateT DBState m Blocks)
-> (Int -> Int) -> Int -> StateT DBState m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        Text
l | Text
l Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
titledBlockElements -> Text -> StateT DBState m Blocks
parseAdmonition Text
l
        Text
l | Text
l Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
admonitionTags -> Text -> StateT DBState m Blocks
parseAdmonition Text
l
        Text
"area" -> StateT DBState m Blocks
skip
        Text
"areaset" -> StateT DBState m Blocks
skip
        Text
"areaspec" -> StateT DBState m Blocks
skip
        Text
"qandadiv" -> (DBState -> Int) -> StateT DBState m Int
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> Int
dbSectionLevel StateT DBState m Int
-> (Int -> StateT DBState m Blocks) -> StateT DBState m Blocks
forall a b.
StateT DBState m a
-> (a -> StateT DBState m b) -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Int -> StateT DBState m Blocks
sect (Int -> StateT DBState m Blocks)
-> (Int -> Int) -> Int -> StateT DBState m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
        Text
"question" -> Inlines -> Blocks -> Blocks
addToStart (Inlines -> Inlines
strong (Text -> Inlines
str Text
"Q:") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
" ") (Blocks -> Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"answer" -> Inlines -> Blocks -> Blocks
addToStart (Inlines -> Inlines
strong (Text -> Inlines
str Text
"A:") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
" ") (Blocks -> Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"abstract" -> Blocks -> Blocks
blockQuote (Blocks -> Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"calloutlist" -> StateT DBState m Blocks -> StateT DBState m Blocks
withOptionalTitle (StateT DBState m Blocks -> StateT DBState m Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
bulletList ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Blocks]
callouts
        Text
"itemizedlist" -> StateT DBState m Blocks -> StateT DBState m Blocks
withOptionalTitle (StateT DBState m Blocks -> StateT DBState m Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$
                            [Blocks] -> Blocks
bulletList ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> [Blocks]
handleCompact ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Blocks]
listitems
        Text
"orderedlist" -> StateT DBState m Blocks -> StateT DBState m Blocks
withOptionalTitle (StateT DBState m Blocks -> StateT DBState m Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ do
          let listStyle :: ListNumberStyle
listStyle = case Text -> Element -> Text
attrValue Text
"numeration" Element
e of
                               Text
"arabic"     -> ListNumberStyle
Decimal
                               Text
"loweralpha" -> ListNumberStyle
LowerAlpha
                               Text
"upperalpha" -> ListNumberStyle
UpperAlpha
                               Text
"lowerroman" -> ListNumberStyle
LowerRoman
                               Text
"upperroman" -> ListNumberStyle
UpperRoman
                               Text
_            -> ListNumberStyle
Decimal
          let start :: Int
start = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$
                      (Element -> Bool) -> Element -> Maybe Element
filterElement (Text -> Element -> Bool
named Text
"listitem") Element
e
                       Maybe Element -> (Element -> Maybe Int) -> Maybe Int
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Int) -> (Element -> Text) -> Element -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Element -> Text
attrValue Text
"override"
          ListAttributes -> [Blocks] -> Blocks
orderedListWith (Int
start,ListNumberStyle
listStyle,ListNumberDelim
DefaultDelim) ([Blocks] -> Blocks)
-> ([Blocks] -> [Blocks]) -> [Blocks] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> [Blocks]
handleCompact
            ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Blocks]
listitems
        Text
"variablelist" -> [(Inlines, [Blocks])] -> Blocks
definitionList ([(Inlines, [Blocks])] -> Blocks)
-> StateT DBState m [(Inlines, [Blocks])]
-> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [(Inlines, [Blocks])]
deflistitems
        Text
"procedure" -> [Blocks] -> Blocks
orderedList ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Blocks]
steps
        Text
"substeps" -> [Blocks] -> Blocks
orderedList ([Blocks] -> Blocks)
-> StateT DBState m [Blocks] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Blocks]
steps
        Text
"figure" -> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getFigure Element
e
        Text
"informalfigure" -> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getFigure Element
e
        Text
"mediaobject" -> Inlines -> Blocks
para (Inlines -> Blocks)
-> StateT DBState m Inlines -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getMediaobject Element
e
        Text
"caption" -> StateT DBState m Blocks
skip
        Text
"info" -> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e
        Text
"articleinfo" -> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e
        Text
"sectioninfo" -> StateT DBState m Blocks
skip 
        Text
"refsectioninfo" -> StateT DBState m Blocks
skip 
        Text
"refsect1info" -> StateT DBState m Blocks
skip 
        Text
"refsect2info" -> StateT DBState m Blocks
skip 
        Text
"refsect3info" -> StateT DBState m Blocks
skip 
        Text
"sect1info" -> StateT DBState m Blocks
skip  
        Text
"sect2info" -> StateT DBState m Blocks
skip  
        Text
"sect3info" -> StateT DBState m Blocks
skip  
        Text
"sect4info" -> StateT DBState m Blocks
skip  
        Text
"sect5info" -> StateT DBState m Blocks
skip  
        Text
"chapterinfo" -> StateT DBState m Blocks
skip 
        Text
"partinfo" -> StateT DBState m Blocks
skip 
        Text
"glossaryinfo" -> StateT DBState m Blocks
skip  
        Text
"appendixinfo" -> StateT DBState m Blocks
skip  
        Text
"bookinfo" -> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e
        Text
"article" -> (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DBState
st -> DBState
st{ dbBook = False }) StateT DBState m ()
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                           Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e StateT DBState m Blocks
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"book" -> (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify (\DBState
st -> DBState
st{ dbBook = True }) StateT DBState m ()
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                    Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
addMetadataFromElement Element
e StateT DBState m Blocks
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"table" -> StateT DBState m Blocks
parseTable
        Text
"informaltable" -> StateT DBState m Blocks
parseTable
        Text
"informalexample" -> Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"informalexample"], []) (Blocks -> Blocks)
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                             Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
        Text
"linegroup" -> [Inlines] -> Blocks
lineBlock ([Inlines] -> Blocks)
-> StateT DBState m [Inlines] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m [Inlines]
lineItems
        Text
"literallayout" -> StateT DBState m Blocks
codeBlockWithLang
        Text
"screen" -> StateT DBState m Blocks
codeBlockWithLang
        Text
"programlisting" -> StateT DBState m Blocks
codeBlockWithLang
        Text
"?xml"  -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
        Text
"title" -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty     
        Text
"subtitle" -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty  
        Text
_ -> StateT DBState m Blocks
skip StateT DBState m Blocks
-> StateT DBState m Blocks -> StateT DBState m Blocks
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
   where skip :: StateT DBState m Blocks
skip = do
           let qn :: Text
qn = QName -> Text
qName (QName -> Text) -> QName -> Text
forall a b. (a -> b) -> a -> b
$ Element -> QName
elName Element
e
           let name :: Text
name = if Text
"pi-" Text -> Text -> Bool
`T.isPrefixOf` Text
qn
                         then Text
"<?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
qn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"?>"
                         else Text
qn
           m () -> StateT DBState m ()
forall (m :: * -> *) a. Monad m => m a -> StateT DBState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> StateT DBState m ()) -> m () -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
IgnoredElement Text
name
           Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
         compactSpacing :: Bool
compactSpacing = case Text -> Element -> Text
attrValue Text
"spacing" Element
e of
                            Text
"compact" -> Bool
True
                            Text
_         -> Bool
False
         handleCompact :: [Blocks] -> [Blocks]
handleCompact = if Bool
compactSpacing
                            then (Blocks -> Blocks) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map ((Block -> Block) -> Blocks -> Blocks
forall a b. (a -> b) -> Many a -> Many b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Block -> Block
paraToPlain)
                            else [Blocks] -> [Blocks]
forall a. a -> a
id
         codeBlockWithLang :: StateT DBState m Blocks
codeBlockWithLang = do
           let classes' :: [Text]
classes' = case Text -> Element -> Text
attrValue Text
"language" Element
e of
                                Text
"" -> []
                                Text
x  -> [Text
x]
                [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++ [Text
"numberLines" | Text -> Element -> Text
attrValue Text
"linenumbering" Element
e Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"numbered"]
           Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
codeBlockWith (Text -> Element -> Text
attrValue Text
"id" Element
e, [Text]
classes', [])
                  (Text -> Blocks) -> Text -> Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Text
trimNl (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Element -> Text
strContentRecursive Element
e
         parseBlockquote :: StateT DBState m Blocks
parseBlockquote = do
            Blocks
attrib <- case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"attribution") Element
e of
                             Maybe Element
Nothing  -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
                             Just Element
z   -> Inlines -> Blocks
para (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Inlines
str Text
"— " Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>) (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat
                                         ([Inlines] -> Blocks)
-> StateT DBState m [Inlines] -> StateT DBState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                                              (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Element -> [Content]
elContent Element
z)
            Blocks
contents <- Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
            Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks
blockQuote (Blocks
contents Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
attrib)
         listitems :: StateT DBState m [Blocks]
listitems = (Element -> StateT DBState m Blocks)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks ([Element] -> StateT DBState m [Blocks])
-> [Element] -> StateT DBState m [Blocks]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"listitem") Element
e
         callouts :: StateT DBState m [Blocks]
callouts = (Element -> StateT DBState m Blocks)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks ([Element] -> StateT DBState m [Blocks])
-> [Element] -> StateT DBState m [Blocks]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"callout") Element
e
         deflistitems :: StateT DBState m [(Inlines, [Blocks])]
deflistitems = (Element -> StateT DBState m (Inlines, [Blocks]))
-> [Element] -> StateT DBState 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 Element -> StateT DBState m (Inlines, [Blocks])
forall {m :: * -> *}.
PandocMonad m =>
Element -> StateT DBState m (Inlines, [Blocks])
parseVarListEntry ([Element] -> StateT DBState m [(Inlines, [Blocks])])
-> [Element] -> StateT DBState m [(Inlines, [Blocks])]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren
                     (Text -> Element -> Bool
named Text
"varlistentry") Element
e
         steps :: StateT DBState m [Blocks]
steps = (Element -> StateT DBState m Blocks)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks ([Element] -> StateT DBState m [Blocks])
-> [Element] -> StateT DBState m [Blocks]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"step") Element
e
         parseVarListEntry :: Element -> StateT DBState m (Inlines, [Blocks])
parseVarListEntry Element
e' = do
                     let terms :: [Element]
terms = (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"term") Element
e'
                     let items :: [Element]
items = (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"listitem") Element
e'
                     [Inlines]
terms' <- (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines [Element]
terms
                     [Blocks]
items' <- (Element -> StateT DBState m Blocks)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks [Element]
items
                     (Inlines, [Blocks]) -> StateT DBState m (Inlines, [Blocks])
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"; ") [Inlines]
terms', [Blocks]
items')
         parseGlossEntry :: Element -> StateT DBState m (Inlines, [Blocks])
parseGlossEntry Element
e' = do
                     let terms :: [Element]
terms = (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"glossterm") Element
e'
                     let items :: [Element]
items = (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"glossdef") Element
e'
                     [Inlines]
terms' <- (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines [Element]
terms
                     [Blocks]
items' <- (Element -> StateT DBState m Blocks)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks [Element]
items
                     (Inlines, [Blocks]) -> StateT DBState m (Inlines, [Blocks])
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"; ") [Inlines]
terms', [Blocks]
items')
         parseTable :: StateT DBState m Blocks
parseTable = do
                      let elId :: Text
elId = Text -> Element -> Text
attrValue Text
"id" Element
e
                      let attrs :: [(Text, Text)]
attrs = case Text -> Element -> Text
attrValue Text
"tabstyle" Element
e of
                                    Text
"" -> []
                                    Text
x  -> [(Text
"custom-style", Text
x)]
                      let classes :: [Text]
classes = Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Element -> Text
attrValue Text
"class" Element
e
                      let isCaption :: Element -> Bool
isCaption Element
x = Text -> Element -> Bool
named Text
"title" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"caption" Element
x
                      Inlines
capt <- case (Element -> Bool) -> Element -> Maybe Element
filterChild Element -> Bool
isCaption Element
e of
                                    Just Element
t  -> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
t
                                    Maybe Element
Nothing -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
                      let e' :: Element
e' = Element -> Maybe Element -> Element
forall a. a -> Maybe a -> a
fromMaybe Element
e (Maybe Element -> Element) -> Maybe Element -> Element
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"tgroup") Element
e
                      let isColspec :: Element -> Bool
isColspec Element
x = Text -> Element -> Bool
named Text
"colspec" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"col" Element
x
                      let colspecs :: [Element]
colspecs = case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"colgroup") Element
e' of
                                           Just Element
c -> (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
isColspec Element
c
                                           Maybe Element
_      -> (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
isColspec Element
e'
                      let colnames :: [Text]
colnames = case [Element]
colspecs of
                                       [] -> []
                                       [Element]
cs -> (Element -> Maybe Text) -> [Element] -> [Text]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (QName -> Element -> Maybe Text
findAttr (Text -> QName
unqual Text
"colname" )) [Element]
cs
                      let isRow :: Element -> Bool
isRow Element
x = Text -> Element -> Bool
named Text
"row" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"tr" Element
x
                      [Cell]
headrows <- case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"thead") Element
e' of
                                       Just Element
h  -> case (Element -> Bool) -> Element -> Maybe Element
filterChild Element -> Bool
isRow Element
h of
                                                       Just Element
x  -> [Text] -> Element -> StateT DBState m [Cell]
forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m [Cell]
parseRow [Text]
colnames Element
x
                                                       Maybe Element
Nothing -> [Cell] -> StateT DBState m [Cell]
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return []
                                       Maybe Element
Nothing -> [Cell] -> StateT DBState m [Cell]
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return []
                      [[Cell]]
bodyrows <- case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"tbody") Element
e' of
                                       Just Element
b  -> (Element -> StateT DBState m [Cell])
-> [Element] -> StateT DBState 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 ([Text] -> Element -> StateT DBState m [Cell]
forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m [Cell]
parseRow [Text]
colnames)
                                                  ([Element] -> StateT DBState m [[Cell]])
-> [Element] -> StateT DBState m [[Cell]]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
isRow Element
b
                                       Maybe Element
Nothing -> (Element -> StateT DBState m [Cell])
-> [Element] -> StateT DBState 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 ([Text] -> Element -> StateT DBState m [Cell]
forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m [Cell]
parseRow [Text]
colnames)
                                                  ([Element] -> StateT DBState m [[Cell]])
-> [Element] -> StateT DBState m [[Cell]]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
isRow Element
e'
                      let toWidth :: Element -> Maybe b
toWidth Element
c = do
                            Text
w <- QName -> Element -> Maybe Text
findAttr (Text -> QName
unqual Text
"colwidth") Element
c
                            b
n <- Text -> Maybe b
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe b) -> Text -> Maybe b
forall a b. (a -> b) -> a -> b
$ Text
"0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Char -> Bool) -> Text -> Text
T.filter (\Char
x ->
                                                     (Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9')
                                                      Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
w
                            if b
n b -> b -> Bool
forall a. Ord a => a -> a -> Bool
> b
0 then b -> Maybe b
forall a. a -> Maybe a
Just b
n else Maybe b
forall a. Maybe a
Nothing
                      let numrows :: Int
numrows = Int -> (NonEmpty Int -> Int) -> Maybe (NonEmpty Int) -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
0 NonEmpty Int -> Int
forall a. Ord a => NonEmpty a -> a
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum (Maybe (NonEmpty Int) -> Int) -> Maybe (NonEmpty Int) -> Int
forall a b. (a -> b) -> a -> b
$ [Int] -> Maybe (NonEmpty Int)
forall a. [a] -> Maybe (NonEmpty a)
nonEmpty
                                                    ([Int] -> Maybe (NonEmpty Int)) -> [Int] -> Maybe (NonEmpty Int)
forall a b. (a -> b) -> a -> b
$ ([Cell] -> Int) -> [[Cell]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map [Cell] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Cell]]
bodyrows
                      let aligns :: [Alignment]
aligns = case [Element]
colspecs of
                                     [] -> Int -> Alignment -> [Alignment]
forall a. Int -> a -> [a]
replicate Int
numrows Alignment
AlignDefault
                                     [Element]
cs -> (Element -> Alignment) -> [Element] -> [Alignment]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Alignment
toAlignment [Element]
cs
                      let parseWidth :: Text -> m a
parseWidth Text
s = Text -> m a
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead ((Char -> Bool) -> Text -> Text
T.filter (\Char
x -> (Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
>= Char
'0' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'9')
                                                                   Bool -> Bool -> Bool
|| Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') Text
s)
                      let textWidth :: Double
textWidth = case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"pi-dbfo") Element
e of
                                        Just Element
d  -> case Text -> Element -> Text
attrValue Text
"table-width" Element
d of
                                                     Text
"" -> Double
1.0
                                                     Text
w  -> Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
100.0 (Text -> Maybe Double
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
parseWidth Text
w) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
100.0
                                        Maybe Element
Nothing -> Double
1.0
                      let widths :: [ColWidth]
widths = case [Element]
colspecs of
                                     [] -> Int -> ColWidth -> [ColWidth]
forall a. Int -> a -> [a]
replicate Int
numrows ColWidth
ColWidthDefault
                                     [Element]
cs -> let ws :: [Maybe Double]
ws = (Element -> Maybe Double) -> [Element] -> [Maybe Double]
forall a b. (a -> b) -> [a] -> [b]
map Element -> Maybe Double
forall {b}. (Read b, Ord b, Num b) => Element -> Maybe b
toWidth [Element]
cs
                                           in case [Maybe Double] -> Maybe [Double]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
forall (m :: * -> *) a. Monad m => [m a] -> m [a]
sequence [Maybe Double]
ws of
                                                Just [Double]
ws' -> let colTot :: Double
colTot = [Double] -> Double
forall a. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Double]
ws'
                                                                scale :: Double -> Double
scale
                                                                  | Double
textWidth Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
1.0 = (Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
colTot)
                                                                  | Bool
otherwise = (Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
textWidth Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
colTot) )
                                                            in  Double -> ColWidth
ColWidth (Double -> ColWidth) -> (Double -> Double) -> Double -> ColWidth
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Double
scale (Double -> ColWidth) -> [Double] -> [ColWidth]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Double]
ws'
                                                Maybe [Double]
Nothing  -> Int -> ColWidth -> [ColWidth]
forall a. Int -> a -> [a]
replicate Int
numrows ColWidth
ColWidthDefault
                      let toRow :: [Cell] -> Row
toRow = Attr -> [Cell] -> Row
Row Attr
nullAttr
                          toHeaderRow :: [Cell] -> [Row]
toHeaderRow [Cell]
l = [[Cell] -> Row
toRow [Cell]
l | Bool -> Bool
not ([Cell] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Cell]
l)]
                      Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr
-> Caption
-> [ColSpec]
-> TableHead
-> [TableBody]
-> TableFoot
-> Blocks
tableWith (Text
elId,[Text]
classes,[(Text, Text)]
attrs)
                                     (Blocks -> Caption
simpleCaption (Blocks -> Caption) -> Blocks -> Caption
forall a b. (a -> b) -> a -> b
$ Inlines -> Blocks
plain Inlines
capt)
                                     ([Alignment] -> [ColWidth] -> [ColSpec]
forall a b. [a] -> [b] -> [(a, b)]
zip [Alignment]
aligns [ColWidth]
widths)
                                     (Attr -> [Row] -> TableHead
TableHead Attr
nullAttr ([Row] -> TableHead) -> [Row] -> TableHead
forall a b. (a -> b) -> a -> b
$ [Cell] -> [Row]
toHeaderRow [Cell]
headrows)
                                     [Attr -> RowHeadColumns -> [Row] -> [Row] -> TableBody
TableBody Attr
nullAttr RowHeadColumns
0 [] ([Row] -> TableBody) -> [Row] -> TableBody
forall a b. (a -> b) -> a -> b
$ ([Cell] -> Row) -> [[Cell]] -> [Row]
forall a b. (a -> b) -> [a] -> [b]
map [Cell] -> Row
toRow [[Cell]]
bodyrows]
                                     (Attr -> [Row] -> TableFoot
TableFoot Attr
nullAttr [])
         sect :: Int -> StateT DBState m Blocks
sect Int
n = Text -> [Text] -> [(Text, Text)] -> Int -> StateT DBState m Blocks
forall {m :: * -> *}.
PandocMonad m =>
Text -> [Text] -> [(Text, Text)] -> Int -> StateT DBState m Blocks
sectWith(Text -> Element -> Text
attrValue Text
"id" Element
e) [] [] Int
n
         sectWith :: Text -> [Text] -> [(Text, Text)] -> Int -> StateT DBState m Blocks
sectWith Text
elId [Text]
classes [(Text, Text)]
attrs Int
n = do
           Bool
isbook <- (DBState -> Bool) -> StateT DBState m Bool
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> Bool
dbBook
           let n' :: Int
n' = if Bool
isbook Bool -> Bool -> Bool
|| Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
n
           Inlines
headerText <- case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title") Element
e Maybe Element -> Maybe Element -> Maybe Element
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
                              ((Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"info") Element
e Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                                  (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title")) of
                            Just Element
t  -> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
t
                            Maybe Element
Nothing -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
           (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DBState -> DBState) -> StateT DBState m ())
-> (DBState -> DBState) -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ \DBState
st -> DBState
st{ dbSectionLevel = n }
           Blocks
b <- Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
           (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DBState -> DBState) -> StateT DBState m ())
-> (DBState -> DBState) -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ \DBState
st -> DBState
st{ dbSectionLevel = n - 1 }
           Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Int -> Inlines -> Blocks
headerWith (Text
elId, [Text]
classes, Maybe (Text, Text) -> [(Text, Text)]
forall a. Maybe a -> [a]
maybeToList Maybe (Text, Text)
titleabbrevElAsAttr[(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. [a] -> [a] -> [a]
++[(Text, Text)]
attrs) Int
n' Inlines
headerText Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
b
         titleabbrevElAsAttr :: Maybe (Text, Text)
titleabbrevElAsAttr =
           case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"titleabbrev") Element
e Maybe Element -> Maybe Element -> Maybe Element
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
                ((Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"info") Element
e Maybe Element -> (Element -> Maybe Element) -> Maybe Element
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
                 (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"titleabbrev")) of
             Just Element
t  -> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
Just (Text
"titleabbrev", Element -> Text
strContentRecursive Element
t)
             Maybe Element
Nothing -> Maybe (Text, Text)
forall a. Maybe a
Nothing
         lineItems :: StateT DBState m [Inlines]
lineItems = (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines ([Element] -> StateT DBState m [Inlines])
-> [Element] -> StateT DBState m [Inlines]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"line") Element
e
         
         
         
         
         
         
         getTitle :: StateT DBState m (Maybe Inlines)
getTitle = case (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title") Element
e of
                        Just Element
t  -> Inlines -> Maybe Inlines
forall a. a -> Maybe a
Just (Inlines -> Maybe Inlines)
-> StateT DBState m Inlines -> StateT DBState m (Maybe Inlines)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
t
                        Maybe Element
Nothing -> Maybe Inlines -> StateT DBState m (Maybe Inlines)
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Inlines
forall a. Maybe a
Nothing
         withOptionalTitle :: StateT DBState m Blocks -> StateT DBState m Blocks
withOptionalTitle StateT DBState m Blocks
p = do
           Maybe Inlines
mbt <- StateT DBState m (Maybe Inlines)
getTitle
           Blocks
b <- StateT DBState m Blocks
p
           case Maybe Inlines
mbt of
             Maybe Inlines
Nothing -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
b
             Just Inlines
t -> Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text -> Element -> Text
attrValue Text
"id" Element
e,[],[])
                         (Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"title"], []) (Inlines -> Blocks
plain Inlines
t) Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
b)
         
         
         
         parseAdmonition :: Text -> StateT DBState m Blocks
parseAdmonition Text
label = do
           Maybe Inlines
mbt <- StateT DBState m (Maybe Inlines)
getTitle
           
           Blocks
b <- Element -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Element -> DB m Blocks
getBlocks Element
e
           let t :: Blocks
t = Attr -> Blocks -> Blocks
divWith (Text
"", [Text
"title"], []) (Inlines -> Blocks
plain (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Maybe Inlines -> Inlines
forall a. a -> Maybe a -> a
fromMaybe Inlines
forall a. Monoid a => a
mempty Maybe Inlines
mbt)
           
           Blocks -> StateT DBState m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> StateT DBState m Blocks)
-> Blocks -> StateT DBState m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Blocks -> Blocks
divWith (Text -> Element -> Text
attrValue Text
"id" Element
e,[Text
label],[]) (Blocks
t Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
b)
toAlignment :: Element -> Alignment
toAlignment :: Element -> Alignment
toAlignment Element
c = case QName -> Element -> Maybe Text
findAttr (Text -> QName
unqual Text
"align") Element
c of
                  Just Text
"left"   -> Alignment
AlignLeft
                  Just Text
"right"  -> Alignment
AlignRight
                  Just Text
"center" -> Alignment
AlignCenter
                  Maybe Text
_             -> Alignment
AlignDefault
parseMixed :: PandocMonad m => (Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed :: forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
container [Content]
conts = do
  let ([Content]
ils,[Content]
rest) = (Content -> Bool) -> [Content] -> ([Content], [Content])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break Content -> Bool
isBlockElement [Content]
conts
  Inlines
ils' <- Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline [Content]
ils
  let p :: Blocks
p = if Inlines
ils' Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
forall a. Monoid a => a
mempty then Blocks
forall a. Monoid a => a
mempty else Inlines -> Blocks
container Inlines
ils'
  case [Content]
rest of
    [] -> Blocks -> DB m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
p
    (Content
r:[Content]
rs) -> do
      Blocks
b <- Content -> DB m Blocks
forall (m :: * -> *). PandocMonad m => Content -> DB m Blocks
parseBlock Content
r
      Blocks
x <- (Inlines -> Blocks) -> [Content] -> DB m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
container [Content]
rs
      Blocks -> DB m Blocks
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> DB m Blocks) -> Blocks -> DB m Blocks
forall a b. (a -> b) -> a -> b
$ Blocks
p Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
b Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> Blocks
x
parseRow :: PandocMonad m => [Text] -> Element -> DB m [Cell]
parseRow :: forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m [Cell]
parseRow [Text]
cn = do
  let isEntry :: Element -> Bool
isEntry Element
x  = Text -> Element -> Bool
named Text
"entry" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"td" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"th" Element
x
  (Element -> StateT DBState m Cell) -> [Element] -> DB 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 ([Text] -> Element -> StateT DBState m Cell
forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m Cell
parseEntry [Text]
cn) ([Element] -> DB m [Cell])
-> (Element -> [Element]) -> Element -> DB m [Cell]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
isEntry
parseEntry :: PandocMonad m => [Text] -> Element -> DB m Cell
parseEntry :: forall (m :: * -> *).
PandocMonad m =>
[Text] -> Element -> DB m Cell
parseEntry [Text]
cn Element
el = do
  let colDistance :: Text -> Text -> ColSpan
colDistance Text
sa Text
ea = do
        let iStrt :: Maybe Int
iStrt = Text -> [Text] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
sa [Text]
cn
        let iEnd :: Maybe Int
iEnd = Text -> [Text] -> Maybe Int
forall a. Eq a => a -> [a] -> Maybe Int
elemIndex Text
ea [Text]
cn
        case (Maybe Int
iStrt, Maybe Int
iEnd) of
          (Just Int
start, Just Int
end) -> Int -> ColSpan
ColSpan (Int -> ColSpan) -> Int -> ColSpan
forall a b. (a -> b) -> a -> b
$ Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
          (Maybe Int, Maybe Int)
_ -> ColSpan
1
  let toColSpan :: Element -> ColSpan
toColSpan Element
en = do
        let mStrt :: Maybe Text
mStrt = QName -> Element -> Maybe Text
findAttr (Text -> QName
unqual Text
"namest") Element
en
        let mEnd :: Maybe Text
mEnd = QName -> Element -> Maybe Text
findAttr (Text -> QName
unqual Text
"nameend") Element
en
        case (Maybe Text
mStrt, Maybe Text
mEnd) of
          (Just Text
start, Just Text
end) -> Text -> Text -> ColSpan
colDistance Text
start Text
end
          (Maybe Text, Maybe Text)
_ -> ColSpan
1
  let colSpan :: ColSpan
colSpan = Element -> ColSpan
toColSpan Element
el
  let align :: Alignment
align = Element -> Alignment
toAlignment Element
el
  ((Blocks -> Cell) -> StateT DBState m Blocks -> DB m Cell
forall a b. (a -> b) -> StateT DBState m a -> StateT DBState m b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Alignment -> RowSpan -> ColSpan -> Blocks -> Cell
cell Alignment
align RowSpan
1 ColSpan
colSpan) (StateT DBState m Blocks -> DB m Cell)
-> (Element -> StateT DBState m Blocks) -> Element -> DB m Cell
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> Blocks) -> [Content] -> StateT DBState m Blocks
forall (m :: * -> *).
PandocMonad m =>
(Inlines -> Blocks) -> [Content] -> DB m Blocks
parseMixed Inlines -> Blocks
plain ([Content] -> StateT DBState m Blocks)
-> (Element -> [Content]) -> Element -> StateT DBState m Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Content]
elContent) Element
el
getInlines :: PandocMonad m => Element -> DB m Inlines
getInlines :: forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e' = Inlines -> Inlines
trimInlines (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                 (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Element -> [Content]
elContent Element
e')
strContentRecursive :: Element -> Text
strContentRecursive :: Element -> Text
strContentRecursive = Element -> Text
strContent (Element -> Text) -> (Element -> Element) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (\Element
e' -> Element
e'{ elContent = map elementToStr $ elContent e' })
elementToStr :: Content -> Content
elementToStr :: Content -> Content
elementToStr (Elem Element
e') = CData -> Content
Text (CData -> Content) -> CData -> Content
forall a b. (a -> b) -> a -> b
$ CDataKind -> Text -> Maybe Line -> CData
CData CDataKind
CDataText (Element -> Text
strContentRecursive Element
e') Maybe Line
forall a. Maybe a
Nothing
elementToStr Content
x = Content
x
childElTextAsAttr :: Text -> Element -> Maybe (Text, Text)
childElTextAsAttr :: Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
n Element
e = case QName -> Element -> Maybe Element
findChild QName
q Element
e of
        Maybe Element
Nothing -> Maybe (Text, Text)
forall a. Maybe a
Nothing
        Just Element
childEl -> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
Just (Text
n, Element -> Text
strContentRecursive Element
childEl)
        where q :: QName
q = Text -> Maybe Text -> Maybe Text -> QName
QName Text
n (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"http://docbook.org/ns/docbook") Maybe Text
forall a. Maybe a
Nothing
attrValueAsOptionalAttr :: Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr :: Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr Text
n Element
e = case Text -> Element -> Text
attrValue Text
n Element
e of
        Text
"" -> Maybe (Text, Text)
forall a. Maybe a
Nothing
        Text
_ -> (Text, Text) -> Maybe (Text, Text)
forall a. a -> Maybe a
Just (Text
n, Text -> Element -> Text
attrValue Text
n Element
e)
parseInline :: PandocMonad m => Content -> DB m Inlines
parseInline :: forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Text (CData CDataKind
_ Text
s Maybe Line
_)) = Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text Text
s
parseInline (CRef Text
ref) =
  Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe (Text -> Text
T.toUpper Text
ref) (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
lookupEntity Text
ref
parseInline (Elem Element
e) =
  case QName -> Text
qName (Element -> QName
elName Element
e) of
        Text
"anchor" -> do
           Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text -> Element -> Text
attrValue Text
"id" Element
e, [], []) Inlines
forall a. Monoid a => a
mempty
        Text
"phrase" -> do
          let ident :: Text
ident = Text -> Element -> Text
attrValue Text
"id" Element
e
          let classes :: [Text]
classes = Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Element -> Text
attrValue Text
"role" Element
e
          if Text
ident Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"" Bool -> Bool -> Bool
|| [Text]
classes [Text] -> [Text] -> Bool
forall a. Eq a => a -> a -> Bool
/= []
            then (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines (Attr -> Inlines -> Inlines
spanWith (Text
ident,[Text]
classes,[]))
            else (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
forall a. a -> a
id
        Text
"indexterm" -> do
          let ident :: Text
ident = Text -> Element -> Text
attrValue Text
"id" Element
e
          let classes :: [Text]
classes = Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Element -> Text
attrValue Text
"role" Element
e
          let attrs :: [Maybe (Text, Text)]
attrs =
                
                
                
                
                [ Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
"primary" Element
e
                , Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
"secondary" Element
e
                , Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
"tertiary" Element
e
                , Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
"see" Element
e
                , Text -> Element -> Maybe (Text, Text)
childElTextAsAttr Text
"seealso" Element
e
                , Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr Text
"significance" Element
e
                , Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr Text
"startref" Element
e
                , Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr Text
"scope" Element
e
                , Text -> Element -> Maybe (Text, Text)
attrValueAsOptionalAttr Text
"class" Element
e
                
                
                
                ]
          Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Inlines -> Inlines
spanWith (Text
ident, (Text
"indexterm" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
classes), ([Maybe (Text, Text)] -> [(Text, Text)]
forall a. [Maybe a] -> [a]
catMaybes [Maybe (Text, Text)]
attrs)) Inlines
forall a. Monoid a => a
mempty
        Text
"equation" -> Element -> (Text -> Inlines) -> StateT DBState m Inlines
forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
displayMath
        Text
"informalequation" -> Element -> (Text -> Inlines) -> StateT DBState m Inlines
forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
displayMath
        Text
"inlineequation" -> Element -> (Text -> Inlines) -> StateT DBState m Inlines
forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
math
        Text
"subscript" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
subscript
        Text
"superscript" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
superscript
        Text
"inlinemediaobject" -> Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getMediaobject Element
e
        Text
"quote" -> do
            QuoteType
qt <- (DBState -> QuoteType) -> StateT DBState m QuoteType
forall s (m :: * -> *) a. MonadState s m => (s -> a) -> m a
gets DBState -> QuoteType
dbQuoteType
            let qt' :: QuoteType
qt' = if QuoteType
qt QuoteType -> QuoteType -> Bool
forall a. Eq a => a -> a -> Bool
== QuoteType
SingleQuote then QuoteType
DoubleQuote else QuoteType
SingleQuote
            (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DBState -> DBState) -> StateT DBState m ())
-> (DBState -> DBState) -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ \DBState
st -> DBState
st{ dbQuoteType = qt' }
            Inlines
contents <- (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
forall a. a -> a
id
            (DBState -> DBState) -> StateT DBState m ()
forall s (m :: * -> *). MonadState s m => (s -> s) -> m ()
modify ((DBState -> DBState) -> StateT DBState m ())
-> (DBState -> DBState) -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ \DBState
st -> DBState
st{ dbQuoteType = qt }
            Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ if QuoteType
qt QuoteType -> QuoteType -> Bool
forall a. Eq a => a -> a -> Bool
== QuoteType
SingleQuote
                        then Inlines -> Inlines
singleQuoted Inlines
contents
                        else Inlines -> Inlines
doubleQuoted Inlines
contents
        Text
"simplelist" -> StateT DBState m Inlines
simpleList
        Text
"segmentedlist" -> StateT DBState m Inlines
segmentedList
        Text
"classname" -> StateT DBState m Inlines
codeWithLang
        Text
"code" -> StateT DBState m Inlines
codeWithLang
        Text
"citerefentry" -> do
             let title :: Text
title = Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty Element -> Text
strContent (Maybe Element -> Text) -> Maybe Element -> Text
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"refentrytitle") Element
e
             let manvolnum :: Text
manvolnum = Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty (\Element
el -> Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Element -> Text
strContent Element
el Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")") (Maybe Element -> Text) -> Maybe Element -> Text
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"manvolnum") Element
e
             Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Inlines
codeWith (Text
"",[Text
"citerefentry"],[]) (Text
title Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
manvolnum)
        Text
"filename" -> StateT DBState m Inlines
codeWithLang
        Text
"envar" -> StateT DBState m Inlines
codeWithLang
        Text
"literal" -> StateT DBState m Inlines
codeWithLang
        Text
"computeroutput" -> StateT DBState m Inlines
codeWithLang
        Text
"prompt" -> StateT DBState m Inlines
codeWithLang
        Text
"parameter" -> StateT DBState m Inlines
codeWithLang
        Text
"option" -> StateT DBState m Inlines
codeWithLang
        Text
"optional" -> do Inlines
x <- Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e
                         Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
"[" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
"]"
        Text
"replaceable" -> do Inlines
x <- Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines Element
e
                            Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str Text
"<" Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
">"
        Text
"markup" -> StateT DBState m Inlines
codeWithLang
        Text
"wordasword" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
emph
        Text
"command" -> StateT DBState m Inlines
codeWithLang
        Text
"varname" -> StateT DBState m Inlines
codeWithLang
        Text
"function" -> StateT DBState m Inlines
codeWithLang
        Text
"type"    -> StateT DBState m Inlines
codeWithLang
        Text
"symbol"  -> StateT DBState m Inlines
codeWithLang
        Text
"constant" -> StateT DBState m Inlines
codeWithLang
        Text
"userinput" -> StateT DBState m Inlines
codeWithLang
        Text
"systemitem" -> StateT DBState m Inlines
codeWithLang
        Text
"varargs" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
code Text
"(...)"
        Text
"keycap" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Inlines
str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Element -> Text
strContent Element
e)
        Text
"keycombo" -> [Inlines] -> Inlines
keycombo ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                         (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Element -> [Content]
elContent Element
e)
        Text
"menuchoice" -> [Inlines] -> Inlines
menuchoice ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                         (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (
                                        (Content -> Bool) -> [Content] -> [Content]
forall a. (a -> Bool) -> [a] -> [a]
filter Content -> Bool
isGuiMenu ([Content] -> [Content]) -> [Content] -> [Content]
forall a b. (a -> b) -> a -> b
$ Element -> [Content]
elContent Element
e)
        Text
"xref" -> do
            [Content]
content <- DBState -> [Content]
dbContent (DBState -> [Content])
-> StateT DBState m DBState -> StateT DBState m [Content]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StateT DBState m DBState
forall s (m :: * -> *). MonadState s m => m s
get
            let linkend :: Text
linkend = Text -> Element -> Text
attrValue Text
"linkend" Element
e
            let title :: Text
title = case Text -> Element -> Text
attrValue Text
"endterm" Element
e of
                            Text
""      -> Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"???" Element -> Text
xrefTitleByElem
                                         (Text -> [Content] -> Maybe Element
findElementById Text
linkend [Content]
content)
                            Text
endterm -> Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"???" Element -> Text
strContent
                                         (Text -> [Content] -> Maybe Element
findElementById Text
endterm [Content]
content)
            Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
linkend) Text
"" (Text -> Inlines
text Text
title)
        Text
"email" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link (Text
"mailto:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Element -> Text
strContent Element
e) Text
""
                          (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Element -> Text
strContent Element
e
        Text
"uri" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
link (Element -> Text
strContent Element
e) Text
"" (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Element -> Text
strContent Element
e
        Text
"ulink" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines (Text -> Text -> Inlines -> Inlines
link (Text -> Element -> Text
attrValue Text
"url" Element
e) Text
"")
        Text
"link" -> do
             Inlines
ils <- (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
forall a. a -> a
id
             let href :: Text
href = case (QName -> Bool) -> Element -> Maybe Text
findAttrBy
                               (\case
                                 QName Text
"href" Maybe Text
_ Maybe Text
_ -> Bool
True
                                 QName
_ -> Bool
False) Element
e of
                               Just Text
h -> Text
h
                               Maybe Text
_      -> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Element -> Text
attrValue Text
"linkend" Element
e
             let ils' :: Inlines
ils' = if Inlines
ils Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
forall a. Monoid a => a
mempty then Text -> Inlines
str Text
href else Inlines
ils
             let attr :: (Text, [Text], [a])
attr = (Text -> Element -> Text
attrValue Text
"id" Element
e, Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text -> Element -> Text
attrValue Text
"role" Element
e, [])
             Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
linkWith Attr
forall {a}. (Text, [Text], [a])
attr Text
href Text
"" Inlines
ils'
        Text
"foreignphrase" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
emph
        Text
"emphasis" -> case Text -> Element -> Text
attrValue Text
"role" Element
e of
                             Text
"bf"            -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
strong
                             Text
"bold"          -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
strong
                             Text
"strong"        -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
strong
                             Text
"strikethrough" -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
strikeout
                             Text
"underline"     -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
underline
                             Text
_               -> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
emph
        Text
"footnote" -> Blocks -> Inlines
note (Blocks -> Inlines) -> ([Blocks] -> Blocks) -> [Blocks] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Inlines)
-> StateT DBState m [Blocks] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                         (Content -> StateT DBState m Blocks)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Blocks
forall (m :: * -> *). PandocMonad m => Content -> DB m Blocks
parseBlock (Element -> [Content]
elContent Element
e)
        Text
"title" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
        Text
"affiliation" -> StateT DBState m Inlines
skip
        
        
        Text
"pi-asciidoc-br" -> Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
linebreak
        Text
_          -> StateT DBState m Inlines
skip StateT DBState m Inlines
-> StateT DBState m Inlines -> StateT DBState m Inlines
forall a b.
StateT DBState m a -> StateT DBState m b -> StateT DBState m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (Inlines -> Inlines) -> StateT DBState m Inlines
forall {m :: * -> *}.
PandocMonad m =>
(Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
forall a. a -> a
id
   where skip :: StateT DBState m Inlines
skip = do
           let qn :: Text
qn = QName -> Text
qName (QName -> Text) -> QName -> Text
forall a b. (a -> b) -> a -> b
$ Element -> QName
elName Element
e
           let name :: Text
name = if Text
"pi-" Text -> Text -> Bool
`T.isPrefixOf` Text
qn
                         then Text
"<?" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
qn Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"?>"
                         else Text
qn
           m () -> StateT DBState m ()
forall (m :: * -> *) a. Monad m => m a -> StateT DBState m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (m () -> StateT DBState m ()) -> m () -> StateT DBState m ()
forall a b. (a -> b) -> a -> b
$ LogMessage -> m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> m ()) -> LogMessage -> m ()
forall a b. (a -> b) -> a -> b
$ Text -> LogMessage
IgnoredElement Text
name
           Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
         innerInlines :: (Inlines -> Inlines) -> StateT DBState m Inlines
innerInlines Inlines -> Inlines
f = (Inlines -> Inlines) -> Inlines -> Inlines
extractSpaces Inlines -> Inlines
f (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                          (Content -> StateT DBState m Inlines)
-> [Content] -> StateT DBState 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 Content -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Content -> DB m Inlines
parseInline (Element -> [Content]
elContent Element
e)
         codeWithLang :: StateT DBState m Inlines
codeWithLang = do
           let classes' :: [Text]
classes' = case Text -> Element -> Text
attrValue Text
"language" Element
e of
                               Text
"" -> []
                               Text
l  -> [Text
l]
           Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Inlines
codeWith (Text -> Element -> Text
attrValue Text
"id" Element
e,[Text]
classes',[]) (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$
             [Text] -> Text
T.unwords ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.words (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Element -> Text
strContentRecursive Element
e
             
         simpleList :: StateT DBState m Inlines
simpleList = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"," Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
space) ([Inlines] -> Inlines)
-> StateT DBState m [Inlines] -> StateT DBState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines
                         ((Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"member") Element
e)
         segmentedList :: StateT DBState m Inlines
segmentedList = do
           Inlines
tit <- StateT DBState m Inlines
-> (Element -> StateT DBState m Inlines)
-> Maybe Element
-> StateT DBState m Inlines
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty) Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines (Maybe Element -> StateT DBState m Inlines)
-> Maybe Element -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> Maybe Element
filterChild (Text -> Element -> Bool
named Text
"title") Element
e
           [Inlines]
segtits <- (Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines ([Element] -> StateT DBState m [Inlines])
-> [Element] -> StateT DBState m [Inlines]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"segtitle") Element
e
           [[Inlines]]
segitems <- (Element -> StateT DBState m [Inlines])
-> [Element] -> StateT DBState 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 ((Element -> StateT DBState m Inlines)
-> [Element] -> StateT DBState 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 Element -> StateT DBState m Inlines
forall (m :: * -> *). PandocMonad m => Element -> DB m Inlines
getInlines ([Element] -> StateT DBState m [Inlines])
-> (Element -> [Element]) -> Element -> StateT DBState m [Inlines]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"seg"))
                          ([Element] -> StateT DBState m [[Inlines]])
-> [Element] -> StateT DBState m [[Inlines]]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren (Text -> Element -> Bool
named Text
"seglistitem") Element
e
           let toSeg :: [Inlines] -> Inlines
toSeg = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Inlines -> Inlines -> Inlines)
-> [Inlines] -> [Inlines] -> [Inlines]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Inlines
x Inlines
y -> Inlines -> Inlines
strong (Inlines
x Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Text -> Inlines
str Text
":") Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
space Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<>
                                  Inlines
y Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
linebreak) [Inlines]
segtits
           let segs :: Inlines
segs = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ ([Inlines] -> Inlines) -> [[Inlines]] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map [Inlines] -> Inlines
toSeg [[Inlines]]
segitems
           let tit' :: Inlines
tit' = if Inlines
tit Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
forall a. Monoid a => a
mempty
                         then Inlines
forall a. Monoid a => a
mempty
                         else Inlines -> Inlines
strong Inlines
tit Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
linebreak
           Inlines -> StateT DBState m Inlines
forall a. a -> StateT DBState m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> StateT DBState m Inlines)
-> Inlines -> StateT DBState m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines
linebreak Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
tit' Inlines -> Inlines -> Inlines
forall a. Semigroup a => a -> a -> a
<> Inlines
segs
         keycombo :: [Inlines] -> Inlines
keycombo = Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"keycombo"],[]) (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
str Text
"+")
         menuchoice :: [Inlines] -> Inlines
menuchoice = Attr -> Inlines -> Inlines
spanWith (Text
"",[Text
"menuchoice"],[]) (Inlines -> Inlines)
-> ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ([Inlines] -> [Inlines]) -> [Inlines] -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inlines] -> [Inlines]
forall a. a -> [a] -> [a]
intersperse (Text -> Inlines
text Text
" > ")
         isGuiMenu :: Content -> Bool
isGuiMenu (Elem Element
x) = Text -> Element -> Bool
named Text
"guimenu" Element
x Bool -> Bool -> Bool
|| Text -> Element -> Bool
named Text
"guisubmenu" Element
x Bool -> Bool -> Bool
||
                              Text -> Element -> Bool
named Text
"guimenuitem" Element
x
         isGuiMenu Content
_        = Bool
False
         findElementById :: Text -> [Content] -> Maybe Element
findElementById Text
idString [Content]
content
            = [Maybe Element] -> Maybe Element
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum [(Element -> Bool) -> Element -> Maybe Element
filterElement (\Element
x -> Text -> Element -> Text
attrValue Text
"id" Element
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
idString) Element
el | Elem Element
el <- [Content]
content]
         
         
         
         xrefTitleByElem :: Element -> Text
xrefTitleByElem Element
el
             | Bool -> Bool
not (Text -> Bool
T.null Text
xrefLabel) = Text
xrefLabel
             | Bool
otherwise              = case QName -> Text
qName (Element -> QName
elName Element
el) of
                  Text
"book"         -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"part"         -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"chapter"      -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"section"      -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"sect1"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"sect2"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"sect3"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"sect4"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"sect5"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"cmdsynopsis"  -> Text -> Element -> Text
descendantContent Text
"command" Element
el
                  Text
"funcsynopsis" -> Text -> Element -> Text
descendantContent Text
"function" Element
el
                  Text
"figure"       -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
"table"        -> Text -> Element -> Text
descendantContent Text
"title" Element
el
                  Text
_              -> QName -> Text
qName (Element -> QName
elName Element
el) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_title"
          where
            xrefLabel :: Text
xrefLabel = Text -> Element -> Text
attrValue Text
"xreflabel" Element
el
            descendantContent :: Text -> Element -> Text
descendantContent Text
name = Text -> (Element -> Text) -> Maybe Element -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"???" Element -> Text
strContent
                                   (Maybe Element -> Text)
-> (Element -> Maybe Element) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (QName -> Bool) -> Element -> Maybe Element
filterElementName (\QName
n -> QName -> Text
qName QName
n Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
name)
equation
  :: Monad m
  => Element
  
  -> (Text -> Inlines)
  
  -> m Inlines
equation :: forall (m :: * -> *).
Monad m =>
Element -> (Text -> Inlines) -> m Inlines
equation Element
e Text -> Inlines
constructor =
  Inlines -> m Inlines
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> m Inlines) -> Inlines -> m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines) -> [Inlines] -> Inlines
forall a b. (a -> b) -> a -> b
$ (Text -> Inlines) -> [Text] -> [Inlines]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Inlines
constructor ([Text] -> [Inlines]) -> [Text] -> [Inlines]
forall a b. (a -> b) -> a -> b
$ [Text]
mathMLEquations [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
latexEquations
  where
    mathMLEquations :: [Text]
    mathMLEquations :: [Text]
mathMLEquations = ([Exp] -> Text) -> [[Exp]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map [Exp] -> Text
writeTeX ([[Exp]] -> [Text]) -> [[Exp]] -> [Text]
forall a b. (a -> b) -> a -> b
$ [Either Text [Exp]] -> [[Exp]]
forall a b. [Either a b] -> [b]
rights ([Either Text [Exp]] -> [[Exp]]) -> [Either Text [Exp]] -> [[Exp]]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool)
-> (Element -> Either Text [Exp]) -> [Either Text [Exp]]
forall b. (Element -> Bool) -> (Element -> b) -> [b]
readMath
      (\Element
x -> QName -> Text
qName (Element -> QName
elName Element
x) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"math" Bool -> Bool -> Bool
&&
             QName -> Maybe Text
qURI (Element -> QName
elName Element
x) Maybe Text -> Maybe Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"http://www.w3.org/1998/Math/MathML")
      (Text -> Either Text [Exp]
readMathML (Text -> Either Text [Exp])
-> (Element -> Text) -> Element -> Either Text [Exp]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> Text
showElement)
    latexEquations :: [Text]
    latexEquations :: [Text]
latexEquations = (Element -> Bool) -> (Element -> Text) -> [Text]
forall b. (Element -> Bool) -> (Element -> b) -> [b]
readMath (\Element
x -> QName -> Text
qName (Element -> QName
elName Element
x) Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"mathphrase")
                              ([Text] -> Text
T.concat ([Text] -> Text) -> (Element -> [Text]) -> Element -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Content -> Text) -> [Content] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Content -> Text
showVerbatimCData ([Content] -> [Text])
-> (Element -> [Content]) -> Element -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Element -> [Content]
elContent)
    readMath :: (Element -> Bool) -> (Element -> b) -> [b]
    readMath :: forall b. (Element -> Bool) -> (Element -> b) -> [b]
readMath Element -> Bool
childPredicate Element -> b
fromElement =
      (Element -> b) -> [Element] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map (Element -> b
fromElement (Element -> b) -> (Element -> Element) -> Element -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere ((QName -> QName) -> a -> a
forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT QName -> QName
removePrefix))
      ([Element] -> [b]) -> [Element] -> [b]
forall a b. (a -> b) -> a -> b
$ (Element -> Bool) -> Element -> [Element]
filterChildren Element -> Bool
childPredicate Element
e
showVerbatimCData :: Content -> Text
showVerbatimCData :: Content -> Text
showVerbatimCData (Text (CData CDataKind
_ Text
d Maybe Line
_)) = Text
d
showVerbatimCData Content
c = Content -> Text
showContent Content
c
removePrefix :: QName -> QName
removePrefix :: QName -> QName
removePrefix QName
elname = QName
elname { qPrefix = Nothing }
paraToPlain :: Block -> Block
paraToPlain :: Block -> Block
paraToPlain (Para [Inline]
ils) = [Inline] -> Block
Plain [Inline]
ils
paraToPlain Block
x = Block
x
docbookEntityMap :: M.Map Text Text
docbookEntityMap :: Map Text Text
docbookEntityMap = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
  ((Text -> (Text, Text)) -> [Text] -> [(Text, Text)]
forall a b. (a -> b) -> [a] -> [b]
map Text -> (Text, Text)
lineToPair (Text -> [Text]
T.lines (ByteString -> Text
decodeUtf8 ByteString
docbookEntities)))
 where
   lineToPair :: Text -> (Text, Text)
lineToPair Text
l =
     case Text -> [Text]
T.words Text
l of
       (Text
x:[Text]
ys) -> (Text
x, String -> Text
T.pack ((Text -> Maybe Char) -> [Text] -> String
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Text -> Maybe Char
readHex [Text]
ys))
       [] -> (Text
"",Text
"")
   readHex :: Text -> Maybe Char
readHex Text
t = case Reader Int
forall a. Integral a => Reader a
TR.hexadecimal Text
t of
                 Left String
_ -> Maybe Char
forall a. Maybe a
Nothing
                 Right (Int
n,Text
_) -> Char -> Maybe Char
forall a. a -> Maybe a
Just (Int -> Char
chr Int
n)
docbookEntities :: ByteString
docbookEntities :: ByteString
docbookEntities = $(embedFile "data/docbook-entities.txt")