
Hello (Newbie question ahead :) I'm trying to write a program which will build a tree (here represented as a Map) of unix processes. The tree should be built by reading the process information stored in /proc/PID/status. There is also another Map which will be used for faster insertions on the process tree, which I'd like to handle as my program state. So far I have the functions to get a list of entries from /proc, filter the ones that represent processes and get the information from their status file. Now I need an "insertProc" function, which should get the information for a given process ID, update the state and return that information. This is where I think I need StateT, but I couldn't find out how to use it (never used StateT before...). This is what I have so far:
type Pid = FilePath type Uid = String
type PsData = Map String Uid type PsChildren = Map Pid PsInfo
data PsInfo = PsInfo PsData PsChildren type PsMap = Map Pid PsInfo type PsTree = Map Pid PsInfo
parent :: PsData -> Pid parent psData = fromJust $ Map.lookup "PPid" psData
getProcInfo :: PsData -> String -> IO PsData getProcInfo psData line = do case matchRegex (mkRegex "^([a-z]+):[[:space:]]+(.*)$") line of Nothing -> return (psData) Just [key, value] -> return (Map.insert key value psData)
procInfo :: Pid -> IO PsInfo procInfo pid = do procData <- readFile $ "/proc/" ++ pid ++ "/status" psData <- foldM getProcInfo Map.empty (lines procData) let [rUid, eUid, _] = words $ fromJust (Map.lookup "Uid" psData) let [rGid, eGid, _] = words $ fromJust (Map.lookup "Gid" psData) let uids = Map.fromList [("RUid", rUid), ("EUid", eUid), ("RGid", rGid), ("EGid", eGid)] let psData' = Map.union psData uids return (PsInfo psData' Map.empty)
I tried this for insertProc, but it obviously doesn't work... what would be the correct way to do this?
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do proc <- procInfo pid -- XXX this is obviously wrong... psMap <- get put (Map.insert pid proc psMap) return (proc)
A second question: is it possible to make getProcInfo's type to be PsData -> String -> PsData and use some operation similar to lift so that it can be used with foldM, instead of making its return type to be IO PsData explicitely? Thanks in advance, Andre

Andre Nathan wrote:
Hello (Newbie question ahead :
I tried this for insertProc, but it obviously doesn't work... what would be the correct way to do this?
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do proc <- procInfo pid -- XXX this is obviously wrong... psMap <- get put (Map.insert pid proc psMap) return (proc)
I see that using "lift" makes it compile (Control.Monad.Trans.lift):
insertProc pid = do proc <- lift (procInfo pid)

Am Montag, 17. Dezember 2007 21:06 schrieb ChrisK:
Andre Nathan wrote:
Hello (Newbie question ahead :
I tried this for insertProc, but it obviously doesn't work... what would be the correct way to do this?
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do proc <- procInfo pid -- XXX this is obviously wrong... psMap <- get put (Map.insert pid proc psMap) return (proc)
I see that using "lift" makes it compile (Control.Monad.Trans.lift):
insertProc pid = do proc <- lift (procInfo pid)
By the way, be careful with identifiers named “proc”. There is a syntax extension (arrow notation) which introduces a new keyword “proc”. Best wishes, Wolfgang

On Dec 17, 2007, at 14:33 , Andre Nathan wrote:
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do proc <- procInfo pid -- XXX this is obviously wrong...
proc <- lift $ procInfo pid
psMap <- get put (Map.insert pid proc psMap)
modify (Map.insert pid proc) -- same as the above but cleaner
return (proc)
-- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

This is what I have so far:
type Pid = FilePath type Uid = String
type PsData = Map String Uid type PsChildren = Map Pid PsInfo
data PsInfo = PsInfo PsData PsChildren type PsMap = Map Pid PsInfo type PsTree = Map Pid PsInfo
parent :: PsData -> Pid parent psData = fromJust $ Map.lookup "PPid" psData
getProcInfo :: PsData -> String -> IO PsData getProcInfo psData line = do case matchRegex (mkRegex "^([a-z]+):[[:space:]]+(.*)$") line of Nothing -> return (psData) Just [key, value] -> return (Map.insert key value psData)
procInfo :: Pid -> IO PsInfo procInfo pid = do procData <- readFile $ "/proc/" ++ pid ++ "/status" psData <- foldM getProcInfo Map.empty (lines procData) let [rUid, eUid, _] = words $ fromJust (Map.lookup "Uid" psData) let [rGid, eGid, _] = words $ fromJust (Map.lookup "Gid" psData) let uids = Map.fromList [("RUid", rUid), ("EUid", eUid), ("RGid", rGid), ("EGid", eGid)] let psData' = Map.union psData uids return (PsInfo psData' Map.empty)
I tried this for insertProc, but it obviously doesn't work... what would be the correct way to do this?
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do proc <- procInfo pid -- XXX this is obviously wrong... psMap <- get put (Map.insert pid proc psMap) return (proc)
A second question: is it possible to make getProcInfo's type to be PsData -> String -> PsData and use some operation similar to lift so that it can be used with foldM, instead of making its return type to be IO PsData explicitely?
Yes, and in fact, you don't even need foldM. The only thing that actually uses IO is the readFile, so ideally you should just have a small function that just does the readFile and then processes the result using some (pure) functions. Something like this:
procInfo :: Pid -> IO PsInfo procInfo pid = do procData <- readFile $ "/proc/" ++ pid ++ "/status" return $ processData procData
processData :: String -> PsInfo ... and so on ...
and so on. Now instead of using foldM you can just use foldr. IO is a cancer, best to keep it confined to as little of your program as possible! =) -Brent

