{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}

{- |
   Module      : Text.Pandoc.Readers.TikiWiki
   Copyright   : Copyright (C) 2017 Robin Lee Powell
   License     : GNU GPL, version 2 or above

   Maintainer  : Robin Lee Powell <robinleepowell@gmail.com>
   Stability   : alpha
   Portability : portable

Conversion of TikiWiki text to 'Pandoc' document.
-}

module Text.Pandoc.Readers.TikiWiki ( readTikiWiki
                                    ) where

import Control.Monad
import Control.Monad.Except (throwError)
import qualified Data.Foldable as F
import Data.List (dropWhileEnd)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition
import Text.Pandoc.Logging (Verbosity (..))
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed, nested)
import Text.Pandoc.Shared (safeRead)
import Text.Pandoc.XML (fromEntities)
import Text.Printf (printf)

-- | Read TikiWiki from an input string and return a Pandoc document.
readTikiWiki :: (PandocMonad m, ToSources a)
          => ReaderOptions
          -> a
          -> m Pandoc
readTikiWiki :: ReaderOptions -> a -> m Pandoc
readTikiWiki ReaderOptions
opts a
s = do
  let sources :: Sources
sources = Int -> Sources -> Sources
ensureFinalNewlines Int
2 (a -> Sources
forall a. ToSources a => a -> Sources
toSources a
s)
  Either PandocError Pandoc
res <- ParserT Sources ParserState m Pandoc
-> ParserState -> Sources -> m (Either PandocError Pandoc)
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParserT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParserT Sources ParserState m Pandoc
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Pandoc
parseTikiWiki ParserState
forall a. Default a => a
def{ stateOptions :: ReaderOptions
stateOptions = ReaderOptions
opts } Sources
sources
  case Either PandocError Pandoc
res of
       Left PandocError
e  -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
       Right Pandoc
d -> Pandoc -> m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
d

type TikiWikiParser = ParserT Sources ParserState

--
-- utility functions
--

tryMsg :: Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg :: Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
msg TikiWikiParser m a
p = TikiWikiParser m a -> TikiWikiParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TikiWikiParser m a
p TikiWikiParser m a -> String -> TikiWikiParser m a
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> Text -> String
T.unpack Text
msg

skip :: TikiWikiParser m a -> TikiWikiParser m ()
skip :: TikiWikiParser m a -> TikiWikiParser m ()
skip TikiWikiParser m a
parser = TikiWikiParser m a -> TikiWikiParser m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
Control.Monad.void TikiWikiParser m a
parser

nested :: PandocMonad m => TikiWikiParser m a -> TikiWikiParser m a
nested :: TikiWikiParser m a -> TikiWikiParser m a
nested TikiWikiParser m a
p = do
  Int
nestlevel <- ParserState -> Int
stateMaxNestingLevel (ParserState -> Int)
-> ParsecT Sources ParserState m ParserState
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Int
nestlevel Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
  (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMaxNestingLevel :: Int
stateMaxNestingLevel = ParserState -> Int
stateMaxNestingLevel ParserState
st Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 }
  a
res <- TikiWikiParser m a
p
  (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((ParserState -> ParserState) -> ParsecT Sources ParserState m ())
-> (ParserState -> ParserState) -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMaxNestingLevel :: Int
stateMaxNestingLevel = Int
nestlevel }
  a -> TikiWikiParser m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res

--
-- main parser
--

parseTikiWiki :: PandocMonad m => TikiWikiParser m Pandoc
parseTikiWiki :: TikiWikiParser m Pandoc
parseTikiWiki = do
  Blocks
bs <- [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Blocks
-> ParsecT Sources ParserState m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources ParserState m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
block
  ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  Pandoc -> TikiWikiParser m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> TikiWikiParser m Pandoc)
-> Pandoc -> TikiWikiParser m Pandoc
forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc Blocks
bs

block :: PandocMonad m => TikiWikiParser m B.Blocks
block :: TikiWikiParser m Blocks
block = do
  Verbosity
verbosity <- (CommonState -> Verbosity)
-> ParsecT Sources ParserState m Verbosity
forall (m :: * -> *) a. PandocMonad m => (CommonState -> a) -> m a
getsCommonState CommonState -> Verbosity
stVerbosity
  SourcePos
pos <- ParsecT Sources ParserState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  Blocks
res <- Blocks
forall a. Monoid a => a
mempty Blocks
-> ParsecT Sources ParserState m () -> TikiWikiParser m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
         TikiWikiParser m Blocks
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
blockElements
         TikiWikiParser m Blocks
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
para
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
  Bool
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity Verbosity -> Verbosity -> Bool
forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) (ParsecT Sources ParserState m ()
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$
    Text -> ParsecT Sources ParserState m ()
forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Int -> String -> String
forall r. PrintfType r => String -> r
printf String
"line %d: %s" (SourcePos -> Int
sourceLine SourcePos
pos) (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
60 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ [Block] -> String
forall a. Show a => a -> String
show ([Block] -> String) -> [Block] -> String
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
res))
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res

blockElements :: PandocMonad m => TikiWikiParser m B.Blocks
blockElements :: TikiWikiParser m Blocks
blockElements = [TikiWikiParser m Blocks] -> TikiWikiParser m Blocks
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
table
                       , TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
hr
                       , TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
header
                       , TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
mixedList
                       , TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
definitionList
                       , TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
codeMacro
                       ]

-- top
-- ----
-- bottom
--
-- ----
--
hr :: PandocMonad m => TikiWikiParser m B.Blocks
hr :: TikiWikiParser m Blocks
hr = TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"----"
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-')
  ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule

-- ! header
--
-- !! header level two
--
-- !!! header level 3
--
header :: PandocMonad m => TikiWikiParser m B.Blocks
header :: TikiWikiParser m Blocks
header = Text -> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a.
Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
"header" (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  Int
level <- (String -> Int)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'))
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Int
level Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
6
  ParsecT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
  Inlines
content <- Inlines -> Inlines
B.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)
-> ParsecT Sources ParserState m [Inlines]
-> ParsecT Sources ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  Attr
attr <- Attr -> Inlines -> ParserT Sources ParserState m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
 HasIdentifierList st) =>
Attr -> Inlines -> ParserT s st m Attr
registerHeader Attr
nullAttr Inlines
content
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$Attr -> Int -> Inlines -> Blocks
B.headerWith Attr
attr Int
level Inlines
content

tableRow :: PandocMonad m => TikiWikiParser m [B.Blocks]
tableRow :: TikiWikiParser m [Blocks]
tableRow = TikiWikiParser m [Blocks] -> TikiWikiParser m [Blocks]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m [Blocks] -> TikiWikiParser m [Blocks])
-> TikiWikiParser m [Blocks] -> TikiWikiParser m [Blocks]
forall a b. (a -> b) -> a -> b
$ do
--  row <- sepBy1 (many1Till inline $ oneOf "\n|") (try $ string "|" <* notFollowedBy (oneOf "|\n"))
--  return $ map (B.plain . mconcat) row
  [Inlines]
