{-|
Module      : Foreign.Lua.Util
Copyright   : © 2007–2012 Gracjan Polak,
                2012–2016 Ömer Sinan Ağacan,
                2017-2020 Albert Krewinkel
License     : MIT
Maintainer  : Albert Krewinkel <tarleb+hslua@zeitkraut.de>
Stability   : beta
Portability : non-portable (depends on GHC)

HsLua utility functions.
-}
module Foreign.Lua.Util
  ( getglobal'
  , setglobal'
  , run
  , run'
  , runEither
  , raiseError
  , Optional (Optional, fromOptional)
    -- * Default error handling
  , runWith
    -- * getting values
  , 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 computation using the default HsLua state as starting point.
-- Exceptions are masked, thus avoiding some issues when using multiple threads.
-- All exceptions are passed through; error handling is the responsibility of
-- the caller.
run :: Lua a -> IO a
run :: Lua a -> IO a
run = (IO State
Lua.newstate IO State -> (State -> IO ()) -> (State -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
`bracket` State -> IO ()
Lua.close) ((State -> IO a) -> IO a)
-> (Lua a -> State -> IO a) -> Lua a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> Lua a -> IO a) -> Lua a -> State -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip State -> Lua a -> IO a
forall a. State -> Lua a -> IO a
runWith (Lua a -> State -> IO a)
-> (Lua a -> Lua a) -> Lua a -> State -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lua a -> Lua a
forall (m :: * -> *) a. MonadMask m => m a -> m a
Catch.mask_

-- | Run Lua computation using the default HsLua state as starting point.
-- Conversion from Lua errors to Haskell exceptions can be controlled through
-- @'Lua.ErrorConversion'@.
run' :: Lua.ErrorConversion -> Lua a -> IO a
run' :: ErrorConversion -> Lua a -> IO a
run' ErrorConversion
ec = (IO State
Lua.newstate IO State -> (State -> IO ()) -> (State -> IO a) -> IO a
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
`bracket` State -> IO ()
Lua.close) ((State -> IO a) -> IO a)
-> (Lua a -> State -> IO a) -> Lua a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
  (State -> Lua a -> IO a) -> Lua a -> State -> IO a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (ErrorConversion -> State -> Lua a -> IO a
forall a. ErrorConversion -> State -> Lua a -> IO a
Lua.runWithConverter ErrorConversion
ec) (Lua a -> State -> IO a)
-> (Lua a -> Lua a) -> Lua a -> State -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lua a -> Lua a
forall (m :: * -> *) a. MonadMask m => m a -> m a
Catch.mask_

-- | Run the given Lua computation; exceptions raised in haskell code are
-- caught, but other exceptions (user exceptions raised in haskell, unchecked
-- type errors, etc.) are passed through.
runEither :: Catch.Exception e => Lua a -> IO (Either e a)
runEither :: Lua a -> IO (Either e a)
runEither = IO a -> IO (Either e a)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO a -> IO (Either e a))
-> (Lua a -> IO a) -> Lua a -> IO (Either e a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Lua a -> IO a
forall a. Lua a -> IO a
run

-- | Run Lua computation with the given Lua state and the default
-- error-to-exception converter. Exception handling is left to
-- the caller.
runWith :: Lua.State -> Lua a -> IO a
runWith :: State -> Lua a -> IO a
runWith = ErrorConversion -> State -> Lua a -> IO a
forall a. ErrorConversion -> State -> Lua a -> IO a
Lua.runWithConverter ErrorConversion
defaultErrorConversion

-- | Conversions between Lua errors and Haskell exceptions; only deals with
-- @'Lua.Exception'@s.
defaultErrorConversion :: Lua.ErrorConversion
defaultErrorConversion :: ErrorConversion
defaultErrorConversion = ErrorConversion :: (forall a. State -> IO a)
-> (forall a. String -> Lua a -> Lua a)
-> (forall a. Lua a -> Lua a -> Lua a)
-> (Lua NumResults -> Lua NumResults)
-> ErrorConversion
Lua.ErrorConversion
  { errorToException :: forall a. State -> IO a
Lua.errorToException = forall a. State -> IO a
Lua.throwTopMessageWithState
  , addContextToException :: forall a. String -> Lua a -> Lua a
Lua.addContextToException = (String -> String) -> Lua a -> Lua a
forall a. (String -> String) -> Lua a -> Lua a
Lua.withExceptionMessage ((String -> String) -> Lua a -> Lua a)
-> (String -> String -> String) -> String -> Lua a -> Lua a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> String
forall a. [a] -> [a] -> [a]
(++)
  , alternative :: forall a. Lua a -> Lua a -> Lua a
Lua.alternative = \Lua a
x Lua a
y -> Lua a -> Lua (Either Exception a)
forall a. Lua a -> Lua (Either Exception a)
Lua.try Lua a
x Lua (Either Exception a) -> (Either Exception a -> Lua a) -> Lua a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
      Left Exception
_   -> Lua a
y
      Right a
x' -> a -> Lua a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x'
  , exceptionToError :: Lua NumResults -> Lua NumResults
Lua.exceptionToError = (Lua NumResults -> (Exception -> Lua NumResults) -> Lua NumResults
forall a. Lua a -> (Exception -> Lua a) -> Lua a
`Lua.catchException` \ (Lua.Exception String
msg) ->
                            String -> Lua NumResults
forall a. Pushable a => a -> Lua NumResults
raiseError String
msg)
  }

-- | Like @getglobal@, but knows about packages and nested tables. E.g.
--
-- > getglobal' "math.sin"
--
-- will return the function @sin@ in package @math@.
getglobal' :: String -> Lua ()
getglobal' :: String -> Lua ()
getglobal' = [String] -> Lua ()
getnested ([String] -> Lua ()) -> (String -> [String]) -> String -> Lua ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitdot

-- | Like @setglobal@, but knows about packages and nested tables. E.g.
--
-- > pushstring "0.9.4"
-- > setglobal' "mypackage.version"
--
-- All tables and fields, except for the last field, must exist.
setglobal' :: String -> Lua ()
setglobal' :: String -> Lua ()
setglobal' String
s =
  case [String] -> [String]
forall a. [a] -> [a]
reverse (String -> [String]
splitdot String
s) of
    [] ->
      () -> Lua ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    [String
_] ->
      String -> Lua ()
Lua.setglobal String
s
    (String
lastField : [String]
xs) -> do
      [String] -> Lua ()
getnested ([String] -> [String]
forall a. [a] -> [a]
reverse [String]
xs)
      StackIndex -> Lua ()
Lua.pushvalue (CInt -> StackIndex
Lua.nthFromTop CInt
2)
      StackIndex -> String -> Lua ()
Lua.setfield (CInt -> StackIndex
Lua.nthFromTop CInt
2) String
lastField
      StackIndex -> Lua ()
Lua.pop StackIndex
1

-- | Gives the list of the longest substrings not containing dots.
splitdot :: String -> [String]
splitdot :: String -> [String]
splitdot = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
".") ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char -> Bool) -> String -> [String]
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (\Char
a Char
b -> Char
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.' Bool -> Bool -> Bool
&& Char
b Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.')

-- | Pushes the value described by the strings to the stack; where the first
-- value is the name of a global variable and the following strings are the
-- field values in nested tables.
getnested :: [String] -> Lua ()
getnested :: [String] -> Lua ()
getnested [] = () -> Lua ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
getnested (String
x:[String]
xs) = do
  String -> Lua ()
Lua.getglobal String
x
  (String -> Lua ()) -> [String] -> Lua ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
a -> StackIndex -> String -> Lua ()
Lua.getfield StackIndex
Lua.stackTop String
a Lua () -> Lua () -> Lua ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> StackIndex -> Lua ()
Lua.remove (CInt -> StackIndex
Lua.nthFromTop CInt
2)) [String]
xs

