gameServer/OfficialServer/extdbinterface.hs
changeset 4568 f85243bf890e
parent 4295 1f5604cd99be
child 4906 22cc9c2b5ae5
equal deleted inserted replaced
4566:87ee1be17d27 4568:f85243bf890e
     1 {-# LANGUAGE ScopedTypeVariables, OverloadedStrings #-}
     1 {-# LANGUAGE ScopedTypeVariables #-}
     2 
     2 
     3 module Main where
     3 module Main where
     4 
     4 
     5 import Prelude hiding (catch)
     5 import Prelude hiding (catch)
     6 import Control.Monad
     6 import Control.Monad
    24     hPutStrLn stderr $ show q
    24     hPutStrLn stderr $ show q
    25     
    25     
    26     case q of
    26     case q of
    27         CheckAccount clUid clNick _ -> do
    27         CheckAccount clUid clNick _ -> do
    28                 statement <- prepare dbConn dbQueryAccount
    28                 statement <- prepare dbConn dbQueryAccount
    29                 execute statement [SqlByteString $ clNick]
    29                 execute statement [SqlString $ clNick]
    30                 passAndRole <- fetchRow statement
    30                 passAndRole <- fetchRow statement
    31                 finish statement
    31                 finish statement
    32                 let response = 
    32                 let response = 
    33                         if isJust passAndRole then
    33                         if isJust passAndRole then
    34                         (
    34                         (
    45         SendStats clients rooms ->
    45         SendStats clients rooms ->
    46                 run dbConn dbQueryStats [SqlInt32 $ fromIntegral clients, SqlInt32 $ fromIntegral rooms] >> return ()
    46                 run dbConn dbQueryStats [SqlInt32 $ fromIntegral clients, SqlInt32 $ fromIntegral rooms] >> return ()
    47 
    47 
    48 
    48 
    49 dbConnectionLoop mySQLConnectionInfo =
    49 dbConnectionLoop mySQLConnectionInfo =
    50     Control.Exception.handle (\(e :: IOException) -> hPutStrLn stderr $ show e) $ handleSqlError $
    50     Control.Exception.handle (\(_ :: IOException) -> return ()) $ handleSqlError $
    51         bracket
    51         bracket
    52             (connectMySQL mySQLConnectionInfo)
    52             (connectMySQL mySQLConnectionInfo)
    53             (disconnect)
    53             (disconnect)
    54             (dbInteractionLoop)
    54             (dbInteractionLoop)
    55 
    55