module Foreign.Lua.Util
( getglobal'
, setglobal'
, run
, run'
, runEither
, raiseError
, Optional (Optional, fromOptional)
, runWith
, peekEither
, peekRead
, popValue
) where
import Control.Exception (bracket, try)
import Data.List (groupBy)
import Foreign.Lua.Core (Lua, NumResults, StackIndex)
import Foreign.Lua.Types (Peekable, Pushable)
import Text.Read (readMaybe)
import qualified Control.Monad.Catch as Catch
import qualified Foreign.Lua.Core as Lua
import qualified Foreign.Lua.Types as Lua
run :: Lua a -> IO a
run = (Lua.newstate `bracket` Lua.close) . flip runWith . Catch.mask_
run' :: Lua.ErrorConversion -> Lua a -> IO a
run' ec = (Lua.newstate `bracket` Lua.close) .
flip (Lua.runWithConverter ec) . Catch.mask_
runEither :: Catch.Exception e => Lua a -> IO (Either e a)
runEither = try . run
runWith :: Lua.State -> Lua a -> IO a
runWith = Lua.runWithConverter defaultErrorConversion
defaultErrorConversion :: Lua.ErrorConversion
defaultErrorConversion = Lua.ErrorConversion
{ Lua.errorToException = Lua.throwTopMessageWithState
, Lua.addContextToException = Lua.withExceptionMessage . (++)
, Lua.alternative = \x y -> Lua.try x >>= \case
Left _ -> y
Right x' -> return x'
, Lua.exceptionToError = (`Lua.catchException` \ (Lua.Exception msg) ->
raiseError msg)
}
getglobal' :: String -> Lua ()
getglobal' = getnested . splitdot
setglobal' :: String -> Lua ()
setglobal' s =
case reverse (splitdot s) of
[] ->
return ()
[_] ->
Lua.setglobal s
(lastField : xs) -> do
getnested (reverse xs)
Lua.pushvalue (Lua.nthFromTop 2)
Lua.setfield (Lua.nthFromTop 2) lastField
Lua.pop 1
splitdot :: String -> [String]
splitdot = filter (/= ".") . groupBy (\a b -> a /= '.' && b /= '.')
getnested :: [String] -> Lua ()
getnested [] = return ()
getnested (x:xs) = do
Lua.getglobal x
mapM_ (\a -> Lua.getfield Lua.stackTop a *> Lua.remove (Lua.nthFromTop 2)) xs
raiseError :: Pushable a => a -> Lua NumResults
raiseError e = do
Lua.push e
Lua.error
{-# INLINABLE raiseError #-}
newtype Optional a = Optional { fromOptional :: Maybe a }
instance Peekable a => Peekable (Optional a) where
peek idx = do
noValue <- Lua.isnoneornil idx
if noValue
then return $ Optional Nothing
else Optional . Just <$> Lua.peek idx
instance Pushable a => Pushable (Optional a) where
push (Optional Nothing) = Lua.pushnil
push (Optional (Just x)) = Lua.push x
peekRead :: Read a => StackIndex -> Lua a
peekRead idx = do
s <- Lua.peek idx
case readMaybe s of
Just x -> return x
Nothing -> Lua.throwException ("Could not read: " ++ s)
peekEither :: Peekable a => StackIndex -> Lua (Either String a)
peekEither idx = either (Left . Lua.exceptionMessage) Right <$>
Lua.try (Lua.peek idx)
popValue :: Peekable a => Lua a
popValue = Lua.peek Lua.stackTop `Catch.finally` Lua.pop 1
{-# INLINABLE popValue #-}