gameServer/OfficialServer/extdbinterface.hs
author nemo
Fri, 05 Nov 2010 18:56:12 -0400
changeset 4140 1563b216f243
parent 3901 124b4755914b
child 4242 5e3c5fe2cb14
permissions -rw-r--r--
revert attempts to block switching weapon while targetting in infinite attack mode. just getting too messy. probably best to allow any weapon to be targetted, and store the target in the gear and draw it there instead of uworld, but I'm leaving this alone

{-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}

module Main where

import Prelude hiding (catch)
import Control.Monad
import Control.Exception
import System.IO
import Maybe
import Database.HDBC
import Database.HDBC.MySQL
--------------------------
import CoreTypes


dbQueryAccount =
    "SELECT users.pass, users_roles.rid FROM users LEFT JOIN users_roles ON users.uid = users_roles.uid WHERE users.name = ?"

dbQueryStats =
    "UPDATE gameserver_stats SET players = ?, rooms = ?, last_update = UNIX_TIMESTAMP()"

dbInteractionLoop dbConn = forever $ do
    q <- (getLine >>= return . read)
    hPutStrLn stderr $ show q
    
    case q of
        CheckAccount clUid clNick _ -> do
                statement <- prepare dbConn dbQueryAccount
                execute statement [SqlByteString $ clNick]
                passAndRole <- fetchRow statement
                finish statement
                let response = 
                        if isJust passAndRole then
                        (
                            clUid,
                            HasAccount
                                (fromSql $ head $ fromJust $ passAndRole)
                                ((fromSql $ last $ fromJust $ passAndRole) == (Just (3 :: Int)))
                        )
                        else
                        (clUid, Guest)
                putStrLn (show response)
                hFlush stdout

        SendStats clients rooms ->
                run dbConn dbQueryStats [SqlInt32 $ fromIntegral clients, SqlInt32 $ fromIntegral rooms] >> return ()


dbConnectionLoop mySQLConnectionInfo =
    Control.Exception.handle (\(e :: IOException) -> hPutStrLn stderr $ show e) $ handleSqlError $
        bracket
            (connectMySQL mySQLConnectionInfo)
            (disconnect)
            (dbInteractionLoop)


processRequest :: DBQuery -> IO String
processRequest (CheckAccount clUid clNick clHost) = return $ show (clUid, Guest)

main = do
        dbHost <- getLine
        dbLogin <- getLine
        dbPassword <- getLine

        let mySQLConnectInfo = defaultMySQLConnectInfo {mysqlHost = dbHost, mysqlDatabase = "hedge_main", mysqlUser = dbLogin, mysqlPassword = dbPassword}

        dbConnectionLoop mySQLConnectInfo