{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Text.Pandoc.Filter.Plot.Parse
( plotToolkit,
parseFigureSpec,
ParseFigureResult (..),
captionReader,
)
where
import Control.Monad (join, unless, when)
import Data.Char (isSpace)
import Data.Default (def)
import Data.List (find, intersperse)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust, fromMaybe, isJust)
import Data.String (fromString)
import Data.Text (Text, pack, unpack)
import qualified Data.Text as T
import qualified Data.Text.IO as TIO
import Data.Version (showVersion)
import Paths_pandoc_plot (version)
import System.FilePath (makeValid, normalise)
import Text.Pandoc.Class (runPure)
import Text.Pandoc.Definition
( Block (..),
Format (..),
Inline,
Pandoc (..),
)
import Text.Pandoc.Format (parseFlavoredFormat)
import Text.Pandoc.Filter.Plot.Monad
import Text.Pandoc.Filter.Plot.Renderers
import Text.Pandoc.Options (ReaderOptions (..))
import Text.Pandoc.Readers (Reader (..), getReader)
tshow :: Show a => a -> Text
tshow :: forall a. Show a => a -> Text
tshow = FilePath -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> FilePath
show
data ParseFigureResult
= NotAFigure
| PFigure FigureSpec
| MissingToolkit Toolkit
| UnsupportedSaveFormat Toolkit SaveFormat
parseFigureSpec :: Block -> PlotM ParseFigureResult
parseFigureSpec :: Block -> PlotM ParseFigureResult
parseFigureSpec block :: Block
block@(CodeBlock (Text
id', [Text]
classes, [(Text, Text)]
attrs) Text
_) = do
let mtk :: Maybe Toolkit
mtk = Block -> Maybe Toolkit
plotToolkit Block
block
case Maybe Toolkit
mtk of
Maybe Toolkit
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ParseFigureResult
NotAFigure
Just Toolkit
tk -> do
Renderer
r <- Toolkit -> PlotM Renderer
renderer Toolkit
tk
Renderer -> PlotM ParseFigureResult
figureSpec Renderer
r
where
attrs' :: Map Text Text
attrs' = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
attrs
preamblePath :: Maybe FilePath
preamblePath = Text -> FilePath
unpack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
PreambleK) Map Text Text
attrs'
figureSpec :: Renderer -> PlotM ParseFigureResult
figureSpec :: Renderer -> PlotM ParseFigureResult
figureSpec renderer_ :: Renderer
renderer_@Renderer {FilePath
[SaveFormat]
[Text -> CheckResult]
Text
AvailabilityCheck
Toolkit
Text -> Text
OutputSpec -> Text
FigureSpec -> FilePath -> Text
rendererScriptExtension :: Renderer -> FilePath
rendererComment :: Renderer -> Text -> Text
rendererLanguage :: Renderer -> Text
rendererChecks :: Renderer -> [Text -> CheckResult]
rendererSupportedSaveFormats :: Renderer -> [SaveFormat]
rendererAvailability :: Renderer -> AvailabilityCheck
rendererCommand :: Renderer -> OutputSpec -> Text
rendererCapture :: Renderer -> FigureSpec -> FilePath -> Text
rendererToolkit :: Renderer -> Toolkit
rendererScriptExtension :: FilePath
rendererComment :: Text -> Text
rendererLanguage :: Text
rendererChecks :: [Text -> CheckResult]
rendererSupportedSaveFormats :: [SaveFormat]
rendererAvailability :: AvailabilityCheck
rendererCommand :: OutputSpec -> Text
rendererCapture :: FigureSpec -> FilePath -> Text
rendererToolkit :: Toolkit
..} = do
Configuration
conf <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> Configuration
envConfig
let toolkit :: Toolkit
toolkit = Toolkit
rendererToolkit
saveFormat :: SaveFormat
saveFormat = forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Configuration -> SaveFormat
defaultSaveFormat Configuration
conf) (forall a. IsString a => FilePath -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
SaveFormatK) Map Text Text
attrs')
if Bool -> Bool
not (SaveFormat
saveFormat forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [SaveFormat]
rendererSupportedSaveFormats)
then do
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err forall a b. (a -> b) -> a -> b
$ FilePath -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [FilePath
"Save format ", forall a. Show a => a -> FilePath
show SaveFormat
saveFormat, FilePath
" not supported by ", forall a. Show a => a -> FilePath
show Toolkit
toolkit]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Toolkit -> SaveFormat -> ParseFigureResult
UnsupportedSaveFormat Toolkit
toolkit SaveFormat
saveFormat
else do
let extraAttrs' :: Map Text Text
extraAttrs' = Toolkit -> Map Text Text -> Map Text Text
parseExtraAttrs Toolkit
toolkit Map Text Text
attrs'
header :: Text
header = Text -> Text
rendererComment forall a b. (a -> b) -> a -> b
$ Text
"Generated by pandoc-plot " forall a. Semigroup a => a -> a -> a
<> (FilePath -> Text
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> FilePath
showVersion) Version
version
defaultPreamble :: Text
defaultPreamble = Toolkit -> Configuration -> Text
preambleSelector Toolkit
toolkit Configuration
conf
Text
includeScript <-
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(forall (m :: * -> *) a. Monad m => a -> m a
return Text
defaultPreamble)
(forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Text
TIO.readFile)
Maybe FilePath
preamblePath
let
filteredAttrs :: [(Text, Text)]
filteredAttrs = forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
k, Text
_) -> Text
k forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (forall a. Show a => a -> Text
tshow forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [InclusionKey]
inclusionKeys)) [(Text, Text)]
attrs
defWithSource :: Bool
defWithSource = Configuration -> Bool
defaultWithSource Configuration
conf
defDPI :: Int
defDPI = Configuration -> Int
defaultDPI Configuration
conf
Text
content <- Block -> StateT PlotState (ReaderT RuntimeEnv IO) Text
parseContent Block
block
Executable
defaultExe <- Toolkit -> PlotM Executable
executable Toolkit
rendererToolkit
let caption :: Text
caption = forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault forall a. Monoid a => a
mempty (forall a. Show a => a -> Text
tshow InclusionKey
CaptionK) Map Text Text
attrs'
fsExecutable :: Executable
fsExecutable = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Executable
defaultExe (FilePath -> Executable
exeFromPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK) Map Text Text
attrs'
withSource :: Bool
withSource = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
defWithSource Text -> Bool
readBool (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
WithSourceK) Map Text Text
attrs')
script :: Text
script = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a. a -> [a] -> [a]
intersperse Text
"\n" [Text
header, Text
includeScript, Text
content]
directory :: FilePath
directory = FilePath -> FilePath
makeValid forall a b. (a -> b) -> a -> b
$ Text -> FilePath
unpack forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault (FilePath -> Text
pack forall a b. (a -> b) -> a -> b
$ Configuration -> FilePath
defaultDirectory Configuration
conf) (forall a. Show a => a -> Text
tshow InclusionKey
DirectoryK) Map Text Text
attrs'
dpi :: Int
dpi = forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
defDPI (forall a. Read a => FilePath -> a
read forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) (forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
DpiK) Map Text Text
attrs')
extraAttrs :: [(Text, Text)]
extraAttrs = forall k a. Map k a -> [(k, a)]
Map.toList Map Text Text
extraAttrs'
blockAttrs :: (Text, [Text], [(Text, Text)])
blockAttrs = (Text
id', forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Toolkit -> Text
cls Toolkit
toolkit) [Text]
classes, [(Text, Text)]
filteredAttrs)
let blockDependencies :: [FilePath]
blockDependencies = Text -> [FilePath]
parseFileDependencies forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a -> a
fromMaybe forall a. Monoid a => a
mempty forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
DependenciesK) Map Text Text
attrs'
dependencies :: [FilePath]
dependencies = Configuration -> [FilePath]
defaultDependencies Configuration
conf forall a. Semigroup a => a -> a -> a
<> [FilePath]
blockDependencies
()
_' <-
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SaveFormat
saveFormat forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [SaveFormat]
rendererSupportedSaveFormats) forall a b. (a -> b) -> a -> b
$
let msg :: Text
msg = FilePath -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [FilePath
"Save format ", forall a. Show a => a -> FilePath
show SaveFormat
saveFormat, FilePath
" not supported by ", forall a. Show a => a -> FilePath
show Toolkit
toolkit]
in forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err Text
msg
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ FigureSpec -> ParseFigureResult
PFigure (FigureSpec {Bool
Int
FilePath
[FilePath]
[(Text, Text)]
(Text, [Text], [(Text, Text)])
Text
Renderer
SaveFormat
Executable
blockAttrs :: (Text, [Text], [(Text, Text)])
extraAttrs :: [(Text, Text)]
dependencies :: [FilePath]
dpi :: Int
directory :: FilePath
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
fsExecutable :: Executable
renderer_ :: Renderer
dependencies :: [FilePath]
blockAttrs :: (Text, [Text], [(Text, Text)])
extraAttrs :: [(Text, Text)]
dpi :: Int
directory :: FilePath
script :: Text
withSource :: Bool
fsExecutable :: Executable
caption :: Text
saveFormat :: SaveFormat
renderer_ :: Renderer
..})
parseFigureSpec Block
_ = forall (m :: * -> *) a. Monad m => a -> m a
return ParseFigureResult
NotAFigure
parseContent :: Block -> PlotM Script
parseContent :: Block -> StateT PlotState (ReaderT RuntimeEnv IO) Text
parseContent (CodeBlock (Text
_, [Text]
_, [(Text, Text)]
attrs) Text
content) = do
let attrs' :: Map Text Text
attrs' = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
attrs
mfile :: Maybe FilePath
mfile = FilePath -> FilePath
normalise forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (forall a. Show a => a -> Text
tshow InclusionKey
FileK) Map Text Text
attrs'
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
content forall a. Eq a => a -> a -> Bool
/= forall a. Monoid a => a
mempty Bool -> Bool -> Bool
&& forall a. Maybe a -> Bool
isJust Maybe FilePath
mfile) forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
warning forall a b. (a -> b) -> a -> b
$
forall a. Monoid a => [a] -> a
mconcat
[ Text
"Figure refers to a file (",
FilePath -> Text
pack forall a b. (a -> b) -> a -> b
$ forall a. HasCallStack => Maybe a -> a
fromJust Maybe FilePath
mfile,
Text
") but also has content in the document.\nThe file content will be preferred."
]
let loadFromFile :: FilePath -> m Text
loadFromFile FilePath
fp = do
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
info forall a b. (a -> b) -> a -> b
$ Text
"Loading figure content from " forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
pack FilePath
fp
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ FilePath -> IO Text
TIO.readFile FilePath
fp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return Text
content) forall {m :: * -> *}.
(MonadLogger m, MonadIO m) =>
FilePath -> m Text
loadFromFile Maybe FilePath
mfile
parseContent Block
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
plotToolkit :: Block -> Maybe Toolkit
plotToolkit :: Block -> Maybe Toolkit
plotToolkit (CodeBlock (Text
_, [Text]
classes, [(Text, Text)]
_) Text
_) =
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\Toolkit
tk -> Toolkit -> Text
cls Toolkit
tk forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes) [Toolkit]
toolkits
plotToolkit Block
_ = forall a. Maybe a
Nothing
captionReader :: Format -> Text -> Maybe [Inline]
captionReader :: Format -> Text -> Maybe [Inline]
captionReader (Format Text
f) Text
t = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) (forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pandoc -> [Inline]
extractFromBlocks) forall a b. (a -> b) -> a -> b
$
forall a. PandocPure a -> Either PandocError a
runPure forall a b. (a -> b) -> a -> b
$ do
FlavoredFormat
fmt <- forall (m :: * -> *). PandocMonad m => Text -> m FlavoredFormat
parseFlavoredFormat Text
f
(Reader PandocPure
reader, Extensions
exts) <- forall (m :: * -> *).
PandocMonad m =>
FlavoredFormat -> m (Reader m, Extensions)
getReader FlavoredFormat
fmt
let readerOpts :: ReaderOptions
readerOpts = forall a. Default a => a
def {readerExtensions :: Extensions
readerExtensions = Extensions
exts}
case Reader PandocPure
reader of
TextReader forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
fct -> forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
fct ReaderOptions
readerOpts Text
t
Reader PandocPure
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Monoid a => a
mempty
where
extractFromBlocks :: Pandoc -> [Inline]
extractFromBlocks (Pandoc Meta
_ [Block]
blocks) = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ Block -> [Inline]
extractInlines forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Block]
blocks
extractInlines :: Block -> [Inline]
extractInlines (Plain [Inline]
inlines) = [Inline]
inlines
extractInlines (Para [Inline]
inlines) = [Inline]
inlines
extractInlines (LineBlock [[Inline]]
multiinlines) = forall (m :: * -> *) a. Monad m => m (m a) -> m a
join [[Inline]]
multiinlines
extractInlines Block
_ = []
readBool :: Text -> Bool
readBool :: Text -> Bool
readBool Text
s
| Text
s forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"True", Text
"true", Text
"'True'", Text
"'true'", Text
"1"] = Bool
True
| Text
s forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text
"False", Text
"false", Text
"'False'", Text
"'false'", Text
"0"] = Bool
False
| Bool
otherwise = forall a. FilePath -> a
errorWithoutStackTrace forall a b. (a -> b) -> a -> b
$ Text -> FilePath
unpack forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat [Text
"Could not parse '", Text
s, Text
"' into a boolean. Please use 'True' or 'False'"]
parseFileDependencies :: Text -> [FilePath]
parseFileDependencies :: Text -> [FilePath]
parseFileDependencies Text
t
| Text
t forall a. Eq a => a -> a -> Bool
== forall a. Monoid a => a
mempty = forall a. Monoid a => a
mempty
| Bool
otherwise =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath
normalise forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropAround Char -> Bool
isSpace)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
","
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropAround (\Char
c -> Char
c forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'[', Char
']'])
forall a b. (a -> b) -> a -> b
$ Text
t