{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE OverloadedStrings #-}
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)
readTikiWiki :: (PandocMonad m, ToSources a)
          => ReaderOptions
          -> a
          -> m Pandoc
readTikiWiki :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readTikiWiki ReaderOptions
opts a
s = do
  let sources :: Sources
sources = Int -> Sources -> Sources
ensureFinalNewlines Int
2 (forall a. ToSources a => a -> Sources
toSources a
s)
  Either PandocError Pandoc
res <- forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParserT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM forall (m :: * -> *). PandocMonad m => TikiWikiParser m Pandoc
parseTikiWiki forall a. Default a => a
def{ stateOptions :: ReaderOptions
stateOptions = ReaderOptions
opts } Sources
sources
  case Either PandocError Pandoc
res of
       Left PandocError
e  -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
       Right Pandoc
d -> forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
d
type TikiWikiParser = ParserT Sources ParserState
tryMsg :: Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg :: forall (m :: * -> *) a.
Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
msg TikiWikiParser m a
p = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try TikiWikiParser m a
p 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 :: forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip TikiWikiParser m a
parser = 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 :: forall (m :: * -> *) a.
PandocMonad m =>
TikiWikiParser m a -> TikiWikiParser m a
nested TikiWikiParser m a
p = do
  Int
nestlevel <- ParserState -> Int
stateMaxNestingLevel forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Int
nestlevel forall a. Ord a => a -> a -> Bool
> Int
0
  forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMaxNestingLevel :: Int
stateMaxNestingLevel = ParserState -> Int
stateMaxNestingLevel ParserState
st forall a. Num a => a -> a -> a
- Int
1 }
  a
res <- TikiWikiParser m a
p
  forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState forall a b. (a -> b) -> a -> b
$ \ParserState
st -> ParserState
st{ stateMaxNestingLevel :: Int
stateMaxNestingLevel = Int
nestlevel }
  forall (m :: * -> *) a. Monad m => a -> m a
return a
res
parseTikiWiki :: PandocMonad m => TikiWikiParser m Pandoc
parseTikiWiki :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Pandoc
parseTikiWiki = do
  Blocks
bs <- forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
block
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Blocks -> Pandoc
B.doc Blocks
bs
block :: PandocMonad m => TikiWikiParser m B.Blocks
block :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
block = do
  Verbosity
verbosity <- forall (m :: * -> *) a. PandocMonad m => (CommonState -> a) -> m a
getsCommonState CommonState -> Verbosity
stVerbosity
  SourcePos
pos <- forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  Blocks
res <- forall a. Monoid a => a
mempty forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
         forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
blockElements
         forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
para
  forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Verbosity
verbosity forall a. Ord a => a -> a -> Bool
>= Verbosity
INFO) forall a b. (a -> b) -> a -> b
$
    forall (m :: * -> *). PandocMonad m => Text -> m ()
trace (String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall r. PrintfType r => String -> r
printf String
"line %d: %s" (SourcePos -> Int
sourceLine SourcePos
pos) (forall a. Int -> [a] -> [a]
take Int
60 forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
B.toList Blocks
res))
  forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res
blockElements :: PandocMonad m => TikiWikiParser m B.Blocks
blockElements :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
blockElements = forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
table
                       , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
hr
                       , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
header
                       , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
mixedList
                       , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
definitionList
                       , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
codeMacro
                       ]
hr :: PandocMonad m => TikiWikiParser m B.Blocks
hr :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
hr = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"----"
  forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-')
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
B.horizontalRule
header :: PandocMonad m => TikiWikiParser m B.Blocks
 = forall (m :: * -> *) a.
Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
"header" forall a b. (a -> b) -> a -> b
$ do
  Int
level <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'!'))
  forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Int
level forall a. Ord a => a -> a -> Bool
<= Int
6
  forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
  Inlines
content <- Inlines -> Inlines
B.trimInlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  Attr
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
  forall (m :: * -> *) a. Monad m => a -> m a
