{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

-- |

-- 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 Data.Char (isSpace)
import Data.Default (def)
import Data.List (intersperse)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust, fromMaybe, isJust, listToMaybe)
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.Options (ReaderOptions (..))
import Text.Pandoc.Readers (Reader (..), getReader)

tshow :: Show a => a -> Text
tshow :: a -> Text
tshow = String -> Text
pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
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 :: Block -> PlotM (Maybe FigureSpec)
parseFigureSpec block :: Block
block@(CodeBlock (Text
id', [Text]
classes, [(Text, Text)]
attrs) Text
_) =
  Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
-> PlotM (Maybe FigureSpec)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
 -> PlotM (Maybe FigureSpec))
-> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
-> PlotM (Maybe FigureSpec)
forall a b. (a -> b) -> a -> b
$
    (Toolkit -> StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
-> Maybe Toolkit
-> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Toolkit -> StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec
figureSpec (Maybe Toolkit
 -> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec))
-> Maybe Toolkit
-> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec)
forall a b. (a -> b) -> a -> b
$
      Block -> Maybe Toolkit
plotToolkit Block
block Maybe Toolkit -> (Toolkit -> Maybe Toolkit) -> Maybe Toolkit
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Toolkit -> Maybe Toolkit
hasToolkit
  where
    hasToolkit :: Toolkit -> Maybe Toolkit
hasToolkit = \Toolkit
tk -> if Toolkit -> Text
cls Toolkit
tk Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
classes then Toolkit -> Maybe Toolkit
forall (m :: * -> *) a. Monad m => a -> m a
return Toolkit
tk else Maybe Toolkit
forall a. Maybe a
Nothing
    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 String
preamblePath = Text -> String
unpack (Text -> String) -> Maybe Text -> Maybe String
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 :: Toolkit -> PlotM FigureSpec
    figureSpec :: Toolkit -> StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec
figureSpec Toolkit
toolkit = 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 extraAttrs' :: Map Text Text
extraAttrs' = Toolkit -> Map Text Text -> Map Text Text
parseExtraAttrs Toolkit
toolkit Map Text Text
attrs'
          header :: Text
header = Toolkit -> Text -> Text
comment Toolkit
toolkit (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
<> ((String -> Text
pack (String -> Text) -> (Version -> String) -> Version -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Version -> String
showVersion) Version
version)
          defaultPreamble :: Text
defaultPreamble = Toolkit -> Configuration -> Text
preambleSelector Toolkit
toolkit Configuration
conf

      Text
includeScript <-
        StateT PlotState (ReaderT RuntimeEnv IO) Text
-> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a. a -> Maybe a -> a
fromMaybe
          (Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
defaultPreamble)
          ((IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> (String -> IO Text)
-> String
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO Text
TIO.readFile) (String -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> Maybe String
-> Maybe (StateT PlotState (ReaderT RuntimeEnv IO) Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
preamblePath)
      let -- Filtered attributes that are not relevant to pandoc-plot

          -- This presumes that inclusionKeys includes ALL possible keys, for all toolkits

          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
          defSaveFmt :: SaveFormat
defSaveFmt = Configuration -> SaveFormat
defaultSaveFormat Configuration
conf
          defDPI :: Int
defDPI = Configuration -> Int
defaultDPI Configuration
conf

      -- Decide between reading from file or using document content

      Text
content <- Block -> StateT PlotState (ReaderT RuntimeEnv IO) Text
parseContent Block
block

      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'
          withSource :: Bool
withSource = Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
defWithSource (Maybe Bool -> Bool) -> Maybe Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
readBool (Text -> Bool) -> Maybe Text -> Maybe Bool
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
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]
          saveFormat :: SaveFormat
saveFormat = SaveFormat -> Maybe SaveFormat -> SaveFormat
forall a. a -> Maybe a -> a
fromMaybe SaveFormat
defSaveFmt (Maybe SaveFormat -> SaveFormat) -> Maybe SaveFormat -> SaveFormat
forall a b. (a -> b) -> a -> b
$ (String -> SaveFormat
forall a. IsString a => String -> a
fromString (String -> SaveFormat) -> (Text -> String) -> Text -> SaveFormat
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack) (Text -> SaveFormat) -> Maybe Text -> Maybe SaveFormat
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
SaveFormatK) Map Text Text
attrs'
          directory :: String
directory = String -> String
makeValid (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ Text -> String
unpack (Text -> String) -> Text -> String
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 (String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Configuration -> String
defaultDirectory Configuration
conf) (InclusionKey -> Text
forall a. Show a => a -> Text
tshow InclusionKey
DirectoryK) Map Text Text
attrs'
          dpi :: Int
dpi = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
defDPI (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Int
forall a. Read a => String -> a
read (String -> Int) -> (Text -> String) -> Text -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack) (Text -> Int) -> Maybe Text -> Maybe Int
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
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)

      let blockDependencies :: [String]
blockDependencies = Text -> [String]
parseFileDependencies (Text -> [String]) -> Text -> [String]
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 :: [String]
dependencies = (Configuration -> [String]
defaultDependencies Configuration
conf) [String] -> [String] -> [String]
forall a. Semigroup a => a -> a -> a
<> [String]
blockDependencies

      -- This is the first opportunity to check save format compatibility

      let saveFormatSupported :: Bool
saveFormatSupported = SaveFormat
saveFormat SaveFormat -> [SaveFormat] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (Toolkit -> [SaveFormat]
supportedSaveFormats Toolkit
toolkit)
      Bool
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
-> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not Bool
saveFormatSupported) (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
        let msg :: Text
msg = String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall a. Monoid a => [a] -> a
mconcat [String
"Save format ", SaveFormat -> String
forall a. Show a => a -> String
show SaveFormat
saveFormat, String
" not supported by ", Toolkit -> String
forall a. Show a => a -> String
show Toolkit
toolkit]
        Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
err Text
msg
      FigureSpec -> StateT PlotState (ReaderT RuntimeEnv IO) FigureSpec
forall (m :: * -> *) a. Monad m => a -> m a
return FigureSpec :: Toolkit
-> Text
-> Bool
-> Text
-> SaveFormat
-> String
-> Int
-> [String]
-> [(Text, Text)]
-> (Text, [Text], [(Text, Text)])
-> FigureSpec
FigureSpec {Bool
Int
String
[String]
[(Text, Text)]
(Text, [Text], [(Text, Text)])
Text
SaveFormat
Toolkit
blockAttrs :: (Text, [Text], [(Text, Text)])
extraAttrs :: [(Text, Text)]
dependencies :: [String]
dpi :: Int
directory :: String
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
toolkit :: Toolkit
dependencies :: [String]
blockAttrs :: (Text, [Text], [(Text, Text)])
extraAttrs :: [(Text, Text)]
dpi :: Int
directory :: String
saveFormat :: SaveFormat
script :: Text
withSource :: Bool
caption :: Text
toolkit :: Toolkit
..}
parseFigureSpec Block
_ = Maybe FigureSpec -> PlotM (Maybe FigureSpec)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FigureSpec
forall a. Maybe a
Nothing

-- | Parse script content from a block, if possible.

-- The script content can either come from a file

-- or from the code block itself. If both are present,

-- the file is preferred.

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 String
mfile = String -> String
normalise (String -> String) -> (Text -> String) -> Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
unpack (Text -> String) -> Maybe Text -> Maybe String
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 String -> Bool
forall a. Maybe a -> Bool
isJust Maybe String
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) ()
err (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 (",
          String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Maybe String -> String
forall a. HasCallStack => Maybe a -> a
fromJust Maybe String
mfile,
          Text
") but also has content in the document.\nThe file content will be preferred."
        ]
  let loadFromFile :: String -> StateT PlotState (ReaderT RuntimeEnv IO) Text
loadFromFile String
fp = do
        Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
info (Text -> StateT PlotState (ReaderT RuntimeEnv IO) ())
-> Text -> StateT PlotState (ReaderT RuntimeEnv IO) ()
forall a b. (a -> b) -> a -> b
$ Text
"Loading figure content from " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack String
fp
        IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> IO Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall a b. (a -> b) -> a -> b
$ String -> IO Text
TIO.readFile String
fp
  StateT PlotState (ReaderT RuntimeEnv IO) Text
-> (String -> StateT PlotState (ReaderT RuntimeEnv IO) Text)
-> Maybe String
-> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
content) String -> StateT PlotState (ReaderT RuntimeEnv IO) Text
loadFromFile Maybe String
mfile
parseContent Block
_ = Text -> StateT PlotState (ReaderT RuntimeEnv IO) Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
forall a. Monoid a => a
mempty

