{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Lua.Util
   Copyright   : © 2012-2021 John MacFarlane,
                 © 2017-2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
   Stability   : alpha

Lua utility functions.
-}
module Text.Pandoc.Lua.Util
  ( getTag
  , rawField
  , addField
  , addFunction
  , addValue
  , pushViaConstructor
  , defineHowTo
  , throwTopMessageAsError'
  , callWithTraceback
  , dofileWithTraceback
  ) where

import Control.Monad (unless, when)
import Data.Text (Text)
import Foreign.Lua ( Lua, NumArgs, NumResults, Peekable, Pushable, StackIndex
                   , Status, ToHaskellFunction )
import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.UTF8 as UTF8

-- | Get value behind key from table at given index.
rawField :: Peekable a => StackIndex -> String -> Lua a
rawField :: StackIndex -> String -> Lua a
rawField StackIndex
idx String
key = do
  StackIndex
absidx <- StackIndex -> Lua StackIndex
Lua.absindex StackIndex
idx
  String -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push String
key
  StackIndex -> Lua ()
Lua.rawget StackIndex
absidx
  Lua a
forall a. Peekable a => Lua a
Lua.popValue

-- | Add a value to the table at the top of the stack at a string-index.
addField :: Pushable a => String -> a -> Lua ()
addField :: String -> a -> Lua ()
addField = String -> a -> Lua ()
forall a b. (Pushable a, Pushable b) => a -> b -> Lua ()
addValue

-- | Add a key-value pair to the table at the top of the stack.
addValue :: (Pushable a, Pushable b) => a -> b -> Lua ()
addValue :: a -> b -> Lua ()
addValue a
key b
value = do
  a -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push a
key
  b -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push b
value
  StackIndex -> Lua ()
Lua.rawset (CInt -> StackIndex
Lua.nthFromTop CInt
3)

-- | Add a function to the table at the top of the stack, using the given name.
addFunction :: ToHaskellFunction a => String -> a -> Lua ()
addFunction :: String -> a -> Lua ()
addFunction String
name a
fn = do
  String -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push String
name
  a -> Lua ()
forall a. ToHaskellFunction a => a -> Lua ()
Lua.pushHaskellFunction a
fn
  StackIndex -> Lua ()
Lua.rawset (-StackIndex
3)

-- | Helper class for pushing a single value to the stack via a lua function.
-- See @pushViaCall@.
class PushViaCall a where
  pushViaCall' :: String -> Lua () -> NumArgs -> a

instance PushViaCall (Lua ()) where
  pushViaCall' :: String -> Lua () -> NumArgs -> Lua ()
pushViaCall' String
fn Lua ()
pushArgs NumArgs
num = do
    String -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push String
fn
    StackIndex -> Lua ()
Lua.rawget StackIndex
Lua.registryindex
    Lua ()
pushArgs
    NumArgs -> NumResults -> Lua ()
Lua.call NumArgs
num NumResults
1

instance (Pushable a, PushViaCall b) => PushViaCall (a -> b) where
  pushViaCall' :: String -> Lua () -> NumArgs -> a -> b
pushViaCall' String
fn Lua ()
pushArgs NumArgs
num a
x =
    String -> Lua () -> NumArgs -> b
forall a. PushViaCall a => String -> Lua () -> NumArgs -> a
pushViaCall' String
fn (Lua ()
pushArgs Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> a -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push a
x) (NumArgs
num NumArgs -> NumArgs -> NumArgs
forall a. Num a => a -> a -> a
+ NumArgs
1)

-- | Push an value to the stack via a lua function. The lua function is called
-- with all arguments that are passed to this function and is expected to return
-- a single value.
pushViaCall :: PushViaCall a => String -> a
pushViaCall :: String -> a
pushViaCall String
fn = String -> Lua () -> NumArgs -> a
forall a. PushViaCall a => String -> Lua () -> NumArgs -> a
pushViaCall' String
fn (() -> Lua ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()) NumArgs
0

-- | Call a pandoc element constructor within Lua, passing all given arguments.
pushViaConstructor :: PushViaCall a => String -> a
pushViaConstructor :: String -> a
pushViaConstructor String
pandocFn = String -> a
forall a. PushViaCall a => String -> a
pushViaCall (String
"pandoc." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
pandocFn)

-- | Get the tag of a value. This is an optimized and specialized version of
-- @Lua.getfield idx "tag"@. It only checks for the field on the table at index
-- @idx@ and on its metatable, also ignoring any @__index@ value on the
-- metatable.
getTag :: StackIndex -> Lua String
getTag :: StackIndex -> Lua String
getTag StackIndex
idx = do
  -- push metatable or just the table
  StackIndex -> Lua Bool
Lua.getmetatable StackIndex
idx Lua Bool -> (Bool -> Lua ()) -> Lua ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
hasMT -> Bool -> Lua () -> Lua ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless Bool
hasMT (StackIndex -> Lua ()
Lua.pushvalue StackIndex
idx)
  Text -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push (Text
"tag" :: Text)
  StackIndex -> Lua ()
Lua.rawget (CInt -> StackIndex
Lua.nthFromTop CInt
2)
  StackIndex -> Lua (Maybe ByteString)
