diff options
author | Albert Krewinkel <albert@zeitkraut.de> | 2017-06-03 12:28:52 +0200 |
---|---|---|
committer | Albert Krewinkel <albert@zeitkraut.de> | 2017-06-03 13:35:19 +0200 |
commit | 55d679e382954dd458acd6233609851748522d99 (patch) | |
tree | 4ed5996a1fed938b85c27e7b3671da6e52491c3e /src/Text/Pandoc/Readers | |
parent | d55f01c65f0a149b0951d4350293622385cceae9 (diff) | |
download | pandoc-55d679e382954dd458acd6233609851748522d99.tar.gz |
Improve code style in lua and org modules
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/DocumentTree.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Inlines.hs | 13 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Meta.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 19 |
5 files changed, 24 insertions, 26 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index f669abc27..3e0ab0127 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -351,7 +351,7 @@ switchesAsAttributes = try $ do Just num -> ("startFrom", num):kv Nothing -> kv cls' = case pol of - SwitchPlus -> "continuedSourceBlock":cls + SwitchPlus -> "continuedSourceBlock":cls SwitchMinus -> cls in ("numberLines":cls', kv') addToAttr _ x = x diff --git a/src/Text/Pandoc/Readers/Org/DocumentTree.hs b/src/Text/Pandoc/Readers/Org/DocumentTree.hs index cee740e30..743f6cc0e 100644 --- a/src/Text/Pandoc/Readers/Org/DocumentTree.hs +++ b/src/Text/Pandoc/Readers/Org/DocumentTree.hs @@ -35,14 +35,14 @@ module Text.Pandoc.Readers.Org.DocumentTree import Control.Arrow ((***)) import Control.Monad (guard, void) import Data.Char (toLower, toUpper) -import Data.List ( intersperse ) +import Data.List (intersperse) import Data.Monoid ((<>)) import Text.Pandoc.Builder (Blocks, Inlines) import Text.Pandoc.Class (PandocMonad) import Text.Pandoc.Definition import Text.Pandoc.Readers.Org.BlockStarts -import Text.Pandoc.Readers.Org.Parsing import Text.Pandoc.Readers.Org.ParserState +import Text.Pandoc.Readers.Org.Parsing import qualified Data.Map as Map import qualified Text.Pandoc.Builder as B @@ -78,7 +78,7 @@ documentTree blocks inline = do getTitle metamap = case Map.lookup "title" metamap of Just (MetaInlines inlns) -> inlns - _ -> [] + _ -> [] newtype Tag = Tag { fromTag :: String } deriving (Show, Eq) diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs index af28701d7..66273e05d 100644 --- a/src/Text/Pandoc/Readers/Org/Inlines.hs +++ b/src/Text/Pandoc/Readers/Org/Inlines.hs @@ -343,11 +343,10 @@ orgRefCiteKey = let citeKeySpecialChars = "-_:\\./," :: String isCiteKeySpecialChar c = c `elem` citeKeySpecialChars isCiteKeyChar c = isAlphaNum c || isCiteKeySpecialChar c - - in try $ many1Till (satisfy isCiteKeyChar) - $ try . lookAhead $ do - many . satisfy $ isCiteKeySpecialChar - satisfy $ not . isCiteKeyChar + endOfCitation = try $ do + many $ satisfy isCiteKeySpecialChar + satisfy $ not . isCiteKeyChar + in try $ satisfy isCiteKeyChar `many1Till` lookAhead endOfCitation -- | Supported citation types. Only a small subset of org-ref types is @@ -415,7 +414,7 @@ referencedNote = try $ do return $ do notes <- asksF orgStateNotes' case lookup ref notes of - Nothing -> return $ B.str $ "[" ++ ref ++ "]" + Nothing -> return . B.str $ "[" ++ ref ++ "]" Just contents -> do st <- askF let contents' = runF contents st{ orgStateNotes' = [] } @@ -439,7 +438,7 @@ explicitOrImageLink = try $ do src <- srcF case cleanLinkString title of Just imgSrc | isImageFilename imgSrc -> - pure $ B.link src "" $ B.image imgSrc mempty mempty + pure . B.link src "" $ B.image imgSrc mempty mempty _ -> linkToInlinesF src =<< title' diff --git a/src/Text/Pandoc/Readers/Org/Meta.hs b/src/Text/Pandoc/Readers/Org/Meta.hs index a87042871..d22902eae 100644 --- a/src/Text/Pandoc/Readers/Org/Meta.hs +++ b/src/Text/Pandoc/Readers/Org/Meta.hs @@ -75,9 +75,9 @@ declarationLine :: PandocMonad m => OrgParser m () declarationLine = try $ do key <- map toLower <$> metaKey (key', value) <- metaValue key - when (key' /= "results") $ - updateState $ \st -> - st { orgStateMeta = B.setMeta key' <$> value <*> orgStateMeta st } + let addMetaValue st = + st { orgStateMeta = B.setMeta key' <$> value <*> orgStateMeta st } + when (key' /= "results") $ updateState addMetaValue metaKey :: Monad m => OrgParser m String metaKey = map toLower <$> many1 (noneOf ": \n\r") @@ -236,8 +236,8 @@ macroDefinition = try $ do expansionPart = try $ many (notFollowedBy placeholder *> noneOf "\n\r") alternate :: [a] -> [a] -> [a] - alternate [] ys = ys - alternate xs [] = xs + alternate [] ys = ys + alternate xs [] = xs alternate (x:xs) (y:ys) = x : y : alternate xs ys reorder :: [Int] -> [String] -> [String] diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 6a78ce276..92f868516 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} {- Copyright (C) 2014-2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -60,15 +60,14 @@ import qualified Data.Set as Set import Text.Pandoc.Builder (Blocks, Inlines) import Text.Pandoc.Definition (Meta (..), nullMeta) -import Text.Pandoc.Options (ReaderOptions (..)) import Text.Pandoc.Logging -import Text.Pandoc.Parsing (HasHeaderMap (..), HasIdentifierList (..), - HasLogMessages (..), - HasLastStrPosition (..), HasQuoteContext (..), - HasReaderOptions (..), HasIncludeFiles (..), - ParserContext (..), - QuoteContext (..), SourcePos, Future, - askF, asksF, returnF, runF, trimInlinesF) +import Text.Pandoc.Options (ReaderOptions (..)) +import Text.Pandoc.Parsing (Future, HasHeaderMap (..), HasIdentifierList (..), + HasIncludeFiles (..), HasLastStrPosition (..), + HasLogMessages (..), HasQuoteContext (..), + HasReaderOptions (..), ParserContext (..), + QuoteContext (..), SourcePos, askF, asksF, returnF, + runF, trimInlinesF) -- | This is used to delay evaluation until all relevant information has been -- parsed and made available in the parser state. |