return 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 :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m [Blocks]
tableRow = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  [Inlines]
row <- 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 (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"\n|") forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {m :: * -> *}.
PandocMonad m =>
Text -> ParsecT Sources ParserState m Inlines
parseColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"|" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
"|\n"))
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ 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 <- forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
x
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Inlines]
parsed
table :: PandocMonad m => TikiWikiParser m B.Blocks
table :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
table = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||"
  [[Blocks]]
rows <- 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 forall (m :: * -> *). PandocMonad m => TikiWikiParser m [Blocks]
tableRow (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"\n" forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||" forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"\n")))
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"||"
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [Blocks] -> [[Blocks]] -> Blocks
B.simpleTable (forall {t :: * -> *} {a}. Foldable t => [t a] -> [Blocks]
headers [[Blocks]]
rows) [[Blocks]]
rows
  where
    
    
    headers :: [t a] -> [Blocks]
headers [t a]
rows = forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ forall a. [a] -> a
head [t a]
rows) ((Inlines -> Blocks
B.plain forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.str) Text
"")
para :: PandocMonad m => TikiWikiParser m B.Blocks
para :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
para =  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Blocks
result forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat) ( 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 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline ParsecT Sources ParserState m ()
endOfParaElement)
 where
   endOfParaElement :: ParsecT Sources ParserState m ()
endOfParaElement = forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead forall a b. (a -> b) -> a -> b
$ forall {u}. ParsecT Sources u m ()
endOfInput forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. ParsecT Sources u m ()
endOfPara forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m ()
newBlockElement
   endOfInput :: ParsecT Sources u m ()
endOfInput       = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
   endOfPara :: ParsecT Sources u m ()
endOfPara        = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline
   newBlockElement :: ParsecT Sources ParserState m ()
newBlockElement  = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
blankline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
blockElements
   result :: Inlines -> Blocks
result Inlines
content   = if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
F.all (forall a. Eq a => a -> a -> Bool
==Inline
Space) Inlines
content
                      then forall a. Monoid a => a
mempty
                      else Inlines -> Blocks
B.para forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.trimInlines Inlines
content
definitionList :: PandocMonad m => TikiWikiParser m B.Blocks
definitionList :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
definitionList = forall (m :: * -> *) a.
Text -> TikiWikiParser m a -> TikiWikiParser m a
tryMsg Text
"definitionList" forall a b. (a -> b) -> a -> b
$ do
  [(Inlines, [Blocks])]
elements <-forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Inlines, [Blocks])
parseDefinitionListItem
  forall (m :: * -> *) a. Monad m => a -> m a
return 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 :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Inlines, [Blocks])
parseDefinitionListItem = do
      forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
';' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
      [Inlines]
term <- 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 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
':' forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m ()
skipSpaces
      Inlines
line <- forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine Int
1
      forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. Monoid a => [a] -> a
mconcat [Inlines]
term, [Inlines -> Blocks
B.plain Inlines
line])
data ListType = None | Numbered | Bullet deriving (Eq 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
Ord, ListType -> ListType -> Bool
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
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
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
Ord, ListNesting -> ListNesting -> Bool
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
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)
mixedList :: PandocMonad m => TikiWikiParser m B.Blocks
mixedList :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
mixedList = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  [(ListNesting, Blocks)]
items <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
listItem
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting forall a b. (a -> b) -> a -> b
$ ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList (ListType -> Int -> ListNesting
LN ListType
None Int
0) [(ListNesting, Blocks)]
items
fixListNesting :: [B.Blocks] -> [B.Blocks]
fixListNesting :: [Blocks] -> [Blocks]
fixListNesting [] = []
fixListNesting [Blocks
first] = [Blocks -> Blocks
recurseOnList Blocks
first]
fixListNesting (Blocks
first:Blocks
second:[Blocks]
rest) =
  let secondBlock :: Block
secondBlock = forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
B.toList Blocks
second in
    case Block
secondBlock of
      BulletList [[Block]]
