diff options
Diffstat (limited to 'pandoc-lua-engine/src')
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs | 21 | ||||
| -rw-r--r-- | pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs | 18 |
2 files changed, 35 insertions, 4 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs index 3ebc4c03e..564ddd6d3 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs @@ -1,5 +1,6 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE TupleSections #-} {-# OPTIONS_GHC -fno-warn-orphans #-} {- | Module : Text.Pandoc.Lua.Marshaling.Format @@ -14,6 +15,7 @@ module Text.Pandoc.Lua.Marshal.Format ( peekExtensions , pushExtensions , peekExtensionsConfig + , pushExtensionsConfig , peekFlavoredFormat ) where @@ -23,20 +25,25 @@ import Data.Maybe (fromMaybe) import HsLua import Text.Pandoc.Error (PandocError (..)) import Text.Pandoc.Extensions - ( Extension, Extensions, extensionsFromList - , getDefaultExtensions, readExtension ) + ( Extension, Extensions, extensionsFromList, extensionsToList + , getDefaultExtensions, readExtension, showExtension ) import Text.Pandoc.Format ( ExtensionsConfig (..), ExtensionsDiff (..), FlavoredFormat (..) , diffExtensions, parseFlavoredFormat) import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua)) --- | Retrieves an 'Extensions' set from the Lua stack. +-- | Retrieves a single 'Extension' from the Lua stack. peekExtension :: LuaError e => Peeker e Extension peekExtension idx = do extString <- peekString idx return $ readExtension extString {-# INLINE peekExtension #-} +-- | Pushes an individual 'Extension' to the Lua stack. +pushExtension :: LuaError e => Pusher e Extension +pushExtension = pushText . showExtension +{-# INLINE pushExtension #-} + -- | Retrieves an 'Extensions' set from the Lua stack. peekExtensions :: LuaError e => Peeker e Extensions peekExtensions = fmap extensionsFromList . peekList peekExtension @@ -62,6 +69,14 @@ peekExtensionsConfig idx = do , extsSupported = extsToEnable diff <> extsToDisable diff } +-- | Pushes an 'ExtensionsConfig' value as a table with that maps +-- extensions to their default enabled/disabled status. +pushExtensionsConfig :: LuaError e => Pusher e ExtensionsConfig +pushExtensionsConfig (ExtensionsConfig def supported) = + pushKeyValuePairs pushExtension pushBool $ + map (,False) (extensionsToList supported) ++ + map (,True) (extensionsToList def) + instance Peekable ExtensionsConfig where safepeek = peekExtensionsConfig diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs index 8707acbf9..63753532a 100644 --- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs +++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Format.hs @@ -14,7 +14,8 @@ module Text.Pandoc.Lua.Module.Format import HsLua import Text.Pandoc.Error (PandocError) import Text.Pandoc.Extensions (getAllExtensions, getDefaultExtensions) -import Text.Pandoc.Lua.Marshal.Format (pushExtensions) +import Text.Pandoc.Format (getExtensionsConfig) +import Text.Pandoc.Lua.Marshal.Format (pushExtensions, pushExtensionsConfig) import Text.Pandoc.Lua.PandocLua () import qualified Data.Text as T @@ -56,4 +57,19 @@ functions = , "can have an effect when reading a format but not when" , "writing it, or *vice versa*." ] + + , defun "extensions" + ### liftPure getExtensionsConfig + <#> textParam "format" "format identifier" + =#> functionResult pushExtensionsConfig "table" "extensions config" + #? T.unlines + [ "Returns the extension configuration for the given format." + , "The configuration is represented as a table with all supported" + , "extensions as keys and their default status as value, with" + , "`true` indicating that the extension is enabled by default," + , "while `false` marks a supported extension that's disabled." + , "" + , "This function can be used to assign a value to the `Extensions`" + , "global in custom readers and writers." + ] ] |
