aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-09-24 14:47:01 +0200
committerJohn MacFarlane <[email protected]>2022-09-30 08:33:40 -0700
commit704f337697db0a061817cb02c186841cf999db83 (patch)
tree43d684a7b8ad90c7d90ed2ef12a8c174242a86b5 /src
parentddaadc88bc7e09fdff35fcf100a0f9fbe5d17728 (diff)
[API Change] Export new module Text.Pandoc.Scripting
The module contains the central data structure for scripting engines.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Scripting.hs53
1 files changed, 53 insertions, 0 deletions
diff --git a/src/Text/Pandoc/Scripting.hs b/src/Text/Pandoc/Scripting.hs
new file mode 100644
index 000000000..a16f273af
--- /dev/null
+++ b/src/Text/Pandoc/Scripting.hs
@@ -0,0 +1,53 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ImpredicativeTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{- |
+Module : Text.Pandoc.Scripting
+Copyright : © 2022 Albert Krewinkel
+License : GPL-2.0-or-later
+Maintainer : Albert Krewinkel <[email protected]>
+
+Central data structure for scripting engines.
+-}
+module Text.Pandoc.Scripting
+ ( ScriptingEngine (..)
+ , noEngine
+ )
+where
+
+import Control.Monad.IO.Class (MonadIO)
+import Data.Text (Text)
+import Text.Pandoc.Definition (Pandoc)
+import Text.Pandoc.Class.PandocMonad (PandocMonad)
+import Text.Pandoc.Filter.Environment (Environment)
+import Text.Pandoc.Options (ReaderOptions, WriterOptions)
+import Text.Pandoc.Sources (Sources)
+
+-- | Structure to define a scripting engine.
+data ScriptingEngine = ScriptingEngine
+ { engineName :: Text -- ^ Name of the engine.
+
+ , engineApplyFilter :: forall m. (PandocMonad m, MonadIO m)
+ => Environment -> [String] -> FilePath
+ -> Pandoc -> m Pandoc
+ -- ^ Use the scripting engine to run a filter.
+
+ , engineReadCustom :: forall m. (PandocMonad m, MonadIO m)
+ => FilePath -> ReaderOptions -> Sources -> m Pandoc
+ -- ^ Function to parse input into a 'Pandoc' document.
+
+ , engineWriteCustom :: forall m. (PandocMonad m, MonadIO m)
+ => FilePath -> WriterOptions -> Pandoc -> m Text
+ -- ^ Invoke the given script file to convert to any custom format.
+ }
+
+noEngine :: ScriptingEngine
+noEngine = ScriptingEngine
+ { engineName = "none"
+ , engineApplyFilter = \_env _args _fp _doc ->
+ error "Custom filters are not supported."
+ , engineReadCustom = \_fp _ropts _sources ->
+ error "Custom readers are not supported."
+ , engineWriteCustom = \_fp _wopts _doc ->
+ error "Custom writers are not supported."
+ }