Skip to content

Commit d2c577b

Browse files
committed
Formatting using ormolu 0.7
1 parent 825c633 commit d2c577b

26 files changed

+378
-327
lines changed

executable/Main.hs

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -61,11 +61,11 @@ import Text.Pandoc.Filter.Plot.Internal
6161
cls,
6262
configurationPathMeta,
6363
executable,
64+
pathToExe,
6465
readDoc,
6566
runPlotM,
6667
supportedSaveFormats,
67-
toolkits,
68-
pathToExe
68+
toolkits,
6969
)
7070
import Text.Pandoc.JSON (toJSONFilter)
7171
import Text.ParserCombinators.ReadP (readP_to_S)
@@ -105,10 +105,12 @@ main = do
105105
]
106106
)
107107
<> header (mconcat ["pandoc-plot ", V.showVersion pandocPlotVersion, " - generate figures directly in documents"])
108-
<> footerDoc ( Just $ P.vsep
109-
[ "More information can be found via the manual (pandoc-plot --manual) or the"
110-
, "repository README, located at https://github.com/LaurentRDC/pandoc-plot"
111-
]
108+
<> footerDoc
109+
( Just $
110+
P.vsep
111+
[ "More information can be found via the manual (pandoc-plot --manual) or the",
112+
"repository README, located at https://github.com/LaurentRDC/pandoc-plot"
113+
]
112114
)
113115
)
114116