row <- ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepBy1 (ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"\n|") ParsecT Sources ParserState m String
-> (String -> ParsecT Sources ParserState m Inlines)
-> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> ParsecT Sources ParserState m Inlines
parseColumn (Text -> ParsecT Sources ParserState m Inlines)
-> (String -> Text)
-> String
-> ParsecT Sources ParserState m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) (ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"|" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
"|\n"))
  [Blocks] -> TikiWikiParser m [Blocks]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Blocks] -> TikiWikiParser m [Blocks])
-> [Blocks] -> TikiWikiParser m [Blocks]
forall a b. (a -> b) -> a -> b
$ (Inlines -> Blocks) -> [Inlines] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map Inlines -> Blocks
B.plain [Inlines]
row
  where
    parseColumn :: Text -> ParsecT Sources ParserState m Inlines
parseColumn Text
x = do
      [Inlines]
parsed <- ParserT Sources ParserState m [Inlines]
-> Text -> ParserT Sources ParserState m [Inlines]
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (ParsecT Sources ParserState m Inlines
-> ParserT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
x
      Inlines -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState m Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
parsed



-- Tables:
--
-- ||foo||
--
-- ||row1-column1|row1-column2||row2-column1|row2-column2||
--
-- ||row1-column1|row1-column2
-- row2-column1|row2-column2||
--
-- ||row1-column1|row1-column2
-- row2-column1|row2-column2||row3-column1|row3-column2||
--
-- || Orange | Apple     | more
--  Bread  | Pie       | more
--  Butter | Ice cream | and more ||
--
table :: PandocMonad m => TikiWikiParser m B.Blocks
table :: TikiWikiParser m Blocks
table = TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||"
  [[Blocks]]
rows <- ParsecT Sources ParserState m [Blocks]
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m [[Blocks]]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepBy1 ParsecT Sources ParserState m [Blocks]
forall (m :: * -> *). PandocMonad m => TikiWikiParser m [Blocks]
tableRow (ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"\n" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||" ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"\n")))
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||"
  ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  -- return $ B.simpleTable (headers rows) $ trace ("rows: " ++ (show rows)) rows
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$[Blocks] -> [[Blocks]] -> Blocks
B.simpleTable ([[Blocks]] -> [Blocks]
forall (t :: * -> *) a. Foldable t => [t a] -> [Blocks]
headers [[Blocks]]
rows) [[Blocks]]
rows
  where
    -- The headers are as many empty strings as the number of columns
    -- in the first row
    headers :: [t a] -> [Blocks]
headers [t a]
rows = (Text -> Blocks) -> [Text] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map (Inlines -> Blocks
B.plain (Inlines -> Blocks) -> (Text -> Inlines) -> Text -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str) ([Text] -> [Blocks]) -> [Text] -> [Blocks]
forall a b. (a -> b) -> a -> b
$Int -> Text -> [Text]
forall a. Int -> a -> [a]
replicate (t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (t a -> Int) -> t a -> Int
forall a b. (a -> b) -> a -> b
$ [t a] -> t a
forall a. [a] -> a
head [t a]
rows) Text
""

para :: PandocMonad m => TikiWikiParser m B.Blocks
para :: TikiWikiParser m Blocks
para =  ([Inlines] -> Blocks)
-> ParsecT Sources ParserState m [Inlines]
-> TikiWikiParser m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Blocks
result (Inlines -> Blocks)
-> ([Inlines] -> Inlines) -> [Inlines] -> Blocks
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat) ( ParserT Sources ParserState m Inlines
-> ParserT Sources ParserState m ()
-> ParsecT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till ParserT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline ParserT Sources ParserState m ()
endOfParaElement)
 where
   endOfParaElement :: ParserT Sources ParserState m ()
endOfParaElement = ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParserT Sources ParserState m ()
 -> ParserT Sources ParserState m ())
-> ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserT Sources ParserState m ()
forall u. ParsecT Sources u m ()
endOfInput ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Sources ParserState m ()
forall u. ParsecT Sources u m ()
endOfPara ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Sources ParserState m ()
newBlockElement
   endOfInput :: ParsecT Sources u m ()
endOfInput       = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParsecT Sources u m ()
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
   endOfPara :: ParsecT Sources u m ()
endOfPara        = ParsecT Sources u m () -> ParsecT Sources u m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m () -> ParsecT Sources u m ())
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall a b. (a -> b) -> a -> b
$ ParserT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline ParserT Sources u m Char
-> ParsecT Sources u m () -> ParsecT Sources u m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParserT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParserT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
   newBlockElement :: ParserT Sources ParserState m ()
newBlockElement  = ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParserT Sources ParserState m ()
 -> ParserT Sources ParserState m ())
-> ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline ParserT Sources ParserState m Char
-> ParserT Sources ParserState m ()
-> ParserT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TikiWikiParser m Blocks -> ParserT Sources ParserState m ()
forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip TikiWikiParser m Blocks
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
blockElements
   result :: Inlines -> Blocks
result Inlines
content   = if (Inline -> Bool) -> Inlines -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (Inline -> Inline -> Bool
forall a. Eq a => a -> a -> Bool
==Inline
Space) Inlines
content
                      then Blocks
forall a. Monoid a => a
mempty
                      else Inlines -> Blocks
B.para (Inlines -> Blocks) -> Inlines -> Blocks
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.trimInlines Inlines
content

-- ;item 1: definition 1
-- ;item 2: definition 2-1
-- + definition 2-2
-- ;item ''3'': definition ''3''
--
definitionList :: PandocMonad m => TikiWikiParser m B.Blocks
definitionList :: TikiWikiParser m Blocks
definitionList = Text -> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a.
Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
"definitionList" (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  [(Inlines, [Blocks])]
elements <-ParsecT Sources ParserState m (Inlines, [Blocks])
-> ParsecT Sources ParserState m [(Inlines, [Blocks])]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m (Inlines, [Blocks])
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Inlines, [Blocks])
parseDefinitionListItem
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ [(Inlines, [Blocks])] -> Blocks
B.definitionList [(Inlines, [Blocks])]
elements
  where
    parseDefinitionListItem :: PandocMonad m => TikiWikiParser m (B.Inlines, [B.Blocks])
    parseDefinitionListItem :: TikiWikiParser m (Inlines, [Blocks])
parseDefinitionListItem = do
      ParserT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces ParserT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
';' ParsecT Sources ParserState m Char
-> ParserT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
      [Inlines]
term <- ParserT Sources ParserState m Inlines
-> ParsecT Sources ParserState m Char
-> ParserT Sources ParserState m [Inlines]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till ParserT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline (ParsecT Sources ParserState m Char
 -> ParserT Sources ParserState m [Inlines])
-> ParsecT Sources ParserState m Char
-> ParserT Sources ParserState m [Inlines]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':' ParsecT Sources ParserState m Char
-> ParserT Sources ParserState m ()
-> ParsecT Sources ParserState m Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParserT Sources ParserState m ()
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
      Inlines
