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
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
|
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
Module : Text.Pandoc.Lua.PandocLua
Copyright : Copyright © 2020-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability : alpha
PandocMonad instance which allows execution of Lua operations and which
uses Lua to handle state.
-}
module Text.Pandoc.Lua.PandocLua
( PandocLua (..)
, runPandocLua
, liftPandocLua
, addFunction
, loadDefaultModule
) where
import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow)
import Control.Monad.Except (MonadError (catchError, throwError))
import Control.Monad.IO.Class (MonadIO)
import HsLua as Lua
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), readDefaultDataFile)
import Text.Pandoc.Error (PandocError (PandocLuaError))
import Text.Pandoc.Lua.Global (Global (..), setGlobals)
import Text.Pandoc.Lua.Marshaling.CommonState (peekCommonState)
import qualified Control.Monad.Catch as Catch
import qualified Data.Text as T
import qualified Text.Pandoc.Class.IO as IO
-- | Type providing access to both, pandoc and Lua operations.
newtype PandocLua a = PandocLua { unPandocLua :: LuaE PandocError a }
deriving
( Applicative
, Functor
, Monad
, MonadCatch
, MonadIO
, MonadMask
, MonadThrow
)
-- | Lift a @'Lua'@ operation into the @'PandocLua'@ type.
liftPandocLua :: LuaE PandocError a -> PandocLua a
liftPandocLua = PandocLua
-- | Evaluate a @'PandocLua'@ computation, running all contained Lua
-- operations..
runPandocLua :: (PandocMonad m, MonadIO m) => PandocLua a -> m a
runPandocLua pLua = do
origState <- getCommonState
globals <- defaultGlobals
(result, newState) <- liftIO . Lua.run . unPandocLua $ do
putCommonState origState
liftPandocLua $ setGlobals globals
r <- pLua
c <- getCommonState
return (r, c)
putCommonState newState
return result
instance {-# OVERLAPPING #-} Exposable PandocError (PandocLua NumResults) where
partialApply _narg = unPandocLua
instance Pushable a => Exposable PandocError (PandocLua a) where
partialApply _narg x = 1 <$ (unPandocLua x >>= Lua.push)
-- | Add a function to the table at the top of the stack, using the given name.
addFunction :: Exposable PandocError a => Name -> a -> PandocLua ()
addFunction name fn = liftPandocLua $ do
Lua.pushName name
Lua.pushHaskellFunction $ toHaskellFunction fn
Lua.rawset (-3)
-- | Load a pure Lua module included with pandoc. Leaves the result on
-- the stack and returns @NumResults 1@.
--
-- The script is loaded from the default data directory. We do not load
-- from data directories supplied via command line, as this could cause
-- scripts to be executed even though they had not been passed explicitly.
loadDefaultModule :: String -> PandocLua NumResults
loadDefaultModule name = do
script <- readDefaultDataFile (name <> ".lua")
result <- liftPandocLua $ Lua.dostring script
if result == Lua.OK
then return (1 :: NumResults)
else do
msg <- liftPandocLua Lua.popValue
let err = "Error while loading `" <> name <> "`.\n" <> msg
throwError $ PandocLuaError (T.pack err)
-- | Global variables which should always be set.
defaultGlobals :: PandocMonad m => m [Global]
defaultGlobals = do
commonState <- getCommonState
return
[ PANDOC_API_VERSION
, PANDOC_STATE commonState
, PANDOC_VERSION
]
instance MonadError PandocError PandocLua where
catchError = Catch.catch
throwError = Catch.throwM
instance PandocMonad PandocLua where
lookupEnv = IO.lookupEnv
getCurrentTime = IO.getCurrentTime
getCurrentTimeZone = IO.getCurrentTimeZone
newStdGen = IO.newStdGen
newUniqueHash = IO.newUniqueHash
openURL = IO.openURL
readFileLazy = IO.readFileLazy
readFileStrict = IO.readFileStrict
readStdinStrict = IO.readStdinStrict
glob = IO.glob
fileExists = IO.fileExists
getDataFileName = IO.getDataFileName
getModificationTime = IO.getModificationTime
getCommonState = PandocLua $ do
Lua.getglobal "PANDOC_STATE"
forcePeek $ peekCommonState Lua.top
putCommonState = PandocLua . setGlobals . (:[]) . PANDOC_STATE
logOutput = IO.logOutput
|