On Dec 17, 2007, at 15:41 , Brent Yorgey wrote:
Yes, and in fact, you don't even need foldM. The only thing that actually uses IO is the readFile, so ideally
Actually, a quick check indicates that the regex functions used in getProcInfo are in IO as well (?!). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On Mon, 17 Dec 2007 16:04:24 -0500
"Brandon S. Allbery KF8NH"
On Dec 17, 2007, at 15:41 , Brent Yorgey wrote:
Yes, and in fact, you don't even need foldM. The only thing that actually uses IO is the readFile, so ideally
Actually, a quick check indicates that the regex functions used in getProcInfo are in IO as well (?!).
That's because they're implemented in C, and anything implemented in C is potentially impure. Although, I'd have thought that they'd *actually* be pure. -- Robin

On Dec 17, 2007 1:04 PM, Brandon S. Allbery KF8NH
On Dec 17, 2007, at 15:41 , Brent Yorgey wrote:
Yes, and in fact, you don't even need foldM. The only thing that actually uses IO is the readFile, so ideally
Actually, a quick check indicates that the regex functions used in getProcInfo are in IO as well (?!).
Those functions look pure to me: GHCi, version 6.8.1: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Prelude> :m +Text.Regex Prelude Text.Regex> :t matchRegex . mkRegex matchRegex . mkRegex :: String -> String -> Maybe [String]

On Mon, 2007-12-17 at 17:33 -0200, Andre Nathan wrote:
Hello (Newbie question ahead :)
Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :) This is the first non-tutorial program I'm writing and all this monad stuff is easier than I thought it would be. I think newbies like me tend to get scared after reading all those monad tutorials and maybe give up before actually trying to use them, and don't realize they're more like... I don't know... warm fuzzy things? ;) [I'm talking about my own experience here... I've given up many times while trying to learn all this, but at least this time it seems to be working better.] Thanks again, Andre

On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote:
On Mon, 2007-12-17 at 17:33 -0200, Andre Nathan wrote:
Hello (Newbie question ahead :)
Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :)
This is the first non-tutorial program I'm writing and all this monad stuff is easier than I thought it would be. I think newbies like me tend to get scared after reading all those monad tutorials and maybe give up before actually trying to use them, and don't realize they're more like... I don't know... warm fuzzy things? ;)
[I'm talking about my own experience here... I've given up many times while trying to learn all this, but at least this time it seems to be working better.]
Have you read Wadler's papers? http://homepages.inf.ed.ac.uk/wadler/topics/monads.html In particular one of "The essence of functional programming" or "Monads for Functional Programming"? If not, I think you'll find them better in every way* than any "tutorial" despite being written 15 years ago. * And I do mean -every- way; they are also more entertaining and easier to read.

On Mon, 2007-12-17 at 17:56 -0600, Derek Elkins wrote:
Have you read Wadler's papers?
Yeah, I read the two you mentioned. While I can't say I've already understood 100% of them, I completely agree with you in that they're the best texts on monads, from what I've seen (maybe because they explain so clearly why it is a good thing to have monads). "You could have invented monads" was good too, but I think those papers should be read first. Andre

