123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778 |
- {-# LANGUAGE NamedFieldPuns #-}
- module Main where
- import qualified Control.Applicative as App
- import qualified Control.Exception as Exn
- import qualified Control.Monad as Monad
- import qualified Foreign.Lua as Lua
- data Config = Config
- { cfgHost :: String,
- cfgPort :: Int,
- cfgFiles :: [String]
- }
- deriving (Show)
- -- a very barebones attempt at doing error conversion: we ignore a
- -- bunch of stuff, but we do translate Lua errors into Haskell errors
- errorConversion :: Lua.ErrorConversion
- errorConversion = Lua.ErrorConversion {Lua.errorToException, Lua.addContextToException, Lua.alternative, Lua.exceptionToError}
- where
- errorToException = Lua.throwTopMessageWithState
- addContextToException _ x = x
- alternative x y = x App.<|> y
- exceptionToError = id
- readConfig :: FilePath -> IO Config
- readConfig configPath =
- -- set up a new Lua state, and make sure we close it at the end
- Exn.bracket Lua.newstate Lua.close $ \st ->
- -- we should set up a mechanism to convert Lua/Haskell errors into
- -- one another, but that seems like a lot of work here, so this
- -- just panics whenever any errors happen, hence `unsafeRunWith`
- Lua.runWithConverter errorConversion st $ do
- -- this loads the stdlib into Lua, but you probably don't
- -- actually want this in a config file! (it allows e.g. file IO
- -- and stuff)
- Lua.openlibs
- -- load the actual config path
- res <- Lua.loadfile configPath
- -- if that didn't work, then take the Lua error and turn it into
- -- a Haskell exception
- Monad.when
- (res /= Lua.OK)
- Lua.throwErrorAsException
- -- that simply loads the code as a zero-argument function: now
- -- call it
- Lua.call 0 0
- -- use the `readGlobal` helper to extract the globals defined by
- -- the config file...
- cfgHost <- readGlobal "host"
- cfgPort <- readGlobal "port"
- cfgFiles <- readGlobal "files"
- -- and return the values
- return Config {cfgHost, cfgPort, cfgFiles}
- -- | Read the global variable @name@ into a Haskell value
- readGlobal :: Lua.Peekable t => String -> Lua.Lua t
- readGlobal name = do
- -- this pushes the global named `name` onto the top of the stack
- Lua.getglobal name
- -- this finds out what index is at the top of the stack
- idx <- Lua.gettop
- -- this uses the `peek` functionality, already parameterized by a
- -- typeclass, to convert the value at the given index into the
- -- appropriate Haskell type
- value <- Lua.peek idx
- -- pop the global, now that we've already got it in Haskell-land
- Lua.pop 1
- -- ...and return it
- return value
- main :: IO ()
- main = do
- cfg <- readConfig "sample.lua"
- print cfg
|