summaryrefslogtreecommitdiffstats
path: root/src/Text/Pandoc/Filter/Plot/Renderers/GNUPlot.hs
blob: 1386d7bb3738cb5e1b3e267fa482402361c04f0f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module      : $header$
-- Copyright   : (c) Laurent P René de Cotret, 2019 - present
-- License     : GNU GPL, version 2 or above
-- Maintainer  : laurent.decotret@outlook.com
-- Stability   : internal
-- Portability : portable
--
-- Rendering gnuplot plots code blocks
module Text.Pandoc.Filter.Plot.Renderers.GNUPlot
  ( gnuplot,
    gnuplotSupportedSaveFormats,
  )
where

import Text.Pandoc.Filter.Plot.Renderers.Prelude

gnuplot :: PlotM Renderer
gnuplot = do
      cmdargs <- asksConfig gnuplotCmdArgs
      return $
        Renderer
          { rendererToolkit = GNUPlot,
            rendererCapture = gnuplotCapture,
            rendererCommand = gnuplotCommand cmdargs,
            rendererAvailability = CommandSuccess $ \exe -> [st|#{pathToExe exe} -h|],
            rendererSupportedSaveFormats = gnuplotSupportedSaveFormats,
            rendererChecks = mempty,
            rendererLanguage = "gnuplot",
            rendererComment = mappend "# ",
            rendererScriptExtension = ".gp"
          }

gnuplotSupportedSaveFormats :: [SaveFormat]
gnuplotSupportedSaveFormats = [LaTeX, PNG, SVG, EPS, GIF, JPG, PDF]

gnuplotCommand :: Text -> OutputSpec -> Text
gnuplotCommand cmdargs OutputSpec {..} = [st|#{pathToExe oExecutable} #{cmdargs} -c "#{oScriptPath}"|]

gnuplotCapture :: FigureSpec -> FilePath -> Script
gnuplotCapture = prependCapture gnuplotCaptureFragment
  where
    prependCapture f s fp = mconcat [f s fp, "\n", script s]

gnuplotCaptureFragment :: FigureSpec -> FilePath -> Script
gnuplotCaptureFragment FigureSpec {..} fname =
  [st|
set terminal #{terminalString saveFormat}
set output '#{normalizePath fname}'
|]
  where
    normalizePath = map f
      where
        f '\\' = '/'
        f x = x

-- | Terminal name for supported save formats
terminalString :: SaveFormat -> Text
terminalString PNG = "pngcairo"
terminalString SVG = "svg"
terminalString EPS = "postscript eps"
terminalString GIF = "gif"
terminalString JPG = "jpeg"
terminalString PDF = "pdfcairo"
terminalString LaTeX = "cairolatex"
terminalString fmt = errorWithoutStackTrace $ "gnuplot: unsupported save format" <> show fmt