line <- Int -> ParserT Sources ParserState m Inlines
forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine Int
1
      (Inlines, [Blocks]) -> TikiWikiParser m (Inlines, [Blocks])
forall (m :: * -> *) a. Monad m => a -> m a
return ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
term, [Inlines -> Blocks
B.plain Inlines
line])

data ListType = None | Numbered | Bullet deriving (Eq ListType
Eq ListType
-> (ListType -> ListType -> Ordering)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> ListType)
-> (ListType -> ListType -> ListType)
-> Ord ListType
ListType -> ListType -> Bool
ListType -> ListType -> Ordering
ListType -> ListType -> ListType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ListType -> ListType -> ListType
$cmin :: ListType -> ListType -> ListType
max :: ListType -> ListType -> ListType
$cmax :: ListType -> ListType -> ListType
>= :: ListType -> ListType -> Bool
$c>= :: ListType -> ListType -> Bool
> :: ListType -> ListType -> Bool
$c> :: ListType -> ListType -> Bool
<= :: ListType -> ListType -> Bool
$c<= :: ListType -> ListType -> Bool
< :: ListType -> ListType -> Bool
$c< :: ListType -> ListType -> Bool
compare :: ListType -> ListType -> Ordering
$ccompare :: ListType -> ListType -> Ordering
$cp1Ord :: Eq ListType
Ord, ListType -> ListType -> Bool
(ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool) -> Eq ListType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListType -> ListType -> Bool
$c/= :: ListType -> ListType -> Bool
== :: ListType -> ListType -> Bool
$c== :: ListType -> ListType -> Bool
Eq, Int -> ListType -> String -> String
[ListType] -> String -> String
ListType -> String
(Int -> ListType -> String -> String)
-> (ListType -> String)
-> ([ListType] -> String -> String)
-> Show ListType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListType] -> String -> String
$cshowList :: [ListType] -> String -> String
show :: ListType -> String
$cshow :: ListType -> String
showsPrec :: Int -> ListType -> String -> String
$cshowsPrec :: Int -> ListType -> String -> String
Show)

data ListNesting = LN { ListNesting -> ListType
lntype :: ListType, ListNesting -> Int
lnnest :: Int } deriving (Eq ListNesting
Eq ListNesting
-> (ListNesting -> ListNesting -> Ordering)
-> (ListNesting -> ListNesting -> Bool)
-> (ListNesting -> ListNesting -> Bool)
-> (ListNesting -> ListNesting -> Bool)
-> (ListNesting -> ListNesting -> Bool)
-> (ListNesting -> ListNesting -> ListNesting)
-> (ListNesting -> ListNesting -> ListNesting)
-> Ord ListNesting
ListNesting -> ListNesting -> Bool
ListNesting -> ListNesting -> Ordering
ListNesting -> ListNesting -> ListNesting
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ListNesting -> ListNesting -> ListNesting
$cmin :: ListNesting -> ListNesting -> ListNesting
max :: ListNesting -> ListNesting -> ListNesting
$cmax :: ListNesting -> ListNesting -> ListNesting
>= :: ListNesting -> ListNesting -> Bool
$c>= :: ListNesting -> ListNesting -> Bool
> :: ListNesting -> ListNesting -> Bool
$c> :: ListNesting -> ListNesting -> Bool
<= :: ListNesting -> ListNesting -> Bool
$c<= :: ListNesting -> ListNesting -> Bool
< :: ListNesting -> ListNesting -> Bool
$c< :: ListNesting -> ListNesting -> Bool
compare :: ListNesting -> ListNesting -> Ordering
$ccompare :: ListNesting -> ListNesting -> Ordering
$cp1Ord :: Eq ListNesting
Ord, ListNesting -> ListNesting -> Bool
(ListNesting -> ListNesting -> Bool)
-> (ListNesting -> ListNesting -> Bool) -> Eq ListNesting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNesting -> ListNesting -> Bool
$c/= :: ListNesting -> ListNesting -> Bool
== :: ListNesting -> ListNesting -> Bool
$c== :: ListNesting -> ListNesting -> Bool
Eq, Int -> ListNesting -> String -> String
[ListNesting] -> String -> String
ListNesting -> String
(Int -> ListNesting -> String -> String)
-> (ListNesting -> String)
-> ([ListNesting] -> String -> String)
-> Show ListNesting
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListNesting] -> String -> String
$cshowList :: [ListNesting] -> String -> String
show :: ListNesting -> String
$cshow :: ListNesting -> String
showsPrec :: Int -> ListNesting -> String -> String
$cshowsPrec :: Int -> ListNesting -> String -> String
Show)

-- The first argument is a stack (most recent == head) of our list
-- nesting status; the list type and the nesting level; if we're in
-- a number list in a bullet list it'd be
-- [LN Numbered 2, LN Bullet 1]
--
-- Mixed list example:
--
-- # one
-- # two
-- ** two point one
-- ** two point two
-- # three
-- # four
--
mixedList :: PandocMonad m => TikiWikiParser m B.Blocks
mixedList :: TikiWikiParser m Blocks
mixedList = TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  [(ListNesting, Blocks)]
items <- ParsecT Sources ParserState m [(ListNesting, Blocks)]
-> ParsecT Sources ParserState m [(ListNesting, Blocks)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources ParserState m [(ListNesting, Blocks)]
 -> ParsecT Sources ParserState m [(ListNesting, Blocks)])
-> ParsecT Sources ParserState m [(ListNesting, Blocks)]
-> ParsecT Sources ParserState m [(ListNesting, Blocks)]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (ListNesting, Blocks)
-> ParsecT Sources ParserState m [(ListNesting, Blocks)]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m (ListNesting, Blocks)
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
listItem
  Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList (ListType -> Int -> ListNesting
LN ListType
None Int
0) [(ListNesting, Blocks)]
items

-- See the "Handling Lists" section of DESIGN-CODE for why this
-- function exists.  It's to post-process the lists and do some
-- mappends.
--
-- We need to walk the tree two items at a time, so we can see what
-- we're going to join *to* before we get there.
--
-- Because of that, it seemed easier to do it by hand than to try to
-- figre out a fold or something.
fixListNesting :: [B.Blocks] -> [B.Blocks]
fixListNesting :: [Blocks] -> [Blocks]
fixListNesting [] = []
fixListNesting [Blocks
first] = [Blocks -> Blocks
recurseOnList Blocks
first]
-- fixListNesting nestall | trace ("\n\nfixListNesting: " ++ (show nestall)) False = undefined
-- fixListNesting nestall@(first:second:rest) =
fixListNesting (Blocks
first:Blocks
second:[Blocks]
rest) =
  let secondBlock :: Block
secondBlock = [Block] -> Block
forall a. [a] -> a
head ([Block] -> Block) -> [Block] -> Block
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
second in
    case Block