Hello On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote:
Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :)
I'm trying to finish the process tree construction but I guess I'll need some help again. My idea is to have a function that would return a map representing the process tree
createTree :: IO PsTree createTree = do entries <- getDirectoryContents "/proc" return $ foldr buildTree Map.empty entries
The "return $ foldr ..." part is missing something, because buildTree would have be something like:
buildTree :: String -> PsTree -> StateT PsMap IO PsTree buildTree entry tree = do case matchRegex (mkRegex "^[0-9]+$") entry of Nothing -> return tree -- skip this entry Just _ -> do psMap <- get if Map.member dir psMap then return tree -- alread inserted else return $ insertInTree dir tree
so the types don't match. insertInTree would be something like (in pseudo-code):
insertInTree pid tree = do procInfo <- insertProc pid -- this inserts pid in the state map -- and returns a PsInfo, so its type is -- Pid -> StateT PsMap IO PsInfo. -- Can I use it here though? psMap <- get if pid == "1" -- init is the root of the tree then do modify (Map.insert "1" procInfo psMap) return $ Map.insert "1" procInfo tree else do let pPid = parentPid procInfo if Map.member pPid psMap then do psMap' <- new psMap with pid appended pPid's children return tree else do tree' <- insert pPid in the process tree modify (new psMap with pid appended pPid's children) return tree'
insertProc was in my first message, and it's like this:
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do process <- lift $ procInfo pid psMap <- get modify (Map.insert pid process) return (process)
At this point I'm not sure if this design is good or even correct. I'm mixing (StateT PsMap IO PsInfo) with (StateT PsMap IO PsTree), which I'm not sure I can do. There is probably a much cleaner way to do this but I cannot see through the types right now :/ Anyone has any hints on how to make that scheme work? Thanks, Andre

On Tue, 2007-12-18 at 16:47 -0200, Andre Nathan wrote:
I'm trying to finish the process tree construction but I guess I'll need some help again.
I guess I could do away with StateT and just pass the PsMap around as a parameter, but I guess that wouldn't be the haskell way... I think my code is a bit too long and that probably makes it hard for someone to help... Does anyone know of good example code using StateT for keeping a global state other than the one at the "Simple StateT use" page on the wiki? Best regards, Andre

On Dec 19, 2007 11:28 AM, Andre Nathan
I guess I could do away with StateT and just pass the PsMap around as a parameter, but I guess that wouldn't be the haskell way...
I wouldn't say that. Manual state-passing is a perfectly legitimate technique, and can be clearer in some cases. Once your program works with manual state-passing, you might then find it easier to express using StateT -- or perhaps you'll decide that you didn't need StateT after all. Stuart

Andre Nathan wrote:
I think my code is a bit too long and that probably makes it hard for someone to help... Does anyone know of good example code using StateT for keeping a global state other than the one at the "Simple StateT use" page on the wiki?
The one I have used is All About Monads: http://www.haskell.org/all_about_monads/html/index.html Then, there is sigfpe's (always excellent) short but sweet blog posting: http://sigfpe.blogspot.com/2006/05/grok-haskell-monad-transformers.html And finally (although I hesitate to mention it), there is my nroff-alike from Software Tools: http://www.crsr.net/Programming_Languages/SoftwareTools/ch7.html (Note: I haven't gotten to it in the revisions following the comments I received here and there are many things that need work. The notes are incoherent, it's more Pascallish than Haskell, and there are no guarantees that it won't ruin you forever.) -- Tommy M. McGuire mcguire@crsr.net

On Wed, 2007-12-19 at 17:54 -0600, Tommy McGuire wrote:
(Note: I haven't gotten to it in the revisions following the comments I received here and there are many things that need work. The notes are incoherent, it's more Pascallish than Haskell, and there are no guarantees that it won't ruin you forever.)
Sounds safe enough =) Andre

