module Scripting.Lua.ConfigFile
(
Config,
openConfig,
closeConfig,
getBool,
getString,
getInt,
getDouble,
getList,
getNestedLists,
getAssocList,
getListOfAssocLists,
getNestedAssocLists,
ConfigFileException
) where
import qualified Scripting.Lua as Lua
import System.IO (FilePath)
import Control.Exception (Exception, throwIO)
import Control.Monad (forM, forM_)
import Data.Typeable (Typeable)
data Config = Config Lua.LuaState
data ConfigFileException = ConfigFileException String
deriving (Show, Typeable)
instance Exception ConfigFileException
openConfig :: FilePath -> IO Config
openConfig path = do
l <- Lua.newstate
loadResult <- Lua.loadfile l path
callResult <- Lua.call l 0 0
if loadResult /= 0 || callResult /= 0 then
do
errMsg <- Lua.tostring l (1)
throwIO $ ConfigFileException $ "cannot run config file: " ++ errMsg
else return (Config l)
closeConfig :: Config -> IO ()
closeConfig (Config l) =
Lua.close l
getBool :: Config -> String -> IO Bool
getBool (Config l) name = do
(val, valType) <- getGlobalVal l name
case (val, valType) of
(Just v, Lua.TBOOLEAN) -> return v
(Nothing, Lua.TNIL) -> return False
(_, _) -> throwIO $ ConfigFileException $
"expected boolean value: " ++ name
getString :: Config -> String -> IO String
getString (Config l) name = do
(val, valType) <- getGlobalVal l name
case (val, valType) of
(Just v, Lua.TSTRING) -> return v
(Nothing, Lua.TNIL) -> return ""
(_, _) -> throwIO $ ConfigFileException $
"expected string value: " ++ name
getInt :: Config -> String -> IO (Maybe Int)
getInt (Config l) name = do
(val, valType) <- getGlobalVal l name
case (val, valType) of
(Just v, Lua.TNUMBER) -> return (Just v)
(Nothing, Lua.TNIL) -> return Nothing
(_, _) -> throwIO $ ConfigFileException $
"expected numeric value: " ++ name
getDouble :: Config -> String -> IO (Maybe Double)
getDouble (Config l) name = do
(val, valType) <- getGlobalVal l name
case (val, valType) of
(Just v, Lua.TNUMBER) -> return (Just v)
(Nothing, Lua.TNIL) -> return Nothing
(_, _) -> throwIO $ ConfigFileException $
"expected numeric value: " ++ name
getList :: Config -> String -> IO [String]
getList (Config l) name =
getTable l name getListOfStrings
getNestedLists :: Config -> String -> IO [[String]]
getNestedLists (Config l) name =
getTable l name (\l name -> getOuterList l name getListOfStrings)
getAssocList :: Config -> String -> IO [(String, String)]
getAssocList (Config l) name =
getTable l name getColumns
getListOfAssocLists :: Config -> String -> IO [[(String, String)]]
getListOfAssocLists (Config l) name =
getTable l name (\l name -> getOuterList l name getColumns)
getNestedAssocLists :: Config -> String -> IO [(String, [(String, String)])]
getNestedAssocLists (Config l) name =
getTable l name getRows
getGlobalVal l name = do
Lua.getglobal l name
val <- Lua.peek l (1)
valType <- Lua.ltype l (1)
Lua.pop l 1
return (val, valType)
canBeString valType =
valType `elem` [Lua.TSTRING, Lua.TNUMBER]
getTable :: Lua.LuaState ->
String ->
(Lua.LuaState -> String -> IO [a]) ->
IO [a]
getTable l name f = do
Lua.getglobal l name
valType <- Lua.ltype l (1)
case valType of
Lua.TTABLE -> do items <- f l name
Lua.pop l 1
return items
Lua.TNIL -> return []
_ -> throwIO $ ConfigFileException $ "expected table: " ++ name
forList :: Lua.LuaState ->
IO a ->
IO [a]
forList l f = do
tableSize <- Lua.objlen l (1)
forM [1..tableSize] $ \i -> do
Lua.push l i
Lua.gettable l (2)
f
getListOfStrings :: Lua.LuaState ->
String ->
IO [String]
getListOfStrings l name =
forList l $ do
valType <- Lua.ltype l (1)
if canBeString valType then
do
valStr <- Lua.tostring l (1)
Lua.pop l 1
return valStr
else throwIO $ ConfigFileException $
"expected table of strings: " ++ name
getOuterList :: Lua.LuaState ->
String ->
(Lua.LuaState -> String -> IO a) ->
IO [a]
getOuterList l name f =
forList l $ do
valType <- Lua.ltype l (1)
case valType of
Lua.TTABLE -> do innerItems <- f l name
Lua.pop l 1
return innerItems
_ -> throwIO $ ConfigFileException $ "expected table: " ++ name
getRows :: Lua.LuaState -> String -> IO [(String, [(String, String)])]
getRows l name = do
Lua.pushnil l
getRemainingRows l name
getRemainingRows :: Lua.LuaState -> String -> IO [(String, [(String, String)])]
getRemainingRows l name = do
hasNext <- Lua.next l (2)
if hasNext then
do
keyType <- Lua.ltype l (2)
valType <- Lua.ltype l (1)
case (keyType, valType) of
(Lua.TSTRING, Lua.TTABLE) ->
do keyStr <- Lua.tostring l (2)
columns <- getColumns l name
Lua.pop l 1
rest <- getRemainingRows l name
return ((keyStr, columns) : rest)
(_, _) -> throwIO $ ConfigFileException $
"expected string keys and table values: " ++ name
else return []
getColumns :: Lua.LuaState -> String -> IO [(String, String)]
getColumns l name = do
Lua.pushnil l
getRemainingColumns l name
getRemainingColumns :: Lua.LuaState -> String -> IO [(String, String)]
getRemainingColumns l name = do
hasNext <- Lua.next l (2)
if hasNext then
do
keyType <- Lua.ltype l (2)
valType <- Lua.ltype l (1)
if keyType == Lua.TSTRING && canBeString valType then
do
keyStr <- Lua.tostring l (2)
valStr <- Lua.tostring l (1)
Lua.pop l 1
rest <- getRemainingColumns l name
return ((keyStr, valStr) : rest)
else throwIO $ ConfigFileException $
"expected string keys and string values: " ++ name
else return []
stackDump l = do
stackSize <- Lua.gettop l
forM_ (reverse [1..stackSize]) $ \i -> do
let relativeIndex = stackSize i + 1
putStr $ "Index[" ++ show i ++ " / -" ++ show relativeIndex ++ "] = "
itemType <- Lua.ltype l i
case itemType of
Lua.TNONE -> putStr "TNONE"
Lua.TNIL -> putStr "TNIL"
Lua.TBOOLEAN -> do boolVal <- Lua.toboolean l i
putStr $ "TBOOLEAN " ++ show boolVal
Lua.TLIGHTUSERDATA -> putStr "TLIGHTUSERDATA"
Lua.TNUMBER -> do iVal <- Lua.tointeger l i
putStr $ "TNUMBER " ++ show iVal
Lua.TSTRING -> do sVal <- Lua.tostring l i
putStr $ "TSTRING " ++ sVal
Lua.TTABLE -> putStr "TTABLE"
Lua.TFUNCTION -> putStr "TFUNCTION"
Lua.TTHREAD -> putStr "TTHREAD"
putStr "\n"
putStr "\n"