secondBlock of
      BulletList [[Block]]
_ -> [Blocks] -> [Blocks]
fixListNesting ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks -> Blocks
forall a. Monoid a => a -> a -> a
mappend (Blocks -> Blocks
recurseOnList Blocks
first) (Blocks -> Blocks
recurseOnList Blocks
second) Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
: [Blocks]
rest
      OrderedList ListAttributes
_ [[Block]]
_ -> [Blocks] -> [Blocks]
fixListNesting ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ Blocks -> Blocks -> Blocks
forall a. Monoid a => a -> a -> a
mappend (Blocks -> Blocks
recurseOnList Blocks
first) (Blocks -> Blocks
recurseOnList Blocks
second) Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
: [Blocks]
rest
      Block
_ -> Blocks -> Blocks
recurseOnList Blocks
first Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
: [Blocks] -> [Blocks]
fixListNesting (Blocks
secondBlocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
:[Blocks]
rest)

-- This function walks the Block structure for fixListNesting,
-- because it's a bit complicated, what with converting to and from
-- lists and so on.
recurseOnList :: B.Blocks -> B.Blocks
-- recurseOnList item | trace ("rOL: " ++ (show $ length $ B.toList item) ++ ", " ++ (show $ B.toList item)) False = undefined
recurseOnList :: Blocks -> Blocks
recurseOnList Blocks
items
  | [Block] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
items) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 =
    let itemBlock :: Block
itemBlock = [Block] -> Block
forall a. [a] -> a
head ([Block] -> Block) -> [Block] -> Block
forall a b. (a -> b) -> a -> b
$ Blocks -> [Block]
forall a. Many a -> [a]
B.toList Blocks
items in
      case Block
itemBlock of
        BulletList [[Block]]
listItems -> [Blocks] -> Blocks
B.bulletList ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ ([Block] -> Blocks) -> [[Block]] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map [Block] -> Blocks
forall a. [a] -> Many a
B.fromList [[Block]]
listItems
        OrderedList ListAttributes
_ [[Block]]
listItems -> [Blocks] -> Blocks
B.orderedList ([Blocks] -> Blocks) -> [Blocks] -> Blocks
forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ ([Block] -> Blocks) -> [[Block]] -> [Blocks]
forall a b. (a -> b) -> [a] -> [b]
map [Block] -> Blocks
forall a. [a] -> Many a
B.fromList [[Block]]
listItems
        Block
_ -> Blocks
items

  -- The otherwise works because we constructed the blocks, and we
  -- know for a fact that no mappends have been run on them; each
  -- Blocks consists of exactly one Block.
  --
  -- Anything that's not like that has already been processed by
  -- fixListNesting; don't bother to process it again.
  | Bool
otherwise = Blocks
items


-- Turn the list if list items into a tree by breaking off the first
-- item, splitting the remainder of the list into items that are in
-- the tree of the first item and those that aren't, wrapping the
-- tree of the first item in its list time, and recursing on both
-- sections.
spanFoldUpList :: ListNesting -> [(ListNesting, B.Blocks)] -> [B.Blocks]
spanFoldUpList :: ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList ListNesting
_ [] = []
spanFoldUpList ListNesting
ln [(ListNesting, Blocks)
first] =
  ListNesting -> ListNesting -> [Blocks] -> [Blocks]
listWrap ListNesting
ln ((ListNesting, Blocks) -> ListNesting
forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first) [(ListNesting, Blocks) -> Blocks
forall a b. (a, b) -> b
snd (ListNesting, Blocks)
first]
spanFoldUpList ListNesting
ln ((ListNesting, Blocks)
first:[(ListNesting, Blocks)]
rest) =
  let ([(ListNesting, Blocks)]
span1, [(ListNesting, Blocks)]
span2) = ((ListNesting, Blocks) -> Bool)
-> [(ListNesting, Blocks)]
-> ([(ListNesting, Blocks)], [(ListNesting, Blocks)])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (ListNesting -> (ListNesting, Blocks) -> Bool
splitListNesting ((ListNesting, Blocks) -> ListNesting
forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first)) [(ListNesting, Blocks)]
rest
      newTree1 :: [Blocks]
newTree1 = ListNesting -> ListNesting -> [Blocks] -> [Blocks]
listWrap ListNesting
ln ((ListNesting, Blocks) -> ListNesting
forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first) ([Blocks] -> [Blocks]) -> [Blocks] -> [Blocks]
forall a b. (a -> b) -> a -> b
$ (ListNesting, Blocks) -> Blocks
forall a b. (a, b) -> b
snd (ListNesting, Blocks)
first Blocks -> [Blocks] -> [Blocks]
forall a. a -> [a] -> [a]
: ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList ((ListNesting, Blocks) -> ListNesting
forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first) [(ListNesting, Blocks)]
span1
      newTree2 :: [Blocks]
newTree2 = ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList ListNesting
ln [(ListNesting, Blocks)]
span2
  in
    [Blocks]
newTree1 [Blocks] -> [Blocks] -> [Blocks]
forall a. [a] -> [a] -> [a]
++ [Blocks]
newTree2

-- Decide if the second item should be in the tree of the first
-- item, which is true if the second item is at a deeper nesting
-- level and of the same type.
splitListNesting :: ListNesting -> (ListNesting, B.Blocks) -> Bool
splitListNesting :: ListNesting -> (ListNesting, Blocks) -> Bool
splitListNesting ListNesting
ln1 (ListNesting
ln2, Blocks
_)
  | ListNesting -> Int
lnnest ListNesting
ln1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< ListNesting -> Int
lnnest ListNesting
ln2 =
  Bool
True
  | ListNesting
ln1 ListNesting -> ListNesting -> Bool
forall a. Eq a => a -> a -> Bool
== ListNesting
ln2 =
  Bool
True
  | Bool
otherwise =
  Bool
False

-- If we've moved to a deeper nesting level, wrap the new level in
-- the appropriate type of list.
listWrap :: ListNesting -> ListNesting -> [B.Blocks] -> [B.Blocks]
listWrap :: ListNesting -> ListNesting -> [Blocks] -> [Blocks]
listWrap ListNesting
upperLN ListNesting
curLN [Blocks]
retTree =
  if ListNesting
upperLN ListNesting -> ListNesting -> Bool
forall a. Eq a => a -> a -> Bool
== ListNesting
curLN then
    [Blocks]
retTree
  else
    case ListNesting -> ListType
lntype ListNesting
curLN of
      ListType
None     -> []
      ListType
Bullet   -> [[Blocks] -> Blocks
B.bulletList [Blocks]
retTree]
      ListType
Numbered -> [[Blocks] -> Blocks
B.orderedList [Blocks]
retTree]

listItem :: PandocMonad m => TikiWikiParser m (ListNesting, B.Blocks)
listItem :: TikiWikiParser m (ListNesting, Blocks)
listItem = [TikiWikiParser m (ListNesting, Blocks)]
-> TikiWikiParser m (ListNesting, Blocks)
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [
    TikiWikiParser m (ListNesting, Blocks)
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
bulletItem
  , TikiWikiParser m (ListNesting, Blocks)
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
numberedItem
  ]


