summaryrefslogtreecommitdiffstats
path: root/src/Text/Pandoc/Filter/Plot/Monad/Types.hs
blob: f06b30021f258422c5b1a22078e921a08438f8eb (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
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

-- |
-- 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
--
-- This module defines base types in use in pandoc-plot
module Text.Pandoc.Filter.Plot.Monad.Types
  ( Toolkit (..),
    Renderer (..),
    AvailabilityCheck (..),
    Script,
    CheckResult (..),
    InclusionKey (..),
    FigureSpec (..),
    OutputSpec (..),
    SaveFormat (..),
    cls,
    extension,
    toolkits,
    inclusionKeys,
    Executable (..),
    exeFromPath,
    pathToExe,
    -- Utilities
    isWindows,
  )
where

import Data.Char (toLower)
import Data.List (intersperse)
import Data.String (IsString (..))
import Data.Text (Text, pack, unpack)
import Data.Yaml (FromJSON (..), ToJSON (toJSON), withText)
import GHC.Generics (Generic)
import System.FilePath (isAbsolute, splitFileName, (</>))
import System.Info (os)
import Text.Pandoc.Definition (Attr)

-- | List of supported toolkits.
toolkits :: [Toolkit]
toolkits = enumFromTo minBound maxBound

-- | Enumeration of supported toolkits
data Toolkit
  = Matplotlib
  | Matlab
  | PlotlyPython
  | PlotlyR
  | Mathematica
  | Octave
  | GGPlot2
  | GNUPlot
  | Graphviz
  | Bokeh
  | Plotsjl
  | PlantUML
  | SageMath
  | D2
  deriving (Bounded, Eq, Enum, Generic, Ord)

-- | This instance should only be used to display toolkit names
instance Show Toolkit where
  show Matplotlib = "Python/Matplotlib"
  show Matlab = "MATLAB"
  show PlotlyPython = "Python/Plotly"
  show PlotlyR = "R/Plotly"
  show Mathematica = "Mathematica"
  show Octave = "GNU Octave"
  show GGPlot2 = "ggplot2"
  show GNUPlot = "gnuplot"
  show Graphviz = "graphviz"
  show Bokeh = "Python/Bokeh"
  show Plotsjl = "Julia/Plots.jl"
  show PlantUML = "PlantUML"
  show SageMath = "SageMath"
  show D2 = "D2"

-- | Class name which will trigger the filter
cls :: Toolkit -> Text
cls Matplotlib = "matplotlib"
cls Matlab = "matlabplot"
cls PlotlyPython = "plotly_python"
cls PlotlyR = "plotly_r"
cls Mathematica = "mathplot"
cls Octave = "octaveplot"
cls GGPlot2 = "ggplot2"
cls GNUPlot = "gnuplot"
cls Graphviz = "graphviz"
cls Bokeh = "bokeh"
cls Plotsjl = "plotsjl"
cls PlantUML = "plantuml"
cls SageMath = "sageplot"
cls D2 = "d2"

-- | Executable program, and sometimes the directory where it can be found.
data Executable
  = AbsExe FilePath Text
  | RelExe Text

exeFromPath :: FilePath -> Executable
exeFromPath fp
  | isAbsolute fp =
      let (dir, name) = splitFileName fp
       in AbsExe dir (pack name)
  | otherwise = RelExe (pack fp)

pathToExe :: Executable -> FilePath
pathToExe (AbsExe dir name) = dir </> unpack name
pathToExe (RelExe name) = unpack name

-- | Source context for plotting scripts
type Script = Text

-- | Result of checking scripts for problems
data CheckResult
  = CheckPassed
  | CheckFailed Text
  deriving (Eq)

instance Semigroup CheckResult where
  (<>) CheckPassed a = a
  (<>) a CheckPassed = a
  (<>) (CheckFailed msg1) (CheckFailed msg2) = CheckFailed (msg1 <> msg2)

instance Monoid CheckResult where
  mempty = CheckPassed

-- | Description of any possible inclusion key, both in documents
-- and in configuration files.
data InclusionKey
  = DirectoryK
  | CaptionK
  | SaveFormatK
  | WithSourceK
  | CaptionFormatK
  | PreambleK
  | DpiK
  | SourceCodeLabelK
  | StrictModeK
  | ExecutableK
  | CommandLineArgsK
  | DependenciesK
  | FileK
  | MatplotlibTightBBoxK
  | MatplotlibTransparentK
  deriving (Bounded, Eq, Enum)

-- | Keys that pandoc-plot will look for in code blocks.
-- These are only exported for testing purposes.
instance Show InclusionKey where
  show DirectoryK = "directory"
  show CaptionK = "caption"
  show SaveFormatK = "format"
  show WithSourceK = "source"
  show CaptionFormatK = "caption_format"
  show PreambleK = "preamble"
  show DpiK = "dpi"
  show SourceCodeLabelK = "source_label"
  show StrictModeK = "strict"
  show ExecutableK = "executable"
  show CommandLineArgsK = "command_line_arguments"
  show DependenciesK = "dependencies"
  show FileK = "file"
  show MatplotlibTightBBoxK = "tight_bbox"
  show MatplotlibTransparentK = "transparent"

-- | List of all keys related to pandoc-plot that
-- can be specified in source material.
inclusionKeys :: [InclusionKey]
inclusionKeys = enumFromTo (minBound :: InclusionKey) maxBound

-- | Datatype containing all parameters required to specify a figure.
--
-- It is assumed that once a @FigureSpec@ has been created, no configuration
-- can overload it; hence, a @FigureSpec@ completely encodes a particular figure.
data FigureSpec = FigureSpec
  { -- | Renderer to use for this figure.
    renderer_ :: !Renderer,
    -- | Executable to use in rendering this figure.
    fsExecutable :: Executable,
    -- | Figure caption.
    caption :: !Text,
    -- | Append link to source code in caption.
    withSource :: !Bool,
    -- | Source code for the figure.
    script :: !Script,
    -- | Save format of the figure.
    saveFormat :: !SaveFormat,
    -- | Directory where to save the file.
    directory :: !FilePath,
    -- | Dots-per-inch of figure.
    dpi :: !Int,
    -- | Files/directories on which this figure depends, e.g. data files.
    dependencies :: ![FilePath],
    -- | Renderer-specific extra attributes.
    extraAttrs :: ![(Text, Text)],
    -- | Attributes not related to @pandoc-plot@ will be propagated.
    blockAttrs :: !Attr
  }

-- | Generated figure file format supported by pandoc-plot.
-- Note that not all formats are supported by all toolkits.
data SaveFormat
  = -- | Portable network graphics
    PNG
  | -- | Portable document format
    PDF
  | -- | Scalable vector graphics
    SVG
  | -- | JPEG/JPG compressed image
    JPG
  | -- | Encapsulated postscript
    EPS
  | -- | GIF format
    GIF
  | -- | Tagged image format
    TIF
  | -- | WebP image format
    WEBP
  | -- | HTML for interactive plots.
    HTML
  | -- | LaTeX text and pdf graphics
    LaTeX
  deriving (Bounded, Enum, Ord, Eq, Show, Generic)

instance IsString SaveFormat where
  fromString s
    | s `elem` ["png", "PNG", ".png"] = PNG
    | s `elem` ["pdf", "PDF", ".pdf"] = PDF
    | s `elem` ["svg", "SVG", ".svg"] = SVG
    | s `elem` ["eps", "EPS", ".eps"] = EPS
    | s `elem` ["gif", "GIF", ".gif"] = GIF
    | s `elem` ["jpg", "jpeg", "JPG", "JPEG", ".jpg", ".jpeg"] = JPG
    | s `elem` ["tif", "tiff", "TIF", "TIFF", ".tif", ".tiff"] = TIF
    | s `elem` ["webp", "WEBP", ".webp"] = WEBP
    | s `elem` ["html", "HTML", ".html"] = HTML
    | s `elem` ["latex", "LaTeX", ".tex"] = LaTeX
    | otherwise =
        errorWithoutStackTrace $
          mconcat
            [ s,
              " is not one of the valid save formats : ",
              mconcat $ intersperse ", " $ show <$> saveFormats,
              " (and lowercase variations). "
            ]
    where
      saveFormats = enumFromTo minBound maxBound :: [SaveFormat]

-- | Use the IsString instance to parse JSON so that the parsing is flexible
-- with respect to uppercase/lowercase (#42)
instance FromJSON SaveFormat where
  parseJSON = withText "SaveFormat" (pure . fromString . unpack)

instance ToJSON SaveFormat where
  toJSON = toJSON . extension

-- | Save format file extension
extension :: SaveFormat -> String
extension LaTeX = ".tex"
extension fmt = mconcat [".", fmap toLower . show $ fmt]

isWindows :: Bool
isWindows = os `elem` ["mingw32", "win32", "cygwin32"] -- Aliases taken from cabal's Distribution.System module

-- | Internal description of all information
-- needed to output a figure.
data OutputSpec = OutputSpec
  { -- | Figure spec