{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-| Module : $header$ Copyright : (c) Laurent P René de Cotret, 2020 License : GNU GPL, version 2 or above Maintainer : laurent.decotret@outlook.com Stability : internal Portability : portable This module defines types and functions that help with keeping track of figure specifications -} module Text.Pandoc.Filter.Plot.Parse ( plotToolkit , parseFigureSpec , captionReader ) where import Control.Monad (join, when) import Control.Monad.Reader (asks, liftIO) import Data.Default.Class (def) import Data.List (intersperse) import qualified Data.Map.Strict as Map import Data.Maybe (fromMaybe, listToMaybe) import Data.Monoid ((<>)) import Data.String (fromString) import Data.Text (Text, pack, unpack) import qualified Data.Text.IO as TIO import Data.Version (showVersion) import Paths_pandoc_plot (version) import System.FilePath (makeValid) import Text.Pandoc.Definition (Block (..), Inline, Pandoc (..)) 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.Plot.Renderers import Text.Pandoc.Filter.Plot.Types tshow :: Show a => a -> Text tshow = pack . show -- | Determine inclusion specifications from @Block@ attributes. -- If an environment is detected, but the save format is incompatible, -- an error will be thrown. parseFigureSpec :: Block -> PlotM (Maybe FigureSpec) parseFigureSpec (CodeBlock (id', classes, attrs) content) = do toolkit <- asks toolkit if not (cls toolkit `elem` classes) then return Nothing else Just <$> figureSpec where attrs' = Map.fromList attrs preamblePath = unpack <$> Map.lookup (tshow PreambleK) attrs' figureSpec :: PlotM FigureSpec figureSpec = do conf <- asks config toolkit <- asks toolkit let extraAttrs' = parseExtraAttrs toolkit attrs' header = comment toolkit $ "Generated by pandoc-plot " <> ((pack . showVersion) version) defaultPreamble = preambleSelector toolkit conf -- Note that the default preamble changes based on the RendererM -- which is why we use @preambleSelector@ as the default value includeScript <- fromMaybe (return defaultPreamble) ((liftIO . TIO.readFile) <$> preamblePath) let -- Filtered attributes that are not relevant to pandoc-plot -- This presumes that inclusionKeys includes ALL possible keys, for all renderers filteredAttrs = filter (\(k, _) -> k `notElem` (tshow <$> inclusionKeys)) attrs defWithSource = defaultWithSource conf defSaveFmt = defaultSaveFormat conf defDPI = defaultDPI conf let caption = Map.findWithDefault mempty (tshow CaptionK) attrs' withSource = fromMaybe defWithSource $ readBool <$> Map.lookup (tshow WithSourceK) attrs' script = mconcat $ intersperse "\n" [header, includeScript, content] saveFormat = fromMaybe defSaveFmt $ (fromString . unpack) <$> Map.lookup (tshow SaveFormatK) attrs' directory = makeValid $ unpack $ Map.findWithDefault (pack $ defaultDirectory conf) (tshow DirectoryK) attrs' dpi = fromMaybe defDPI $ (read . unpack) <$> Map.lookup (tshow DpiK) attrs' extraAttrs = Map.toList extraAttrs' blockAttrs = (id', classes, filteredAttrs) -- This is the first opportunity to check save format compatibility let saveFormatSupported = saveFormat `elem` (supportedSaveFormats toolkit) when (not saveFormatSupported) $ do (error $ mconcat ["Save format ", show saveFormat, " not supported by ", show toolkit ]) return FigureSpec{..} parseFigureSpec _ = return Nothing -- | Determine which toolkit should be used to render the plot -- from a code block, if any. plotToolkit :: Block -> Maybe Toolkit plotToolkit (CodeBlock (_, classes, _) _) = listToMaybe $ filter (\tk->cls tk `elem` classes) toolkits plotToolkit _ = Nothing -- | Reader options for captions. readerOptions :: ReaderOptions readerOptions = def {readerExtensions = extensionsFromList [ Ext_tex_math_dollars , Ext_superscript , Ext_subscript , Ext_raw_tex ] } -- | Read a figure caption in Markdown format. LaTeX math @$...$@ is supported, -- as are Markdown subscripts and superscripts. captionReader :: Text -> Maybe [Inline] captionReader t = either (const Nothing) (Just . extractFromBlocks) $ runPure $ readMarkdown' 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 _ = [] -- | Flexible boolean parsing readBool :: Text -> Bool readBool s | s `elem` ["True", "true", "'True'", "'true'", "1"] = True | s `elem` ["False", "false", "'False'", "'false'", "0"] = False | otherwise = error $ unpack $ mconcat ["Could not parse '", s, "' into a boolean. Please use 'True' or 'False'"]