-- * Start each line
-- * with an asterisk (*).
-- ** More asterisks gives deeper
-- *** and deeper levels.
--
bulletItem :: PandocMonad m => TikiWikiParser m (ListNesting, B.Blocks)
bulletItem :: TikiWikiParser m (ListNesting, Blocks)
bulletItem = TikiWikiParser m (ListNesting, Blocks)
-> TikiWikiParser m (ListNesting, Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m (ListNesting, Blocks)
 -> TikiWikiParser m (ListNesting, Blocks))
-> TikiWikiParser m (ListNesting, Blocks)
-> TikiWikiParser m (ListNesting, Blocks)
forall a b. (a -> b) -> a -> b
$ do
  String
prefix <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*'
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
  Inlines
content <- Int -> TikiWikiParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix)
  (ListNesting, Blocks) -> TikiWikiParser m (ListNesting, Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (ListType -> Int -> ListNesting
LN ListType
Bullet (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix), Inlines -> Blocks
B.plain Inlines
content)

-- # Start each line
-- # with a number (1.).
-- ## More number signs gives deeper
-- ### and deeper
--
numberedItem :: PandocMonad m => TikiWikiParser m (ListNesting, B.Blocks)
numberedItem :: TikiWikiParser m (ListNesting, Blocks)
numberedItem = TikiWikiParser m (ListNesting, Blocks)
-> TikiWikiParser m (ListNesting, Blocks)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m (ListNesting, Blocks)
 -> TikiWikiParser m (ListNesting, Blocks))
-> TikiWikiParser m (ListNesting, Blocks)
-> TikiWikiParser m (ListNesting, Blocks)
forall a b. (a -> b) -> a -> b
$ do
  String
prefix <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'#'
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
  Inlines
content <- Int -> TikiWikiParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix)
  (ListNesting, Blocks) -> TikiWikiParser m (ListNesting, Blocks)
forall (m :: * -> *) a. Monad m => a -> m a
return (ListType -> Int -> ListNesting
LN ListType
Numbered (String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix), Inlines -> Blocks
B.plain Inlines
content)

listItemLine :: PandocMonad m => Int -> TikiWikiParser m B.Inlines
listItemLine :: Int -> TikiWikiParser m Inlines
listItemLine Int
nest = ParsecT Sources ParserState m Text
forall u. ParsecT Sources u m Text
lineContent ParsecT Sources ParserState m Text
-> (Text -> TikiWikiParser m Inlines) -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> TikiWikiParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> ParsecT Sources ParserState m Inlines
parseContent
  where
    lineContent :: ParsecT Sources u m Text
lineContent = do
      Text
content <- ParsecT Sources u m Text
forall (m :: * -> *) st. Monad m => ParserT Sources st m Text
anyLine
      Maybe Text
continuation <- ParsecT Sources u m Text -> ParsecT Sources u m (Maybe Text)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Sources u m Text
listContinuation
      Text -> ParsecT Sources u m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParsecT Sources u m Text)
-> Text -> ParsecT Sources u m Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
filterSpaces Text
content Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\n" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
Data.Maybe.fromMaybe Text
"" Maybe Text
continuation
    filterSpaces :: Text -> Text
filterSpaces = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ')
    listContinuation :: ParsecT Sources u m Text
listContinuation = String -> ParsecT Sources u m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
nest Char
'+') ParsecT Sources u m String
-> ParsecT Sources u m Text -> ParsecT Sources u m Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources u m Text
lineContent
    parseContent :: Text -> ParsecT Sources ParserState m Inlines
parseContent Text
x = do
      [Inlines]
parsed <- ParserT Sources ParserState m [Inlines]
-> Text -> ParserT Sources ParserState m [Inlines]
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (ParsecT Sources ParserState m Inlines
-> ParserT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
x
      Inlines -> ParsecT Sources ParserState m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> ParsecT Sources ParserState m Inlines)
-> Inlines -> ParsecT Sources ParserState 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
$ (Inlines -> Bool) -> [Inlines] -> [Inlines]
forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
B.space) [Inlines]
parsed

-- Turn the CODE macro attributes into Pandoc code block attributes.
mungeAttrs :: [(Text, Text)] -> (Text, [Text], [(Text, Text)])
mungeAttrs :: [(Text, Text)] -> Attr
mungeAttrs [(Text, Text)]
rawAttrs = (Text
"", [Text]
classes, [(Text, Text)]
rawAttrs)
  where
    -- "colors" is TikiWiki CODE macro for "name of language to do
    -- highlighting for"; turn the value into a class
    color :: Text
color = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"colors" [(Text, Text)]
rawAttrs
    -- ln = 1 means line numbering.  It's also the default.  So we
    -- emit numberLines as a class unless ln = 0
    lnRaw :: Text
lnRaw = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"1" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"ln" [(Text, Text)]
rawAttrs
    ln :: Text
ln = if Text
lnRaw Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"0" then
            Text
""
         else
            Text
"numberLines"
    classes :: [Text]
classes = (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"") [Text
color, Text
ln]

codeMacro :: PandocMonad m => TikiWikiParser m B.Blocks
codeMacro :: TikiWikiParser m Blocks
codeMacro = TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Blocks -> TikiWikiParser m Blocks)
-> TikiWikiParser m Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{CODE("
  [(Text, Text)]
rawAttrs <- TikiWikiParser m [(Text, Text)]
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m [(Text, Text)]
macroAttrs
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
")}"
  Text
body <- String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{CODE}"))
  ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  if Bool -> Bool
not ([(Text, Text)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Text, Text)]
rawAttrs)
    then
      Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith ([(Text, Text)] -> Attr
mungeAttrs [(Text, Text)]
rawAttrs) Text
body
    else
      Blocks -> TikiWikiParser m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> TikiWikiParser m Blocks)
-> Blocks -> TikiWikiParser m Blocks
forall a b. (a -> b) -> a -> b
$ Text -> Blocks
B.codeBlock Text
body


--
-- inline parsers
--

inline :: PandocMonad m => TikiWikiParser m B.Inlines
inline :: TikiWikiParser m Inlines
inline = [TikiWikiParser m Inlines] -> TikiWikiParser m Inlines
forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
noparse
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strong
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
emph
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
nbsp
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
image
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
htmlComment
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strikeout
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
code
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
wikiLink
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
notExternalLink
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
externalLink
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superTag
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superMacro
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subTag
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subMacro
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
escapedChar
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
colored
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
centered
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
underlined
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
boxed
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
breakChars
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
str
                , TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
symbol
                ] TikiWikiParser m Inlines -> String -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> String -> ParsecT s u m a
<?> String
"inline"

