aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Custom.hs
blob: 7b6c99ed8e25a5ce9988e02da2b7dbc08b7d4669 (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
{-# LANGUAGE FlexibleContexts    #-}
{-# LANGUAGE FlexibleInstances   #-}
{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications    #-}
{- |
   Module      : Text.Pandoc.Readers.Custom
   Copyright   : Copyright (C) 2021 John MacFarlane
   License     : GNU GPL, version 2 or above

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

Supports custom parsers written in Lua which produce a Pandoc AST.
-}
module Text.Pandoc.Readers.Custom ( readCustom ) where
import Control.Exception
import Control.Monad (when)
import HsLua as Lua hiding (Operation (Div), render)
import HsLua.Class.Peekable (PeekError)
import Control.Monad.IO.Class (MonadIO)
import Text.Pandoc.Definition
import Text.Pandoc.Lua (Global (..), runLua, setGlobals)
import Text.Pandoc.Lua.Util (dofileWithTraceback)
import Text.Pandoc.Options
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Sources (Sources, ToSources(..))

-- | Convert custom markup to Pandoc.
readCustom :: (PandocMonad m, MonadIO m, ToSources s)
            => FilePath -> ReaderOptions -> s -> m Pandoc
readCustom luaFile opts srcs = do
  let input = toSources srcs
  let globals = [ PANDOC_SCRIPT_FILE luaFile ]
  res <- runLua $ do
    setGlobals globals
    stat <- dofileWithTraceback luaFile
    -- check for error in lua script (later we'll change the return type
    -- to handle this more gracefully):
    when (stat /= Lua.OK)
      Lua.throwErrorAsException
    parseCustom input opts
  case res of
    Left msg -> throw msg
    Right doc -> return doc

parseCustom :: forall e. PeekError e
            => Sources
            -> ReaderOptions
            -> LuaE e Pandoc
parseCustom = invoke @e "Reader"