
Am Montag 02 November 2009 05:57:41 schrieb iæfai:
I have been trying to work out a problem for the last few hours with little success.
In the following code, using ConfigFile, I obtain the results of the configuration file, but in the main function I am trying to get the Config type out of the case statement. I need to be able to generate that error, but it means the two branches of the case are not the same type.
I am not particularly attached to this direction, I am quite willing to do any way that works. I might be adding more configuration in the future.
Any ideas?
iæfai -- import Network.Shed.Httpd import Network.URI
import Data.Either import Data.ConfigFile as C
import Control.Monad.Error import Control.Applicative
import ChessBoard
data Config = Config { documentRoot :: String } deriving (Read, Show)
main :: IO () main = do opt <- getConf "./config" config <- case opt of Left (_, err) -> ioError (userError err) Right (config) -> config
docPath <- documentRoot config
Wrong type here, documentRoot config :: String
putStrLn "Starting up httpd." server <- initServer 6666 request return ()
main = do opt <- getConf "./config" case opt of Left (_,err) -> ioError (userError err) Right config -> do let docPath = documentRoot config putStrLn "Starting up httpd." server <- initServer 6666 request return () -- though if you don't use the server later, it would be better to replace the last two lines with just "initServer 6666 request" Perhaps better to separate getting the config from using it: main = do opt <- getConf "./config" case opt of Left (_,err) -> ioError (userError err) Right config -> workWith config workWith config = do let docPath = documentRoot config putStrLn ...
request :: Request -> IO Response request req = do putStrLn $ "Recieved " ++ (show $ uriPath $ reqURI req) return $ Response 404 [] "Not found."
-- Mostly from Chris Done's Blog getConf :: FilePath -> IO (Either (C.CPErrorData, String) Config) getConf filePath = runErrorT $ do let cp = C.emptyCP { optionxform = id } contents <- liftIO $ readFile filePath config <- C.readstring cp contents let get = C.get config "DEFAULT" Config <$> get "Document-Root"