Am Dienstag, 18. Dezember 2007 19:47 schrieb Andre Nathan:
Hello
On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote:
Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :)
I'm trying to finish the process tree construction but I guess I'll need some help again.
My idea is to have a function that would return a map representing the process tree
createTree :: IO PsTree createTree = do entries <- getDirectoryContents "/proc" return $ foldr buildTree Map.empty entries
I believe instead of return $ foldr... you should use evalStateT $ foldM (flip buildTree) Map.empty entries
The "return $ foldr ..." part is missing something, because buildTree
would have be something like:
buildTree :: String -> PsTree -> StateT PsMap IO PsTree buildTree entry tree = do case matchRegex (mkRegex "^[0-9]+$") entry of Nothing -> return tree -- skip this entry Just _ -> do
where does 'dir' below come from? should the pattern match not be Just dir -> do ?
psMap <- get if Map.member dir psMap then return tree -- alread inserted else return $ insertInTree dir tree
perhaps just else insertInTree dir tree if insertInTree :: dirtype -> PsTree -> StateT PsMap IO PsTree
so the types don't match. insertInTree would be something like (in
pseudo-code):
insertInTree pid tree = do procInfo <- insertProc pid -- this inserts pid in the state map -- and returns a PsInfo, so its type is -- Pid -> StateT PsMap IO PsInfo. -- Can I use it here though?
sure you can use it here, the monad is m = (StateT PsMap IO), you can chain m a, m b, m Int, m PsTree, m PsInfo freely, as long as it's only the same m.
psMap <- get if pid == "1" -- init is the root of the tree then do modify (Map.insert "1" procInfo psMap) return $ Map.insert "1" procInfo tree else do let pPid = parentPid procInfo if Map.member pPid psMap then do psMap' <- new psMap with pid appended pPid's children
rather: then do modify (insert pid in pPid's children) return tree you don't do anything with the new map here, so no need to bind the name psMap' to it. I believe here you want something like modify (Map.adjust (Map.insert pid procInfo) pPid) but perhaps you also want to insert pid into the PsMap?
return tree else do tree' <- insert pPid in the process tree modify (new psMap with pid appended pPid's children)
Insert pPid in the PsMap before that? I think, you can treat both cases at once using Map.insertWith.
return tree'
insertProc was in my first message, and it's like this:
insertProc :: Pid -> StateT PsMap IO PsInfo insertProc pid = do process <- lift $ procInfo pid psMap <- get
delete above line, it's dead code, originally you did psMap <- get put (Map.insert pid process psMap) modify does both.
modify (Map.insert pid process) return (process)
At this point I'm not sure if this design is good or even correct.
I'm not sure what the design is, what's the role of PsMap and the PsTree, respectively?
I'm mixing (StateT PsMap IO PsInfo) with (StateT PsMap IO PsTree), which I'm not sure I can do.
No problem :)
There is probably a much cleaner way to do this but I cannot see through the types right now :/
Anyone has any hints on how to make that scheme work?
Take a piece of paper and write down your intended algorithm. In that process, think about how to represent your data. From that, much of the code becomes automatic (well, if you know the libraries better than I do, otherwise it's still a lot of searching the docs and looking what functions/data types are on offer). It looks like a promising start, though it definitely needs some polishing. Cheers, Daniel

On Wed, 2007-12-19 at 02:45 +0100, Daniel Fischer wrote:
I believe instead of return $ foldr... you should use evalStateT $ foldM (flip buildTree) Map.empty entries
This seems to have done it: evalStateT $ (foldM (flip buildTree) Map.empty entries)) Map.empty (the second argument to evalStateT being the initial state).
where does 'dir' below come from? should the pattern match not be
Sorry for that, 'dir' should be 'entry'.
I believe here you want something like modify (Map.adjust (Map.insert pid procInfo) pPid) but perhaps you also want to insert pid into the PsMap?
Almost that. procInfo is (PsInfo procData procChildren), procChildren being a map where pid should be added. pid is inserted in the PsMap in the call to insertProc.
return tree else do tree' <- insert pPid in the process tree modify (new psMap with pid appended pPid's children)
Insert pPid in the PsMap before that?
Well, the "insert pPid in the process tree" part should actually be a recursive call to insertInTree, so that should be taken care of.
I think, you can treat both cases at once using Map.insertWith.
Thanks, I'll have a look at it.
I'm not sure what the design is, what's the role of PsMap and the PsTree, respectively?
The idea is to have a map (the PsMap) where pids are keys and the process information are values. The process information includes a map that has a key for each child of the process, which should point to the other entries of the map. The PsTree then would just point to the entry in the PsMap that corresponds to pid 1, which is the root of the tree. Now thinking about it, I guess there's no need for PsTree to be a map... Thanks a lot for your help, Andre
participants (11)
-
Andre Nathan
-
Brandon S. Allbery KF8NH
-
Brent Yorgey
-
ChrisK
-
Daniel Fischer
-
Derek Elkins
-
Judah Jacobson
-
Robin Green
-
Stuart Cook
-
Tommy McGuire
-
Wolfgang Jeltsch