diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/LocalPeerCred.hs | 138 |
1 files changed, 114 insertions, 24 deletions
diff --git a/Presence/LocalPeerCred.hs b/Presence/LocalPeerCred.hs index 0122b5d0..2d5c0628 100644 --- a/Presence/LocalPeerCred.hs +++ b/Presence/LocalPeerCred.hs | |||
@@ -1,23 +1,25 @@ | |||
1 | {-# LANGUAGE ViewPatterns #-} | 1 | {-# LANGUAGE ViewPatterns #-} |
2 | {-# LANGUAGE TupleSections #-} | ||
2 | module LocalPeerCred where | 3 | module LocalPeerCred where |
3 | 4 | ||
4 | {- for main | ||
5 | import System.Environment | ||
6 | import Control.Monad | ||
7 | -} | ||
8 | |||
9 | import System.Endian | 5 | import System.Endian |
10 | import Data.ByteString.Lazy.Char8 as L hiding (map,putStrLn,tail,splitAt,tails,filter) | 6 | import qualified Data.ByteString.Lazy.Char8 as L |
11 | import qualified Data.ByteString.Lazy.Char8 as L (splitAt) | 7 | -- hiding (map,putStrLn,tail,splitAt,tails,filter) |
8 | -- import qualified Data.ByteString.Lazy.Char8 as L (splitAt) | ||
12 | import qualified Data.ByteString.Lazy as W8 | 9 | import qualified Data.ByteString.Lazy as W8 |
13 | import Data.List (tails) | 10 | import Data.List as List (tails,groupBy) |
14 | import System.IO ( withFile, IOMode(..)) | 11 | import System.IO ( withFile, IOMode(..)) |
12 | import System.Directory | ||
13 | import Control.Arrow (first) | ||
14 | import Data.Char | ||
15 | import Data.Maybe | 15 | import Data.Maybe |
16 | import Data.Binary | 16 | import Data.Binary |
17 | import Data.Bits | 17 | import Data.Bits |
18 | import System.Posix.Types | 18 | import System.Posix.Types |
19 | import System.Posix.Files | ||
19 | import Debug.Trace | 20 | import Debug.Trace |
20 | import SocketLike | 21 | import SocketLike |
22 | import ControlMaybe | ||
21 | 23 | ||
22 | xs ?? n | n < 0 = Nothing | 24 | xs ?? n | n < 0 = Nothing |
23 | [] ?? _ = Nothing | 25 | [] ?? _ = Nothing |
@@ -71,7 +73,7 @@ as16 :: Word16 -> Word16 | |||
71 | as16 = id | 73 | as16 = id |
72 | 74 | ||
73 | parseProcNet port host h = do | 75 | parseProcNet port host h = do |
74 | tcp <- hGetContents h -- Failed: tcp <- hFileSize h >>= hGet h . fromIntegral | 76 | tcp <- L.hGetContents h -- Failed: tcp <- hFileSize h >>= hGet h . fromIntegral |
75 | let u = do | 77 | let u = do |
76 | ls <- listToMaybe . tail . tails . L.lines $ tcp | 78 | ls <- listToMaybe . tail . tails . L.lines $ tcp |
77 | let ws = map L.words ls | 79 | let ws = map L.words ls |
@@ -86,7 +88,7 @@ parseProcNet port host h = do | |||
86 | uid <- listToMaybe ys' | 88 | uid <- listToMaybe ys' |
87 | inode <- listToMaybe ys'' | 89 | inode <- listToMaybe ys'' |
88 | let peer = (port,decode addr) | 90 | let peer = (port,decode addr) |
89 | user = toEnum (read (unpack uid) ::Int) ::UserID -- CUid . fromIntegral $ (read (unpack uid)::Int) | 91 | user = toEnum (read (L.unpack uid) ::Int) ::UserID -- CUid . fromIntegral $ (read (unpack uid)::Int) |
90 | return $ {-trace ("peer:"++show(peer,user,inode))-} (peer,(user,inode)) | 92 | return $ {-trace ("peer:"++show(peer,user,inode))-} (peer,(user,inode)) |
91 | ) | 93 | ) |
92 | fmap snd . listToMaybe $ filter ((==(port,host)).fst) rs | 94 | fmap snd . listToMaybe $ filter ((==(port,host)).fst) rs |
@@ -97,20 +99,108 @@ parseProcNet port host h = do | |||
97 | a === b = let r= a==b in trace ("Comparing "++show (a,b)++"-->"++show r) r | 99 | a === b = let r= a==b in trace ("Comparing "++show (a,b)++"-->"++show r) r |
98 | -} | 100 | -} |
99 | 101 | ||
100 | {- | ||
101 | main = do | ||
102 | args <- getArgs | ||
103 | let addr_str = fromJust (args??0) | ||
104 | port_str = fromJust (args??1) | ||
105 | info <- getAddrInfo (Just $ defaultHints { addrFlags = [ AI_NUMERICHOST ] }) | ||
106 | (Just addr_str) | ||
107 | (Just port_str) | ||
108 | let addrs = map addrAddress info | ||
109 | forM_ addrs $ \addr -> do | ||
110 | r <- getLocalPeerCred' addr | ||
111 | putStrLn $ "r{"++show addr++"} = " ++ show r | ||
112 | -} | ||
113 | 102 | ||
114 | -- PEER NAME: [::ffff:127.0.0.1]:34307 | 103 | -- PEER NAME: [::ffff:127.0.0.1]:34307 |
115 | unmap6mapped4 addr@(SockAddrInet6 port _ (0,0,0xFFFF,a) _) = SockAddrInet port (toBE32 a) | 104 | unmap6mapped4 addr@(SockAddrInet6 port _ (0,0,0xFFFF,a) _) = SockAddrInet port (toBE32 a) |
116 | unmap6mapped4 addr = addr | 105 | unmap6mapped4 addr = addr |
106 | |||
107 | identifyTTY tty_pids uid inode = do | ||
108 | pid <- scanProc (show uid) (L.unpack inode) | ||
109 | -- putStrLn $ "scanProc --> "++show pid | ||
110 | flip (maybe (return Nothing)) pid $ \(pid,ttydev) -> do | ||
111 | tty <- ttyOrDisplay pid ttydev | ||
112 | -- putStrLn $ "users = " ++ show tty_pids | ||
113 | dts <- ttyToXorgs tty_pids | ||
114 | -- putStrLn $ "displays = " ++ show dts | ||
115 | -- putStrLn $ "tty = " ++ show tty | ||
116 | -- -- displays = [(":5",Chunk "tty7" Empty)] | ||
117 | let tty' = if take 3 tty=="tty" then Just (L.pack tty) else lookup (parseTty tty) (map (first parseTty) dts) | ||
118 | return tty' | ||
119 | where | ||
120 | parseTty :: String -> Float | ||
121 | parseTty = read . tail . dropWhile (/=':') | ||
122 | |||
123 | ttyToXorgs tty_pids = do | ||
124 | dts' <- flip mapM tty_pids $ \(tty,pid) -> do | ||
125 | cmd' <- readFile $ "/proc/"++show pid++"/cmdline" | ||
126 | case listToMaybe . words . takeWhile (/='\0') $ cmd' of | ||
127 | Nothing -> return Nothing | ||
128 | Just cmd -> do | ||
129 | if notElem cmd ["gdm-session-worker"] | ||
130 | then return Nothing | ||
131 | else do | ||
132 | display <- readDisplayVariable pid | ||
133 | return (fmap ( (,tty) . snd ) display) | ||
134 | let dts = catMaybes dts' | ||
135 | return dts | ||
136 | |||
137 | |||
138 | scanProc uid inode = do | ||
139 | contents <- getDirectoryContents "/proc" `catchIO_` return [] | ||
140 | let pids = reverse $ filter (\n -> not (null n) && isDigit (head n)) contents | ||
141 | let searchPids [] = return Nothing | ||
142 | searchPids (pid:pids) = do | ||
143 | loginuid <- fmap makeUidStr $ readFile $ "/proc/"++pid++"/loginuid" | ||
144 | if False -- (uid/=loginuid) -- this check proved bad when mcabber ran on tty3 | ||
145 | then searchPids pids | ||
146 | else do | ||
147 | -- putStrLn $ "pid "++show pid ++ " --> uid "++show loginuid | ||
148 | let loop [] = return Nothing | ||
149 | loop ("0":fds) = loop fds | ||
150 | loop (fd:fds) = do | ||
151 | handleIO_ (loop fds) $ do | ||
152 | what <- readSymbolicLink $ "/proc/"++pid++"/fd/"++fd | ||
153 | -- putStrLn $ " what= "++show what | ||
154 | if (what=="socket:["++inode++"]") | ||
155 | then do | ||
156 | tty <- readSymbolicLink $ "/proc/"++pid++"/fd/0" | ||
157 | return (Just (pid,tty)) | ||
158 | else loop fds | ||
159 | fds <- getDirectoryContents ("/proc/"++pid++"/fd") `catchIO_` return [] | ||
160 | mb <- loop fds | ||
161 | maybe (searchPids pids) (return . Just) mb | ||
162 | |||
163 | fmap (fmap (first (read :: String -> CPid))) $ searchPids pids | ||
164 | |||
165 | ttyOrDisplay pid ttydev = do | ||
166 | ptty <- searchParentsForTTY (show pid) ttydev | ||
167 | case ptty of | ||
168 | Just tty -> return tty | ||
169 | Nothing -> do | ||
170 | display <- readDisplayVariable pid | ||
171 | -- putStrLn $ "display = " ++ show display | ||
172 | case display of | ||
173 | Just (_,disp) -> return disp | ||
174 | _ -> return ttydev | ||
175 | |||
176 | |||
177 | readDisplayVariable pid = do | ||
178 | env <- handleIO_ (return "") | ||
179 | . readFile $ "/proc/"++show pid++"/environ" | ||
180 | let vs = unzero $ List.groupBy (\_ c->c/='\0') env | ||
181 | unzero [] = [] | ||
182 | unzero (v:vs) = v:map tail vs | ||
183 | keyvalue xs = (key,value) | ||
184 | where | ||
185 | (key,ys) = break (=='=') xs | ||
186 | value = case ys of { [] -> []; (_:ys') -> ys' } | ||
187 | display = listToMaybe | ||
188 | . filter ((=="DISPLAY").fst) | ||
189 | . map keyvalue | ||
190 | $ vs | ||
191 | return display | ||
192 | |||
193 | |||
194 | makeUidStr "4294967295" = "invalid" | ||
195 | makeUidStr uid = uid | ||
196 | |||
197 | |||
198 | searchParentsForTTY pid ttydev | take 8 ttydev == "/dev/tty" = return . Just $ drop 5 ttydev | ||
199 | searchParentsForTTY "1" ttydev | otherwise = return Nothing | ||
200 | searchParentsForTTY pid ttydev = do | ||
201 | stat <- handleIO_ (return "") . readFile $ "/proc/"++pid++"/stat" | ||
202 | case words stat ?? 3 of | ||
203 | Nothing -> return Nothing | ||
204 | Just ppid -> do | ||
205 | tty <- handleIO_ (return "") $ readSymbolicLink $ "/proc/"++ppid++"/fd/0" | ||
206 | searchParentsForTTY ppid tty | ||