netserver/Miscutils.hs
changeset 901 2f5ce9a584f9
parent 895 6aee2f335726
child 902 3cc10f0aae37
--- a/netserver/Miscutils.hs	Fri May 02 09:23:51 2008 +0000
+++ b/netserver/Miscutils.hs	Sun May 04 13:49:55 2008 +0000
@@ -1,12 +1,12 @@
 module Miscutils where
 
 import IO
-import System.IO
-import Control.Concurrent
 import Control.Concurrent.STM
-import Control.Exception (finally)
 import Data.Word
 import Data.Char
+import Data.List
+import Maybe (fromJust)
+
 
 data ClientInfo =
 	ClientInfo
@@ -26,10 +26,30 @@
 		password :: String
 	}
 
-tselect :: [ClientInfo] -> STM (String, ClientInfo)
-tselect = foldl orElse retry . map (\ci -> (flip (,) ci) `fmap` readTChan (chan ci))
+clientByHandle :: Handle -> [ClientInfo] -> ClientInfo
+clientByHandle clhandle clients = fromJust $ find (\ci -> handle ci == clhandle) clients
+
+fromRoomHandles :: String -> [ClientInfo] -> [Handle]
+fromRoomHandles roomName clients = map (\ci -> handle ci) $ filter (\ci -> room ci == roomName) clients
+
+modifyClient :: Handle -> [ClientInfo] -> (ClientInfo -> ClientInfo) -> [ClientInfo]
+modifyClient clhandle (cl:cls) func =
+	if handle cl == clhandle then
+		(func cl) : cls
+	else
+		cl : (modifyClient clhandle cls func)
+
+tselect :: [ClientInfo] -> STM (String, Handle)
+tselect = foldl orElse retry . map (\ci -> (flip (,) $ handle ci) `fmap` readTChan (chan ci))
 
 maybeRead :: Read a => String -> Maybe a
 maybeRead s = case reads s of
 	[(x, rest)] | all isSpace rest -> Just x
 	_         -> Nothing
+
+deleteBy2t :: (a -> b -> Bool) -> b -> [a] -> [a]
+deleteBy2t _  _ [] = []
+deleteBy2t eq x (y:ys) = if y `eq` x then ys else y : deleteBy2t eq x ys
+
+deleteFirstsBy2t :: (a -> b -> Bool) -> [a] -> [b] -> [a]
+deleteFirstsBy2t eq =  foldl (flip (deleteBy2t eq))