_ -> [Blocks] -> [Blocks]
fixListNesting forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => a -> a -> a
mappend (Blocks -> Blocks
recurseOnList Blocks
first) (Blocks -> Blocks
recurseOnList Blocks
second) forall a. a -> [a] -> [a]
: [Blocks]
rest
      OrderedList ListAttributes
_ [[Block]]
_ -> [Blocks] -> [Blocks]
fixListNesting forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => a -> a -> a
mappend (Blocks -> Blocks
recurseOnList Blocks
first) (Blocks -> Blocks
recurseOnList Blocks
second) forall a. a -> [a] -> [a]
: [Blocks]
rest
      Block
_ -> Blocks -> Blocks
recurseOnList Blocks
first forall a. a -> [a] -> [a]
: [Blocks] -> [Blocks]
fixListNesting (Blocks
secondforall a. a -> [a] -> [a]
:[Blocks]
rest)
recurseOnList :: B.Blocks -> B.Blocks
recurseOnList :: Blocks -> Blocks
recurseOnList Blocks
items
  | forall (t :: * -> *) a. Foldable t => t a -> Int
length (forall a. Many a -> [a]
B.toList Blocks
items) forall a. Eq a => a -> a -> Bool
== Int
1 =
    let itemBlock :: Block
itemBlock = forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ forall a. Many a -> [a]
B.toList Blocks
items in
      case Block
itemBlock of
        BulletList [[Block]]
listItems -> [Blocks] -> Blocks
B.bulletList forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Many a
B.fromList [[Block]]
listItems
        OrderedList ListAttributes
_ [[Block]]
listItems -> [Blocks] -> Blocks
B.orderedList forall a b. (a -> b) -> a -> b
$ [Blocks] -> [Blocks]
fixListNesting forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> Many a
B.fromList [[Block]]
listItems
        Block
_ -> Blocks
items
  
  
  
  
  
  
  | Bool
otherwise = Blocks
items
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 (forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first) [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) = forall a. (a -> Bool) -> [a] -> ([a], [a])
span (ListNesting -> (ListNesting, Blocks) -> Bool
splitListNesting (forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first)) [(ListNesting, Blocks)]
rest
      newTree1 :: [Blocks]
newTree1 = ListNesting -> ListNesting -> [Blocks] -> [Blocks]
listWrap ListNesting
ln (forall a b. (a, b) -> a
fst (ListNesting, Blocks)
first) forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd (ListNesting, Blocks)
first forall a. a -> [a] -> [a]
: ListNesting -> [(ListNesting, Blocks)] -> [Blocks]
spanFoldUpList (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 forall a. [a] -> [a] -> [a]
++ [Blocks]
newTree2
splitListNesting :: ListNesting -> (ListNesting, B.Blocks) -> Bool
splitListNesting :: ListNesting -> (ListNesting, Blocks) -> Bool
splitListNesting ListNesting
ln1 (ListNesting
ln2, Blocks
_)
  | ListNesting -> Int
lnnest ListNesting
ln1 forall a. Ord a => a -> a -> Bool
< ListNesting -> Int
lnnest ListNesting
ln2 =
  Bool
True
  | ListNesting
ln1 forall a. Eq a => a -> a -> Bool
== ListNesting
ln2 =
  Bool
True
  | Bool
otherwise =
  Bool
False
listWrap :: ListNesting -> ListNesting -> [B.Blocks] -> [B.Blocks]
listWrap :: ListNesting -> ListNesting -> [Blocks] -> [Blocks]
listWrap ListNesting
upperLN ListNesting
curLN [Blocks]
retTree =
  if ListNesting
upperLN 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 :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
listItem = forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [
    forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
bulletItem
  , forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
numberedItem
  ]
bulletItem :: PandocMonad m => TikiWikiParser m (ListNesting, B.Blocks)
bulletItem :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
bulletItem = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  String
prefix <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'*'
  forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
  Inlines
content <- forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix)
  forall (m :: * -> *) a. Monad m => a -> m a
return (ListType -> Int -> ListNesting
LN ListType
Bullet (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix), Inlines -> Blocks
B.plain Inlines
content)
numberedItem :: PandocMonad m => TikiWikiParser m (ListNesting, B.Blocks)
numberedItem :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (ListNesting, Blocks)
numberedItem = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  String
prefix <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'#'
  forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
