Re: [Haskell-cafe] Trouble with the ST monad

2008-12-29 Thread Andre Nathan
On Mon, 2008-12-29 at 14:19 -0500, Ross Mellgren wrote:
 The problem is that you're trying to take a STMatrix from some other  
 ST computation and freeze it in a new ST computation. The isolation  
 between separate computations is done via the rank-2 type variable s  
 in all those ST functions.

I guess I should go and read the rank-n types page on the wiki...

 Try this:
 
 freezeMatrix :: (forall s . STMatrix s a) - Matrix a
 freezeMatrix f :: runST (freezeMatrix f)

Do you know why point-free style doesn't work here even with the type
annotation?

 Also, instead of using an array of arrays, maybe an array with (Int,  
 Int) as the Ix might be a bit smoother?

Thanks for the suggestion. It didn't occur to me that there was an Ix
instance for that.

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Trouble with the ST monad

2008-12-21 Thread Andre Nathan
Hello,

I'm trying to write a function that would take an STArray and and
shuffle its elements. I'm having trouble with the ST monad, though, and
couldn't find out how fix this issue.

The problem happens when I use runST to extract the shuffled array from
the ST monad. I'm getting the following error:

  Inferred type is less polymorphic than expected
Quantified type variable `s' is mentioned in the environment:
  a :: STArray s Int a

The full code is at

  http://hpaste.org/13240#a1

Any help would be appreciated.

Thanks,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with the ST monad

2008-12-21 Thread Andre Nathan
On Sun, 2008-12-21 at 16:47 -0800, Ryan Ingram wrote:
 The problem is that you are trying to return a mutable array out of an
 ST computation.  This lets the mutability of the computation escape.
  That's what the s type variable is for;  without it, runST is just
 unsafePerformIO.

Thanks!

If only I knew that was the problem... It wouldn't have costed me the 
whole afternoon :P

Is there any difference between using freeze/thaw from Data.Array.MArray
versus freezeSTArray/thawSTArray from GHC.Arr?

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Library design question

2008-09-20 Thread Andre Nathan
On Sat, 2008-09-20 at 14:56 +0200, Daniel Fischer wrote:
  modify' f = do
  s - get
  put $! f s
 
 Or try Control.Monad.State.Strict.

Control.Monad.State.Strict did it for me, but the strict modify didn't.
I tried using modify' and also

  randomDouble = do
g - get
let (r, g') = random g
put $! g'
return r

instead of

  randomDouble = State random

Any hints on how I could find where else the program is being too lazy?

Thanks,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Library design question

2008-09-19 Thread Andre Nathan
On Fri, 2008-09-19 at 10:35 +0200, Christian Maeder wrote:
 I agree. Duncan's version also looks more atomic to me,
[...]

OK, so what I have now is

  addVertex :: Int - a - Graph a b - Graph a b
  addVertex v l g = Graph adj (numVertices g + 1) (numEdges g)
where adj = Map.insert v (l, Map.empty) (adjacencies g)

  addEdge :: Int - Int - b - Graph a b - Graph a b
  addEdge v w l g = Graph adj (numVertices g) (numEdges g + 1)
where adj = Map.insert v (vl, ns') (adjacencies g)
  ns' = Map.insert w l ns
  (vl, ns) = fromJust $ Map.lookup v (adjacencies g)

Creating a random graph [G(n,p) model] the naive way:

  type RandomGraph a b = StateT (Graph a b) IO ()

  randomGraph :: Int - Double - IO (Graph Int Int)
  randomGraph n p = execStateT create Graph.empty
where create = mapM_ (uncurry $ createVertex p) vls
  vls= zip [1..n] (repeat 1)

  createVertex :: Double - Int - a - RandomGraph a Int
  createVertex p v l = do
modify (Graph.addVertex v l)
createEdges v p

  createEdges :: Int - Double - RandomGraph a Int
  createEdges n p = mapM_ (maybeAddEdges n) [1..n-1]
where maybeAddEdges v w = do
maybeAddEdge v w
maybeAddEdge w v
  maybeAddEdge v w = do
r - lift randomDouble
when (r  p) $ modify (addEdge v w 1)

  randomDouble :: IO Double
  randomDouble = randomIO

So, to reference another thread, does this make anyone cry? :)

Thanks a lot for the suggestions,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Library design question

2008-09-19 Thread Andre Nathan
On Fri, 2008-09-19 at 09:51 +0200, apfelmus wrote:
 There's also Martin Erwig's functional graph library in  Data.Graph.Inductive 
  (
 fgl  on hackage).

I tried it some time ago, but for large graphs it has a very high memory
usage.

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Library design question

2008-09-19 Thread Andre Nathan
On Fri, 2008-09-19 at 23:16 +0200, Daniel Fischer wrote:
 Yes. What's IO gotta do with it?

I did it because of randomIO :(

 (or what about StateT (Graph a b) (State StdGen) ?).

Now there's something I wouldn't have thought of... I changed the
RandomGraph type to

  type RandomGraph a b = StateT (Graph a b) (State StdGen) ()

and randomFloat to

  randomDouble :: State StdGen Double
  randomDouble = State random

and randomGraph to

  randomGraph :: StdGen - Int - Double - Graph Int Int
  randomGraph gen n p = evalState (execStateT create Graph.empty) gen
where create = mapM_ (uncurry $ createVertex p) vls
  vls= zip [1..n] (repeat 42)

However, when I try to create a graph with 1000 vertices I get a stack
overflow, which didn't happen in the IO version. Any idea why that happens?

Thanks,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Library design question

2008-09-18 Thread Andre Nathan
Hello

I'm trying to write a simple graph library for a project of mine
(actually, I'm porting it from OCaml) but I've got a design question
right in the beginning.

My Graph type is the following.

  data Graph a b = Graph
{ adjacencies :: Map Int (a, (Map Int b))
, numVertices :: Int
, numEdges:: Int
}

Types a and b refer to vertex and edge labels (I know it's kind of
weird to use a Map of Maps to represent a graph, but it helps me
removing vertices later, which is something I'll need to do.)

Creating an empty graph is trivial:

  empty :: Graph a b
  empty = Graph Map.empty 0 0

The issue I hit was when writing the function to add a vertex to the
graph. Since I need to update the vertex counter, I've used the state
monad:

  addVertex :: Int - a - State (Graph a b) ()
  addVertex vertex label = do
g - get
let adj = Map.insert vertex (label, Map.empty) (adjacencies g)
put $ g { adjacencies = adj, numVertices = numVertices g + 1 }

That works fine, but from the point of view of a user of the library,
the addVertex function should take a Graph a b as its first argument,
as one would expect to be able to say which graph is going to be
modified.

So I'm confused right now about how I should proceed. Any hints
regarding that?

Best regards,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Library design question

2008-09-18 Thread Andre Nathan
On Thu, 2008-09-18 at 21:15 +0200, Henning Thielemann wrote:
 Think of the state monad as processing a graph in-place. Which graph is 
 addressed is declared when running the State monad using runState or 
 evalState.

Interesting. Is it good practice then to do something like

  type GraphM a b = State (Graph a b)

to hide from the user that I'm using the State monad underneath?

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Library design question

2008-09-18 Thread Andre Nathan
On Thu, 2008-09-18 at 21:13 +0200, minh thu wrote:
 If you need the one inside the State monad, you can reuse the new
 version of addVertex.

You mean making the graph creation functions (which will call
addVertex/Edge) use the State monad instead? Interesting idea... what I
really wanted was to hide from the user how the graph library is
implemented, so he wouldn't need to know about the state monad to use
the library, but maybe I should keep these basic functions pure and let
the user decide. I'll think about it :)

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Inductive graphs memory usage

2008-07-10 Thread Andre Nathan
Hello

I'm trying to create a directed graph using the Data.Graph.Inductive.
The graph is a random graph using the G(n, p) model, that is, each of
the n nodes is linked to every other node with probability p.

I'm seeing a large increase of memory usage when n grows (this is using
p = 0.1):

n = 1000 -  96MB
n = 2000 - 283MB
n = 3000 - 760MB

So, I'm probably doing something very stupid :) The code is below. Is
there anything I could do to optimize memory usage here?

  module Main where

  import Control.Monad
  import Data.Graph.Inductive
  import System.Random

  createEdges :: Int - Double - IO [LEdge Int]
  createEdges n prob = foldM create [] [1..n]
where create es i = foldM (flip $ link i) es [i, i-1 .. 1]
  link i j es | i == j= return es  -- no self-loops
  | otherwise = do
  es'  - maybeCreateEdge i j prob es
  es'' - maybeCreateEdge j i prob es'
  return es''

  maybeCreateEdge :: Node - Node - Double - [LEdge Int]
  - IO [LEdge Int]
  maybeCreateEdge i j prob es = do
r - randomDouble
return $ if r  prob then (i, j, 0):es else es

  randomDouble :: IO Double
  randomDouble = getStdRandom $ random

  main :: IO ()
  main = do
let (n, p) = (3000, 0.1)
es - createEdges n p
let g = mkGraph [(i, 0) | i - [1..n]] es :: Gr Int Int
return ()


Thanks,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inductive graphs memory usage

2008-07-10 Thread Andre Nathan
On Thu, 2008-07-10 at 18:32 -0400, Ronald Guida wrote:
 Your ratios are about 1 : 3 : 8.
 That pretty close to quadratic growth, 1 : 4 : 9, so I think all is well.

Maybe, but 96MB of resident memory for a 1000-node graph looks bad,
especially considering p is low. Is the internal representation of
inductive graphs perhaps not very memory-efficient? I still haven't read
Erwig's paper...

I know this is probably not fair, but I'm comparing these numbers with a
C implementation which uses Ruby's C API for its complex data
structures, and a 10,000 nodes graph uses around 6MB of memory.

Thanks,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Inductive graphs memory usage

2008-07-10 Thread Andre Nathan
On Thu, 2008-07-10 at 16:52 -0700, Don Stewart wrote:
 Well, they're radically different graph representations, and fgl
 hasn't been designed for large graphs.

Do you know if King and Launchbury's implementation (Data.Graph) scales
better?

 What C library is Ruby's binding to? It might be quite cheap to bind
 to that. I've been on the look out for a good C graph lib to use for
 Haskell bindings for a while..

None. I've built my own representing the graph as a hash table with
nodes as keys and arrays of nodes as values, and I'm using ruby's hash
and array classes (which are written in C) for that.

Did you have a look at igraph [http://cneurocvs.rmki.kfki.hu/igraph/]?
It would probably be a lot of work to bind to it (it has many public
functions), but it looks nice and has bindings for a few languages.

Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-12 Thread Andre Nathan
On Fri, 2008-01-11 at 19:14 -0800, Jonathan Cast wrote:
 These are all known and expected.  As I said, you can expect lazy  
 versions to normally be slower than explicit loops.  The question is  
 whether 50% more time and 300% more memory has a higher cost in your  
 case than the extra complexity and reduced modularity of the lazy code.

I think I understand... I expected the getDirectoryContents + mapM_ to
have about the same memory usage of the readDirStream version, because
getDirectoryContents would lazily give me one entry at a time, but the
list of entries returned by it ends up being created anyway, hence the
larger memory usage, as the readDirStream version never builds a list.

Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-12 Thread Andre Nathan
On Sat, 2008-01-12 at 10:11 -0800, Jonathan Cast wrote:
 A nit: the list is almost certainly getting created lazily, or you'd  
 get more than 300% more memory usage.  But you still get the list's  
 cons cells as your bookkeeping baggage, and they take up space in  
 exchange for greater flexibility.

But when I'm processing, say, the last directory entry, I have memory
allocated for the other  entries that have already been processed,
right? I think that's where the 8M vs 2M difference comes from.

Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-12 Thread Andre Nathan
On Sat, 2008-01-12 at 16:00 -0800, Jonathan Cast wrote:
 Wait, the last entry?  If you're just printing out the values, then  
 no --- those should have been garbage collected already.

Won't they be garbage collected only after the last entry is used,
though? Since getDirectoryEntries returns a list, won't its elements
have to be kept until the list is not used anymore, i.e., after the last
entry is processed?

Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-11 Thread Andre Nathan
On Thu, 2008-01-10 at 20:37 -0800, Jonathan Cast wrote:
 It might be faster; laziness usually has higher constants than direct  
 implementations.  But I doubt the difference is critical in this  
 case, and I would definitely time a re-writing and throw it away  
 unless it was significantly faster.  But I don't think this is a case  
 where laziness actually alters either the time or the space  
 asymptotics of the algorithm (you end up creating an ~ O(n) tree  
 anyway, so I'd figure O(n) space was OK for the loop, too).

I was wondering if laziness would make it run as if it was a single O(n)
operation (get one directory entry on demand, pass it to filter and
then to insertInTree), because only one entry is used at a time, so that
only the current entry needs to be evaluated.

I still find it hard to evaluate the effects of laziness on the
complexity of programs...

Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-11 Thread Andre Nathan
On Fri, 2008-01-11 at 20:20 -0200, Andre Nathan wrote:
 Both versions which use getDirectoryContents also use much more memory
 than the one which uses readDirStream (about 8M vs about 2M). Maybe I'm
 not exploting getDirectoryContents' laziness correctly? I expected the
 second and third versions to run in about the same time.

Forgot to paste the code...

foo :: IO ()
foo = do
  entries - getDirectoryContents .
  let procs = filter (=~ ^[0-9]+$) entries
  mapM_ putStrLn procs

processEntry :: DirStream - IO ()
processEntry ds = do
  entry - readDirStream ds
  if entry =~ ^[0-9]+$
then do
  putStrLn entry
  processEntry ds
else
  if entry ==  then return () else processEntry ds

bar :: IO ()
bar = do
  ds - openDirStream .
  processEntry ds
  closeDirStream ds

processEntry' :: FilePath - IO ()
processEntry' entry = do
  if entry =~ ^[0-9]+$
then putStrLn entry
else return ()

baz :: IO ()
baz = do
  entries - getDirectoryContents .
  mapM_ processEntry' entries

main = forM_ [1..1000] $ \_ - foo {- bar -} {- baz -}

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Comments and suggestions on code

2008-01-10 Thread Andre Nathan
Hi Jonathan

On Wed, 2008-01-09 at 21:32 -0800, Jonathan Cast wrote:
 An actual coding question, abuse?  We should be so lucky.

:) Your comments are much appreciated.

 This function is fairly complicated, simply because of the number of  
 separate definitions involved; I would be looking for opportunities  
 to inline definitions here, so it's clearer what the definitions  
 are.  (Also, I would try to build a single, self-recursive function  
 at the top level, put the call to procInfo there, and make everything  
 else pure).

I rewrote insertInTree like below. Now it is the only function that has
a StateT return type, and I also got rid of addProc, insertPid and
insertParent :)

insertInTree :: Pid - StateT PsTree IO ()
insertInTree pid = do
  tree - get
  if Map.member pid tree
then return ()
else do
  info - lift $ procInfo pid
  modify (Map.insert pid info)
  let ppid = parentPid info
  if ppid /= 0
then do
  insertInTree ppid
  modify (appendChild ppid pid)
else return ()

I also rewrote createTree like this:

createTree :: IO PsTree
createTree = do
  entries - getDirectoryContents /proc
  let procs = filter (=~ ^[0-9]+$) entries
  execStateT (mapM_ insertInTree procs) Map.empty

Is that a bad way to do it? If haskell wasn't lazy this would be 3 O(n)
operations, and I could write it using readDirStream to process all
entries in one pass. I'm not sure if that's really necessary when
laziness is present though.

Thanks a lot for the other comments. I'll look into using a record for
PsInfo now.

Best,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Comments and suggestions on code

2008-01-09 Thread Andre Nathan
Hello

I've just found time to finish writing my first real world program, so
I thought I'd post it here and ask for insight on general issues such as
if there's anything that isn't done the Haskell way, or if there's
something that could be done more efficiently.

The code is at the bottom of this message and also at
http://hpaste.org/4893. I realize it's a bit long, so if anyone could
just skim through it and see if there's anything really ugly or stupid
and point it out, it would be of great help :)

Just to make it easier to follow the code, its idea is simple:

- Build a process tree by reading entries from /proc (represented as a 
  map);
- Compare each child of the init process against a whitelist (which 
  comes from a configuration file);
- For each child not in the whitelist, send it a KILL signal.

The idea here is to run this on webservers and try to catch bad
customers who try to run daemons from their accounts, the typical script
kiddie stuff.

Anyway, there's one specific question I'd like to ask. I'm using StateT
PsTree IO to keep program state (the process tree). IO is necessary
because all information is read from /proc files. Now consider the
following function:

appendChild :: Pid - Pid - StateT PsTree IO Bool
appendChild ppid pid = do
  tree - get
  let PsInfo psData children = mapLookup ppid tree
  put $ Map.insert ppid (PsInfo psData (pid:children)) tree
  return True

It changes the program state by modifying a process tree entry, but it
does no I/O at all. The return type is there basically to match the
return type of the function which calls it (insertParent), which calls
functions that do I/O. Is there anyway to avoid the IO in
appendChild's signature (other than making it a pure function by passing
the process tree as a parameter and returning a modified map)?

I would also like to try ways to improve efficiency, maybe trying a hash
table instead of a map for the state, and also using bytestrings. I
guess I could try making it parallel, since each child of init can be
checked independently.

Anyway, this is already longer than I thought it would be (I hope I'm
not abusing too much :) The code follows. Thanks in advance for any
comments or suggestions.

Andre


module Main where

import qualified Data.Map as Map
import Directory
import Control.Monad.State
import Maybe
import System.Environment
import System.IO
import System.Posix.Files
import System.Posix.Signals
import System.Posix.Unistd
import System.Posix.User
import Text.Printf
import Text.Regex
import Text.Regex.Posix

type Pid = FilePath
type Uid = String

type PsData   = Map.Map String String
type PsChildren   = [Pid]
type KillFunction = PsTree - Pid - IO ()

data PsInfo = PsInfo PsData PsChildren
type PsTree = Map.Map Pid PsInfo

type Whitelist = Map.Map FilePath String

mapLookup :: (Ord a) = a - Map.Map a b - b
mapLookup k = fromJust . Map.lookup k

-- Process Tree construction

parentPid :: PsInfo - Pid
parentPid (PsInfo psData _) = mapLookup PPid psData
  
getProcInfo :: String - PsData - PsData
getProcInfo line psData = do
  case line =~~ ^([A-Za-z]+):[[:space:]]+(.*)$ of
Nothing  - psData
Just ([_, key, value]:_) - Map.insert key value psData 
  
getIds :: String - PsData - (String, String)
getIds id psData = (rId, eId)
  where (rId:eId:_) = words (mapLookup id psData)
  
processData :: String - PsData
processData procData = addIds psData
  where psData = foldr getProcInfo Map.empty (lines procData)
addIds psData = Map.union psData (idMap psData)
idMap psData = Map.fromList [(RUid, rUid), (EUid, eUid),
 (RGid, rGid), (EGid, eGid)]
(rUid, eUid) = getIds Uid psData
(rGid, eGid) = getIds Gid psData

readLink :: String - IO String
readLink link = catch (readSymbolicLink link) (\e - return ?)

procInfo :: Pid - IO PsInfo
procInfo pid = do
  let dir = /proc/ ++ pid ++ /
  procData - readFile $ dir ++ status
  exe - readLink $ dir ++ exe
  cwd - readLink $ dir ++ cwd
  cmd - readFile $ dir ++ cmdline
  let cmd' = subRegex (mkRegex [^a-zA-z[:space:]\\/\\.-]) cmd  
  info = processData procData
  adminInfo = Map.fromList [(Exe, exe), (Cwd, cwd),
(Cmd, cmd')]
  return $ PsInfo (Map.union info adminInfo) []

addProc :: Pid - StateT PsTree IO PsInfo
addProc pid = do
  info - lift $ procInfo pid
  modify (Map.insert pid info)
  return info

appendChild :: Pid - Pid - StateT PsTree IO Bool
appendChild ppid pid = do
  tree - get
  let PsInfo psData children = mapLookup ppid tree
  put $ Map.insert ppid (PsInfo psData (pid:children)) tree
  return True

insertParent :: Pid - Pid - StateT PsTree IO Bool
insertParent ppid pid = do
  tree - get
  if Map.member ppid tree
then appendChild ppid pid
else do
  built - insertInTree ppid
  if built
then appendChild ppid pid
else return False

insertPid :: Pid - StateT PsTree IO Bool
insertPid 1 = do
  info - addProc 1
  

Re: [Haskell-cafe] Is StateT what I need?

2007-12-19 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-19 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-18 Thread 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

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-18 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Is StateT what I need?

2007-12-17 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-17 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is StateT what I need?

2007-12-17 Thread Andre Nathan
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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help with Programming in Haskell example

2007-05-18 Thread Andre Nathan
On Fri, 2007-05-18 at 22:32 +0200, Tillmann Rendel wrote:
[snip]
 Now you should be able to use do notation with your own Parser type.

Thanks! Monads and instances weren't mentioned until that point, so I
was assuming that all that was needed for the do notation to work was
having (=) and return defined...

Best regards,
Andre

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe