aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorAlbert Krewinkel <albert@zeitkraut.de>2017-06-03 12:28:52 +0200
committerAlbert Krewinkel <albert@zeitkraut.de>2017-06-03 13:35:19 +0200
commit55d679e382954dd458acd6233609851748522d99 (patch)
tree4ed5996a1fed938b85c27e7b3671da6e52491c3e /src/Text/Pandoc
parentd55f01c65f0a149b0951d4350293622385cceae9 (diff)
downloadpandoc-55d679e382954dd458acd6233609851748522d99.tar.gz
Improve code style in lua and org modules
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Lua.hs18
-rw-r--r--src/Text/Pandoc/Lua/Compat.hs4
-rw-r--r--src/Text/Pandoc/Lua/PandocModule.hs26
-rw-r--r--src/Text/Pandoc/Lua/SharedInstances.hs12
-rw-r--r--src/Text/Pandoc/Lua/StackInstances.hs12
-rw-r--r--src/Text/Pandoc/Lua/Util.hs6
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/DocumentTree.hs6
-rw-r--r--src/Text/Pandoc/Readers/Org/Inlines.hs13
-rw-r--r--src/Text/Pandoc/Readers/Org/Meta.hs10
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs19
-rw-r--r--src/Text/Pandoc/Writers/Org.hs30
12 files changed, 75 insertions, 83 deletions
diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs
index f4a22b92a..f74c0e425 100644
--- a/src/Text/Pandoc/Lua.hs
+++ b/src/Text/Pandoc/Lua.hs
@@ -15,8 +15,8 @@ You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{- |
Module : Text.Pandoc.Lua
@@ -30,12 +30,12 @@ Pandoc lua utils.
-}
module Text.Pandoc.Lua ( runLuaFilter, pushPandocModule ) where
-import Control.Monad ( (>=>), when )
-import Control.Monad.Trans ( MonadIO(..) )
-import Data.Map ( Map )
-import Scripting.Lua ( LuaState, StackValue(..) )
+import Control.Monad (unless, when, (>=>))
+import Control.Monad.Trans (MonadIO (..))
+import Data.Map (Map)
+import Scripting.Lua (LuaState, StackValue (..))
import Text.Pandoc.Definition
-import Text.Pandoc.Lua.PandocModule ( pushPandocModule )
+import Text.Pandoc.Lua.PandocModule (pushPandocModule)
import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Walk
@@ -80,7 +80,7 @@ pushGlobalFilter lua =
*> Lua.rawseti lua (-2) 1
runAll :: [LuaFilter] -> Pandoc -> IO Pandoc
-runAll [] = return
+runAll [] = return
runAll (x:xs) = walkMWithLuaFilter x >=> runAll xs
walkMWithLuaFilter :: LuaFilter -> Pandoc -> IO Pandoc
@@ -225,7 +225,7 @@ instance StackValue LuaFilterFunction where
push lua v = pushFilterFunction lua v
peek lua i = do
isFn <- Lua.isfunction lua i
- when (not isFn) (error $ "Not a function at index " ++ (show i))
+ unless isFn (error $ "Not a function at index " ++ (show i))
Lua.pushvalue lua i
push lua ("PANDOC_FILTER_FUNCTIONS"::String)
Lua.rawget lua Lua.registryindex
diff --git a/src/Text/Pandoc/Lua/Compat.hs b/src/Text/Pandoc/Lua/Compat.hs
index 998d8d032..3fc81a15c 100644
--- a/src/Text/Pandoc/Lua/Compat.hs
+++ b/src/Text/Pandoc/Lua/Compat.hs
@@ -28,13 +28,13 @@ Compatibility helpers for hslua
-}
module Text.Pandoc.Lua.Compat ( loadstring ) where
-import Scripting.Lua ( LuaState )
+import Scripting.Lua (LuaState)
import qualified Scripting.Lua as Lua
-- | Interpret string as lua code and load into the lua environment.
loadstring :: LuaState -> String -> String -> IO Int
#if MIN_VERSION_hslua(0,5,0)
-loadstring lua script _ = Lua.loadstring lua script
+loadstring lua script _ = Lua.loadstring lua script
#else
loadstring lua script cn = Lua.loadstring lua script cn
#endif
diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs
index 15f19f024..8e0f3a5b4 100644
--- a/src/Text/Pandoc/Lua/PandocModule.hs
+++ b/src/Text/Pandoc/Lua/PandocModule.hs
@@ -27,25 +27,23 @@ Pandoc module for lua.
-}
module Text.Pandoc.Lua.PandocModule ( pushPandocModule ) where
-import Data.ByteString.Char8 ( unpack )
-import Data.Default ( Default(..) )
-import Scripting.Lua ( LuaState, call, push, pushhsfunction, rawset)
-import Text.Pandoc.Class hiding ( readDataFile )
-import Text.Pandoc.Definition ( Pandoc )
-import Text.Pandoc.Lua.Compat ( loadstring )
+import Control.Monad (unless)
+import Data.ByteString.Char8 (unpack)
+import Data.Default (Default (..))
+import Scripting.Lua (LuaState, call, push, pushhsfunction, rawset)
+import Text.Pandoc.Class hiding (readDataFile)
+import Text.Pandoc.Definition (Pandoc)
+import Text.Pandoc.Lua.Compat (loadstring)
import Text.Pandoc.Lua.StackInstances ()
-import Text.Pandoc.Readers ( Reader(..), getReader )
-import Text.Pandoc.Shared ( readDataFile )
+import Text.Pandoc.Readers (Reader (..), getReader)
+import Text.Pandoc.Shared (readDataFile)
-- | Push the "pandoc" on the lua stack.
pushPandocModule :: LuaState -> IO ()
pushPandocModule lua = do
script <- pandocModuleScript
status <- loadstring lua script "pandoc.lua"
- if (status /= 0)
- then return ()
- else do
- call lua 0 1
+ unless (status /= 0) $ call lua 0 1
push lua "__read"
pushhsfunction lua read_doc
rawset lua (-3)
@@ -57,13 +55,13 @@ pandocModuleScript = unpack <$> readDataFile Nothing "pandoc.lua"
read_doc :: String -> String -> IO (Either String Pandoc)
read_doc formatSpec content = do
case getReader formatSpec of
- Left s -> return $ Left s
+ Left s -> return $ Left s
Right reader ->
case reader of
StringReader r -> do
res <- runIO $ r def content
case res of
- Left s -> return . Left $ show s
+ Left s -> return . Left $ show s
Right pd -> return $ Right pd
_ -> return $ Left "Only string formats are supported at the moment."
diff --git a/src/Text/Pandoc/Lua/SharedInstances.hs b/src/Text/Pandoc/Lua/SharedInstances.hs
index 019a82446..a5d4ba1e9 100644
--- a/src/Text/Pandoc/Lua/SharedInstances.hs
+++ b/src/Text/Pandoc/Lua/SharedInstances.hs
@@ -16,9 +16,9 @@ You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
-{-# LANGUAGE CPP #-}
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE LambdaCase #-}
#if !MIN_VERSION_base(4,8,0)
{-# LANGUAGE OverlappingInstances #-}
#endif
@@ -36,8 +36,8 @@ Shared StackValue instances for pandoc and generic types.
-}
module Text.Pandoc.Lua.SharedInstances () where
-import Scripting.Lua ( LTYPE(..), StackValue(..), newtable )
-import Text.Pandoc.Lua.Util ( addRawInt, addValue, getRawInt, keyValuePairs )
+import Scripting.Lua (LTYPE (..), StackValue (..), newtable)
+import Text.Pandoc.Lua.Util (addRawInt, addValue, getRawInt, keyValuePairs)
import qualified Data.Map as M
import qualified Text.Pandoc.UTF8 as UTF8
@@ -112,5 +112,5 @@ instance (StackValue a, StackValue b) => StackValue (Either a b) where
peek lua idx = peek lua idx >>= \case
Just left -> return . Just $ Left left
Nothing -> fmap Right <$> peek lua idx
- valuetype (Left x) = valuetype x
+ valuetype (Left x) = valuetype x
valuetype (Right x) = valuetype x
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index cfc4389c2..d2e3f630a 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -17,7 +17,7 @@ along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
-}
{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
Module : Text.Pandoc.Lua.StackInstances
@@ -32,13 +32,13 @@ StackValue instances for pandoc types.
-}
module Text.Pandoc.Lua.StackInstances () where
-import Control.Applicative ( (<|>) )
-import Scripting.Lua
- ( LTYPE(..), LuaState, StackValue(..), ltype, newtable, objlen )
+import Control.Applicative ((<|>))
+import Scripting.Lua (LTYPE (..), LuaState, StackValue (..), ltype, newtable,
+ objlen)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.SharedInstances ()
-import Text.Pandoc.Lua.Util ( addValue, getTable, pushViaConstructor )
-import Text.Pandoc.Shared ( safeRead )
+import Text.Pandoc.Lua.Util (addValue, getTable, pushViaConstructor)
+import Text.Pandoc.Shared (safeRead)
instance StackValue Pandoc where
push lua (Pandoc meta blocks) = do
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index ff07ba7d7..0a704d027 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -42,10 +42,8 @@ module Text.Pandoc.Lua.Util
, pushViaConstructor
) where
-import Scripting.Lua
- ( LuaState, StackValue(..)
- , call, getglobal2, gettable, next, pop, pushnil, rawgeti, rawseti, settable
- )
+import Scripting.Lua (LuaState, StackValue (..), call, getglobal2, gettable,
+ next, pop, pushnil, rawgeti, rawseti, settable)
-- | Adjust the stack index, assuming that @n@ new elements have been pushed on
-- the stack.
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.
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index ef60e2f6c..78c102db6 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -34,7 +34,7 @@ Conversion of 'Pandoc' documents to Emacs Org-Mode.
Org-Mode: <http://orgmode.org>
-}
-module Text.Pandoc.Writers.Org ( writeOrg) where
+module Text.Pandoc.Writers.Org (writeOrg) where
import Control.Monad.State
import Data.Char (isAlphaNum, toLower)
import Data.List (intersect, intersperse, isPrefixOf, partition, transpose)
@@ -77,9 +77,9 @@ pandocToOrg (Pandoc meta blocks) = do
body <- blockListToOrg blocks
notes <- gets (reverse . stNotes) >>= notesToOrg
hasMath <- gets stHasMath
- let main = render colwidth $ foldl ($+$) empty $ [body, notes]
+ let main = render colwidth . foldl ($+$) empty $ [body, notes]
let context = defField "body" main
- $ defField "math" hasMath
+ . defField "math" hasMath
$ metadata
case writerTemplate opts of
Nothing -> return main
@@ -88,8 +88,7 @@ pandocToOrg (Pandoc meta blocks) = do
-- | Return Org representation of notes.
notesToOrg :: PandocMonad m => [[Block]] -> Org m Doc
notesToOrg notes =
- mapM (\(num, note) -> noteToOrg num note) (zip [1..] notes) >>=
- return . vsep
+ vsep <$> zipWithM noteToOrg [1..] notes
-- | Return Org representation of a note.
noteToOrg :: PandocMonad m => Int -> [Block] -> Org m Doc
@@ -221,16 +220,16 @@ blockToOrg (Table caption' _ _ headers rows) = do
-- FIXME: Org doesn't allow blocks with height more than 1.
let hpipeBlocks blocks = hcat [beg, middle, end]
where h = maximum (1 : map height blocks)
- sep' = lblock 3 $ vcat (map text $ replicate h " | ")
- beg = lblock 2 $ vcat (map text $ replicate h "| ")
- end = lblock 2 $ vcat (map text $ replicate h " |")
+ sep' = lblock 3 $ vcat (replicate h (text " | "))
+ beg = lblock 2 $ vcat (replicate h (text "| "))
+ end = lblock 2 $ vcat (replicate h (text " |"))
middle = hcat $ intersperse sep' blocks
let makeRow = hpipeBlocks . zipWith lblock widthsInChars
let head' = makeRow headers'
rows' <- mapM (\row -> do cols <- mapM blockListToOrg row
return $ makeRow cols) rows
let border ch = char '|' <> char ch <>
- (hcat $ intersperse (char ch <> char '+' <> char ch) $
+ (hcat . intersperse (char ch <> char '+' <> char ch) $
map (\l -> text $ replicate l ch) widthsInChars) <>
char ch <> char '|'
let body = vcat rows'
@@ -251,8 +250,7 @@ blockToOrg (OrderedList (start, _, delim) items) = do
let maxMarkerLength = maximum $ map length markers
let markers' = map (\m -> let s = maxMarkerLength - length m
in m ++ replicate s ' ') markers
- contents <- mapM (\(item, num) -> orderedListItemToOrg item num) $
- zip markers' items
+ contents <- zipWithM orderedListItemToOrg markers' items
-- ensure that sublists have preceding blank line
return $ blankline $$ vcat contents $$ blankline
blockToOrg (DefinitionList items) = do
@@ -279,8 +277,8 @@ definitionListItemToOrg :: PandocMonad m
=> ([Inline], [[Block]]) -> Org m Doc
definitionListItemToOrg (label, defs) = do
label' <- inlineListToOrg label
- contents <- liftM vcat $ mapM blockListToOrg defs
- return $ hang 2 "- " $ label' <> " :: " <> (contents <> cr)
+ contents <- vcat <$> mapM blockListToOrg defs
+ return . hang 2 "- " $ label' <> " :: " <> (contents <> cr)
-- | Convert list of key/value pairs to Org :PROPERTIES: drawer.
propertiesDrawer :: Attr -> Doc
@@ -312,13 +310,13 @@ attrHtml (ident, classes, kvs) =
blockListToOrg :: PandocMonad m
=> [Block] -- ^ List of block elements
-> Org m Doc
-blockListToOrg blocks = mapM blockToOrg blocks >>= return . vcat
+blockListToOrg blocks = vcat <$> mapM blockToOrg blocks
-- | Convert list of Pandoc inline elements to Org.
inlineListToOrg :: PandocMonad m
=> [Inline]
-> Org m Doc
-inlineListToOrg lst = mapM inlineToOrg lst >>= return . hcat
+inlineListToOrg lst = hcat <$> mapM inlineToOrg lst
-- | Convert Pandoc inline element to Org.
inlineToOrg :: PandocMonad m => Inline -> Org m Doc
@@ -350,7 +348,7 @@ inlineToOrg (Quoted DoubleQuote lst) = do
return $ "\"" <> contents <> "\""
inlineToOrg (Cite _ lst) = inlineListToOrg lst
inlineToOrg (Code _ str) = return $ "=" <> text str <> "="
-inlineToOrg (Str str) = return $ text $ escapeString str
+inlineToOrg (Str str) = return . text $ escapeString str
inlineToOrg (Math t str) = do
modify $ \st -> st{ stHasMath = True }
return $ if t == InlineMath