' '
  Inlines
content <- forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
prefix)
  forall (m :: * -> *) a. Monad m => a -> m a
return (ListType -> Int -> ListNesting
LN ListType
Numbered (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 :: forall (m :: * -> *).
PandocMonad m =>
Int -> TikiWikiParser m Inlines
listItemLine Int
nest = forall {st}. ParsecT Sources st m Text
lineContent forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {m :: * -> *}.
PandocMonad m =>
Text -> ParsecT Sources ParserState m Inlines
parseContent
  where
    lineContent :: ParsecT Sources st m Text
lineContent = do
      Text
content <- forall (m :: * -> *) st. Monad m => ParserT Sources st m Text
anyLine
      Maybe Text
continuation <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m (Maybe a)
optionMaybe ParsecT Sources st m Text
listContinuation
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Text
filterSpaces Text
content forall a. Semigroup a => a -> a -> a
<> Text
"\n" forall a. Semigroup a => a -> a -> a
<> forall a. a -> Maybe a -> a
Data.Maybe.fromMaybe Text
"" Maybe Text
continuation
    filterSpaces :: Text -> Text
filterSpaces = (Char -> Bool) -> Text -> Text
T.dropWhileEnd (forall a. Eq a => a -> a -> Bool
== Char
' ')
    listContinuation :: ParsecT Sources st m Text
listContinuation = forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string (forall a. Int -> a -> [a]
replicate Int
nest Char
'+') forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Sources st m Text
lineContent
    parseContent :: Text -> ParsecT Sources ParserState m Inlines
parseContent Text
x = do
      [Inlines]
parsed <- forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
x
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
dropWhileEnd (forall a. Eq a => a -> a -> Bool
== Inlines
B.space) [Inlines]
parsed
mungeAttrs :: [(Text, Text)] -> (Text, [Text], [(Text, Text)])
mungeAttrs :: [(Text, Text)] -> Attr
mungeAttrs [(Text, Text)]
rawAttrs = (Text
"", [Text]
classes, [(Text, Text)]
rawAttrs)
  where
    
    
    color :: Text
color = forall a. a -> Maybe a -> a
fromMaybe Text
"" forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"colors" [(Text, Text)]
rawAttrs
    
    
    lnRaw :: Text
lnRaw = forall a. a -> Maybe a -> a
fromMaybe Text
"1" forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"ln" [(Text, Text)]
rawAttrs
    ln :: Text
ln = if Text
lnRaw forall a. Eq a => a -> a -> Bool
== Text
"0" then
            Text
""
         else
            Text
"numberLines"
    classes :: [Text]
classes = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Text
"") [Text
color, Text
ln]
codeMacro :: PandocMonad m => TikiWikiParser m B.Blocks
codeMacro :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Blocks
codeMacro = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  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 <- forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m [(Text, Text)]
macroAttrs
  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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{CODE}"))
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  if Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Text, Text)]
rawAttrs)
    then
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Blocks
B.codeBlockWith ([(Text, Text)] -> Attr
mungeAttrs [(Text, Text)]
rawAttrs) Text
body
    else
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Blocks
B.codeBlock Text
body
inline :: PandocMonad m => TikiWikiParser m B.Inlines
inline :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline = forall s (m :: * -> *) t u a.
Stream s m t =>
[ParsecT s u m a] -> ParsecT s u m a
choice [ forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
noparse
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strong
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
emph
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
nbsp
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
image
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
htmlComment
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strikeout
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
code
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
wikiLink
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
notExternalLink
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
externalLink
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superTag
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superMacro
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subTag
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subMacro
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
escapedChar
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
colored
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
centered
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
underlined
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
boxed
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
breakChars
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
str
                , forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
symbol
                ] 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 :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace = ParsecT Sources ParserState m Inlines
lb forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall {u}. ParsecT Sources u m Inlines
regsp
  where lb :: ParsecT Sources ParserState m Inlines
