aboutsummaryrefslogtreecommitdiff
path: root/pandoc-cli/src/pandoc-wasm.hs
blob: a8d7cc80aa4b293fe505cc3e2e38e225ce0c8672 (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
65
66
67
68
69
70
71
72
73
74
{-# LANGUAGE ScopedTypeVariables #-}

{- |
   Module      : Main
   Copyright   : Copyright (C) 2006-2024 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley@edu>
   Stability   : alpha
   Portability : portable

Parses command-line options and calls the appropriate readers and
writers (wasm version).
-}
module Main where
import qualified Data.Map as M
import Text.Read (readMaybe)
import qualified Control.Exception as E
import Data.Maybe (fromMaybe)
import Text.Pandoc.App ( convertWithOpts, Opt(..), defaultOpts )
import Text.Pandoc (Verbosity(ERROR))
import Text.Pandoc.Extensions (extensionsToList, extensionEnabled, getAllExtensions,
                               getDefaultExtensions)
import PandocCLI.Lua
import Control.Exception
import Foreign
import Foreign.C
import qualified Data.Aeson as Aeson
import qualified Text.Pandoc.UTF8 as UTF8
import qualified Data.ByteString.Lazy as BL

foreign export ccall "wasm_main" wasm_main :: Ptr CChar -> Int -> IO ()

wasm_main :: Ptr CChar -> Int -> IO ()
wasm_main raw_args_ptr raw_args_len =
  E.catch act (\(err :: SomeException) ->
                 writeFile "/stderr" ("ERROR: " <> displayException err))
  where
    act = do
      args <- peekCStringLen (raw_args_ptr, raw_args_len)
      free raw_args_ptr
      engine <- getEngine
      let aesonRes = Aeson.eitherDecode (UTF8.fromStringLazy args)
      case aesonRes of
        Left e -> error e
        Right (f :: Opt -> Opt) -> do
          let opts = f defaultOpts
          let opts' = opts{ optInputFiles =
                             Just $ fromMaybe ["/stdin"] (optInputFiles opts)
                          , optOutputFile =
                             Just $ fromMaybe "/stdout" (optOutputFile opts)
                          , optLogFile =
                             Just $ fromMaybe "/warnings" (optLogFile opts)
                          , optVerbosity = ERROR -- only show errors to stderr
                          }
          convertWithOpts engine opts'

foreign export ccall "get_extensions_for_format" getExtensionsForFormat :: Ptr CChar -> Int -> IO ()

getExtensionsForFormat :: Ptr CChar -> Int -> IO ()
getExtensionsForFormat raw_fmt_ptr raw_fmt_len = do
  formatName <- readMaybe <$> peekCStringLen (raw_fmt_ptr, raw_fmt_len)
  free raw_fmt_ptr
  case formatName of
    Just fmt -> do
       let allExts = getAllExtensions fmt
       let defExts = getDefaultExtensions fmt
       let addExt x = M.insert (drop 4 (show x)) (extensionEnabled x defExts)
       BL.writeFile "/stdout" $ Aeson.encode $ foldr addExt mempty (extensionsToList allExts)
    Nothing -> writeFile "/stdout" "{}"

-- This must be included or we get an error:
main :: IO ()
main = pure ()