gameServer/OfficialServer/DBInteraction.hs
author koda
Sat, 04 Jan 2014 02:18:57 +0100
branch0.9.20
changeset 9922 58dee07f7552
parent 9661 788fd9eedfb0
child 10460 8dcea9087d75
permissions -rw-r--r--
correctly set this pascal flag for future compatibility
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
4906
22cc9c2b5ae5 Fix even more
unc0rr
parents: 4568
diff changeset
     1
{-# LANGUAGE CPP, ScopedTypeVariables, OverloadedStrings #-}
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
     2
module OfficialServer.DBInteraction
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
     3
(
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
     4
    startDBConnection
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
     5
) where
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
     6
1979
912e450d4db2 - Add gameServer to build system
unc0rr
parents: 1970
diff changeset
     7
import Prelude hiding (catch);
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
     8
import Control.Concurrent
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
     9
import Control.Monad
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    10
import Data.List as L
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    11
import Data.ByteString.Char8 as B
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    12
#if defined(OFFICIAL_SERVER)
2116
dec7ead2d178 Bring back authentication to official server, now using separate process to perform database interaction
unc0rr
parents: 1979
diff changeset
    13
import System.Process
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
    14
import System.IO as SIO
2296
19f2f76dc346 Patch for compiling with 6.10 (define NEW_EXCEPTIONS to do that)
unc0rr
parents: 2245
diff changeset
    15
import qualified Control.Exception as Exception
2117
1ac0e10e546f Add caching for accounts information (entries are stored in memory forever)
unc0rr
parents: 2116
diff changeset
    16
import qualified Data.Map as Map
4334
82cfbbab73da fix compilation server for me
koda
parents: 4242
diff changeset
    17
import Data.Maybe
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    18
import Data.Time
1839
5dd4cb7fd7e5 Server now send ASKPASSWORD command to frontend when user has web account
unc0rr
parents: 1834
diff changeset
    19
import System.Log.Logger
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    20
#endif
1833
e901ec5644b4 Add options for configuring database access
unc0rr
parents: 1804
diff changeset
    21
------------------------
e901ec5644b4 Add options for configuring database access
unc0rr
parents: 1804
diff changeset
    22
import CoreTypes
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    23
#if defined(OFFICIAL_SERVER)
2116
dec7ead2d178 Bring back authentication to official server, now using separate process to perform database interaction
unc0rr
parents: 1979
diff changeset
    24
import Utils
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    25
#endif
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
    26
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    27
localAddressList :: [B.ByteString]
1921
2a09f7f786a0 - User from localhost is server admin
unc0rr
parents: 1857
diff changeset
    28
localAddressList = ["127.0.0.1", "0:0:0:0:0:0:0:1", "0:0:0:0:0:ffff:7f00:1"]
1839
5dd4cb7fd7e5 Server now send ASKPASSWORD command to frontend when user has web account
unc0rr
parents: 1834
diff changeset
    29
4989
4771fed9272e - Write server config into .ini file on change
unc0rr
parents: 4982
diff changeset
    30
fakeDbConnection :: forall b. ServerInfo -> IO b
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    31
fakeDbConnection si = forever $ do
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    32
    q <- readChan $ dbQueries si
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    33
    case q of
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
    34
        CheckAccount clId clUid _ clHost ->
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    35
            writeChan (coreChan si) $ ClientAccountInfo clId clUid (if clHost `L.elem` localAddressList then Admin else Guest)
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    36
        ClearCache -> return ()
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    37
        SendStats {} -> return ()
1857
b835395659e2 Fake database connection with routine which marks all users as guests, when no database host was specified
unc0rr
parents: 1847
diff changeset
    38
4996
76ef3d8bd78e Fix crash (accessing already deleted client record) by reverting to old client removing handling + throwTo
unc0rr
parents: 4992
diff changeset
    39
dbConnectionLoop :: ServerInfo -> IO ()
76ef3d8bd78e Fix crash (accessing already deleted client record) by reverting to old client removing handling + throwTo
unc0rr
parents: 4992
diff changeset
    40
2116
dec7ead2d178 Bring back authentication to official server, now using separate process to perform database interaction
unc0rr
parents: 1979
diff changeset
    41
#if defined(OFFICIAL_SERVER)
4989
4771fed9272e - Write server config into .ini file on change
unc0rr
parents: 4982
diff changeset
    42
flushRequests :: ServerInfo -> IO ()
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    43
flushRequests si = do
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    44
    e <- isEmptyChan $ dbQueries si
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    45
    unless e $ do
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    46
        q <- readChan $ dbQueries si
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    47
        case q of
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    48
            CheckAccount clId clUid _ clHost ->
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    49
                writeChan (coreChan si) $ ClientAccountInfo clId clUid (if clHost `L.elem` localAddressList then Admin else Guest)
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    50
            ClearCache -> return ()
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    51
            SendStats {} -> return ()
9661
788fd9eedfb0 Fix 'non-exhaustive pattern' server crash
unc0rr
parents: 9450
diff changeset
    52
            GetReplayName {} -> return ()
788fd9eedfb0 Fix 'non-exhaustive pattern' server crash
unc0rr
parents: 9450
diff changeset
    53
            StoreAchievements {} -> return ()
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    54
        flushRequests si
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    55
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    56
pipeDbConnectionLoop :: Chan DBQuery -> Chan CoreMessage -> Handle -> Handle -> Map.Map ByteString (UTCTime, AccountInfo) -> Int -> IO (Map.Map ByteString (UTCTime, AccountInfo), Int)
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    57
pipeDbConnectionLoop queries cChan hIn hOut accountsCache req =
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    58
    Exception.handle (\(e :: Exception.IOException) -> warningM "Database" (show e) >> return (accountsCache, req)) $
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    59
    do
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    60
    q <- readChan queries
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    61
    (updatedCache, newReq) <- case q of
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
    62
        CheckAccount clId clUid clNick _ -> do
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    63
            let cacheEntry = clNick `Map.lookup` accountsCache
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    64
            currentTime <- getCurrentTime
7331
0e50456d652c Well, since we have database on the same computer as game server, could remove caching, but I just set expiration time to 10 minutes
unc0rr
parents: 4996
diff changeset
    65
            if (isNothing cacheEntry) || (currentTime `diffUTCTime` (fst . fromJust) cacheEntry > 10 * 60) then
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    66
                do
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
    67
                    SIO.hPutStrLn hIn $ show q
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    68
                    hFlush hIn
2117
1ac0e10e546f Add caching for accounts information (entries are stored in memory forever)
unc0rr
parents: 2116
diff changeset
    69
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
    70
                    (clId', clUid', accountInfo) <- SIO.hGetLine hOut >>= (maybeException . maybeRead)
2117
1ac0e10e546f Add caching for accounts information (entries are stored in memory forever)
unc0rr
parents: 2116
diff changeset
    71
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    72
                    writeChan cChan $ ClientAccountInfo clId' clUid' accountInfo
2117
1ac0e10e546f Add caching for accounts information (entries are stored in memory forever)
unc0rr
parents: 2116
diff changeset
    73
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    74
                    return $ (Map.insert clNick (currentTime, accountInfo) accountsCache, req + 1)
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    75
                `Exception.onException`
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    76
                    (unGetChan queries q)
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    77
                else
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    78
                do
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
    79
                    writeChan cChan $ ClientAccountInfo clId clUid (snd $ fromJust cacheEntry)
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    80
                    return (accountsCache, req)
2155
d897222d3339 Implement ability for server admin to clear accounts cache
unc0rr
parents: 2129
diff changeset
    81
9446
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    82
        GetReplayName {} -> do
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    83
            SIO.hPutStrLn hIn $ show q
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    84
            hFlush hIn
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    85
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    86
            (clId', clUid', accountInfo) <- SIO.hGetLine hOut >>= (maybeException . maybeRead)
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    87
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    88
            writeChan cChan $ ClientAccountInfo clId' clUid' accountInfo
9450
2084b1b7839c Fix official server build
unc0rr
parents: 9446
diff changeset
    89
            return (accountsCache, req)
9446
4fd5df03deb8 Start support of achievement replay query:
unc0rr
parents: 9399
diff changeset
    90
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
    91
        ClearCache -> return (Map.empty, req)
9399
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    92
        StoreAchievements {} -> (
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    93
                (SIO.hPutStrLn hIn $ show q) >>
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    94
                hFlush hIn >>
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    95
                return (accountsCache, req))
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    96
                `Exception.onException`
1767c92eff37 Pass achievements info to extdbinterface
unc0rr
parents: 7331
diff changeset
    97
                (unGetChan queries q)
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
    98
        SendStats {} -> (
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
    99
                (SIO.hPutStrLn hIn $ show q) >>
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   100
                hFlush hIn >>
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
   101
                return (accountsCache, req))
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   102
                `Exception.onException`
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   103
                (unGetChan queries q)
2184
f59f80e034b1 Oops, fix database process interaction
unc0rr
parents: 2172
diff changeset
   104
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
   105
    pipeDbConnectionLoop queries cChan hIn hOut updatedCache newReq
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   106
    where
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   107
        maybeException (Just a) = return a
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   108
        maybeException Nothing = ioError (userError "Can't read")
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
   109
4992
408301a9d2d6 - Simplify insane TConfig code
unc0rr
parents: 4989
diff changeset
   110
pipeDbConnection ::
4982
3572eaf14340 Add dbName parameter to .ini file, fix some warnings
unc0rr
parents: 4975
diff changeset
   111
        Map.Map ByteString (UTCTime, AccountInfo)
4989
4771fed9272e - Write server config into .ini file on change
unc0rr
parents: 4982
diff changeset
   112
        -> ServerInfo
4992
408301a9d2d6 - Simplify insane TConfig code
unc0rr
parents: 4989
diff changeset
   113
        -> Int
408301a9d2d6 - Simplify insane TConfig code
unc0rr
parents: 4989
diff changeset
   114
        -> IO ()
4982
3572eaf14340 Add dbName parameter to .ini file, fix some warnings
unc0rr
parents: 4975
diff changeset
   115
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   116
pipeDbConnection accountsCache si errNum = do
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   117
    (updatedCache, newErrNum) <-
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   118
        Exception.handle (\(e :: Exception.IOException) -> warningM "Database" (show e) >> return (accountsCache, errNum + 1)) $ do
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   119
            (Just hIn, Just hOut, _, _) <- createProcess (proc "./OfficialServer/extdbinterface" [])
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   120
                    {std_in = CreatePipe,
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   121
                    std_out = CreatePipe}
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   122
            hSetBuffering hIn LineBuffering
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   123
            hSetBuffering hOut LineBuffering
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
   124
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   125
            B.hPutStrLn hIn $ dbHost si
4982
3572eaf14340 Add dbName parameter to .ini file, fix some warnings
unc0rr
parents: 4975
diff changeset
   126
            B.hPutStrLn hIn $ dbName si
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   127
            B.hPutStrLn hIn $ dbLogin si
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   128
            B.hPutStrLn hIn $ dbPassword si
4944
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
   129
            (c, r) <- pipeDbConnectionLoop (dbQueries si) (coreChan si) hIn hOut accountsCache 0
e43a3da2fc22 More robust login system when db server goes away
unc0rr
parents: 4943
diff changeset
   130
            return (c, if r > 0 then 0 else errNum + 1)
2184
f59f80e034b1 Oops, fix database process interaction
unc0rr
parents: 2172
diff changeset
   131
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   132
    when (newErrNum > 1) $ flushRequests si
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   133
    threadDelay (3000000)
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   134
    pipeDbConnection updatedCache si newErrNum
2116
dec7ead2d178 Bring back authentication to official server, now using separate process to perform database interaction
unc0rr
parents: 1979
diff changeset
   135
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   136
dbConnectionLoop si =
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   137
        if (not . B.null $ dbHost si) then
4943
21d6b2b79cfe Allow users to join official server even when there's no db connection
unc0rr
parents: 4932
diff changeset
   138
            pipeDbConnection Map.empty si 0
2869
93cc73dcc421 Replace tabs with spaces here too
unc0rr
parents: 2387
diff changeset
   139
        else
4921
2efad3acbb74 Fix build of official server
unc0rr
parents: 4918
diff changeset
   140
            fakeDbConnection si
1979
912e450d4db2 - Add gameServer to build system
unc0rr
parents: 1970
diff changeset
   141
#else
912e450d4db2 - Add gameServer to build system
unc0rr
parents: 1970
diff changeset
   142
dbConnectionLoop = fakeDbConnection
912e450d4db2 - Add gameServer to build system
unc0rr
parents: 1970
diff changeset
   143
#endif
1804
4e78ad846fb6 New game server:
unc0rr
parents:
diff changeset
   144
4989
4771fed9272e - Write server config into .ini file on change
unc0rr
parents: 4982
diff changeset
   145
startDBConnection :: ServerInfo -> IO ()
1833
e901ec5644b4 Add options for configuring database access
unc0rr
parents: 1804
diff changeset
   146
startDBConnection serverInfo =
4932
f11d80bac7ed - Take into account hlint suggestions
unc0rr
parents: 4921
diff changeset
   147
    forkIO (dbConnectionLoop serverInfo) >> return ()