diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/ByteStringOperators.hs | 18 | ||||
-rw-r--r-- | Presence/FGConsole.hs | 62 | ||||
-rw-r--r-- | Presence/Server.hs | 81 | ||||
-rw-r--r-- | Presence/Todo.hs | 12 | ||||
-rw-r--r-- | Presence/UTmp.hs | 93 | ||||
-rw-r--r-- | Presence/main.hs | 85 |
6 files changed, 351 insertions, 0 deletions
diff --git a/Presence/ByteStringOperators.hs b/Presence/ByteStringOperators.hs new file mode 100644 index 00000000..8ecb214b --- /dev/null +++ b/Presence/ByteStringOperators.hs | |||
@@ -0,0 +1,18 @@ | |||
1 | module ByteStringOperators where | ||
2 | |||
3 | import qualified Data.ByteString as S (ByteString) | ||
4 | import Data.ByteString.Lazy.Char8 as L | ||
5 | |||
6 | (<++>) :: ByteString -> ByteString -> ByteString | ||
7 | (<++.>) :: ByteString -> S.ByteString -> ByteString | ||
8 | (<.++>) :: S.ByteString -> ByteString -> ByteString | ||
9 | (<.++.>) :: S.ByteString -> S.ByteString -> ByteString | ||
10 | a <++> b = L.append a b | ||
11 | a <++.> b = L.append a (fromChunks [b]) | ||
12 | a <.++> b = L.append (fromChunks [a]) b | ||
13 | a <.++.> b = fromChunks [a,b] | ||
14 | infixr 5 <.++.> | ||
15 | infixr 5 <.++> | ||
16 | infixr 5 <++> | ||
17 | infixr 5 <++.> | ||
18 | |||
diff --git a/Presence/FGConsole.hs b/Presence/FGConsole.hs new file mode 100644 index 00000000..fc1ece65 --- /dev/null +++ b/Presence/FGConsole.hs | |||
@@ -0,0 +1,62 @@ | |||
1 | {-# LANGUAGE ForeignFunctionInterface #-} | ||
2 | {-# LANGUAGE ScopedTypeVariables #-} | ||
3 | module FGConsole where | ||
4 | |||
5 | import Data.Word | ||
6 | import System.Posix.IO | ||
7 | import System.Posix.Types | ||
8 | import Control.Concurrent | ||
9 | -- import GHC.IO.Handle | ||
10 | import Unsafe.Coerce | ||
11 | import Control.Exception as E | ||
12 | -- import Prelude as E | ||
13 | import Control.Monad | ||
14 | import Foreign.C.Error | ||
15 | import Foreign.C | ||
16 | |||
17 | import Todo | ||
18 | import Debug.Trace | ||
19 | import System.Posix.Signals | ||
20 | |||
21 | -- c_monitorTTY fd = trace "c_monitorTTY" (return ()) -- (trace "WTF" todo) | ||
22 | |||
23 | foreign import ccall "monitorTTY" c_monitorTTY :: Fd -> IO () | ||
24 | foreign import ccall "closeTTY" c_closeTTY :: IO () | ||
25 | |||
26 | monitorTTY :: (Word8 -> IO ()) -> IO (Fd,ThreadId) | ||
27 | monitorTTY handler = do | ||
28 | (rfd,wfd) <- createPipe | ||
29 | thread <- forkIO $ do | ||
30 | let cleanup = do | ||
31 | trace "quitting monitorTTY thread." (return ()) | ||
32 | closeFd wfd `E.catch` \(e::IOException) -> return () | ||
33 | closeFd rfd `E.catch` \(e::IOException) -> return () | ||
34 | c_closeTTY | ||
35 | -- rh <- fdToHandle rfd | ||
36 | c_monitorTTY wfd | ||
37 | let monitor = | ||
38 | (do | ||
39 | threadWaitRead rfd | ||
40 | (cs,cnt) <- fdRead rfd 1 | ||
41 | forM_ cs (handler . unsafeCoerce . trace "read byte") | ||
42 | monitor) | ||
43 | `E.catch` | ||
44 | \(e :: IOException) -> do | ||
45 | err <- getErrno | ||
46 | case () of | ||
47 | _ | err==eAGAIN -> monitor | ||
48 | _ | otherwise -> cleanup | ||
49 | `E.catch` | ||
50 | \(e :: AsyncException) -> cleanup | ||
51 | monitor | ||
52 | return (rfd,thread) | ||
53 | |||
54 | unmonitorTTY (rfd,thread) = do | ||
55 | closeFd rfd | ||
56 | yield | ||
57 | killThread thread | ||
58 | raiseSignal sigUSR1 | ||
59 | -- threadDelay 1000000 | ||
60 | |||
61 | |||
62 | -- vim:ft=haskell: | ||
diff --git a/Presence/Server.hs b/Presence/Server.hs new file mode 100644 index 00000000..c41f047f --- /dev/null +++ b/Presence/Server.hs | |||
@@ -0,0 +1,81 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE TypeOperators #-} | ||
3 | module Server where | ||
4 | |||
5 | import Network.Socket | ||
6 | import qualified Data.ByteString as S (ByteString) | ||
7 | import Data.ByteString.Lazy.Char8 as L | ||
8 | ( ByteString | ||
9 | , hPutStrLn | ||
10 | , fromChunks | ||
11 | , putStrLn ) | ||
12 | import Data.ByteString.Char8 | ||
13 | ( hGetNonBlocking | ||
14 | ) | ||
15 | import System.IO | ||
16 | ( Handle | ||
17 | , IOMode(..) | ||
18 | , hSetBuffering | ||
19 | , BufferMode(..) | ||
20 | , hWaitForInput | ||
21 | , hClose | ||
22 | , hIsEOF | ||
23 | ) | ||
24 | import Control.Monad | ||
25 | import Control.Monad.Fix (fix) | ||
26 | import Todo | ||
27 | import Control.Concurrent (forkIO) | ||
28 | import Control.Exception (handle,SomeException(..)) | ||
29 | import Data.HList | ||
30 | import Data.HList.TypeEqGeneric1() | ||
31 | import Data.HList.TypeCastGeneric1() | ||
32 | |||
33 | |||
34 | newtype ConnId = ConnId Int | ||
35 | deriving Eq | ||
36 | |||
37 | newtype ConnectionFinalizer = ConnectionFinalizer (IO ()) | ||
38 | |||
39 | getPacket h = do { hWaitForInput h (-1) ; fmap (fromChunks . (:[])) $ hGetNonBlocking h 1024 } | ||
40 | |||
41 | {- | ||
42 | doServer :: | ||
43 | HList st | ||
44 | => PortNumber :*: st | ||
45 | -> ( Handle :*: ConnId :*: PortNumber :*: st | ||
46 | -> S.ByteString | ||
47 | -> (() -> IO ()) | ||
48 | -> IO () ) | ||
49 | -> IO b | ||
50 | -} | ||
51 | doServer port g startCon = runServer2 port (runConn2 g) | ||
52 | where | ||
53 | runConn2 g st (sock,_) = do | ||
54 | h <- socketToHandle sock ReadWriteMode | ||
55 | hSetBuffering h NoBuffering | ||
56 | st'' <- startCon (h .*. st) | ||
57 | handle (\(SomeException _) -> return ()) $ fix $ \loop -> do | ||
58 | let continue () = hIsEOF h >>= flip when loop . not | ||
59 | packet <- getPacket h | ||
60 | g st'' packet continue | ||
61 | let ConnectionFinalizer cleanup = hOccursFst st'' | ||
62 | cleanup | ||
63 | hClose h | ||
64 | |||
65 | {- | ||
66 | runServer2 :: | ||
67 | Num num => | ||
68 | PortNumber -> (num -> (Socket, SockAddr) -> IO b -> IO b) -> IO b | ||
69 | -} | ||
70 | runServer2 st@(HCons port _) go = do | ||
71 | sock <- socket AF_INET Stream 0 | ||
72 | setSocketOption sock ReuseAddr 1 | ||
73 | bindSocket sock (SockAddrInet port iNADDR_ANY) | ||
74 | listen sock 2 | ||
75 | mainLoop sock (ConnId 0) go | ||
76 | where | ||
77 | mainLoop sock idnum@(ConnId n) go = do | ||
78 | con <- accept sock | ||
79 | forkIO $ go (idnum .*. st) con | ||
80 | mainLoop sock (ConnId (n+1)) go | ||
81 | |||
diff --git a/Presence/Todo.hs b/Presence/Todo.hs new file mode 100644 index 00000000..7428565e --- /dev/null +++ b/Presence/Todo.hs | |||
@@ -0,0 +1,12 @@ | |||
1 | module Todo where | ||
2 | |||
3 | todo = todo -- bottom that means unimplemented function | ||
4 | |||
5 | withType :: v -> v -> v | ||
6 | withType = const | ||
7 | |||
8 | type Todo = () | ||
9 | |||
10 | -- Bad idea: -xc backtrace shows it looking just like the other | ||
11 | -- bottom defined above. | ||
12 | -- crash = crash -- bottom used to crash to indicate error | ||
diff --git a/Presence/UTmp.hs b/Presence/UTmp.hs new file mode 100644 index 00000000..c94dcef2 --- /dev/null +++ b/Presence/UTmp.hs | |||
@@ -0,0 +1,93 @@ | |||
1 | |||
2 | {-# LANGUAGE TemplateHaskell #-} | ||
3 | module UTmp (users, utmp_file) where | ||
4 | |||
5 | import qualified Data.ByteString as S | ||
6 | import qualified Data.ByteString.Char8 as C | ||
7 | import Data.BitSyntax | ||
8 | import Data.Functor.Identity | ||
9 | import Foreign.C.String | ||
10 | import Data.Maybe | ||
11 | import System.Posix.Signals | ||
12 | import System.Posix.Types | ||
13 | import Control.Monad | ||
14 | import Unsafe.Coerce | ||
15 | import Data.Word | ||
16 | import Data.Int | ||
17 | import Control.Monad.Error.Class | ||
18 | import System.IO.Error | ||
19 | |||
20 | import Todo | ||
21 | |||
22 | utmp_file = "/var/run/utmp" | ||
23 | |||
24 | utmp_bs = S.readFile utmp_file | ||
25 | |||
26 | decode_utmp_bytestring = | ||
27 | runIdentity | ||
28 | . $(bitSyn [ UnsignedLE 4 -- type | ||
29 | , UnsignedLE 4 -- pid | ||
30 | , Fixed 32 -- tty | ||
31 | , Fixed 4 -- inittab id | ||
32 | , Fixed 32 -- username | ||
33 | , Fixed 256 -- remote host | ||
34 | , UnsignedLE 4 -- termination status | ||
35 | , UnsignedLE 4 -- exit status | ||
36 | , Fixed 4 -- session id | ||
37 | , Fixed 8 -- time entry was made | ||
38 | , Fixed 16 -- remote addr v6 | ||
39 | , Skip 20 -- reserved | ||
40 | ]) | ||
41 | |||
42 | utmp_size = 384 -- 768 | ||
43 | |||
44 | |||
45 | utmp_records bs | S.length bs >= utmp_size | ||
46 | = u:utmp_records us | ||
47 | where | ||
48 | (u,us) = S.splitAt utmp_size bs | ||
49 | |||
50 | utmp_records bs = [bs] | ||
51 | |||
52 | utmp = fmap (map decode_utmp_bytestring . utmp_records) utmp_bs | ||
53 | |||
54 | |||
55 | interp_utmp_record (typ,pid,tty,inittab,user,hostv4,term,exit,session,time,hostv6) = | ||
56 | (toStr user, toStr tty, processId pid, (toEnum . fromIntegral) typ :: UT_Type) | ||
57 | where | ||
58 | toStr = takeWhile (/='\0') . C.unpack | ||
59 | processId = CPid . coerce | ||
60 | coerce :: Word32 -> Int32 | ||
61 | coerce = unsafeCoerce | ||
62 | |||
63 | |||
64 | data UT_Type | ||
65 | = EMPTY -- No valid user accounting information. */ | ||
66 | |||
67 | | RUN_LVL -- The system's runlevel. */ | ||
68 | | BOOT_TIME -- Time of system boot. */ | ||
69 | | NEW_TIME -- Time after system clock changed. */ | ||
70 | | OLD_TIME -- Time when system clock changed. */ | ||
71 | |||
72 | | INIT_PROCESS -- Process spawned by the init process. */ | ||
73 | | LOGIN_PROCESS -- Session leader of a logged in user. */ | ||
74 | | USER_PROCESS -- Normal process. */ | ||
75 | | DEAD_PROCESS -- Terminated process. */ | ||
76 | |||
77 | | ACCOUNTING | ||
78 | |||
79 | deriving (Enum,Show,Eq,Read) | ||
80 | |||
81 | processAlive pid = do | ||
82 | catchError (do { signalProcess nullSignal pid ; return True }) | ||
83 | $ \e -> do { return (not ( isDoesNotExistError e)); } | ||
84 | |||
85 | users = do | ||
86 | us <- utmp | ||
87 | let us' = map interp_utmp_record us | ||
88 | us'' = mapMaybe user_proc us' | ||
89 | user_proc (u,tty,pid,USER_PROCESS) = Just (u,tty,pid) | ||
90 | user_proc _ = Nothing | ||
91 | onThrd f (_,_,pid) = f pid | ||
92 | us3 <- filterM (onThrd processAlive) us'' | ||
93 | return us3 | ||
diff --git a/Presence/main.hs b/Presence/main.hs new file mode 100644 index 00000000..99f58ee4 --- /dev/null +++ b/Presence/main.hs | |||
@@ -0,0 +1,85 @@ | |||
1 | |||
2 | import System.Directory | ||
3 | import System.IO | ||
4 | import Control.Monad | ||
5 | import System.Posix.Signals | ||
6 | import System.Posix.Types | ||
7 | import Control.Monad.Error.Class | ||
8 | import Control.Exception (throw) | ||
9 | import System.Posix.Process | ||
10 | import Data.Maybe | ||
11 | |||
12 | import System.INotify | ||
13 | import UTmp | ||
14 | import FGConsole | ||
15 | |||
16 | jid user host rsrc = user ++ "@" ++ host ++ "/" ++ rsrc | ||
17 | |||
18 | toJabberId :: String -> (String,String,t) -> Maybe String | ||
19 | toJabberId host (user,tty,_) = | ||
20 | if take 3 tty == "tty" | ||
21 | then Just (jid user host tty) | ||
22 | else Nothing | ||
23 | |||
24 | utmp_event e = do | ||
25 | -- print e | ||
26 | putStrLn "---" | ||
27 | us <- users | ||
28 | let ids = mapMaybe (toJabberId "localhost") us | ||
29 | ids :: [String] | ||
30 | forM_ ids putStrLn | ||
31 | |||
32 | on_chvt vtnum = do | ||
33 | putStrLn $ "changed vt to "++ show vtnum | ||
34 | |||
35 | start :: IO () | ||
36 | start = do | ||
37 | installHandler sigUSR1 (Catch (utmp_event (userError "signaled"))) Nothing | ||
38 | inotify <- initINotify | ||
39 | print inotify | ||
40 | wd <- addWatch | ||
41 | inotify | ||
42 | [CloseWrite] -- [Open,Close,Access,Modify,Move] | ||
43 | utmp_file | ||
44 | utmp_event | ||
45 | print wd | ||
46 | mtty <- monitorTTY on_chvt | ||
47 | putStrLn "Hit enter to terminate..." | ||
48 | getLine | ||
49 | unmonitorTTY mtty | ||
50 | removeWatch wd | ||
51 | |||
52 | sendUSR1 pid = do | ||
53 | signalProcess sigUSR1 pid | ||
54 | |||
55 | getStartupAction [] = throw (userError "pid file?") >> return (Right "") | ||
56 | getStartupAction (p:ps) = do | ||
57 | catch | ||
58 | ( do | ||
59 | pid <- fmap CPid (readFile p >>= readIO) | ||
60 | -- signal pid | ||
61 | return (Left pid) ) | ||
62 | onEr | ||
63 | where | ||
64 | onEr e = do | ||
65 | pid <- getProcessID | ||
66 | putStrLn $ "starting pid = "++show pid | ||
67 | catch (do | ||
68 | writeFile p (show pid) | ||
69 | putStrLn $ "writing "++show p | ||
70 | -- start daemon | ||
71 | return (Right p) ) | ||
72 | (\_ -> getStartupAction ps) | ||
73 | |||
74 | runOnce ps run notify = getStartupAction ps >>= doit | ||
75 | where | ||
76 | doit (Left pid ) = notify pid | ||
77 | doit (Right pidfile ) = do | ||
78 | run | ||
79 | removeFile pidfile | ||
80 | |||
81 | |||
82 | main = do | ||
83 | runOnce ["/var/run/presence.pid","/tmp/presence.pid"] start sendUSR1 | ||
84 | |||
85 | |||