lb = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
linebreak forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
        regsp :: ParsecT Sources u m Inlines
regsp = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
skipMany1 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.space
nbsp :: PandocMonad m => TikiWikiParser m B.Inlines
nbsp :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
nbsp = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~hs~"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str Text
" NOT SUPPORTED BEGIN: ~hs~ (non-breaking space) :END "
htmlComment :: PandocMonad m => TikiWikiParser m B.Inlines
 = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~hc~"
  Text
inner <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"~"
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~/hc~"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ~hc~ (html comment opener) BEGIN: " forall a. Semigroup a => a -> a -> a
<> Text
inner forall a. Semigroup a => a -> a -> a
<> Text
" ~/hc~ :END "
linebreak :: PandocMonad m => TikiWikiParser m B.Inlines
linebreak :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
linebreak = forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> (forall {u}. ParsecT Sources u m Inlines
lastNewline forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
innerNewline)
  where lastNewline :: ParsecT Sources u m Inlines
lastNewline  = forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
        innerNewline :: ParsecT Sources ParserState m Inlines
innerNewline = 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 :: 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
start TikiWikiParser m b
end TikiWikiParser m b -> TikiWikiParser m c
p =
  forall a. Monoid a => [a] -> a
mconcat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (TikiWikiParser m a
start forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 :: forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed TikiWikiParser m a
sep TikiWikiParser m a -> TikiWikiParser m b
p = 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 (forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ TikiWikiParser m a
sep 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   = forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip forall {u}. ParsecT Sources u m Inlines
endSpace forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) a. TikiWikiParser m a -> TikiWikiParser m ()
skip (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
oneOf String
".,!?:)|'_") forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
    endSpace :: ParsecT Sources u m Inlines
endSpace    = (forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> 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 :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines TikiWikiParser m a
end = ParsecT Sources ParserState m Inlines
innerSpace forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> ParsecT Sources ParserState m Inlines
nestedInline
  where
    innerSpace :: ParsecT Sources ParserState m Inlines
innerSpace   = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* 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 :: ParsecT Sources ParserState m Inlines
nestedInline = forall s (m :: * -> *) t a u.
(Stream s m t, Show a) =>
ParsecT s u m a -> ParsecT s u m ()
notFollowedBy forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
whitespace forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a.
PandocMonad m =>
TikiWikiParser m a -> TikiWikiParser m a
nested forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline
image :: PandocMonad m => TikiWikiParser m B.Inlines
image :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
image = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  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 <- 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 forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
imageAttr forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  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 = forall a. a -> Maybe a -> a
fromMaybe Text
"" forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"src" [(Text, Text)]
rawAttrs
  let title :: Text
title = forall a. a -> Maybe a -> a
fromMaybe Text
src forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"desc" [(Text, Text)]
rawAttrs
  let alt :: Text
alt = forall a. a -> Maybe a -> a
fromMaybe Text
title forall a b. (a -> b) -> a -> b
$ forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
"alt" [(Text, Text)]
rawAttrs
  let classes :: [Text]
classes = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
_,Text
b) -> Text
b forall a. Eq a => a -> a -> Bool
== Text
"" Bool -> Bool -> Bool
|| Text
b forall a. Eq a => a -> a -> Bool
== Text
"y") [(Text, Text)]
rawAttrs
  if Bool -> Bool
not (Text -> Bool
T.null Text
src)
    then
      forall (m :: * -> *) a. Monad m => a -> m a
return 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
      forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: image without src attribute BEGIN: {img " forall a. Semigroup a => a -> a -> a
<> [(Text, Text)] -> Text
printAttrs [(Text, Text)]
rawAttrs forall a. Semigroup a => a -> a -> a
<> Text
"} :END "
  where
    printAttrs :: [(Text, Text)] -> Text
printAttrs [(Text, Text)]
attrs = [Text] -> Text
T.unwords forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (\(Text
a, Text
b) -> Text
a forall a. Semigroup a => a -> a -> a
<> Text
"=\"" forall a. Semigroup a => a -> a -> a
<> Text
b forall a. Semigroup a => a -> a -> a
<> Text
"\"") [(Text, Text)]
attrs
imageAttr :: PandocMonad m => TikiWikiParser m (Text, Text)
imageAttr :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
imageAttr = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  String
key <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"=} \t\n")
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
  forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  String
