{-# 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.Filter.Plot.Monad
import Text.Pandoc.Filter.Plot.Renderers
import Text.Pandoc.Format (parseFlavoredFormat)
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 (FilePath -> Text) -> (a -> FilePath) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> FilePath
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 -> ParseFigureResult -> PlotM ParseFigureResult
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
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' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
attrs
preamblePath :: Maybe FilePath
preamblePath = Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
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
rendererToolkit :: Toolkit
rendererCapture :: FigureSpec -> FilePath -> Text
rendererCommand :: OutputSpec -> Text
rendererAvailability :: AvailabilityCheck
rendererSupportedSaveFormats :: [SaveFormat]
rendererChecks :: [Text -> CheckResult]
rendererLanguage :: Text
rendererComment :: Text -> Text
rendererScriptExtension :: FilePath
rendererToolkit :: Renderer -> Toolkit
rendererCapture :: Renderer -> FigureSpec -> FilePath -> Text
rendererCommand :: Renderer -> OutputSpec -> Text
rendererAvailability :: Renderer -> AvailabilityCheck
rendererSupportedSaveFormats :: Renderer -> [SaveFormat]
rendererChecks :: Renderer -> [Text -> CheckResult]
rendererLanguage :: Renderer -> Text
rendererComment :: Renderer -> Text -> Text
rendererScriptExtension :: Renderer -> FilePath
..} = do
Configuration
conf <- (RuntimeEnv -> Configuration)
-> StateT PlotState (ReaderT RuntimeEnv IO) Configuration
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks RuntimeEnv -> Configuration
envConfig
let toolkit :: Toolkit
toolkit = Toolkit
rendererToolkit
saveFormat :: SaveFormat
saveFormat = SaveFormat -> (Text -> SaveFormat) -> Maybe Text -> SaveFormat
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Configuration -> SaveFormat
defaultSaveFormat Configuration
conf) (FilePath -> SaveFormat
forall a. IsString a => FilePath -> a
fromString (FilePath -> SaveFormat)
-> (Text -> FilePath) -> Text -> SaveFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) (Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
SaveFormatK) Map Text Text
attrs')
if SaveFormat
saveFormat SaveFormat -> [SaveFormat] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [SaveFormat]
rendererSupportedSaveFormats
then do
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Save format ", SaveFormat -> FilePath
forall a. Show a => a -> FilePath
show SaveFormat
saveFormat, FilePath
" not supported by ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
toolkit]
ParseFigureResult -> PlotM ParseFigureResult
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseFigureResult -> PlotM ParseFigureResult)
-> ParseFigureResult -> PlotM ParseFigureResult
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
"Generated by pandoc-plot " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (FilePath -> Text
pack (FilePath -> Text) -> (Version -> FilePath) -> Version -> Text
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 <-
StateT PlotState (ReaderT RuntimeEnv IO) Text
-> (FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> Maybe FilePath
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
defaultPreamble)
(IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a. IO a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> (FilePath -> IO Text)
-> FilePath
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Text
TIO.readFile)
Maybe FilePath
preamblePath
let
filteredAttrs :: [(Text, Text)]
filteredAttrs = ((Text, Text) -> Bool) -> [(Text, Text)] -> [(Text, Text)]
forall a. (a -> Bool) -> [a] -> [a]
filter (\(Text
k, Text
_) -> Text
k Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` (InclusionKey -> Text
forall a. Show a => a -> Text
tshow (InclusionKey -> Text) -> [InclusionKey] -> [Text]
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 = Text -> Text -> Map Text Text -> Text
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault Text
forall a. Monoid a => a
mempty (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
CaptionK) Map Text Text
attrs'
fsExecutable :: Executable
fsExecutable = Executable -> (Text -> Executable) -> Maybe Text -> Executable
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Executable
defaultExe (FilePath -> Executable
exeFromPath (FilePath -> Executable)
-> (Text -> FilePath) -> Text -> Executable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) (Maybe Text -> Executable) -> Maybe Text -> Executable
forall a b. (a -> b) -> a -> b
$ Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
ExecutableK) Map Text Text
attrs'
withSource :: Bool
withSource = Bool -> (Text -> Bool) -> Maybe Text -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
defWithSource Text -> Bool
readBool (Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
WithSourceK) Map Text Text
attrs')
script :: Text
script = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
intersperse Text
"\n" [Text
header, Text
includeScript, Text
content]
directory :: FilePath
directory = FilePath -> FilePath
makeValid (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
unpack (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Map Text Text -> Text
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault (FilePath -> Text
pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Configuration -> FilePath
defaultDirectory Configuration
conf) (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DirectoryK) Map Text Text
attrs'
dpi :: Int
dpi = Int -> (Text -> Int) -> Maybe Text -> Int
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Int
defDPI (FilePath -> Int
forall a. Read a => FilePath -> a
read (FilePath -> Int) -> (Text -> FilePath) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack) (Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DpiK) Map Text Text
attrs')
extraAttrs :: [(Text, Text)]
extraAttrs = Map Text Text -> [(Text, Text)]
forall k a. Map k a -> [(k, a)]
Map.toList Map Text Text
extraAttrs'
blockAttrs :: (Text, [Text], [(Text, Text)])
blockAttrs = (Text
id', (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
filter (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Toolkit -> Text
cls Toolkit
toolkit) [Text]
classes, [(Text, Text)]
filteredAttrs)
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
debug (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ Text
"Propagating attributes unrelated to pandoc-plot: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Text, [Text], [(Text, Text)]) -> Text
forall a. Show a => a -> Text
tshow (Text, [Text], [(Text, Text)])
blockAttrs
let blockDependencies :: [FilePath]
blockDependencies = Text -> [FilePath]
parseFileDependencies (Text -> [FilePath]) -> Text -> [FilePath]
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text) -> Maybe Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DependenciesK) Map Text Text
attrs'
dependencies :: [FilePath]
dependencies = Configuration -> [FilePath]
defaultDependencies Configuration
conf [FilePath] -> [FilePath] -> [FilePath]
forall a. Semigroup a => a -> a -> a
<> [FilePath]
blockDependencies
()
_' <-
Bool
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (SaveFormat
saveFormat SaveFormat -> [SaveFormat] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [SaveFormat]
rendererSupportedSaveFormats) (StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$
let msg :: Text
msg = FilePath -> Text
pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ [FilePath] -> FilePath
forall a. Monoid a => [a] -> a
mconcat [FilePath
"Save format ", SaveFormat -> FilePath
forall a. Show a => a -> FilePath
show SaveFormat
saveFormat, FilePath
" not supported by ", Toolkit -> FilePath
forall a. Show a => a -> FilePath
show Toolkit
toolkit]
in Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
err Text
msg
ParseFigureResult -> PlotM ParseFigureResult
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return (ParseFigureResult -> PlotM ParseFigureResult)
-> ParseFigureResult -> PlotM ParseFigureResult
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
renderer_ :: Renderer
saveFormat :: SaveFormat
caption :: Text
fsExecutable :: Executable
withSource :: Bool
script :: Text
directory :: FilePath
dpi :: Int
extraAttrs :: [(Text, Text)]
blockAttrs :: (Text, [Text], [(Text, Text)])
dependencies :: [FilePath]
renderer_ :: Renderer
fsExecutable :: Executable
caption :: Text
withSource :: Bool
script :: Text
saveFormat :: SaveFormat
directory :: FilePath
dpi :: Int
dependencies :: [FilePath]
extraAttrs :: [(Text, Text)]
blockAttrs :: (Text, [Text], [(Text, Text)])
..})
parseFigureSpec Block
_ = ParseFigureResult -> PlotM ParseFigureResult
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
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' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
attrs
mfile :: Maybe FilePath
mfile = FilePath -> FilePath
normalise (FilePath -> FilePath) -> (Text -> FilePath) -> Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack (Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Map Text Text -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
FileK) Map Text Text
attrs'
Bool
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Text
content Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
forall a. Monoid a => a
mempty Bool -> Bool -> Bool
&& Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust Maybe FilePath
mfile) (StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ do
Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
warning (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$
[Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ Text
"Figure refers to a file (",
FilePath -> Text
pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Maybe FilePath -> FilePath
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
Text -> m ()
forall (m :: * -> *). (MonadLogger m, MonadIO m) => Text -> m ()
info (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Loading figure content from " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FilePath -> Text
pack FilePath
fp
IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ FilePath -> IO Text
TIO.readFile FilePath
fp
StateT PlotState (ReaderT RuntimeEnv IO) Text
-> (FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> Maybe FilePath
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
content) FilePath -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall {m :: * -> *}.
(MonadLogger m, MonadIO m) =>
FilePath -> m Text
loadFromFile Maybe FilePath
mfile
parseContent Block
_ = Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a. a -> StateT PlotState (ReaderT RuntimeEnv IO) a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
forall a. Monoid a => a
mempty
plotToolkit :: Block -> Maybe Toolkit
plotToolkit :: Block -> Maybe Toolkit
plotToolkit (CodeBlock (Text
_, [Text]
classes, [(Text, Text)]
_) Text
_) =
(Toolkit -> Bool) -> [Toolkit] -> Maybe Toolkit
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (\Toolkit
tk -> Toolkit -> Text
cls Toolkit
tk Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes) [Toolkit]
toolkits
plotToolkit Block
_ = Maybe Toolkit
forall a. Maybe a
Nothing
captionReader :: Format -> Text -> Maybe [Inline]
captionReader :: Format -> Text -> Maybe [Inline]
captionReader (Format Text
f) Text
t = (PandocError -> Maybe [Inline])
-> (Pandoc -> Maybe [Inline])
-> Either PandocError Pandoc
-> Maybe [Inline]
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe [Inline] -> PandocError -> Maybe [Inline]
forall a b. a -> b -> a
const Maybe [Inline]
forall a. Maybe a
Nothing) ([Inline] -> Maybe [Inline]
forall a. a -> Maybe a
Just ([Inline] -> Maybe [Inline])
-> (Pandoc -> [Inline]) -> Pandoc -> Maybe [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Pandoc -> [Inline]
extractFromBlocks) (Either PandocError Pandoc -> Maybe [Inline])
-> Either PandocError Pandoc -> Maybe [Inline]
forall a b. (a -> b) -> a -> b
$
PandocPure Pandoc -> Either PandocError Pandoc
forall a. PandocPure a -> Either PandocError a
runPure (PandocPure Pandoc -> Either PandocError Pandoc)
-> PandocPure Pandoc -> Either PandocError Pandoc
forall a b. (a -> b) -> a -> b
$ do
FlavoredFormat
fmt <- Text -> PandocPure FlavoredFormat
forall (m :: * -> *). PandocMonad m => Text -> m FlavoredFormat
parseFlavoredFormat Text
f
(Reader PandocPure
reader, Extensions
exts) <- FlavoredFormat -> PandocPure (Reader PandocPure, Extensions)
forall (m :: * -> *).
PandocMonad m =>
FlavoredFormat -> m (Reader m, Extensions)
getReader FlavoredFormat
fmt
let readerOpts :: ReaderOptions
readerOpts = ReaderOptions
forall a. Default a => a
def {readerExtensions = exts}
case Reader PandocPure
reader of
TextReader forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
fct -> ReaderOptions -> Text -> PandocPure Pandoc
forall a. ToSources a => ReaderOptions -> a -> PandocPure Pandoc
fct ReaderOptions
readerOpts Text
t
Reader PandocPure
_ -> Pandoc -> PandocPure Pandoc
forall a. a -> PandocPure a
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
forall a. Monoid a => a
mempty
where
extractFromBlocks :: Pandoc -> [Inline]
extractFromBlocks (Pandoc Meta
_ [Block]
blocks) = [[Inline]] -> [Inline]
forall a. Monoid a => [a] -> a
mconcat ([[Inline]] -> [Inline]) -> [[Inline]] -> [Inline]
forall a b. (a -> b) -> a -> b
$ Block -> [Inline]
extractInlines (Block -> [Inline]) -> [Block] -> [[Inline]]
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) = [[Inline]] -> [Inline]
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 Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
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 Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
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 = FilePath -> Bool
forall a. FilePath -> a
errorWithoutStackTrace (FilePath -> Bool) -> FilePath -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
unpack (Text -> FilePath) -> Text -> FilePath
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
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 Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
forall a. Monoid a => a
mempty = [FilePath]
forall a. Monoid a => a
mempty
| Bool
otherwise =
(Text -> FilePath) -> [Text] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> FilePath
normalise (FilePath -> FilePath) -> (Text -> FilePath) -> Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
unpack (Text -> FilePath) -> (Text -> Text) -> Text -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropAround Char -> Bool
isSpace)
([Text] -> [FilePath]) -> (Text -> [Text]) -> Text -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HasCallStack => Text -> Text -> [Text]
Text -> Text -> [Text]
T.splitOn Text
","
(Text -> [Text]) -> (Text -> Text) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Text -> Text
T.dropAround (\Char
c -> Char
c Char -> FilePath -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'[', Char
']'])
(Text -> [FilePath]) -> Text -> [FilePath]
forall a b. (a -> b) -> a -> b
$ Text
t