Fixes suggested by hlint tool
authorunc0rr
Fri, 04 Sep 2009 16:50:52 +0000
changeset 2352 7eaf82cf0890
parent 2351 a4a17b8df591
child 2353 31170b0850fa
Fixes suggested by hlint tool
gameServer/Actions.hs
gameServer/ClientIO.hs
gameServer/CoreTypes.hs
gameServer/HWProtoInRoomState.hs
gameServer/HWProtoLobbyState.hs
gameServer/HWProtoNEState.hs
gameServer/stresstest.hs
gameServer/stresstest2.hs
--- a/gameServer/Actions.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/Actions.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -65,7 +65,7 @@
 
 processAction (clID, serverInfo, clients, rooms) (AnswerAllOthers msg) = do
 	mapM_ (\id -> writeChan (sendChan $ clients ! id) msg) $
-		Prelude.filter (\id' -> (id' /= clID) && (logonPassed $ clients ! id')) (keys clients)
+		Prelude.filter (\id' -> (id' /= clID) && logonPassed (clients ! id')) (keys clients)
 	return (clID, serverInfo, clients, rooms)
 
 
@@ -98,7 +98,7 @@
 
 
 processAction (clID, serverInfo, clients, rooms) SendServerMessage = do
-	writeChan (sendChan $ clients ! clID) $ ["SERVER_MESSAGE", message serverInfo]
+	writeChan (sendChan $ clients ! clID) ["SERVER_MESSAGE", message serverInfo]
 	return (clID, serverInfo, clients, rooms)
 	where
 		client = clients ! clID
@@ -119,7 +119,7 @@
 
 
 processAction (clID, serverInfo, clients, rooms) (ByeClient msg) = do
-	infoM "Clients" ((show $ clientUID client) ++ " quits: " ++ msg)
+	infoM "Clients" (show (clientUID client) ++ " quits: " ++ msg)
 	(_, _, newClients, newRooms) <-
 			if roomID client /= 0 then
 				processAction  (clID, serverInfo, clients, rooms) $ RoomRemoveThisClient "quit"
@@ -159,21 +159,21 @@
 				[]
 
 
-processAction (clID, serverInfo, clients, rooms) (ModifyClient func) = do
+processAction (clID, serverInfo, clients, rooms) (ModifyClient func) =
 	return (clID, serverInfo, adjust func clID clients, rooms)
 
 
-processAction (clID, serverInfo, clients, rooms) (ModifyRoom func) = do
+processAction (clID, serverInfo, clients, rooms) (ModifyRoom func) =
 	return (clID, serverInfo, clients, adjust func rID rooms)
 	where
 		rID = roomID $ clients ! clID
 
 
-processAction (clID, serverInfo, clients, rooms) (ModifyServerInfo func) = do
+processAction (clID, serverInfo, clients, rooms) (ModifyServerInfo func) =
 	return (clID, func serverInfo, clients, rooms)
 
 
-processAction (clID, serverInfo, clients, rooms) (RoomAddThisClient rID) = do
+processAction (clID, serverInfo, clients, rooms) (RoomAddThisClient rID) =
 	processAction (
 		clID,
 		serverInfo,
@@ -321,7 +321,7 @@
 
 
 processAction (clID, serverInfo, clients, rooms) (ClearAccountsCache) = do
-	writeChan (dbQueries serverInfo) $ ClearCache
+	writeChan (dbQueries serverInfo) ClearCache
 	return (clID, serverInfo, clients, rooms)
 	where
 		client = clients ! clID
@@ -332,7 +332,7 @@
 	return (clID, serverInfo, clients, rooms)
 
 
-processAction (clID, serverInfo, clients, rooms) (ProcessAccountInfo info) = do
+processAction (clID, serverInfo, clients, rooms) (ProcessAccountInfo info) =
 	case info of
 		HasAccount passwd isAdmin -> do
 			infoM "Clients" $ show clID ++ " has account"
@@ -346,7 +346,7 @@
 			foldM processAction (clID, serverInfo, adjust (\cl -> cl{logonPassed = True, isAdministrator = True}) clID clients, rooms) [MoveToLobby, AnswerThisClient ["ADMIN_ACCESS"]]
 
 
-processAction (clID, serverInfo, clients, rooms) (MoveToLobby) = do
+processAction (clID, serverInfo, clients, rooms) (MoveToLobby) =
 	foldM processAction (clID, serverInfo, clients, rooms) $
 		(RoomAddThisClient 0)
 		: answerLobbyNicks
@@ -355,17 +355,14 @@
 		-- ++ (answerServerMessage client clients)
 	where
 		lobbyNicks = Prelude.map nick $ Prelude.filter logonPassed $ elems clients
-		answerLobbyNicks = if not $ Prelude.null lobbyNicks then
-					[AnswerThisClient (["LOBBY:JOINED"] ++ lobbyNicks)]
-				else
-					[]
+		answerLobbyNicks = [AnswerThisClient ("LOBBY:JOINED": lobbyNicks) | not $ Prelude.null lobbyNicks]
 
 
-processAction (clID, serverInfo, clients, rooms) (KickClient kickID) = do
+processAction (clID, serverInfo, clients, rooms) (KickClient kickID) =
 	liftM2 replaceID (return clID) (processAction (kickID, serverInfo, clients, rooms) $ ByeClient "Kicked")
 
 
-processAction (clID, serverInfo, clients, rooms) (BanClient banNick) = do
+processAction (clID, serverInfo, clients, rooms) (BanClient banNick) =
 	return (clID, serverInfo, clients, rooms)
 
 
@@ -374,9 +371,9 @@
 	liftM2 replaceID (return clID) (processAction (kickID, serverInfo, clients, rooms) $ RoomRemoveThisClient "kicked")
 
 
-processAction (clID, serverInfo, clients, rooms) (RemoveClientTeams teamsClID) = do
+processAction (clID, serverInfo, clients, rooms) (RemoveClientTeams teamsClID) =
 	liftM2 replaceID (return clID) $
-		foldM processAction (teamsClID, serverInfo, clients, rooms) $ removeTeamsActions
+		foldM processAction (teamsClID, serverInfo, clients, rooms) removeTeamsActions
 	where
 		client = clients ! teamsClID
 		room = rooms ! (roomID client)
@@ -386,8 +383,8 @@
 
 processAction (clID, serverInfo, clients, rooms) (AddClient client) = do
 	let updatedClients = insert (clientUID client) client clients
-	infoM "Clients" ((show $ clientUID client) ++ ": New client. Time: " ++ (show $ connectTime client))
-	writeChan (sendChan $ client) ["CONNECTED", "Hedgewars server http://www.hedgewars.org/"]
+	infoM "Clients" (show (clientUID client) ++ ": New client. Time: " ++ show (connectTime client))
+	writeChan (sendChan client) ["CONNECTED", "Hedgewars server http://www.hedgewars.org/"]
 
 	let newLogins = takeWhile (\(_ , time) -> (connectTime client) `diffUTCTime` time <= 11) $ lastLogins serverInfo
 
--- a/gameServer/ClientIO.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/ClientIO.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -23,7 +23,7 @@
 clientRecvLoop :: Handle -> Chan CoreMessage -> Int -> IO ()
 clientRecvLoop handle chan clientID =
 	listenLoop handle 0 [] chan clientID
-		`catch` (\e -> (clientOff $ show e) >> return ())
+		`catch` (\e -> clientOff (show e) >> return ())
 	where clientOff msg = writeChan chan $ ClientMessage (clientID, ["QUIT", msg]) -- if the client disconnects, we perform as if it sent QUIT message
 
 clientSendLoop :: Handle -> Chan CoreMessage -> Chan [String] -> Int -> IO()
@@ -31,7 +31,7 @@
 	answer <- readChan chan
 	doClose <- Exception.handle
 		(\(e :: Exception.IOException) -> if isQuit answer then return True else sendQuit e >> return False) $ do
-		forM_ answer (\str -> hPutStrLn handle str)
+		forM_ answer (hPutStrLn handle)
 		hPutStrLn handle ""
 		hFlush handle
 		return $ isQuit answer
--- a/gameServer/CoreTypes.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/CoreTypes.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -10,6 +10,7 @@
 import Data.Sequence(Seq, empty)
 import Data.Time
 import Network
+import Data.Function
 
 
 data ClientInfo =
@@ -33,12 +34,12 @@
 	}
 
 instance Show ClientInfo where
-	show ci = (show $ clientUID ci)
+	show ci = show (clientUID ci)
 			++ " nick: " ++ (nick ci)
 			++ " host: " ++ (host ci)
 
 instance Eq ClientInfo where
-	a1 == a2 = clientHandle a1 == clientHandle a2
+	(==) = (==) `on` clientHandle
 
 data HedgehogInfo =
 	HedgehogInfo String String
@@ -78,13 +79,13 @@
 	}
 
 instance Show RoomInfo where
-	show ri = (show $ roomUID ri)
-			++ ", players ids: " ++ (show $ IntSet.size $ playersIDs ri)
-			++ ", players: " ++ (show $ playersIn ri)
-			++ ", ready: " ++ (show $ readyPlayers ri)
+	show ri = show (roomUID ri)
+			++ ", players ids: " ++ show (IntSet.size $ playersIDs ri)
+			++ ", players: " ++ show (playersIn ri)
+			++ ", ready: " ++ show (readyPlayers ri)
 
 instance Eq RoomInfo where
-	a1 == a2 = roomUID a1 == roomUID a2
+	(==) = (==) `on` roomUID
 
 newRoom = (
 	RoomInfo
--- a/gameServer/HWProtoInRoomState.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/HWProtoInRoomState.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -27,33 +27,27 @@
 
 
 handleCmd_inRoom clID clients rooms ["PART"] =
-		[RoomRemoveThisClient "part"]
+	[RoomRemoveThisClient "part"]
 	where
 		client = clients IntMap.! clID
 
 
-handleCmd_inRoom clID clients rooms ("CFG" : paramName : paramStrs) =
-	if isMaster client then
-		[ModifyRoom (\r -> r{params = Map.insert paramName paramStrs (params r)})
-		, AnswerOthersInRoom ("CFG" : paramName : paramStrs)]
-	else
-		[ProtocolError "Not room master"]
+handleCmd_inRoom clID clients rooms ("CFG" : paramName : paramStrs)
+	| isMaster client =
+		[ModifyRoom (\r -> r{params = Map.insert paramName paramStrs (params r)}),
+		AnswerOthersInRoom ("CFG" : paramName : paramStrs)]
+	| otherwise = [ProtocolError "Not room master"]
 	where
 		client = clients IntMap.! clID
 
 handleCmd_inRoom clID clients rooms ("ADD_TEAM" : name : color : grave : fort : voicepack : difStr : hhsInfo)
-	| length hhsInfo == 16 =
-	if length (teams room) == 6 then
-		[Warning "too many teams"]
-	else if canAddNumber <= 0 then
-		[Warning "too many hedgehogs"]
-	else if isJust findTeam then
-		[Warning "already have a team with same name"]
-	else if gameinprogress room then
-		[Warning "round in progress"]
-	else if isRestrictedTeams room then
-		[Warning "restricted"]
-	else
+	| length hhsInfo /= 16 = []
+	| length (teams room) == 6 = [Warning "too many teams"]
+	| canAddNumber <= 0 = [Warning "too many hedgehogs"]
+	| isJust findTeam = [Warning "There's already a team with same name in the list"]
+	| gameinprogress room = [Warning "round in progress"]
+	| isRestrictedTeams room = [Warning "restricted"]
+	| otherwise =
 		[ModifyRoom (\r -> r{teams = teams r ++ [newTeam]}),
 		ModifyClient (\c -> c{teamsInGame = teamsInGame c + 1}),
 		AnswerThisClient ["TEAM_ACCEPTED", name],
@@ -72,15 +66,12 @@
 		newTeamHHNum = min 4 canAddNumber
 
 
-handleCmd_inRoom clID clients rooms ["REMOVE_TEAM", teamName] =
-	if noSuchTeam then
-		[Warning "REMOVE_TEAM: no such team"]
-	else
-		if not $ nick client == teamowner team then
-			[ProtocolError "Not team owner!"]
-		else
+handleCmd_inRoom clID clients rooms ["REMOVE_TEAM", teamName]
+	| noSuchTeam = [Warning "REMOVE_TEAM: no such team"]
+	| nick client /= teamowner team = [ProtocolError "Not team owner!"]
+	| otherwise =
 			[RemoveTeam teamName,
-			ModifyClient (\c -> c{teamsInGame = teamsInGame c - 1})	
+			ModifyClient (\c -> c{teamsInGame = teamsInGame c - 1})
 			]
 	where
 		client = clients IntMap.! clID
@@ -90,15 +81,12 @@
 		findTeam = find (\t -> teamName == teamname t) $ teams room
 
 
-handleCmd_inRoom clID clients rooms ["HH_NUM", teamName, numberStr] =
-	if not $ isMaster client then
-		[ProtocolError "Not room master"]
-	else
-		if hhNumber < 1 || hhNumber > 8 || noSuchTeam || hhNumber > (canAddNumber + (hhnum team)) then
-			[]
-		else
-			[ModifyRoom $ modifyTeam team{hhnum = hhNumber},
-			AnswerOthersInRoom ["HH_NUM", teamName, show hhNumber]]
+handleCmd_inRoom clID clients rooms ["HH_NUM", teamName, numberStr]
+	| not $ isMaster client = [ProtocolError "Not room master"]
+	| hhNumber < 1 || hhNumber > 8 || noSuchTeam || hhNumber > (canAddNumber + (hhnum team)) = []
+	| otherwise =
+		[ModifyRoom $ modifyTeam team{hhnum = hhNumber},
+		AnswerOthersInRoom ["HH_NUM", teamName, show hhNumber]]
 	where
 		client = clients IntMap.! clID
 		room = rooms IntMap.! (roomID client)
@@ -109,14 +97,10 @@
 		canAddNumber = 48 - (sum . map hhnum $ teams room)
 
 
-handleCmd_inRoom clID clients rooms ["TEAM_COLOR", teamName, newColor] =
-	if not $ isMaster client then
-		[ProtocolError "Not room master"]
-	else
-		if noSuchTeam then
-			[]
-		else
-			[ModifyRoom $ modifyTeam team{teamcolor = newColor},
+handleCmd_inRoom clID clients rooms ["TEAM_COLOR", teamName, newColor]
+	| not $ isMaster client = [ProtocolError "Not room master"]
+	| noSuchTeam = []
+	| otherwise = [ModifyRoom $ modifyTeam team{teamcolor = newColor},
 			AnswerOthersInRoom ["TEAM_COLOR", teamName, newColor]]
 	where
 		noSuchTeam = isNothing findTeam
@@ -129,13 +113,13 @@
 handleCmd_inRoom clID clients rooms ["TOGGLE_READY"] =
 	[ModifyClient (\c -> c{isReady = not $ isReady client}),
 	ModifyRoom (\r -> r{readyPlayers = readyPlayers r + (if isReady client then -1 else 1)}),
-	AnswerThisRoom $ [if isReady client then "NOT_READY" else "READY", nick client]]
+	AnswerThisRoom [if isReady client then "NOT_READY" else "READY", nick client]]
 	where
 		client = clients IntMap.! clID
 
 
 handleCmd_inRoom clID clients rooms ["START_GAME"] =
-	if isMaster client && (playersIn room == readyPlayers room) && (not $ gameinprogress room) then
+	if isMaster client && (playersIn room == readyPlayers room) && (not . gameinprogress) room then
 		if enoughClans then
 			[ModifyRoom
 					(\r -> r{
@@ -184,34 +168,21 @@
 		answerRemovedTeams = map (\t -> AnswerThisRoom ["REMOVE_TEAM", t]) $ leftTeams room
 
 
-handleCmd_inRoom clID clients _ ["TOGGLE_RESTRICT_JOINS"] =
-	if isMaster client then
-		[ModifyRoom (\r -> r{isRestrictedJoins = not $ isRestrictedJoins r})]
-	else
-		[ProtocolError "Not room master"]
+handleCmd_inRoom clID clients _ ["TOGGLE_RESTRICT_JOINS"]
+	| isMaster client = [ModifyRoom (\r -> r{isRestrictedJoins = not $ isRestrictedJoins r})]
+	| otherwise = [ProtocolError "Not room master"]
 	where
 		client = clients IntMap.! clID
 
 
-handleCmd_inRoom clID clients _ ["TOGGLE_RESTRICT_TEAMS"] =
-	if isMaster client then
-		[ModifyRoom (\r -> r{isRestrictedTeams = not $ isRestrictedTeams r})]
-	else
-		[ProtocolError "Not room master"]
+handleCmd_inRoom clID clients _ ["TOGGLE_RESTRICT_TEAMS"]
+	| isMaster client = [ModifyRoom (\r -> r{isRestrictedTeams = not $ isRestrictedTeams r})]
+	| otherwise = [ProtocolError "Not room master"]
 	where
 		client = clients IntMap.! clID
 
 handleCmd_inRoom clID clients rooms ["KICK", kickNick] =
-	if not $ isMaster client then
-		[]
-	else
-		if noSuchClient then
-			[]
-		else
-			if (kickID == clID) || (roomID client /= roomID kickClient) then
-				[]
-			else
-				[KickRoomClient kickID]
+	[KickRoomClient kickID | isMaster client && not noSuchClient && (kickID /= clID) && (roomID client == roomID kickClient)]
 	where
 		client = clients IntMap.! clID
 		maybeClient = Foldable.find (\cl -> kickNick == nick cl) clients
--- a/gameServer/HWProtoLobbyState.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/HWProtoLobbyState.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -23,14 +23,14 @@
 handleCmd_lobby clID clients rooms ["LIST"] =
 	[AnswerThisClient ("ROOMS" : roomsInfoList)]
 	where
-		roomsInfoList = concatMap roomInfo $ sameProtoRooms
-		sameProtoRooms = filter (\r -> (roomProto r == protocol) && (not $ isRestrictedJoins r)) roomsList
+		roomsInfoList = concatMap roomInfo sameProtoRooms
+		sameProtoRooms = filter (\r -> (roomProto r == protocol) && not (isRestrictedJoins r)) roomsList
 		roomsList = IntMap.elems rooms
 		protocol = clientProto client
 		client = clients IntMap.! clID
 		roomInfo room = [
 				name room,
-				(show $ playersIn room) ++ "(" ++ (show $ length $ teams room) ++ ")",
+				show (playersIn room) ++ "(" ++ show (length $ teams room) ++ ")",
 				show $ gameinprogress room
 				]
 
@@ -41,12 +41,10 @@
 		clientNick = nick $ clients IntMap.! clID
 
 
-handleCmd_lobby clID clients rooms ["CREATE_ROOM", newRoom, roomPassword] =
-	if haveSameRoom then
-		[Warning "Room exists"]
-	else if illegalName newRoom then
-		[Warning "Illegal room name"]
-	else
+handleCmd_lobby clID clients rooms ["CREATE_ROOM", newRoom, roomPassword]
+	| haveSameRoom = [Warning "Room exists"]
+	| illegalName newRoom = [Warning "Illegal room name"]
+	| otherwise =
 		[RoomRemoveThisClient "", -- leave lobby
 		AddRoom newRoom roomPassword,
 		AnswerThisClient ["NOT_READY", clientNick]
@@ -60,14 +58,11 @@
 	handleCmd_lobby clID clients rooms ["CREATE_ROOM", newRoom, ""]
 
 
-handleCmd_lobby clID clients rooms ["JOIN_ROOM", roomName, roomPassword] =
-	if noSuchRoom then
-		[Warning "No such room"]
-	else if isRestrictedJoins jRoom then
-		[Warning "Joining restricted"]
-	else if roomPassword /= password jRoom then
-		[Warning "Wrong password"]
-	else
+handleCmd_lobby clID clients rooms ["JOIN_ROOM", roomName, roomPassword]
+	| noSuchRoom = [Warning "No such room"]
+	| isRestrictedJoins jRoom = [Warning "Joining restricted"]
+	| roomPassword /= password jRoom = [Warning "Wrong password"]
+	| otherwise =
 		[RoomRemoveThisClient "", -- leave lobby
 		RoomAddThisClient rID] -- join room
 		++ answerNicks
@@ -78,18 +73,20 @@
 		++ watchRound
 	where
 		noSuchRoom = isNothing mbRoom
-		mbRoom = find (\r -> roomName == name r && roomProto r == clientProto client) $ IntMap.elems rooms 
+		mbRoom = find (\r -> roomName == name r && roomProto r == clientProto client) $ IntMap.elems rooms
 		jRoom = fromJust mbRoom
 		rID = roomUID jRoom
 		client = clients IntMap.! clID
 		roomClientsIDs = IntSet.elems $ playersIDs jRoom
-		answerNicks = if playersIn jRoom /= 0 then
-					[AnswerThisClient $ ["JOINED"] ++ (map (\clID -> nick $ clients IntMap.! clID) $ roomClientsIDs)]
-				else
-					[]
-		answerReady =
-			map (\c -> AnswerThisClient [if isReady c then "READY" else "NOT_READY", nick c]) $
-			map (\clID -> clients IntMap.! clID) roomClientsIDs
+		answerNicks =
+			[AnswerThisClient $ "JOINED" :
+			map (\clID -> nick $ clients IntMap.! clID) roomClientsIDs | playersIn jRoom /= 0]
+		answerReady = map
+			((\ c ->
+				AnswerThisClient
+				[if isReady c then "READY" else "NOT_READY", nick c])
+			. (\ clID -> clients IntMap.! clID))
+			roomClientsIDs
 
 		toAnswer (paramName, paramStrs) = AnswerThisClient $ "CFG" : paramName : paramStrs
 		
@@ -100,7 +97,7 @@
 					[]
 				else
 					[AnswerThisClient  ["RUN_GAME"],
-					AnswerThisClient $ "EM" : toEngineMsg "e$spectate 1" : (Foldable.toList $ roundMsgs jRoom)]
+					AnswerThisClient $ "EM" : toEngineMsg "e$spectate 1" : Foldable.toList (roundMsgs jRoom)]
 
 		answerTeams = if gameinprogress jRoom then
 				answerAllTeams (teamsAtStart jRoom)
@@ -115,16 +112,7 @@
 	-- Administrator's stuff --
 
 handleCmd_lobby clID clients rooms ["KICK", kickNick] =
-	if not $ isAdministrator client then
-		[]
-	else
-		if noSuchClient then
-			[]
-		else
-			if kickID == clID then
-				[]
-			else
-				[KickClient kickID]
+		[KickClient kickID | isAdministrator client && (not noSuchClient) && kickID /= clID]
 	where
 		client = clients IntMap.! clID
 		maybeClient = Foldable.find (\cl -> kickNick == nick cl) clients
@@ -142,19 +130,13 @@
 
 
 handleCmd_lobby clID clients rooms ["SET_SERVER_MESSAGE", newMessage] =
-	if not $ isAdministrator client then
-		[]
-	else
-		[ModifyServerInfo (\si -> si{serverMessage = newMessage})]
+		[ModifyServerInfo (\si -> si{serverMessage = newMessage}) | isAdministrator client]
 	where
 		client = clients IntMap.! clID
 
 
 handleCmd_lobby clID clients rooms ["CLEAR_ACCOUNTS_CACHE"] =
-	if not $ isAdministrator client then
-		[]
-	else
-		[ClearAccountsCache]
+		[ClearAccountsCache | isAdministrator client]
 	where
 		client = clients IntMap.! clID
 
--- a/gameServer/HWProtoNEState.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/HWProtoNEState.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -11,35 +11,29 @@
 
 handleCmd_NotEntered :: CmdHandler
 
-handleCmd_NotEntered clID clients _ ["NICK", newNick] =
-	if not . null $ nick client then
-		[ProtocolError "Nickname already chosen"]
-	else if haveSameNick then
-		[AnswerThisClient ["WARNING", "Nickname collision"]]
-		++ [ByeClient ""]
-	else if illegalName newNick then
-		[ByeClient "Illegal nickname"]
-	else
-		[ModifyClient (\c -> c{nick = newNick}),
-		AnswerThisClient ["NICK", newNick]]
-		++ checkPassword
+handleCmd_NotEntered clID clients _ ["NICK", newNick]
+	| not . null $ nick client = [ProtocolError "Nickname already chosen"]
+	| haveSameNick = [AnswerThisClient ["WARNING", "Nickname collision"], ByeClient ""]
+	| illegalName newNick = [ByeClient "Illegal nickname"]
+	| otherwise =
+		ModifyClient (\c -> c{nick = newNick}) :
+		AnswerThisClient ["NICK", newNick] :
+		[CheckRegistered | clientProto client /= 0]
 	where
 		client = clients IntMap.! clID
 		haveSameNick = isJust $ find (\cl -> newNick == nick cl) $ IntMap.elems clients
-		checkPassword = [CheckRegistered | clientProto client /= 0]
 
 
 handleCmd_NotEntered clID clients _ ["PROTO", protoNum]
 	| clientProto client > 0 = [ProtocolError "Protocol already known"]
 	| parsedProto == 0 = [ProtocolError "Bad number"]
 	| otherwise =
-		[ModifyClient (\ c -> c{clientProto = parsedProto}),
-		AnswerThisClient ["PROTO", show parsedProto]]
-		++ checkPassword
+		ModifyClient (\c -> c{clientProto = parsedProto}) :
+		AnswerThisClient ["PROTO", show parsedProto] :
+		[CheckRegistered | (not . null) (nick client)]
 	where
 		client = clients IntMap.! clID
 		parsedProto = fromMaybe 0 (maybeRead protoNum :: Maybe Word16)
-		checkPassword = [CheckRegistered | (not . null) (nick client)]
 
 
 handleCmd_NotEntered clID clients _ ["PASSWORD", passwd] =
--- a/gameServer/stresstest.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/stresstest.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -23,15 +23,15 @@
 	hFlush sock
 	threadDelay 225000
 
-testing = Control.Exception.handle (\e -> putStrLn $ show e) $ do
+testing = Control.Exception.handle print $ do
 	putStrLn "Start"
 	sock <- connectTo "127.0.0.1" (PortNumber 46631)
 
 	num1 <- randomRIO (70000::Int, 70100)
 	num2 <- randomRIO (0::Int, 2)
 	num3 <- randomRIO (0::Int, 5)
-	let nick1 = show $ num1
-	let room1 = show $ num2
+	let nick1 = show num1
+	let room1 = show num2
 	case num2 of 
 		0 -> emulateSession sock $ session1 nick1 room1
 		1 -> emulateSession sock $ session2 nick1 room1
--- a/gameServer/stresstest2.hs	Fri Sep 04 16:39:51 2009 +0000
+++ b/gameServer/stresstest2.hs	Fri Sep 04 16:50:52 2009 +0000
@@ -14,7 +14,7 @@
 import System.Posix
 #endif
 
-testing = Control.Exception.handle (\e -> putStrLn $ show e) $ do
+testing = Control.Exception.handle print $ do
 	delay <- randomRIO (100::Int, 300)
 	threadDelay delay
 	sock <- connectTo "127.0.0.1" (PortNumber 46631)