aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/System.hs
blob: ef5c63d6ae9d03204b61da7e9016146fd9e3b13c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications    #-}
{- |
   Module      : Text.Pandoc.Lua.Module.System
   Copyright   : © 2019-2024 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <[email protected]>
   Stability   : alpha

Pandoc's system Lua module.
-}
module Text.Pandoc.Lua.Module.System
  ( documentedModule
  ) where

import Data.Version (makeVersion)
import HsLua
import HsLua.Module.System
  ( arch, cputime, env, getwd, ls, mkdir, os, rmdir
  , with_env, with_tmpdir, with_wd)
import qualified HsLua.Module.System as MSys

-- | Push the pandoc.system module on the Lua stack.
documentedModule :: forall e. LuaError e => Module e
documentedModule = Module
  { moduleName = "pandoc.system"
  , moduleDescription = moduleDescription @e MSys.documentedModule
  , moduleFields =
      [ arch
      , os
      ]
  , moduleFunctions =
      [ cputime                                        `since` v[3,1,1]
      , setName "environment" env                      `since` v[2,7,3]
      , setName "get_working_directory" getwd          `since` v[2,8]
      , setName "list_directory" ls                    `since` v[2,19]
      , setName "make_directory" mkdir                 `since` v[2,19]
      , setName "remove_directory" rmdir               `since` v[2,19]
      , setName "with_environment" with_env            `since` v[2,7,3]
      , setName "with_temporary_directory" with_tmpdir `since` v[2,8]
      , setName "with_working_directory" with_wd       `since` v[2,7,3]
      ]
  , moduleOperations = []
  , moduleTypeInitializers = []
  }
 where
  v = makeVersion