aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Vimwiki.hs
diff options
context:
space:
mode:
authorAlexander Krotov <ilabdsf@gmail.com>2018-10-10 12:26:29 +0300
committerAlexander Krotov <ilabdsf@gmail.com>2018-10-10 12:26:29 +0300
commit8d959179f96134ee9b96fafbbd061aefbf7968cd (patch)
tree567d900c324752674474f35dc01567189d4e2308 /src/Text/Pandoc/Readers/Vimwiki.hs
parent0a7650f87b3ef9ec80e23377ced31d04c2474806 (diff)
downloadpandoc-8d959179f96134ee9b96fafbbd061aefbf7968cd.tar.gz
Vimwiki reader: get rid of F, runF and stateMeta' in favor of stateMeta
Diffstat (limited to 'src/Text/Pandoc/Readers/Vimwiki.hs')
-rw-r--r--src/Text/Pandoc/Readers/Vimwiki.hs12
1 files changed, 6 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Readers/Vimwiki.hs b/src/Text/Pandoc/Readers/Vimwiki.hs
index 15f0d991f..6fdbcb50e 100644
--- a/src/Text/Pandoc/Readers/Vimwiki.hs
+++ b/src/Text/Pandoc/Readers/Vimwiki.hs
@@ -85,12 +85,12 @@ import qualified Text.Pandoc.Builder as B (blockQuote, bulletList, code,
import Text.Pandoc.Class (PandocMonad (..))
import Text.Pandoc.Definition (Attr, Block (BulletList, OrderedList),
Inline (Space), ListNumberDelim (..),
- ListNumberStyle (..), Meta, Pandoc (..),
+ ListNumberStyle (..), Pandoc (..),
nullMeta)
import Text.Pandoc.Options (ReaderOptions)
-import Text.Pandoc.Parsing (F, ParserState, ParserT, blanklines, emailAddress,
+import Text.Pandoc.Parsing (ParserState, ParserT, blanklines, emailAddress,
many1Till, orderedListMarker, readWithM,
- registerHeader, runF, spaceChar, stateMeta',
+ registerHeader, spaceChar, stateMeta,
stateOptions, uri)
import Text.Pandoc.Shared (crFilter, splitBy, stringify, stripFirstAndLast)
import Text.Parsec.Char (alphaNum, anyChar, char, newline, noneOf, oneOf, space,
@@ -126,7 +126,7 @@ parseVimwiki = do
spaces
eof
st <- getState
- let meta = runF (stateMeta' st) st
+ let meta = stateMeta st
return $ Pandoc meta (toList bs)
-- block parser
@@ -444,8 +444,8 @@ ph s = try $ do
many spaceChar >>string ('%':s) >> spaceChar
contents <- trimInlines . mconcat <$> manyTill inline (lookAhead newline)
--use lookAhead because of placeholder in the whitespace parser
- let meta' = return $ B.setMeta s contents nullMeta :: F Meta
- updateState $ \st -> st { stateMeta' = stateMeta' st <> meta' }
+ let meta' = B.setMeta s contents nullMeta
+ updateState $ \st -> st { stateMeta = stateMeta st <> meta' }
noHtmlPh :: PandocMonad m => VwParser m ()
noHtmlPh = try $