-- | Determine which toolkit should be used to render the plot

-- from a code block, if any.

plotToolkit :: Block -> Maybe Toolkit
plotToolkit :: Block -> Maybe Toolkit
plotToolkit (CodeBlock (Text
_, [Text]
classes, [(Text, Text)]
_) Text
_) =
  [Toolkit] -> Maybe Toolkit
forall a. [a] -> Maybe a
listToMaybe ([Toolkit] -> Maybe Toolkit) -> [Toolkit] -> Maybe Toolkit
forall a b. (a -> b) -> a -> b
$ (Toolkit -> Bool) -> [Toolkit] -> [Toolkit]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Toolkit
tk -> Toolkit -> Text
cls Toolkit
tk Text -> [Text] -> 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

-- | Reader a caption, based on input document format

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
    (Reader PandocPure
reader, Extensions
exts) <- Text -> PandocPure (Reader PandocPure, Extensions)
forall (m :: * -> *).
PandocMonad m =>
Text -> m (Reader m, Extensions)
getReader Text
f
    let readerOpts :: ReaderOptions
readerOpts = ReaderOptions
forall a. Default a => a
def {readerExtensions :: Extensions
readerExtensions = Extensions
exts}
    -- Assuming no ByteString readers...

    case Reader PandocPure
reader of
      TextReader ReaderOptions -> Text -> PandocPure Pandoc
fct -> ReaderOptions -> Text -> PandocPure Pandoc
fct ReaderOptions
readerOpts Text
t
      Reader PandocPure
_ -> Pandoc -> PandocPure Pandoc
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
_ = []

-- | Flexible boolean parsing

readBool :: Text -> Bool
readBool :: Text -> Bool
readBool Text
s
  | Text
s Text -> [Text] -> 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 (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 = String -> Bool
forall a. String -> a
errorWithoutStackTrace (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> String
unpack (Text -> String) -> Text -> String
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'"]

-- | Parse a list of file dependencies such as /[foo.bar, hello.txt]/.

parseFileDependencies :: Text -> [FilePath]
parseFileDependencies :: Text -> [String]
parseFileDependencies Text
t
  | Text
t Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
forall a. Monoid a => a
mempty = [String]
forall a. Monoid a => a
mempty
  | Bool
otherwise =
    (String -> String) -> [String] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> String
normalise
      ([String] -> [String]) -> (Text -> [String]) -> Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> String) -> [Text] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> String
unpack
      ([Text] -> [String]) -> (Text -> [Text]) -> Text -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char -> Bool) -> Text -> Text
T.dropAround Char -> Bool
isSpace) -- Remove leading/trailing whitespace on filenames

      ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'[', Char
']'])
      (Text -> [String]) -> Text -> [String]
forall a b. (a -> b) -> a -> b
$ Text
t