#if !MIN_VERSION_base(4,8,0)
#endif
module Foreign.Lua.Types.FromLuaStack
( FromLuaStack (..)
, Result
, peekEither
, pairsFromTable
) where
import Data.ByteString (ByteString)
import Data.Map (Map, fromList)
import Data.Monoid ((<>))
import Foreign.Lua.Api
import Foreign.Lua.Types.Lua
import Foreign.Lua.Types.Error
import Foreign.Ptr (Ptr)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
type Result a = Either String a
class FromLuaStack a where
peek :: StackIndex -> Lua a
instance FromLuaStack () where
peek = typeChecked "nil" isnil (const $ return ())
instance FromLuaStack LuaInteger where
peek = typeChecked "number" isnumber tointeger
instance FromLuaStack LuaNumber where
peek = typeChecked "number" isnumber tonumber
instance FromLuaStack Int where
peek = typeChecked "number" isnumber (fmap fromIntegral . tointeger)
instance FromLuaStack ByteString where
peek = typeChecked "string" isstring tostring
instance FromLuaStack Bool where
peek = typeChecked "boolean" isboolean toboolean
instance FromLuaStack CFunction where
peek = typeChecked "C function" iscfunction tocfunction
instance FromLuaStack (Ptr a) where
peek = typeChecked "user data" isuserdata touserdata
instance FromLuaStack LuaState where
peek = typeChecked "LuaState (i.e., a thread)" isthread tothread
instance FromLuaStack T.Text where
peek = fmap T.decodeUtf8 . peek
#if MIN_VERSION_base(4,8,0)
instance FromLuaStack [Char] where
#else
instance FromLuaStack String where
#endif
peek = fmap T.unpack . peek
instance FromLuaStack a => FromLuaStack [a] where
peek n = catchLuaError (go . enumFromTo 1 =<< rawlen n) amendError
where
go [] = return []
go (i : is) = do
ret <- rawgeti n i *> peek (1) <* pop 1
(ret:) <$> go is
amendError err = throwLuaError ("Could not read list: " ++ show err)
instance (Ord a, FromLuaStack a, FromLuaStack b) => FromLuaStack (Map a b) where
peek idx = fromList <$> pairsFromTable idx
pairsFromTable :: (FromLuaStack a, FromLuaStack b) => StackIndex -> Lua [(a, b)]
pairsFromTable idx = do
pushnil
remainingPairs
where
remainingPairs = do
res <- nextPair (if idx < 0 then idx 1 else idx)
case res of
Nothing -> return []
Just a -> (a:) <$> remainingPairs
nextPair :: (FromLuaStack a, FromLuaStack b)
=> StackIndex -> Lua (Maybe (a, b))
nextPair idx = do
hasNext <- next idx
if hasNext
then do
v <- peek (1)
k <- peek (2)
pop 1
return (Just (k, v))
else return Nothing
typeChecked :: String
-> (StackIndex -> Lua Bool)
-> (StackIndex -> Lua a)
-> StackIndex
-> Lua a
typeChecked expectedType test peekfn n = do
v <- test n
if v
then peekfn n
else do
actual <- ltype n >>= typename
throwLuaError $ "Expected a " <> expectedType <> " but got a " <> actual
peekEither :: FromLuaStack a => StackIndex -> Lua (Either String a)
peekEither idx = catchLuaError (return <$> peek idx) (return . Left . show)