summaryrefslogtreecommitdiff
path: root/Presence/UTmp.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Presence/UTmp.hs')
-rw-r--r--Presence/UTmp.hs249
1 files changed, 249 insertions, 0 deletions
diff --git a/Presence/UTmp.hs b/Presence/UTmp.hs
new file mode 100644
index 00000000..b43278da
--- /dev/null
+++ b/Presence/UTmp.hs
@@ -0,0 +1,249 @@
1{-# LANGUAGE TemplateHaskell #-}
2{-# LANGUAGE RankNTypes #-}
3module UTmp
4 ( users
5 , users2
6 , utmp_file
7 , UserName
8 , Tty
9 , ProcessID
10 , UtmpRecord(..)
11 , UT_Type(..)
12 ) where
13
14import qualified Data.ByteString as S
15import qualified Data.ByteString.Char8 as C
16import qualified Data.ByteString.Lazy.Char8 as L
17import Data.BitSyntax
18import Data.Functor.Identity
19import Data.Maybe
20import System.Posix.Signals
21import System.Posix.Types
22import Control.Monad
23import Data.Word
24import Data.Int
25import Control.Monad.Error.Class
26import System.IO.Error
27import qualified Paths
28import Data.Text ( Text )
29import Unsafe.Coerce ( unsafeCoerce )
30import Network.Socket ( SockAddr(..) )
31import qualified Data.Text.Encoding as Text
32import SockAddr ()
33
34
35utmp_file :: String
36utmp_file = Paths.utmp -- "/var/run/utmp"
37
38utmp_bs :: IO C.ByteString
39utmp_bs = S.readFile utmp_file
40
41decode_utmp_bytestring ::
42 C.ByteString
43 -> (Word32,
44 Word32,
45 C.ByteString,
46 C.ByteString,
47 C.ByteString,
48 C.ByteString,
49 Word16,
50 Word16,
51 Word32,
52 C.ByteString,
53 Word32,
54 Word32,
55 Word32,
56 Word32)
57decode_utmp_bytestring =
58 runIdentity
59 . $(bitSyn [ UnsignedLE 4 -- type
60 , UnsignedLE 4 -- pid
61 , Fixed 32 -- tty
62 , Fixed 4 -- inittab id
63 , Fixed 32 -- username
64 , Fixed 256 -- remote host
65 , UnsignedLE 2 -- termination status
66 , UnsignedLE 2 -- exit status (int)
67 , UnsignedLE 4 -- session id (int)
68 , Fixed 8 -- time entry was made
69 , Unsigned 4 -- remote addr v6 addr[0]
70 , Unsigned 4 -- remote addr v6 addr[1]
71 , Unsigned 4 -- remote addr v6 addr[2]
72 , Unsigned 4 -- remote addr v6 addr[3]
73 , Skip 20 -- reserved
74 ])
75
76utmp_size :: Int
77utmp_size = 384 -- 768
78
79
80utmp_records :: C.ByteString -> [C.ByteString]
81utmp_records bs | S.length bs >= utmp_size
82 = u:utmp_records us
83 where
84 (u,us) = S.splitAt utmp_size bs
85
86utmp_records bs = [bs]
87
88utmp ::
89 IO
90 [(Word32,
91 Word32,
92 C.ByteString,
93 C.ByteString,
94 C.ByteString,
95 C.ByteString,
96 Word16,
97 Word16,
98 Word32,
99 C.ByteString,
100 Word32,
101 Word32,
102 Word32,
103 Word32)]
104utmp = fmap (map decode_utmp_bytestring . utmp_records) utmp_bs
105
106toStr :: C.ByteString -> [Char]
107toStr = takeWhile (/='\0') . C.unpack
108
109interp_utmp_record ::
110 forall t t1 t2 t3 t4 t5 t6 t7 t8 a.
111 Integral a =>
112 (a,
113 Word32,
114 C.ByteString,
115 t,
116 C.ByteString,
117 C.ByteString,
118 t1,
119 t2,
120 t3,
121 t4,
122 t5,
123 t6,
124 t7,
125 t8)
126 -> (UT_Type, [Char], [Char], CPid, [Char])
127interp_utmp_record (typ,pid,tty,inittab,user,hostv4,term,exit,session,time
128 ,addr0,addr1,addr2,addr3) =
129 ( (toEnum . fromIntegral) typ :: UT_Type
130 , toStr user, toStr tty, processId pid, toStr hostv4 )
131 where
132 processId = CPid . coerceToSigned
133
134coerceToSigned :: Word32 -> Int32
135coerceToSigned = unsafeCoerce
136
137
138data UT_Type
139 = EMPTY -- No valid user accounting information. */
140
141 | RUN_LVL -- The system's runlevel. */
142 | BOOT_TIME -- Time of system boot. */
143 | NEW_TIME -- Time after system clock changed. */
144 | OLD_TIME -- Time when system clock changed. */
145
146 | INIT_PROCESS -- Process spawned by the init process. */
147 | LOGIN_PROCESS -- Session leader of a logged in user. */
148 | USER_PROCESS -- Normal process. */
149 | DEAD_PROCESS -- Terminated process. */
150
151 | ACCOUNTING
152
153 deriving (Enum,Show,Eq,Ord,Read)
154
155processAlive :: ProcessID -> IO Bool
156processAlive pid = do
157 catchError (do { signalProcess nullSignal pid ; return True })
158 $ \e -> do { return (not ( isDoesNotExistError e)); }
159
160type UserName = L.ByteString
161type Tty = L.ByteString
162
163users :: IO [(UserName, Tty, ProcessID)]
164users = fmap (map only3) $ do
165 us <- utmp
166 let us' = map interp_utmp_record us
167 us'' = mapMaybe user_proc us'
168 user_proc (USER_PROCESS, u,tty,pid, hostv4)
169 = Just (L.pack u,L.pack tty,pid,hostv4)
170 user_proc _ = Nothing
171 onThrd f (_,_,pid,_) = f pid
172 us3 <- filterM (onThrd processAlive) us''
173 return us3
174
175only3 :: forall t t1 t2 t3. (t1, t2, t3, t) -> (t1, t2, t3)
176only3 (a,b,c,_) = (a,b,c)
177
178data UtmpRecord = UtmpRecord
179 { utmpType :: UT_Type
180 , utmpUser :: Text
181 , utmpTty :: Text
182 , utmpPid :: CPid
183 , utmpHost :: Text
184 , utmpSession :: Int32
185 , utmpRemoteAddr :: Maybe SockAddr
186 }
187 deriving ( Show, Eq, Ord )
188
189toText :: C.ByteString -> Text
190toText bs = Text.decodeUtf8 $ C.takeWhile (/='\0') bs
191
192interp_utmp_record2 ::
193 forall t t1 t2 t3 a.
194 Integral a =>
195 (a,
196 Word32,
197 C.ByteString,
198 t,
199 C.ByteString,
200 C.ByteString,
201 t1,
202 t2,
203 Word32,
204 t3,
205 Word32,
206 Word32,
207 Word32,
208 Word32)
209 -> UtmpRecord
210interp_utmp_record2 (typ,pid,tty,inittab,user,hostv4
211 ,term,exit,session,time,addr0,addr1,addr2,addr3) =
212 UtmpRecord
213 { utmpType = toEnum (fromIntegral typ) :: UT_Type
214 , utmpUser = toText user
215 , utmpTty = toText tty
216 , utmpPid = processId pid
217 , utmpHost = toText hostv4
218 , utmpSession = coerceToSigned session
219 , utmpRemoteAddr =
220 if all (==0) [addr1,addr2,addr3]
221 then do guard (addr0/=0)
222 Just $ SockAddrInet6 0 0 (0,0,0xFFFF,addr0) 0
223 else Just $ SockAddrInet6 0 0 (addr0,addr1,addr2,addr3) 0
224 }
225 where
226 processId = CPid . coerceToSigned
227
228users2 :: IO [UtmpRecord]
229users2 = do
230 us <- utmp
231 let us' = map interp_utmp_record2 us
232 us3 <- filterM (processAlive . utmpPid) us'
233 return us3
234
235{-
236 - This is how the w command reports idle time:
237/* stat the device file to get an idle time */
238static time_t idletime(const char *restrict const tty)
239{
240 struct stat sbuf;
241 if (stat(tty, &sbuf) != 0)
242 return 0;
243 return time(NULL) - sbuf.st_atime;
244}
245 - THis might be useful fo rimplementing
246 - xep-0012 Last Activity
247 - iq get {jabber:iq:last}query
248 -
249 -}