module Foreign.Lua.Module.System (
pushModule
, preloadModule
, arch
, compiler_name
, compiler_version
, os
, env
, getwd
, getenv
, ls
, mkdir
, rmdir
, setenv
, setwd
, tmpdirname
, with_env
, with_tmpdir
, with_wd
)
where
import Control.Applicative ((<$>))
import Control.Monad (forM_)
import Control.Monad.Catch (bracket)
import Data.Maybe (fromMaybe)
import Data.Version (versionBranch)
import Foreign.Lua (Lua, NumResults (..), Optional (..))
import Foreign.Lua.Module.SystemUtils
import qualified Data.Map as Map
import qualified Foreign.Lua as Lua
import qualified System.Directory as Directory
import qualified System.Environment as Env
import qualified System.Info as Info
import qualified System.IO.Temp as Temp
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
Lua.addfield "arch" arch
Lua.addfield "compiler_name" compiler_name
Lua.addfield "compiler_version" compiler_version
Lua.addfield "os" os
Lua.addfunction "env" env
Lua.addfunction "getenv" getenv
Lua.addfunction "getwd" getwd
Lua.addfunction "ls" ls
Lua.addfunction "mkdir" mkdir
Lua.addfunction "rmdir" rmdir
Lua.addfunction "setenv" setenv
Lua.addfunction "setwd" setwd
Lua.addfunction "tmpdirname" tmpdirname
Lua.addfunction "with_env" with_env
Lua.addfunction "with_tmpdir" with_tmpdir
Lua.addfunction "with_wd" with_wd
return 1
preloadModule :: String -> Lua ()
preloadModule = flip Lua.preloadhs pushModule
arch :: String
arch = Info.arch
compiler_name :: String
compiler_name = Info.compilerName
compiler_version :: [Int]
compiler_version = versionBranch Info.compilerVersion
os :: String
os = Info.os
env :: Lua NumResults
env = do
kvs <- ioToLua Env.getEnvironment
let addValue (k, v) = Lua.push k *> Lua.push v *> Lua.rawset (-3)
Lua.newtable
mapM_ addValue kvs
return (NumResults 1)
getwd :: Lua FilePath
getwd = ioToLua Directory.getCurrentDirectory
getenv :: String -> Lua (Optional String)
getenv name = ioToLua (Optional <$> Env.lookupEnv name)
ls :: Optional FilePath -> Lua [FilePath]
ls fp = do
let fp' = fromMaybe "." (fromOptional fp)
ioToLua (Directory.listDirectory fp')
mkdir :: FilePath -> Bool -> Lua ()
mkdir fp createParent =
if createParent
then ioToLua (Directory.createDirectoryIfMissing True fp)
else ioToLua (Directory.createDirectory fp)
rmdir :: FilePath -> Bool -> Lua ()
rmdir fp recursive =
if recursive
then ioToLua (Directory.removeDirectoryRecursive fp)
else ioToLua (Directory.removeDirectory fp)
setenv :: String -> String -> Lua ()
setenv name value = ioToLua (Env.setEnv name value)
setwd :: FilePath -> Lua ()
setwd fp = ioToLua $ Directory.setCurrentDirectory fp
tmpdirname :: Lua FilePath
tmpdirname = ioToLua Directory.getTemporaryDirectory
with_wd :: FilePath -> Callback -> Lua NumResults
with_wd fp callback =
bracket (Lua.liftIO Directory.getCurrentDirectory)
(Lua.liftIO . Directory.setCurrentDirectory)
$ \_ -> do
Lua.liftIO (Directory.setCurrentDirectory fp)
callback `invokeWithFilePath` fp
with_env :: Map.Map String String -> Callback -> Lua NumResults
with_env environment callback =
bracket (Lua.liftIO Env.getEnvironment)
setEnvironment
(\_ -> setEnvironment (Map.toList environment) >> invoke callback)
where
setEnvironment newEnv = Lua.liftIO $ do
curEnv <- Env.getEnvironment
forM_ curEnv (Env.unsetEnv . fst)
forM_ newEnv (uncurry Env.setEnv)
with_tmpdir :: String
-> AnyValue
-> Optional Callback
-> Lua NumResults
with_tmpdir parentDir tmpl callback =
case fromOptional callback of
Nothing -> do
let tmpl' = parentDir
callback' <- Lua.peek (fromAnyValue tmpl)
Temp.withSystemTempDirectory tmpl' (invokeWithFilePath callback')
Just callback' -> do
tmpl' <- Lua.peek (fromAnyValue tmpl)
Temp.withTempDirectory parentDir tmpl' (invokeWithFilePath callback')