module HsLua.Core.Package
( requirehs
, preloadhs
)
where
import Control.Monad (void)
import HsLua.Core.Auxiliary
import HsLua.Core.Closures (pushHaskellFunction)
import HsLua.Core.Error (LuaError)
import HsLua.Core.Primary
import HsLua.Core.Types
requirehs :: LuaError e => Name -> LuaE e () -> LuaE e ()
requirehs :: Name -> LuaE e () -> LuaE e ()
requirehs Name
modname LuaE e ()
pushMod = do
LuaE e Type -> LuaE e ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (LuaE e Type -> LuaE e ()) -> LuaE e Type -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
loaded
StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
top Name
modname LuaE e Type -> (Type -> LuaE e ()) -> LuaE e ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
TypeNil -> do
Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1
LuaE e ()
pushMod
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
pushvalue StackIndex
top
StackIndex -> Name -> LuaE e ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield (CInt -> StackIndex
nth CInt
3) Name
modname
Type
_ -> () -> LuaE e ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
StackIndex -> LuaE e ()
forall e. StackIndex -> LuaE e ()
remove (CInt -> StackIndex
nth CInt
2)
preloadhs :: LuaError e => Name -> LuaE e NumResults -> LuaE e ()
preloadhs :: Name -> LuaE e NumResults -> LuaE e ()
preloadhs Name
name LuaE e NumResults
pushMod = do
LuaE e Type -> LuaE e ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (LuaE e Type -> LuaE e ()) -> LuaE e Type -> LuaE e ()
forall a b. (a -> b) -> a -> b
$ StackIndex -> Name -> LuaE e Type
forall e. LuaError e => StackIndex -> Name -> LuaE e Type
getfield StackIndex
registryindex Name
preload
LuaE e NumResults -> LuaE e ()
forall e. LuaError e => HaskellFunction e -> LuaE e ()
pushHaskellFunction LuaE e NumResults
pushMod
StackIndex -> Name -> LuaE e ()
forall e. LuaError e => StackIndex -> Name -> LuaE e ()
setfield (CInt -> StackIndex
nth CInt
2) Name
name
Int -> LuaE e ()
forall e. Int -> LuaE e ()
pop Int
1