whitespace :: PandocMonad m => TikiWikiParser m B.Inlines
whitespace :: TikiWikiParser m Inlines
whitespace = TikiWikiParser m Inlines
lb TikiWikiParser m Inlines
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Inlines
forall u. ParsecT Sources u m Inlines
regsp
  where lb :: TikiWikiParser m Inlines
lb = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources ParserState m ()
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
linebreak TikiWikiParser m Inlines
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
        regsp :: ParsecT Sources u m Inlines
regsp = ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines)
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall a b. (a -> b) -> a -> b
$ ParsecT Sources u m Char -> ParsecT Sources u m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 ParsecT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space

-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
nbsp :: PandocMonad m => TikiWikiParser m B.Inlines
nbsp :: TikiWikiParser m Inlines
nbsp = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~hs~"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
" NOT SUPPORTED BEGIN: ~hs~ (non-breaking space) :END "

-- UNSUPPORTED, as the desired behaviour (that the data be
-- *retained* and stored as a comment) doesn't exist in calibre, and
-- silently throwing data out seemed bad.
htmlComment :: PandocMonad m => TikiWikiParser m B.Inlines
htmlComment :: TikiWikiParser m Inlines
htmlComment = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~hc~"
  Text
inner <- (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"~"
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~/hc~"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ~hc~ (html comment opener) BEGIN: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" ~/hc~ :END "

linebreak :: PandocMonad m => TikiWikiParser m B.Inlines
linebreak :: TikiWikiParser m Inlines
linebreak = ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline ParsecT Sources ParserState m ()
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (TikiWikiParser m Inlines
forall u. ParsecT Sources u m Inlines
lastNewline TikiWikiParser m Inlines
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Inlines
innerNewline)
  where lastNewline :: ParsecT Sources u m Inlines
lastNewline  = ParsecT Sources u m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof ParsecT Sources u m ()
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
        innerNewline :: TikiWikiParser m Inlines
innerNewline = Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space

between :: (Monoid c, PandocMonad m, Show b) => TikiWikiParser m a -> TikiWikiParser m b -> (TikiWikiParser m b -> TikiWikiParser m c) -> TikiWikiParser m c
between :: TikiWikiParser m a
-> TikiWikiParser m b
-> (TikiWikiParser m b -> TikiWikiParser m c)
-> TikiWikiParser m c
between TikiWikiParser m a
start TikiWikiParser m b
end TikiWikiParser m b -> TikiWikiParser m c
p =
  [c] -> c
forall a. Monoid a => [a] -> a
mconcat ([c] -> c)
-> ParsecT Sources ParserState m [c] -> TikiWikiParser m c
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m [c]
-> ParsecT Sources ParserState m [c]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m a
start TikiWikiParser m a
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources ParserState m Inlines
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy ParsecT Sources ParserState m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [c]
-> ParsecT Sources ParserState m [c]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TikiWikiParser m c
-> TikiWikiParser m b -> ParsecT Sources ParserState m [c]
forall end s (m :: * -> *) t st a.
(Show end, Stream s m t) =>
ParserT s st m a -> ParserT s st m end -> ParserT s st m [a]
many1Till (TikiWikiParser m b -> TikiWikiParser m c
p TikiWikiParser m b
end) TikiWikiParser m b
end)

enclosed :: (Monoid b, PandocMonad m, Show a) => TikiWikiParser m a -> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed :: TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed TikiWikiParser m a
sep TikiWikiParser m a -> TikiWikiParser m b
p = TikiWikiParser m a
-> TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b)
-> TikiWikiParser m b
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TikiWikiParser m a
-> TikiWikiParser m b
-> (TikiWikiParser m b -> TikiWikiParser m c)
-> TikiWikiParser m c
between TikiWikiParser m a
sep (TikiWikiParser m a -> TikiWikiParser m a
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m a -> TikiWikiParser m a)
-> TikiWikiParser m a -> TikiWikiParser m a
forall a b. (a -> b) -> a -> b
$ TikiWikiParser m a
sep TikiWikiParser m a
-> ParsecT Sources ParserState m () -> TikiWikiParser m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT Sources ParserState m ()
endMarker) TikiWikiParser m a -> TikiWikiParser m b
p
  where
    endMarker :: ParsecT Sources ParserState m ()
endMarker   = ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT Sources ParserState m ()
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ TikiWikiParser m Inlines -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip TikiWikiParser m Inlines
forall u. ParsecT Sources u m Inlines
endSpace ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Char -> ParsecT Sources ParserState m ()
forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip (String -> TikiWikiParser m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
".,!?:)|'_") ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m ()
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
    endSpace :: ParsecT Sources u m Inlines
endSpace    = (ParserT Sources u m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar ParserT Sources u m Char
-> ParserT Sources u m Char -> ParserT Sources u m Char
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParserT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline) ParserT Sources u m Char
-> ParsecT Sources u m Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> ParsecT Sources u m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space


nestedInlines :: (Show a, PandocMonad m) => TikiWikiParser m a -> TikiWikiParser m B.Inlines
nestedInlines :: TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines TikiWikiParser m a
end = TikiWikiParser m Inlines
innerSpace TikiWikiParser m Inlines
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> TikiWikiParser m Inlines
nestedInline
  where
    innerSpace :: TikiWikiParser m Inlines
innerSpace   = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace TikiWikiParser m Inlines
-> ParsecT Sources ParserState m () -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* TikiWikiParser m a -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TikiWikiParser m a
end
    nestedInline :: TikiWikiParser m Inlines
nestedInline = TikiWikiParser m Inlines -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace ParsecT Sources ParserState m ()
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a.
PandocMonad m =>
TikiWikiParser m a -> TikiWikiParser m a
nested TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline

-- {img attId="39" imalign="right" link="http://info.tikiwiki.org" alt="Panama Hat"}
--
-- {img attId="37", thumb="mouseover", styleimage="border", desc="150"}
--
-- {img src="img/wiki_up/393px-Pears.jpg" thumb="y" imalign="center" stylebox="border" button="y" desc="Pretty pears" max="200" rel="box"}
--
image :: PandocMonad m => TikiWikiParser m B.Inlines
image :: TikiWikiParser m Inlines
image = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{img "
  [(Text, Text)]
rawAttrs <- ParsecT Sources ParserState m (Text, Text)
-> ParsecT Sources ParserState m ()
-> ParsecT Sources ParserState m [(Text, Text)]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepEndBy1 ParsecT Sources ParserState m (Text, Text)
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
imageAttr ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"}"
  let src :: Text
src = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"src" [(Text, Text)]
rawAttrs
  let title :: Text
title = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
src (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"desc" [(Text, Text)]
rawAttrs
  let alt :: Text
alt = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
title (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"alt" [(Text, Text)]
rawAttrs
  let classes :: [Text]
classes = ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text, Text) -> Text
forall a b. (a, b) -> a
fst ([(Text, Text)] -> [Text]) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
_,Text
b) -> Text
b Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"" Bool -> Bool -> Bool
|| Text
b Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"y") [(Text, Text)]
rawAttrs
  if Bool -> Bool
