gameServer/OfficialServer/extdbinterface.hs
author unc0rr
Sun, 29 Nov 2009 16:56:04 +0000
changeset 2647 0e1208e92dfe
parent 2348 b39d826e1ccd
child 2869 93cc73dcc421
permissions -rw-r--r--
Smaxx patch with tuning by me: - hogs might worry/panic if they're next to explosives (grenade, dynamite, etc.) - play sndVaporice for each fire extinguished only once (not 3 times) - allow "on attack" voices/sounds for weapons (similar to water melon bomb) - allow one voice/sound to be played during emotes - print protocol version in version info (console) - rope sounds (disabled atm) - landscape background - optimized/rewrote explosion drawing - fixed "StopSound" called with an inactive sound to stop some random sound - disabled npott

{-# LANGUAGE ScopedTypeVariables #-}

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 [SqlString $ 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 (\(_ :: IOException) -> return ()) $ 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