-- | Raise a Lua error, using the given value as the error object.
raiseError :: Pushable a => a -> Lua NumResults
raiseError :: a -> Lua NumResults
raiseError a
e = do
  a -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push a
e
  Lua NumResults
Lua.error
{-# INLINABLE raiseError #-}

-- | Newtype wrapper intended to be used for optional Lua values. Nesting this
-- type is strongly discouraged as missing values on inner levels are
-- indistinguishable from missing values on an outer level; wrong values
-- would be the likely result.
newtype Optional a = Optional { Optional a -> Maybe a
fromOptional :: Maybe a }

instance Peekable a => Peekable (Optional a) where
  peek :: StackIndex -> Lua (Optional a)
peek StackIndex
idx = do
    Bool
noValue <- StackIndex -> Lua Bool
Lua.isnoneornil StackIndex
idx
    if Bool
noValue
      then Optional a -> Lua (Optional a)
forall (m :: * -> *) a. Monad m => a -> m a
return (Optional a -> Lua (Optional a)) -> Optional a -> Lua (Optional a)
forall a b. (a -> b) -> a -> b
$ Maybe a -> Optional a
forall a. Maybe a -> Optional a
Optional Maybe a
forall a. Maybe a
Nothing
      else Maybe a -> Optional a
forall a. Maybe a -> Optional a
Optional (Maybe a -> Optional a) -> (a -> Maybe a) -> a -> Optional a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just (a -> Optional a) -> Lua a -> Lua (Optional a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
Lua.peek StackIndex
idx

instance Pushable a => Pushable (Optional a) where
  push :: Optional a -> Lua ()
push (Optional Maybe a
Nothing)  = Lua ()
Lua.pushnil
  push (Optional (Just a
x)) = a -> Lua ()
forall a. Pushable a => a -> Lua ()
Lua.push a
x


--
-- Getting Values
--

-- | Get a value by retrieving a String from Lua, then using @'readMaybe'@ to
-- convert the String into a Haskell value.
peekRead :: Read a => StackIndex -> Lua a
peekRead :: StackIndex -> Lua a
peekRead StackIndex
idx = do
  String
s <- StackIndex -> Lua String
forall a. Peekable a => StackIndex -> Lua a
Lua.peek StackIndex
idx
  case String -> Maybe a
forall a. Read a => String -> Maybe a
readMaybe String
s of
    Just a
x -> a -> Lua a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
    Maybe a
Nothing -> String -> Lua a
forall a. String -> Lua a
Lua.throwException (String
"Could not read: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s)

-- | Try to convert the value at the given stack index to a Haskell value.
-- Returns @Left@ with an error message on failure.
--
-- WARNING: this is not save to use with custom error handling!
peekEither :: Peekable a => StackIndex -> Lua (Either String a)
peekEither :: StackIndex -> Lua (Either String a)
peekEither StackIndex
idx = (Exception -> Either String a)
-> (a -> Either String a) -> Either Exception a -> Either String a
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> Either String a
forall a b. a -> Either a b
Left (String -> Either String a)
-> (Exception -> String) -> Exception -> Either String a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Exception -> String
Lua.exceptionMessage) a -> Either String a
forall a b. b -> Either a b
Right (Either Exception a -> Either String a)
-> Lua (Either Exception a) -> Lua (Either String a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                 Lua a -> Lua (Either Exception a)
forall a. Lua a -> Lua (Either Exception a)
Lua.try (StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
Lua.peek StackIndex
idx)

-- | Get, then pop the value at the top of the stack. The pop operation is
-- executed even if the retrieval operation failed.
popValue :: Peekable a => Lua a
popValue :: Lua a
popValue = StackIndex -> Lua a
forall a. Peekable a => StackIndex -> Lua a
Lua.peek StackIndex
Lua.stackTop Lua a -> Lua () -> Lua a
forall (m :: * -> *) a b. MonadMask m => m a -> m b -> m a
`Catch.finally` StackIndex -> Lua ()
Lua.pop StackIndex
1
{-# INLINABLE popValue #-}