value <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"}\"\n")
  forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
','
  forall (m :: * -> *) a. Monad m => a -> m a
return (String -> Text
T.pack String
key, String -> Text
T.pack String
value)
strong :: PandocMonad m => TikiWikiParser m B.Inlines
strong :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strong = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strong (forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"__") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines)
emph :: PandocMonad m => TikiWikiParser m B.Inlines
emph :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
emph = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.emph (forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"''") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines)
escapedChar :: PandocMonad m => TikiWikiParser m B.Inlines
escapedChar :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
escapedChar = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~"
  Maybe Int
mNumber <- forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
digit
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$
    case Maybe Int
mNumber of
      Just Int
number -> Char -> Text
T.singleton forall a b. (a -> b) -> a -> b
$ forall a. Enum a => Int -> a
toEnum (Int
number :: Int)
      Maybe Int
Nothing     -> Text
""
centered :: PandocMonad m => TikiWikiParser m B.Inlines
centered :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
centered = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"::"
  Text
inner <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
":\n"
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"::"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: :: (centered) BEGIN: ::" forall a. Semigroup a => a -> a -> a
<> Text
inner forall a. Semigroup a => a -> a -> a
<> Text
":: :END "
colored :: PandocMonad m => TikiWikiParser m B.Inlines
colored :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
colored = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~~"
  Text
inner <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"~\n"
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~~"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ~~ (colored) BEGIN: ~~" forall a. Semigroup a => a -> a -> a
<> Text
inner forall a. Semigroup a => a -> a -> a
<> Text
"~~ :END "
underlined :: PandocMonad m => TikiWikiParser m B.Inlines
underlined :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
underlined = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.underline forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"===") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Inlines
nestedInlines
boxed :: PandocMonad m => TikiWikiParser m B.Inlines
boxed :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
boxed = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"^"
  Text
inner <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"^\n"
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"^"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ Text
" NOT SUPPORTED: ^ (boxed) BEGIN: ^" forall a. Semigroup a => a -> a -> a
<> Text
inner forall a. Semigroup a => a -> a -> a
<> Text
"^ :END "
strikeout :: PandocMonad m => TikiWikiParser m B.Inlines
strikeout :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
strikeout = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Inlines -> Inlines
B.strikeout (forall b (m :: * -> *) a.
(Monoid b, PandocMonad m, Show a) =>
TikiWikiParser m a
-> (TikiWikiParser m a -> TikiWikiParser m b) -> TikiWikiParser m b
enclosed (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"--") 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 :: forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString TikiWikiParser m a
end = ParsecT Sources ParserState m Text
innerSpace forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
nonspaceChar
  where
    innerSpace :: ParsecT Sources ParserState m Text
innerSpace = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
spaceChar forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* 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 :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
breakChars = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"%%%" forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
B.linebreak
superTag :: PandocMonad m => TikiWikiParser m B.Inlines
superTag :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superTag = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Inlines
B.superscript forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( 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 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG(tag=>sup)}") (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG}") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)
superMacro :: PandocMonad m => TikiWikiParser m B.Inlines
superMacro :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
superMacro = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUP("
  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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
")}")
  String
body <- 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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUP}")
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.superscript forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body
subTag :: PandocMonad m => TikiWikiParser m B.Inlines
subTag :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subTag = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Inlines -> Inlines
B.subscript forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
B.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( 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 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG(tag=>sub)}") (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{TAG}") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)
subMacro :: PandocMonad m => TikiWikiParser m B.Inlines
subMacro :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
subMacro = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUB("
  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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
")}")
  String
