{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Text.Pandoc.Filter.Pyplot.FigureSpec
( FigureSpec(..)
, SaveFormat(..)
, saveFormatFromString
, toImage
, sourceCodePath
, figurePath
, addPlotCapture
, parseFigureSpec
, extension
) where
import Control.Monad (join)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Reader
import Data.Default.Class (def)
import Data.Hashable (hash)
import Data.List (intersperse)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Data.Version (showVersion)
import Paths_pandoc_pyplot (version)
import System.FilePath (FilePath, addExtension,
makeValid, normalise,
replaceExtension, (</>))
import Text.Pandoc.Builder (fromList, imageWith, link,
para, toList)
import Text.Pandoc.Definition
import Text.Shakespeare.Text (st)
import Text.Pandoc.Class (runPure)
import Text.Pandoc.Extensions (Extension (..),
extensionsFromList)
import Text.Pandoc.Options (ReaderOptions (..))
import Text.Pandoc.Readers (readMarkdown)
import Text.Pandoc.Filter.Pyplot.Types
parseFigureSpec :: Block -> PyplotM (Maybe FigureSpec)
parseFigureSpec (CodeBlock (id', cls, attrs) content)
| "pyplot" `elem` cls = Just <$> figureSpec Matplotlib
| "plotly" `elem` cls = Just <$> figureSpec Plotly
| otherwise = return Nothing
where
attrs' = Map.fromList attrs
filteredAttrs = filter (\(k, _) -> k `notElem` inclusionKeys) attrs
includePath = Map.lookup includePathKey attrs'
figureSpec :: RenderingLibrary -> PyplotM FigureSpec
figureSpec lib = do
config <- ask
includeScript <- fromMaybe
(return $ defaultIncludeScript config)
((liftIO . T.readFile) <$> includePath)
let header = "# Generated by pandoc-pyplot " <> ((T.pack . showVersion) version)
fullScript = mconcat $ intersperse "\n" [header, includeScript, T.pack content]
caption' = Map.findWithDefault mempty captionKey attrs'
format = fromMaybe (defaultSaveFormat config) $ join $ saveFormatFromString <$> Map.lookup saveFormatKey attrs'
dir = makeValid $ Map.findWithDefault (defaultDirectory config) directoryKey attrs'
dpi' = fromMaybe (defaultDPI config) $ read <$> Map.lookup dpiKey attrs'
withLinks' = fromMaybe (defaultWithLinks config) $ readBool <$> Map.lookup withLinksKey attrs'
tightBbox' = isTightBbox config
transparent' = isTransparent config
blockAttrs' = (id', filter (\c -> c `notElem` ["pyplot", "plotly"]) cls, filteredAttrs)
return $ FigureSpec
caption'
withLinks'
fullScript
format
dir
dpi'
lib
tightBbox'
transparent'
blockAttrs'
parseFigureSpec _ = return Nothing
toImage :: FigureSpec -> Block
toImage spec = head . toList $ para $ imageWith attrs' target' "fig:" caption'
where
attrs' = blockAttrs spec
target' = figurePath spec
withLinks' = withLinks spec
srcLink = link (replaceExtension target' ".txt") mempty "Source code"
hiresLink = link (hiresFigurePath spec) mempty "high res."
captionText = fromList $ fromMaybe mempty (captionReader $ caption spec)
captionLinks = mconcat [" (", srcLink, ", ", hiresLink, ")"]
caption' = if withLinks' then captionText <> captionLinks else captionText
figurePath :: FigureSpec -> FilePath
figurePath spec = normalise $ directory spec </> stem spec
where
stem = flip addExtension ext . show . hash
ext = extension . saveFormat $ spec
sourceCodePath :: FigureSpec -> FilePath
sourceCodePath = normalise . flip replaceExtension ".txt" . figurePath
hiresFigurePath :: FigureSpec -> FilePath
hiresFigurePath spec = normalise $ flip replaceExtension (".hires" <> ext) . figurePath $ spec
where
ext = extension . saveFormat $ spec
addPlotCapture :: FigureSpec
-> PythonScript
addPlotCapture spec = mconcat
[ script spec <> "\n"
, plotCapture (renderingLib spec) (figurePath spec) (dpi spec) (transparent spec) (tight')
, plotCapture (renderingLib spec) (hiresFigurePath spec) (minimum [200, 2 * dpi spec]) False (tight')
]
where
tight' = if tightBbox spec then ("'tight'" :: T.Text) else ("None" :: T.Text)
plotCapture Matplotlib = captureMatplotlib
plotCapture Plotly = capturePlotly
type Tight = T.Text
type IsTransparent = Bool
type RenderingFunc = (FilePath -> Int -> IsTransparent -> Tight -> PythonScript)
captureMatplotlib :: RenderingFunc
captureMatplotlib fname' dpi' transparent' tight' = [st|
import matplotlib.pyplot as plt
plt.savefig(r"#{fname'}", dpi=#{dpi'}, transparent=#{transparent''}, bbox_inches=#{tight'})
|]
where
transparent'' :: T.Text
transparent'' = if transparent' then "True" else "False"
capturePlotly :: RenderingFunc
capturePlotly fname' _ _ _ = [st|
import plotly.graph_objects as go
__current_plotly_figure = next(obj for obj in globals().values() if type(obj) == go.Figure)
__current_plotly_figure.write_image("#{fname'}")
|]
readerOptions :: ReaderOptions
readerOptions = def
{readerExtensions =
extensionsFromList
[ Ext_tex_math_dollars
, Ext_superscript
, Ext_subscript
, Ext_raw_tex
]
}
captionReader :: String -> Maybe [Inline]
captionReader t = either (const Nothing) (Just . extractFromBlocks) $ runPure $ readMarkdown' (T.pack t)
where
readMarkdown' = readMarkdown readerOptions
extractFromBlocks (Pandoc _ blocks) = mconcat $ extractInlines <$> blocks
extractInlines (Plain inlines) = inlines
extractInlines (Para inlines) = inlines
extractInlines (LineBlock multiinlines) = join multiinlines
extractInlines _ = []
readBool :: String -> Bool
readBool s | s `elem` ["True", "true", "'True'", "'true'", "1"] = True
| s `elem` ["False", "false", "'False'", "'false'", "0"] = False
| otherwise = error $ mconcat ["Could not parse '", s, "' into a boolean. Please use 'True' or 'False'"]