aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Lua/Module/System.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Lua/Module/System.hs')
-rw-r--r--src/Text/Pandoc/Lua/Module/System.hs41
1 files changed, 23 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Lua/Module/System.hs b/src/Text/Pandoc/Lua/Module/System.hs
index bd35babaf..e329a0125 100644
--- a/src/Text/Pandoc/Lua/Module/System.hs
+++ b/src/Text/Pandoc/Lua/Module/System.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Lua.Module.System
Copyright : © 2019-2021 Albert Krewinkel
@@ -9,25 +11,28 @@
Pandoc's system Lua module.
-}
module Text.Pandoc.Lua.Module.System
- ( pushModule
+ ( documentedModule
) where
-import Foreign.Lua (Lua, NumResults)
-import Foreign.Lua.Module.System (arch, env, getwd, os,
- with_env, with_tmpdir, with_wd)
-import Text.Pandoc.Lua.Util (addFunction, addField)
-
-import qualified Foreign.Lua as Lua
+import HsLua
+import HsLua.Module.System
+ (arch, env, getwd, os, with_env, with_tmpdir, with_wd)
-- | Push the pandoc.system module on the Lua stack.
-pushModule :: Lua NumResults
-pushModule = do
- Lua.newtable
- addField "arch" arch
- addField "os" os
- addFunction "environment" env
- addFunction "get_working_directory" getwd
- addFunction "with_environment" with_env
- addFunction "with_temporary_directory" with_tmpdir
- addFunction "with_working_directory" with_wd
- return 1
+documentedModule :: LuaError e => Module e
+documentedModule = Module
+ { moduleName = "pandoc.system"
+ , moduleDescription = "system functions"
+ , moduleFields =
+ [ arch
+ , os
+ ]
+ , moduleFunctions =
+ [ setName "environment" env
+ , setName "get_working_directory" getwd
+ , setName "with_environment" with_env
+ , setName "with_temporary_directory" with_tmpdir
+ , setName "with_working_directory" with_wd
+ ]
+ , moduleOperations = []
+ }