aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/CLI.hs
blob: 01c94cdbb7bbff31f5a0cc38be20d74d2162557b (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
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Lua.Module.CLI
   Copyright   : © 2022 Albert Krewinkel
   License     : GPL-2.0-or-later
   Maintainer  : Albert Krewinkel <[email protected]>

Command line helpers
-}
module Text.Pandoc.Lua.Module.CLI
  ( documentedModule
  ) where

import Control.Applicative ((<|>))
import HsLua ( Field (..), Module (..), (###), (<#>), (=#>), (#?)
             , defun, failLua, functionResult, liftIO, parameter, pop
             , pushViaJSON, rawgeti, top)
import HsLua.Marshalling (lastly, liftLua, peekList, peekString)
import Text.Pandoc.App (defaultOpts, options, parseOptionsFromArgs)
import Text.Pandoc.Error (PandocError)
import Text.Pandoc.Lua.PandocLua ()
import qualified Data.Text as T

-- | Push the pandoc.types module on the Lua stack.
documentedModule :: Module PandocError
documentedModule = Module
  { moduleName = "pandoc.cli"
  , moduleDescription =
      "Command line options and argument parsing."
  , moduleFields =
      [ Field
        { fieldName = "default_options"
        , fieldDescription = "Default CLI options, using a JSON-like " <>
          "representation."
        , fieldPushValue = pushViaJSON defaultOpts
        }
      ]
  , moduleFunctions =
      [ defun "parse_options"
        ### parseOptions
        <#> parameter peekArgs "{string,...}" "args"
              "list of command line arguments"
        =#> functionResult pushViaJSON "table"
              "parsed options, using their JSON-like representation."
        #? T.unlines
           [ "Parses command line arguments into pandoc options."
           , "Typically this function will be used in stand-alone pandoc Lua"
           , "scripts, taking the list of arguments from the global `arg`."
           ]
      ]
  , moduleOperations = []
  }
 where
  peekArgs idx =
    (,)
    <$> (liftLua (rawgeti idx 0) *> (peekString top <|> pure "") `lastly` pop 1)
    <*> peekList peekString idx

  parseOptions (prg, args) =
    liftIO (parseOptionsFromArgs options defaultOpts prg args) >>=
    \case
      Left e     -> failLua $ "Cannot process info option: " ++ show e
      Right opts -> pure opts