body <- 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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"{SUB}")
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Inlines -> Inlines
B.subscript forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body
code :: PandocMonad m => TikiWikiParser m B.Inlines
code :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
code = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text -> Inlines
B.code forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
fromEntities) ( 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 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"-+") (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"+-") forall a (m :: * -> *).
(Show a, PandocMonad m) =>
TikiWikiParser m a -> TikiWikiParser m Text
nestedString)
macroAttr :: PandocMonad m => TikiWikiParser m (Text, Text)
macroAttr :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
macroAttr = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  String
key <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"=)")
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'='
  forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  String
value <- forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
" )\"")
  forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'"'
  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 :: forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m [(Text, Text)]
macroAttrs = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ 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 forall (m :: * -> *).
PandocMonad m =>
TikiWikiParser m (Text, Text)
macroAttr forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
noparse :: PandocMonad m => TikiWikiParser m B.Inlines
noparse :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
noparse = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~np~"
  String
body <- 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 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
anyChar (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"~/np~")
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.str forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack String
body
str :: PandocMonad m => TikiWikiParser m B.Inlines
str :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
str = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
B.str (String -> Text
T.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
alphaNum forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> 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 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 :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
symbol = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Inlines
B.str (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 forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParserT s st m Char
nonspaceChar)
notExternalLink :: PandocMonad m => TikiWikiParser m B.Inlines
notExternalLink :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
notExternalLink = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  String
start <- forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"[["
  String
body <- forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf String
"\n[]")
  String
end <- forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"]"
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Inlines
B.text forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ String
start forall a. [a] -> [a] -> [a]
++ String
body forall a. [a] -> [a] -> [a]
++ String
end
makeLink :: PandocMonad m => Text -> Text -> Text -> TikiWikiParser m B.Inlines
makeLink :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
start Text
middle Text
end = forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try forall a b. (a -> b) -> a -> b
$ do
  ParserState
st <- forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ ParserState -> Bool
stateAllowLinks ParserState
st
  forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
False }
  (Text
url, Text
title, Text
anchor) <- forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText Text
start Text
middle Text
end
  [Inlines]
parsedTitle <- forall (m :: * -> *) st r.
Monad m =>
ParserT Sources st m r -> Text -> ParserT Sources st m r
parseFromString (forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
inline) Text
title
  forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState forall a b. (a -> b) -> a -> b
$ ParserState
st{ stateAllowLinks :: Bool
stateAllowLinks = Bool
True }
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> Text -> Inlines -> Inlines
B.link (Text
url forall a. Semigroup a => a -> a -> a
<> Text
anchor) Text
"" forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Inlines]
parsedTitle
wikiLinkText :: PandocMonad m => Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText :: forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m (Text, Text, Text)
wikiLinkText Text
start Text
middle Text
end = do
  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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
many1 (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
middle forall a. [a] -> [a] -> [a]
++ String
"\n")
  Text
seg1 <- forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
url forall {u}. ParsecT Sources u m Text
linkContent
  Text
seg2 <- forall s (m :: * -> *) t a u.
Stream s m t =>
a -> ParsecT s u m a -> ParsecT s u m a
option Text
"" forall {u}. ParsecT Sources u m Text
linkContent
  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 forall a. Eq a => a -> a -> Bool
/= Text
""
    then
      forall (m :: * -> *) a. Monad m => a -> m a
return (Text
url, Text
seg2, Text
seg1)
    else
      forall (m :: * -> *) a. Monad m => a -> m a
return (Text
url, Text
seg1, Text
"")
  where
    linkContent :: ParsecT Sources u m Text
linkContent      = do
      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 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many (forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m Char
noneOf forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
middle)
externalLink :: PandocMonad m => TikiWikiParser m B.Inlines
externalLink :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
externalLink = forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
"[" Text
"]|" Text
"]"
wikiLink :: PandocMonad m => TikiWikiParser m B.Inlines
wikiLink :: forall (m :: * -> *). PandocMonad m => TikiWikiParser m Inlines
wikiLink = forall (m :: * -> *).
PandocMonad m =>
Text -> Text -> Text -> TikiWikiParser m Inlines
makeLink Text
"((" Text
")|" Text
"))"