aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-06-01 15:09:38 +0200
committerJohn MacFarlane <jgm@berkeley.edu>2017-06-01 15:09:38 +0200
commit0cf6511f16388fc2bb71cffc733a704d20cfe3e3 (patch)
tree9672ee8b1eacbe95101210d919c185545e140fcc
parentc00471ca0d7a437ab25e0c425b88c48b1236801f (diff)
downloadpandoc-0cf6511f16388fc2bb71cffc733a704d20cfe3e3.tar.gz
Some hlint refactoring.
-rw-r--r--pandoc.hs6
-rw-r--r--src/Text/Pandoc/App.hs37
-rw-r--r--src/Text/Pandoc/Class.hs29
3 files changed, 34 insertions, 38 deletions
diff --git a/pandoc.hs b/pandoc.hs
index 6135aec03..970fc8778 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE CPP #-}
-{-# LANGUAGE PatternGuards #-}
+
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-
@@ -33,9 +33,9 @@ Parses command-line options and calls the appropriate readers and
writers.
-}
module Main where
-import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions)
-import Text.Pandoc.Error (handleError, PandocError)
import qualified Control.Exception as E
+import Text.Pandoc.App (convertWithOpts, defaultOpts, options, parseOptions)
+import Text.Pandoc.Error (PandocError, handleError)
main :: IO ()
main = E.catch (parseOptions options defaultOpts >>= convertWithOpts)
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index bc1d4ce18..58044860b 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE CPP #-}
+{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE DeriveGeneric #-}
{-
Copyright (C) 2006-2017 John MacFarlane <jgm@berkeley.edu>
@@ -40,47 +40,47 @@ module Text.Pandoc.App (
) where
import Control.Applicative ((<|>))
import qualified Control.Exception as E
-import Control.Monad.Except (throwError)
import Control.Monad
+import Control.Monad.Except (throwError)
import Control.Monad.Trans
-import Data.Aeson (eitherDecode', encode, ToJSON(..), FromJSON(..),
- genericToEncoding, defaultOptions)
+import Data.Aeson (FromJSON (..), ToJSON (..), defaultOptions, eitherDecode',
+ encode, genericToEncoding)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as B
import Data.Char (toLower, toUpper)
-import qualified Data.Set as Set
import Data.Foldable (foldrM)
-import GHC.Generics
import Data.List (intercalate, isPrefixOf, isSuffixOf, sort)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, isNothing)
+import qualified Data.Set as Set
import qualified Data.Text as T
import Data.Yaml (decode)
import qualified Data.Yaml as Yaml
+import GHC.Generics
import Network.URI (URI (..), parseURI)
import Paths_pandoc (getDataDir)
import Skylighting (Style, Syntax (..), defaultSyntaxMap, parseTheme)
-import Skylighting.Parser (missingIncludes, parseSyntaxDefinition,
- addSyntaxDefinition)
+import Skylighting.Parser (addSyntaxDefinition, missingIncludes,
+ parseSyntaxDefinition)
import System.Console.GetOpt
import System.Directory (Permissions (..), doesFileExist, findExecutable,
getAppUserDataDirectory, getPermissions)
import System.Environment (getArgs, getEnvironment, getProgName)
import System.Exit (ExitCode (..), exitSuccess)
import System.FilePath
-import System.IO (stdout, nativeNewline)
-import qualified System.IO as IO (Newline(..))
+import System.IO (nativeNewline, stdout)
+import qualified System.IO as IO (Newline (..))
import System.IO.Error (isDoesNotExistError)
import Text.Pandoc
import Text.Pandoc.Builder (setMeta)
-import Text.Pandoc.Class (PandocIO, getLog, withMediaBag,
- extractMedia, fillMediaBag, setResourcePath)
+import Text.Pandoc.Class (PandocIO, extractMedia, fillMediaBag, getLog,
+ setResourcePath, withMediaBag)
import Text.Pandoc.Highlighting (highlightingStyles)
-import Text.Pandoc.Lua ( runLuaFilter )
+import Text.Pandoc.Lua (runLuaFilter)
import Text.Pandoc.PDF (makePDF)
import Text.Pandoc.Process (pipeProcess)
-import Text.Pandoc.SelfContained (makeSelfContained, makeDataURI)
-import Text.Pandoc.Shared (isURI, headerShift, openURL, readDataFile,
+import Text.Pandoc.SelfContained (makeDataURI, makeSelfContained)
+import Text.Pandoc.Shared (headerShift, isURI, openURL, readDataFile,
readDataFileUTF8, safeRead, tabFilter)
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.XML (toEntities)
@@ -243,10 +243,9 @@ convertWithOpts opts = do
withList f (x:xs) vars = f x vars >>= withList f xs
variables <-
- return (("outputfile", optOutputFile opts) : optVariables opts)
- >>=
+
withList (addStringAsVariable "sourcefile")
- (reverse $ optInputFiles opts)
+ (reverse $ optInputFiles opts) (("outputfile", optOutputFile opts) : optVariables opts)
-- we reverse this list because, unlike
-- the other option lists here, it is
-- not reversed when parsed from CLI arguments.
@@ -796,7 +795,7 @@ readURI :: FilePath -> PandocIO String
readURI src = do
res <- liftIO $ openURL src
case res of
- Left e -> throwError $ PandocHttpError src e
+ Left e -> throwError $ PandocHttpError src e
Right (contents, _) -> return $ UTF8.toString contents
readFile' :: MonadIO m => FilePath -> m B.ByteString
diff --git a/src/Text/Pandoc/Class.hs b/src/Text/Pandoc/Class.hs
index f47efb2aa..49b20bd30 100644
--- a/src/Text/Pandoc/Class.hs
+++ b/src/Text/Pandoc/Class.hs
@@ -1,10 +1,8 @@
{-# LANGUAGE DeriveFunctor #-}
-{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE StandaloneDeriving #-}
{-
Copyright (C) 2016 Jesse Rosenthal <jrosenthal@jhu.edu>
@@ -156,7 +154,7 @@ report :: PandocMonad m => LogMessage -> m ()
report msg = do
verbosity <- getsCommonState stVerbosity
let level = messageVerbosity msg
- when (level <= verbosity) $ do
+ when (level <= verbosity) $
logOutput msg
unless (level == DEBUG) $
modifyCommonState $ \st -> st{ stLog = msg : stLog st }
@@ -224,7 +222,7 @@ runIO :: PandocIO a -> IO (Either PandocError a)
runIO ma = flip evalStateT def $ runExceptT $ unPandocIO ma
withMediaBag :: PandocMonad m => m a -> m (a, MediaBag)
-withMediaBag ma = ((,)) <$> ma <*> getMediaBag
+withMediaBag ma = (,) <$> ma <*> getMediaBag
runIOorExplode :: PandocIO a -> IO a
runIOorExplode ma = runIO ma >>= handleError
@@ -250,7 +248,7 @@ instance PandocMonad PandocIO where
getCurrentTime = liftIO IO.getCurrentTime
getCurrentTimeZone = liftIO IO.getCurrentTimeZone
newStdGen = liftIO IO.newStdGen
- newUniqueHash = hashUnique <$> (liftIO IO.newUnique)
+ newUniqueHash = hashUnique <$> liftIO IO.newUnique
openURL u = do
report $ Fetching u
res <- liftIO (IO.openURL u)
@@ -266,7 +264,7 @@ instance PandocMonad PandocIO where
putCommonState x = PandocIO $ lift $ put x
logOutput msg = liftIO $ do
UTF8.hPutStr stderr $ "[" ++
- (map toLower $ show (messageVerbosity msg)) ++ "] "
+ map toLower (show (messageVerbosity msg)) ++ "] "
alertIndent $ lines $ showLogMessage msg
alertIndent :: [String] -> IO ()
@@ -297,14 +295,14 @@ fetchItem :: PandocMonad m
fetchItem sourceURL s = do
mediabag <- getMediaBag
case lookupMedia s mediabag of
- Just (mime, bs) -> return $ (BL.toStrict bs, Just mime)
+ Just (mime, bs) -> return (BL.toStrict bs, Just mime)
Nothing -> downloadOrRead sourceURL s
downloadOrRead :: PandocMonad m
=> Maybe String
-> String
-> m (B.ByteString, Maybe MimeType)
-downloadOrRead sourceURL s = do
+downloadOrRead sourceURL s =
case (sourceURL >>= parseURIReference' .
ensureEscaped, ensureEscaped s) of
(Just u, s') -> -- try fetching from relative path at source
@@ -367,7 +365,7 @@ fillMediaBag sourceURL d = walkM handleImage d
let fname = basename <.> ext
insertMedia fname mt bs'
return $ Image attr lab (fname, tit))
- (\e -> do
+ (\e ->
case e of
PandocResourceNotFound _ -> do
report $ CouldNotFetchResource src
@@ -434,7 +432,7 @@ instance Default PureState where
getPureState :: PandocPure PureState
-getPureState = PandocPure $ lift $ lift $ get
+getPureState = PandocPure $ lift $ lift get
getsPureState :: (PureState -> a) -> PandocPure a
getsPureState f = f <$> getPureState
@@ -505,16 +503,16 @@ instance PandocMonad PandocPure where
case infoFileContents <$> getFileInfo fp fps of
Just bs -> return bs
Nothing -> throwError $ PandocResourceNotFound fp
- readDataFile Nothing "reference.docx" = do
+ readDataFile Nothing "reference.docx" =
(B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceDocx
- readDataFile Nothing "reference.odt" = do
+ readDataFile Nothing "reference.odt" =
(B.concat . BL.toChunks . fromArchive) <$> getsPureState stReferenceODT
readDataFile Nothing fname = do
let fname' = if fname == "MANUAL.txt" then fname else "data" </> fname
readFileStrict fname'
readDataFile (Just userDir) fname = do
userDirFiles <- getsPureState stUserDataDir
- case infoFileContents <$> (getFileInfo (userDir </> fname) userDirFiles) of
+ case infoFileContents <$> getFileInfo (userDir </> fname) userDirFiles of
Just bs -> return bs
Nothing -> readDataFile Nothing fname
@@ -524,12 +522,12 @@ instance PandocMonad PandocPure where
getModificationTime fp = do
fps <- getsPureState stFiles
- case infoFileMTime <$> (getFileInfo fp fps) of
+ case infoFileMTime <$> getFileInfo fp fps of
Just tm -> return tm
Nothing -> throwError $ PandocIOError fp
(userError "Can't get modification time")
- getCommonState = PandocPure $ lift $ get
+ getCommonState = PandocPure $ lift get
putCommonState x = PandocPure $ lift $ put x
logOutput _msg = return ()
@@ -613,4 +611,3 @@ instance PandocMonad m => PandocMonad (StateT st m) where
getCommonState = lift getCommonState
putCommonState = lift . putCommonState
logOutput = lift . logOutput
-