not (Text -> Bool
T.null Text
src)
    then
      Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Text -> Inlines -> Inlines
B.imageWith (Text
"", [Text]
classes, [(Text, Text)]
rawAttrs) Text
src Text
title (Text -> Inlines
B.str Text
alt)
    else
      Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: image without src attribute BEGIN: {img " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [(Text, Text)] -> Text
printAttrs [(Text, Text)]
rawAttrs Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"} :END "
  where
    printAttrs :: [(Text, Text)] -> Text
printAttrs [(Text, Text)]
attrs = [Text] -> Text
T.unwords ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (\(Text
a, Text
b) -> Text
a Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"=\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\"") [(Text, Text)]
attrs

imageAttr :: PandocMonad m => TikiWikiParser m (Text, Text)
imageAttr :: TikiWikiParser m (Text, Text)
imageAttr = TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text))
-> TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
  String
key <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"=} \t\n")
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  String
value <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"}\"\n")
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
','
  (Text, Text) -> TikiWikiParser m (Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Text
T.pack String
key, String -> Text
T.pack String
value)


-- __strong__
strong :: PandocMonad m => TikiWikiParser m B.Inlines
strong :: TikiWikiParser m Inlines
strong = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strong (TikiWikiParser m String
-> (TikiWikiParser m String -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"__") TikiWikiParser m String -> TikiWikiParser m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines)

-- ''emph''
emph :: PandocMonad m => TikiWikiParser m B.Inlines
emph :: TikiWikiParser m Inlines
emph = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.emph (TikiWikiParser m String
-> (TikiWikiParser m String -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"''") TikiWikiParser m String -> TikiWikiParser m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines)

-- ~246~
escapedChar :: PandocMonad m => TikiWikiParser m B.Inlines
escapedChar :: TikiWikiParser m Inlines
escapedChar = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~"
  Maybe Int
mNumber <- Text -> Maybe Int
forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead (Text -> Maybe Int) -> (String -> Text) -> String -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack (String -> Maybe Int)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$
    case Maybe Int
mNumber of
      Just Int
number -> Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Char
forall a. Enum a => Int -> a
toEnum (Int
number :: Int)
      Maybe Int
Nothing     -> Text
""

-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
centered :: PandocMonad m => TikiWikiParser m B.Inlines
centered :: TikiWikiParser m Inlines
centered = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"::"
  Text
inner <- (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
":\n"
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"::"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: :: (centered) BEGIN: ::" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":: :END "

-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
colored :: PandocMonad m => TikiWikiParser m B.Inlines
colored :: TikiWikiParser m Inlines
colored = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~~"
  Text
inner <- (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"~\n"
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~~"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ~~ (colored) BEGIN: ~~" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"~~ :END "

-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
underlined :: PandocMonad m => TikiWikiParser m B.Inlines
underlined :: TikiWikiParser m Inlines
underlined = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"==="
  Text
inner <- (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"=\n"
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"==="
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ==== (underlined) BEGIN: ===" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"=== :END "

-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
boxed :: PandocMonad m => TikiWikiParser m B.Inlines
boxed :: TikiWikiParser m Inlines
boxed = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"^"
  Text
inner <- (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack (ParsecT Sources ParserState m String
 -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m String)
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"^\n"
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"^"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ^ (boxed) BEGIN: ^" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
inner Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"^ :END "

-- --text--
strikeout :: PandocMonad m => TikiWikiParser m B.Inlines
strikeout :: TikiWikiParser m Inlines
strikeout = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ (Inlines -> Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strikeout (TikiWikiParser m String
-> (TikiWikiParser m String -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines
forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"--") TikiWikiParser m String -> TikiWikiParser m Inlines
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines)

nestedString :: (Show a, PandocMonad m) => TikiWikiParser m a -> TikiWikiParser m Text
nestedString :: TikiWikiParser m a -> TikiWikiParser m Text
nestedString TikiWikiParser m a
end = TikiWikiParser m Text
innerSpace TikiWikiParser m Text
-> TikiWikiParser m Text -> TikiWikiParser m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int -> ParsecT Sources ParserState m Char -> TikiWikiParser m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
nonspaceChar
  where
    innerSpace :: TikiWikiParser m Text
innerSpace = TikiWikiParser m Text -> TikiWikiParser m Text
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Text -> TikiWikiParser m Text)
-> TikiWikiParser m Text -> TikiWikiParser m Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String -> TikiWikiParser m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar TikiWikiParser m Text
-> ParsecT Sources ParserState m () -> TikiWikiParser m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* TikiWikiParser m a -> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy TikiWikiParser m a
end

breakChars :: PandocMonad m => TikiWikiParser m B.Inlines
breakChars :: TikiWikiParser m Inlines
breakChars = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"%%%" ParsecT Sources ParserState m String
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak

-- superscript: foo{TAG(tag=>sup)}super{TAG}foo / bar{SUP()}super2{SUP}bar
superTag :: PandocMonad m => TikiWikiParser m B.Inlines
superTag :: TikiWikiParser m Inlines
superTag = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$  (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Inlines
B.superscript (Inlines -> Inlines) -> (Text -> Inlines) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( TikiWikiParser m String
-> TikiWikiParser m String
-> (TikiWikiParser m String -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TikiWikiParser m a
-> TikiWikiParser m b
-> (TikiWikiParser m b -> TikiWikiParser m c)
-> TikiWikiParser m c
between (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG(tag=>sup)}") (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG}") TikiWikiParser m String -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)

superMacro :: PandocMonad m => TikiWikiParser m B.Inlines
superMacro :: TikiWikiParser m Inlines
superMacro = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUP("
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
")}")
  String
body <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUP}")
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.superscript (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body

-- subscript: baz{TAG(tag=>sub)}sub{TAG}qux / qux{SUB()}sub2{SUB}qux
subTag :: PandocMonad m => TikiWikiParser m B.Inlines
subTag :: TikiWikiParser m Inlines
subTag = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$  (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Inlines
B.subscript (Inlines -> Inlines) -> (Text -> Inlines) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( TikiWikiParser m String
-> TikiWikiParser m String
-> (TikiWikiParser m String -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TikiWikiParser m a
-> TikiWikiParser m b
-> (TikiWikiParser m b -> TikiWikiParser m c)
-> TikiWikiParser m c
between (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG(tag=>sub)}") (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG}") TikiWikiParser m String -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)

subMacro :: PandocMonad m => TikiWikiParser m B.Inlines
subMacro :: TikiWikiParser m Inlines
subMacro = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUB("
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
")}")
  String
body <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUB}")
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.subscript (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body

-- -+text+-
code :: PandocMonad m => TikiWikiParser m B.Inlines
code :: TikiWikiParser m Inlines
code = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$  (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Inlines
B.code (Text -> Inlines) -> (Text -> Text) -> Text -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( TikiWikiParser m String
-> TikiWikiParser m String
-> (TikiWikiParser m String -> ParsecT Sources ParserState m Text)
-> ParsecT Sources ParserState m Text
forall c (m :: * -> *) b a.
(Monoid c, PandocMonad m, Show b) =>
TikiWikiParser m a
-> TikiWikiParser m b
-> (TikiWikiParser m b -> TikiWikiParser m c)
-> TikiWikiParser m c
between (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"-+") (String -> TikiWikiParser m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"+-") TikiWikiParser m String -> ParsecT Sources ParserState m Text
forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)

macroAttr :: PandocMonad m => TikiWikiParser m (Text, Text)
macroAttr :: TikiWikiParser m (Text, Text)
macroAttr = TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text)
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text))
-> TikiWikiParser m (Text, Text) -> TikiWikiParser m (Text, Text)
forall a b. (a -> b) -> a -> b
$ do
  String
key <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"=)")
  Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  String
value <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
" )\"")
  ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional (ParsecT Sources ParserState m Char
 -> ParsecT Sources ParserState m ())
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  (Text, Text) -> TikiWikiParser m (Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Text
T.pack String
key, String -> Text
T.pack String
value)

macroAttrs :: PandocMonad m => TikiWikiParser m [(Text, Text)]
macroAttrs :: TikiWikiParser m [(Text, Text)]
macroAttrs = TikiWikiParser m [(Text, Text)] -> TikiWikiParser m [(Text, Text)]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m [(Text, Text)]
 -> TikiWikiParser m [(Text, Text)])
-> TikiWikiParser m [(Text, Text)]
-> TikiWikiParser m [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ ParsecT Sources ParserState m (Text, Text)
-> ParsecT Sources ParserState m ()
-> TikiWikiParser m [(Text, Text)]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
sepEndBy ParsecT Sources ParserState m (Text, Text)
forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
macroAttr ParsecT Sources ParserState m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces

-- ~np~ __not bold__ ~/np~
noparse :: PandocMonad m => TikiWikiParser m B.Inlines
noparse :: TikiWikiParser m Inlines
noparse = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~np~"
  String
body <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~/np~")
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body

str :: PandocMonad m => TikiWikiParser m B.Inlines
str :: TikiWikiParser m Inlines
str = (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
B.str (String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
characterReference)

symbol :: PandocMonad m => TikiWikiParser m B.Inlines
symbol :: TikiWikiParser m Inlines
symbol = (Text -> Inlines)
-> ParsecT Sources ParserState m Text -> TikiWikiParser m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
B.str (Int
-> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char, Monad m) =>
Int -> ParsecT s st m Char -> ParsecT s st m Text
countChar Int
1 ParsecT Sources ParserState m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
nonspaceChar)

-- [[not a link]
notExternalLink :: PandocMonad m => TikiWikiParser m B.Inlines
notExternalLink :: TikiWikiParser m Inlines
notExternalLink = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  String
start <- String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"[["
  String
body <- ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"\n[]")
  String
end <- String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"]"
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text (Text -> Inlines) -> Text -> Inlines
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
start String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
body String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
end

-- [http://www.somesite.org url|Some Site title]
-- ((internal link))
--
-- The ((...)) wiki links and [...] external links are handled
-- exactly the same; this abstracts that out
makeLink :: PandocMonad m => Text -> Text -> Text -> TikiWikiParser m B.Inlines
makeLink :: Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
start Text
middle Text
end = TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m Inlines -> TikiWikiParser m Inlines)
-> TikiWikiParser m Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ do
  ParserState
st <- ParsecT Sources ParserState m ParserState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT Sources ParserState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT Sources ParserState m ())
-> Bool -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
st
  ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
False }
  (Text
url, Text
title, Text
anchor) <- Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText Text
start Text
middle Text
end
  [Inlines]