Lua.tostring StackIndex
Lua.stackTop Lua (Maybe ByteString) -> Lua () -> Lua (Maybe ByteString)
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* StackIndex -> Lua ()
Lua.pop StackIndex
2 Lua (Maybe ByteString)
-> (Maybe ByteString -> Lua String) -> Lua String
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
    Maybe ByteString
Nothing -> String -> Lua String
forall a. String -> Lua a
Lua.throwMessage String
"untagged value"
    Just ByteString
x -> String -> Lua String
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> String
UTF8.toString ByteString
x)

-- | Modify the message at the top of the stack before throwing it as an
-- Exception.
throwTopMessageAsError' :: (String -> String) -> Lua a
throwTopMessageAsError' :: (String -> String) -> Lua a
throwTopMessageAsError' String -> String
modifier = do
  ByteString
msg <- StackIndex -> Lua ByteString
Lua.tostring' StackIndex
Lua.stackTop
  StackIndex -> Lua ()
Lua.pop StackIndex
2 -- remove error and error string pushed by tostring'
  String -> Lua a
forall a. String -> Lua a
Lua.throwMessage (String -> String
modifier (ByteString -> String
UTF8.toString ByteString
msg))

-- | Mark the context of a Lua computation for better error reporting.
defineHowTo :: String -> Lua a -> Lua a
defineHowTo :: String -> Lua a -> Lua a
defineHowTo String
ctx Lua a
op = Lua ErrorConversion
Lua.errorConversion Lua ErrorConversion -> (ErrorConversion -> Lua a) -> Lua a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \ErrorConversion
ec ->
  ErrorConversion -> String -> Lua a -> Lua a
ErrorConversion -> forall a. String -> Lua a -> Lua a
Lua.addContextToException ErrorConversion
ec (String
"Could not " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
ctx String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
": ") Lua a
op

-- | Like @'Lua.pcall'@, but uses a predefined error handler which adds a
-- traceback on error.
pcallWithTraceback :: NumArgs -> NumResults -> Lua Status
pcallWithTraceback :: NumArgs -> NumResults -> Lua Status
pcallWithTraceback NumArgs
nargs NumResults
nresults = do
  let traceback' :: Lua NumResults
      traceback' :: Lua NumResults
traceback' = do
        State
l <- Lua State
Lua.state
        ByteString
msg <- StackIndex -> Lua ByteString
Lua.tostring' (CInt -> StackIndex
Lua.nthFromBottom CInt
1)
        State -> Maybe String -> Int -> Lua ()
Lua.traceback State
l (String -> Maybe String
forall a. a -> Maybe a
Just (ByteString -> String
UTF8.toString ByteString
msg)) Int
2
        NumResults -> Lua NumResults
forall (m :: * -> *) a. Monad m => a -> m a
return NumResults
1
  StackIndex
tracebackIdx <- StackIndex -> Lua StackIndex
Lua.absindex (CInt -> StackIndex
Lua.nthFromTop (NumArgs -> CInt
Lua.fromNumArgs NumArgs
nargs CInt -> CInt -> CInt
forall a. Num a => a -> a -> a
+ CInt
1))
  Lua NumResults -> Lua ()
forall a. ToHaskellFunction a => a -> Lua ()
Lua.pushHaskellFunction Lua NumResults
traceback'
  StackIndex -> Lua ()
Lua.insert StackIndex
tracebackIdx
  Status
result <- NumArgs -> NumResults -> Maybe StackIndex -> Lua Status
Lua.pcall NumArgs
nargs NumResults
nresults (StackIndex -> Maybe StackIndex
forall a. a -> Maybe a
Just StackIndex
tracebackIdx)
  StackIndex -> Lua ()
Lua.remove StackIndex
tracebackIdx
  Status -> Lua Status
forall (m :: * -> *) a. Monad m => a -> m a
return Status
result

-- | Like @'Lua.call'@, but adds a traceback to the error message (if any).
callWithTraceback :: NumArgs -> NumResults -> Lua ()
callWithTraceback :: NumArgs -> NumResults -> Lua ()
callWithTraceback NumArgs
nargs NumResults
nresults = do
  Status
result <- NumArgs -> NumResults -> Lua Status
pcallWithTraceback NumArgs
nargs NumResults
nresults
  Bool -> Lua () -> Lua ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Status
result Status -> Status -> Bool
forall a. Eq a => a -> a -> Bool
/= Status
Lua.OK)
    Lua ()
forall a. Lua a
Lua.throwTopMessage

-- | Run the given string as a Lua program, while also adding a traceback to the
-- error message if an error occurs.
dofileWithTraceback :: FilePath -> Lua Status
dofileWithTraceback :: String -> Lua Status
dofileWithTraceback String
fp = do
  Status
loadRes <- String -> Lua Status
Lua.loadfile String
fp
  case Status
loadRes of
    Status
Lua.OK -> NumArgs -> NumResults -> Lua Status
pcallWithTraceback NumArgs
0 NumResults
Lua.multret
    Status
_ -> Status -> Lua Status
forall (m :: * -> *) a. Monad m => a -> m a
return Status
loadRes