src/Text/Pandoc/Filter/Plot.hs

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@
2222
--
2323
-- @
2424
-- This is a paragraph.
25-
--
25+
--
2626
-- ```{.matlabplot}
2727
-- figure()
2828
-- plot([1,2,3,4,5], [1,2,3,4,5], '-k')
@@ -34,7 +34,7 @@
3434
-- @
3535
-- ```{.gnuplot format=png caption="Sinusoidal function" source=true}
3636
-- sin(x)
37-
--
37+
--
3838
-- set xlabel "x"
3939
-- set ylabel "y"
4040
-- ```
@@ -63,8 +63,7 @@
6363
-- code block will be ignored. This path should be specified with respect to the current working
6464
-- directory, and not with respect to the document.
6565
--
66-
-- All attributes are described in the online documentation, linked on the home page.
67-
66+
-- All attributes are described in the online documentation, linked on the home page.
6867
module Text.Pandoc.Filter.Plot
6968
( -- * Operating on whole Pandoc documents
7069
plotFilter,
@@ -106,7 +105,7 @@ import Data.Map (singleton)
106105
import Data.Text (Text, pack, unpack)
107106
import Data.Version (Version)
108107
import Paths_pandoc_plot (version)
109-
import Text.Pandoc.Definition (Block, Meta (..), Format, MetaValue (..), Pandoc (..))
108+
import Text.Pandoc.Definition (Block, Format, Meta (..), MetaValue (..), Pandoc (..))
110109
import Text.Pandoc.Filter.Plot.Internal
111110
( Configuration (..),
112111
FigureSpec,
@@ -175,19 +174,20 @@ plotFilter conf mfmt (Pandoc meta blocks) = do
175174
-- on documents without having all necessary toolkits installed. In this case, error
176175
-- messages are printed to stderr, and blocks are left unchanged.
177176
--
178-
-- __Note that this function is DEPRECATED in favour of @plotFilter@. It will be
177+
-- __Note that this function is DEPRECATED in favour of @plotFilter@. It will be
179178
-- removed in the next major update (v2+).__
180179
plotTransform ::
181180
-- | Configuration for default values
182181
Configuration ->
183182
-- | Input document
184183
Pandoc ->
185184
IO Pandoc
186-
{-# DEPRECATED plotTransform
187-
[ "plotTransform has been deprecated in favour of plotFilter, which is aware of conversion format."
188-
, "plotTransform will be removed in an upcoming major update."
189-
]
190-
#-}
185+
{-# DEPRECATED
186+
plotTransform
187+
[ "plotTransform has been deprecated in favour of plotFilter, which is aware of conversion format.",
188+
"plotTransform will be removed in an upcoming major update."
189+
]
190+
#-}
191191
plotTransform conf = plotFilter conf Nothing
192192

193193
-- | The version of the pandoc-plot package.
@@ -197,7 +197,7 @@ pandocPlotVersion :: Version
197197
pandocPlotVersion = version
198198

199199
-- | Try to process the block with `pandoc-plot`. If a failure happens (or the block)
200-
-- was not meant to become a figure, return the block as-is unless running in strict mode.
200+
-- was not meant to become a figure, return the block as-is unless running in strict mode.
201201
-- In strict mode, any failure (for example, due to a missing plotting toolkit) will halt execution.
202202
--
203203
-- New in version 1.2.0: this function will detect nested code blocks, for example in @Div@ blocks.
@@ -208,7 +208,7 @@ make = walkM $ \blk -> either (onError blk) return =<< makeEither blk
208208
onError b e = do
209209
whenStrict $ throwStrictError (pack . show $ e)
210210
return b
211-
211+
212212
whenStrict f = asksConfig strictMode >>= \s -> when s f
213213

214214
-- | Try to process the block with `pandoc-plot`, documenting the error.
@@ -239,4 +239,4 @@ instance Show PandocPlotError where
239239
show (ScriptRuntimeError _ exitcode) = "ERROR (pandoc-plot) The script failed with exit code " <> show exitcode <> "."
240240
show (ScriptChecksFailedError msg) = "ERROR (pandoc-plot) A script check failed with message: " <> unpack msg <> "."
241241
show (ToolkitNotInstalledError tk) = "ERROR (pandoc-plot) The " <> show tk <> " toolkit is required but not installed."
242-
show (IncompatibleSaveFormatError tk sv) = "ERROR (pandoc-plot) Save format " <> show sv <> " not supported by the " <> show tk <> " toolkit."
242+
show (IncompatibleSaveFormatError tk sv) = "ERROR (pandoc-plot) Save format " <> show sv <> " not supported by the " <> show tk <> " toolkit."

src/Text/Pandoc/Filter/Plot/Clean.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -31,9 +31,9 @@ import System.FilePath (takeExtension)
3131
import Text.Pandoc.Class (runIO)
3232
import Text.Pandoc.Definition (Block, Pandoc)
3333
import Text.Pandoc.Error (handleError)
34-
import Text.Pandoc.Format (FlavoredFormat(..))
3534
import Text.Pandoc.Filter.Plot.Monad
3635
import Text.Pandoc.Filter.Plot.Parse
36+
import Text.Pandoc.Format (FlavoredFormat (..))
3737
import qualified Text.Pandoc.Options as P
3838
import qualified Text.Pandoc.Readers as P
3939
import Text.Pandoc.Walk (Walkable, query)
@@ -44,7 +44,7 @@ import Text.Pandoc.Walk (Walkable, query)
4444
--
4545
-- The cleaned directories are returned.
4646
cleanOutputDirs ::
47-
Walkable Block b =>
47+
(Walkable Block b) =>
4848
Configuration ->
4949
b ->
5050
IO [FilePath]
@@ -59,7 +59,7 @@ cleanOutputDirs conf doc = do
5959

6060
-- | Analyze a document to determine where would the pandoc-plot output directories be.
6161
outputDirs ::
62-
Walkable Block b =>
62+
(Walkable Block b) =>
6363
b ->
6464
PlotM [FilePath]
6565
outputDirs = fmap (nub . catMaybes) . sequence . query (\b -> [hasDirectory <$> parseFigureSpec b])
@@ -70,7 +70,7 @@ outputDirs = fmap (nub . catMaybes) . sequence . query (\b -> [hasDirectory <$>
7070

7171
-- | PlotM version of @cleanOutputDirs@
7272
cleanOutputDirsM ::
73-
Walkable Block b =>
73+
(Walkable Block b) =>
7474
b ->
7575
PlotM [FilePath]
7676
cleanOutputDirsM doc = do

src/Text/Pandoc/Filter/Plot/Configuration.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ module Text.Pandoc.Filter.Plot.Configuration
1717
)
1818
where
1919

20-
import Data.Aeson ( (.:?), (.!=), Key, Value(Object, Null), FromJSON(parseJSON) )
21-
import Data.String (IsString(..))
20+
import Data.Aeson (FromJSON (parseJSON), Key, Value (Null, Object), (.!=), (.:?))
21+
import Data.String (IsString (..))
2222
import Data.Text (Text, unpack)
2323
import qualified Data.Text.IO as TIO
2424
import Data.Yaml.Config (ignoreEnv, loadYamlSettings)
@@ -228,11 +228,12 @@ data D2Precursor = D2Precursor {_d2Preamble :: !(Maybe FilePath), _d2Exe :: !Fil
228228

229229
instance FromJSON LoggingPrecursor where
230230
parseJSON (Object v) =
231-
LoggingPrecursor <$> v .:? "verbosity" .!= logVerbosity defaultConfiguration
231+
LoggingPrecursor
232+
<$> v .:? "verbosity" .!= logVerbosity defaultConfiguration
232233
<*> v .:? "filepath"
233234
parseJSON _ = fail $ mconcat ["Could not parse logging configuration. "]
234235

235-
asKey :: InclusionKey -> Key
236+
asKey :: InclusionKey -> Key
236237
asKey = fromString . show
237238

238239
instance FromJSON MatplotlibPrecursor where
@@ -297,7 +298,7 @@ instance FromJSON D2Precursor where
297298
parseJSON (Object v) = D2Precursor <$> v .:? asKey PreambleK <*> v .:? asKey ExecutableK .!= d2Exe defaultConfiguration <*> v .:? asKey CommandLineArgsK .!= d2CmdArgs defaultConfiguration
298299
parseJSON _ = fail $ mconcat ["Could not parse ", show SageMath, " configuration."]
299300

300-
toolkitAsKey :: Toolkit -> Key
301+
toolkitAsKey :: Toolkit -> Key
301302
toolkitAsKey = fromString . unpack . cls
302303

303304
instance FromJSON ConfigPrecursor where
@@ -396,4 +397,3 @@ renderConfig ConfigPrecursor {..} = do
396397
return Configuration {..}
397398
where
398399
readPreamble = maybe mempty TIO.readFile
399-

src/Text/Pandoc/Filter/Plot/Embed.hs

Lines changed: 11 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -32,15 +32,15 @@ import Text.HTML.TagSoup
3232
)
3333
import Text.Pandoc.Builder as Builder
3434
( Inlines,
35-
fromList,
3635
figureWith,
36+
fromList,
3737
imageWith,
38-
plain,
3938
link,
40-
str,
39+
plain,
4140
simpleCaption,
41+
str,
4242
toList,
43-
)
43+
)
4444
import Text.Pandoc.Class (runPure)
4545
import Text.Pandoc.Definition (Attr, Block (..), Format, Pandoc (..))
4646
import Text.Pandoc.Error (handleError)
@@ -84,7 +84,9 @@ figure as fp caption' =
8484
return . head . toList $
8585
-- We want the attributes both on the Figure element and the contained Image element
8686
-- so that pandoc-plot plays nice with pandoc-crossref and other filters
87-
figureWith as (simpleCaption (plain caption')) $ plain $ imageWith mempty (pack fp) mempty caption'
87+
figureWith as (simpleCaption (plain caption')) $
88+
plain $
89+
imageWith mempty (pack fp) mempty caption'
8890

8991
-- TODO: also add the case where SVG plots can be
9092
-- embedded in HTML output
@@ -172,11 +174,11 @@ extractPlot :: Text -> Text
172174
extractPlot t =
173175
let tags = canonicalizeTags $ parseTagsOptions parseOptionsFast t
174176
extracted = headScripts tags <> [inside "body" tags]
175-
-- In the past (e.g. commit 8417b011ccb20263427822c7447840ab4a30a41e), we used to
176-
-- make all JS scripts 'deferred'. This turned out to be problematic for plotly
177+
in -- In the past (e.g. commit 8417b011ccb20263427822c7447840ab4a30a41e), we used to
178+
-- make all JS scripts 'deferred'. This turned out to be problematic for plotly
177179
-- specifically (see issue #39). In the future, we may want to defer scripts for
178180
-- certain toolkits, but that's a testing nightmare...
179-
in mconcat $ renderTags <$> extracted
181+
mconcat $ renderTags <$> extracted
180182
where
181183
headScripts = partitions (~== ("<script>" :: String)) . inside "head"
182184

@@ -185,4 +187,4 @@ extractPlot t =
185187
inside :: Text -> [Tag Text] -> [Tag Text]
186188
inside t = init . tail . tgs
187189
where
188-
tgs = takeWhile (~/= TagClose t) . dropWhile (~/= TagOpen t [])
190+
tgs = takeWhile (~/= TagClose t) . dropWhile (~/= TagOpen t [])

src/Text/Pandoc/Filter/Plot/Monad.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -149,7 +149,7 @@ runPlotM fmt conf v = do
149149
\logger -> runReaderT (evalStateT v st) (RuntimeEnv fmt conf logger cwd sem)
150150

151151
-- | maps a function, performing at most @N@ actions concurrently.
152-
mapConcurrentlyN :: Traversable t => Int -> (a -> PlotM b) -> t a -> PlotM (t b)
152+
mapConcurrentlyN :: (Traversable t) => Int -> (a -> PlotM b) -> t a -> PlotM (t b)
153153
mapConcurrentlyN n f xs = do
154154
-- Emulating a pool of processes with locked access
155155
sem <- liftIO $ newQSemN n

src/Text/Pandoc/Filter/Plot/Monad/Logging.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -76,7 +76,7 @@ data Command
7676
= LogMessage Text
7777
| EndLogging
7878

79-
class Monad m => MonadLogger m where
79+
class (Monad m) => MonadLogger m where
8080
askLogger :: m Logger
8181

8282
-- | Ensure that all log messages are flushed, and stop logging

src/Text/Pandoc/Filter/Plot/Monad/Types.hs

Lines changed: 17 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
module Text.Pandoc.Filter.Plot.Monad.Types
1414
( Toolkit (..),
1515
Renderer (..),
16-
AvailabilityCheck(..),
16+
AvailabilityCheck (..),
1717
Script,
1818
CheckResult (..),
1919
InclusionKey (..),
@@ -36,9 +36,9 @@ import Data.Char (toLower)
3636
import Data.List (intersperse)
3737
import Data.String (IsString (..))
3838
import Data.Text (Text, pack, unpack)
39-
import Data.Yaml (FromJSON(..), ToJSON (toJSON), withText)
39+
import Data.Yaml (FromJSON (..), ToJSON (toJSON), withText)
4040
import GHC.Generics (Generic)
41-
import System.FilePath (splitFileName, (</>), isAbsolute)
41+
import System.FilePath (isAbsolute, splitFileName, (</>))
4242
import System.Info (os)
4343
import Text.Pandoc.Definition (Attr)
4444

@@ -99,19 +99,20 @@ cls SageMath = "sageplot"
9999
cls D2 = "d2"
100100

101101
-- | Executable program, and sometimes the directory where it can be found.
102-
data Executable
102+
data Executable
103103
= AbsExe FilePath Text
104104
| RelExe Text
105105

106106
exeFromPath :: FilePath -> Executable
107107
exeFromPath fp
108-
| isAbsolute fp = let (dir, name) = splitFileName fp
109-
in AbsExe dir (pack name)
110-
| otherwise = RelExe (pack fp)
108+
| isAbsolute fp =
109+
let (dir, name) = splitFileName fp
110+
in AbsExe dir (pack name)
111+
| otherwise = RelExe (pack fp)
111112

112113
pathToExe :: Executable -> FilePath
113-
pathToExe (AbsExe dir name) = dir </> unpack name
114-
pathToExe (RelExe name) = unpack name
114+
pathToExe (AbsExe dir name) = dir </> unpack name
115+
pathToExe (RelExe name) = unpack name
115116

116117
-- | Source context for plotting scripts
117118
type Script = Text
@@ -241,13 +242,13 @@ instance IsString SaveFormat where
241242
| s `elem` ["html", "HTML", ".html"] = HTML
242243
| s `elem` ["latex", "LaTeX", ".tex"] = LaTeX
243244
| otherwise =
244-
errorWithoutStackTrace $
245-
mconcat
246-
[ s,
247-
" is not one of the valid save formats : ",
248-
mconcat $ intersperse ", " $ show <$> saveFormats,
249-
" (and lowercase variations). "
250-
]
245+
errorWithoutStackTrace $
246+
mconcat
247+
[ s,
248+
" is not one of the valid save formats : ",
249+
mconcat $ intersperse ", " $ show <$> saveFormats,
250+
" (and lowercase variations). "
251+
]
251252
where
252253
saveFormats = enumFromTo minBound maxBound :: [SaveFormat]
253254

0 commit comments

Comments
 (0)