parsedTitle <- ParserT Sources ParserState m [Inlines]
-> Text -> ParserT Sources ParserState m [Inlines]
forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (TikiWikiParser m Inlines -> ParserT Sources ParserState m [Inlines]
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 TikiWikiParser m Inlines
forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
title
  ParserState -> ParsecT Sources ParserState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState (ParserState -> ParsecT Sources ParserState m ())
-> ParserState -> ParsecT Sources ParserState m ()
forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
True }
  Inlines -> TikiWikiParser m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> TikiWikiParser m Inlines)
-> Inlines -> TikiWikiParser m Inlines
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link (Text
url Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
anchor) Text
"" (Inlines -> Inlines) -> Inlines -> Inlines
forall a b. (a -> b) -> a -> b
$ [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat [Inlines]
parsedTitle

wikiLinkText :: PandocMonad m => Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText :: Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText Text
start Text
middle Text
end = do
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string (Text -> String
T.unpack Text
start)
  Text
url <- String -> Text
T.pack (String -> Text)
-> ParsecT Sources ParserState m String
-> ParsecT Sources ParserState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources ParserState m Char
-> ParsecT Sources ParserState m String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (String -> ParsecT Sources ParserState m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf (String -> ParsecT Sources ParserState m Char)
-> String -> ParsecT Sources ParserState m Char
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
middle String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n")
  Text
seg1 <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
url ParsecT Sources ParserState m Text
forall u. ParsecT Sources u m Text
linkContent
  Text
seg2 <- Text
-> ParsecT Sources ParserState m Text
-> ParsecT Sources ParserState m Text
forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" ParsecT Sources ParserState m Text
forall u. ParsecT Sources u m Text
linkContent
  String -> ParsecT Sources ParserState m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string (Text -> String
T.unpack Text
end)
  if Text
seg2 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
""
    then
      (Text, Text, Text) -> TikiWikiParser m (Text, Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
url, Text
seg2, Text
seg1)
    else
      (Text, Text, Text) -> TikiWikiParser m (Text, Text, Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
url, Text
seg1, Text
"")
  where
    linkContent :: ParsecT Sources u m Text
linkContent      = do
      Char -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'|'
      String -> Text
T.pack (String -> Text)
-> ParsecT Sources u m String -> ParsecT Sources u m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Sources u m Char -> ParsecT Sources u m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (String -> ParsecT Sources u m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf (String -> ParsecT Sources u m Char)
-> String -> ParsecT Sources u m Char
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
middle)

externalLink :: PandocMonad m => TikiWikiParser m B.Inlines
externalLink :: TikiWikiParser m Inlines
externalLink = Text -> Text -> Text -> TikiWikiParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
"[" Text
"]|" Text
"]"

-- NB: this wiki linking is unlikely to work for anyone besides me
-- (rlpowell); it happens to work for me because my Hakyll code has
-- post-processing that treats pandoc .md titles as valid link
-- targets, so something like
-- [see also this other post](My Other Page) is perfectly valid.
wikiLink :: PandocMonad m => TikiWikiParser m B.Inlines
wikiLink :: TikiWikiParser m Inlines
wikiLink = Text -> Text -> Text -> TikiWikiParser m Inlines
forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
"((" Text
")|" Text
"))"