{-# LANGUAGE MultiWayIf #-}
module Text.Pandoc.Filter.Pyplot (
makePlot
, makePlot'
, PandocPyplotError(..)
, showError
) where
import Control.Monad ((>=>))
import qualified Data.Map.Strict as M
import System.FilePath (replaceExtension, isValid)
import Text.Pandoc.Definition
import Text.Pandoc.Filter.Scripting
data PandocPyplotError = ScriptError Int
| InvalidTargetError FilePath
| BlockingCallError
data FigureSpec = FigureSpec
{ target :: FilePath
, alt :: String
, caption :: String
}
targetKey, altTextKey, captionKey :: String
targetKey = "plot_target"
altTextKey = "plot_alt"
captionKey = "plot_caption"
parseFigureSpec :: M.Map String String -> Maybe FigureSpec
parseFigureSpec attrs = createInclusion <$> M.lookup targetKey attrs
where
defaultAltText = "Figure generated by pandoc-pyplot"
defaultCaption = mempty
createInclusion fname = FigureSpec
{ target = fname
, alt = M.findWithDefault defaultAltText altTextKey attrs
, caption = M.findWithDefault defaultCaption captionKey attrs
}
formatScriptSource :: FigureSpec -> PythonScript -> PythonScript
formatScriptSource spec script = mconcat [ "# Source code for " <> target spec
, "\n"
, script
]
makePlot' :: Block -> IO (Either PandocPyplotError Block)
makePlot' cb @ (CodeBlock (id', cls, attrs) scriptSource) =
case parseFigureSpec (M.fromList attrs) of
Nothing -> return $ Right cb
Just spec -> do
let figurePath = target spec
if | not (isValid figurePath) -> return $ Left $ InvalidTargetError figurePath
| hasBlockingShowCall scriptSource -> return $ Left $ BlockingCallError
| otherwise -> do
script <- addPlotCapture figurePath scriptSource
result <- runTempPythonScript script
case result of
ScriptFailure code -> return $ Left $ ScriptError code
ScriptSuccess -> do
let sourcePath = replaceExtension figurePath ".txt"
writeFile sourcePath $ formatScriptSource spec scriptSource
let inclusionKeys = [ targetKey, altTextKey, captionKey ]
filteredAttrs = filter (\(k,_) -> k `notElem` inclusionKeys) attrs
image = Image (id', cls, filteredAttrs) [Str $ alt spec] (figurePath, "")
srcTarget = (sourcePath, "Click on this figure to see the source code")
return $ Right $ Para [
Link nullAttr [image] srcTarget
]
makePlot' x = return $ Right x
showError :: PandocPyplotError -> String
showError (ScriptError exitcode) = "Script error: plot could not be generated. Exit code " <> (show exitcode)
showError (InvalidTargetError fname) = "Target filename " <> fname <> " is not valid."
showError BlockingCallError = "Script contains a blocking call to show, like 'plt.show()'"
makePlot :: Block -> IO Block
makePlot = makePlot' >=> either (fail . showError) return