Re: [Haskell-cafe] State Monad
Thaks a lot for your contribution, this helps me a lot, I see what I've got to do. However, I understand the first version (Stack.hs), but I can't get what StateM.hs is. Is it the same version but using state transformers, so as to be able to do IO (which I would need)? In fact, could you give me a simple example of how to use StackM.hs, a simple example that pushes some ints and add the toppest two. Thanks a lot anyway, Sam. PS: In fact I'm trying to implement a simple RPN "calculator". So at first I need +, push, pop and view which shows the whole list. Attached is what I started to do before I get your mail. Mark Carroll wrote: On Thu, 3 Mar 2005, Sam G. wrote: I need a Monad to represent an internal stack. I mean I've got a lot of functions which operates on lists and I would not like to pass the list as an argument everytime. Could you help me writing this monad? To start, I just need a + function which will return the sum of the 2 toppest elements of the stack. I wrote one which is at, http://www.aetion.com/src/Stack.hs http://www.aetion.com/src/StackM.hs Then, add :: Num a => Stack a () add = do x <- pop y <- pop push (x + y) or whatever. Of course, if you use Control.Monad.State where you store the stack as a list then you can probably just do something like, add = (x:y:z) <- get put ((x+y):z) I hope that helps. -- Mark ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe module Main where main = do putStrLn "Forth Environment\nCopyright (C) Sam G. 2005.\n" doLoop [] doLoop list = do l <- getLine let w = execute (pushWords (words l)) list in do write w doLoop w write [] = return () write (s:ss) = do putStrLn $ show (s::Int) write ss pushWords [] = return [] pushWords (s:ss) = do push $ read (s) pushWords ss newtype State state value = State (state -> (state, value)) instance Monad (State state) where return v = State $ \s -> (s, v) State f >>= k = State $ \s -> let (s0, v0) = f s State g = k v0 in g s0 push a = State $ \s -> (a:s, a) execute (State program) = fst . program ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] haskell DNS resolver w/o using FFI
On Thu, 3 Mar 2005 17:15:52 -0500 (Eastern Standard Time), S. Alexander Jacobson <[EMAIL PROTECTED]> wrote: > Peter Simons told me that someone has written a DNS resolver in > Haskell that doesn't rely on an FFI call. I'd love to look at it if > it is available... I guess it would be me. However, the library is a bit incomplete - it's missing the most interesting piece: an iterative query algorithm. You can use it to query a DNS server supporting recursive queries. I can't send you the code right now, because I temporarily have no access to my notebook. I'll try to do it tomorrow. If I don't, please remind me. Best regards Tomasz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] haskell DNS resolver w/o using FFI
Peter Simons told me that someone has written a DNS resolver in Haskell that doesn't rely on an FFI call. I'd love to look at it if it is available... -Alex- __ S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] getting the name of a function for test diagnostic purposes
Am Donnerstag, 3. März 2005 14:28 schrieb Terrence Brannon: > {- > I have written a program (below) to run a test suite for a list of > functions: > > [isTotalJunc, isPartialJunc] > > where each function receives a datum of type ApplyArg whose value slot is > one element at a time of the list of types below: > > [JNone, JOne, JAny, JAll] > > I therefore must run 8 tests (the cross product of functions and types). > > Right now, here is the output: > > *Main> test_total_partial > ["fun: (->)input: JNoneoutput: True","fun: (->)input: JOneoutput: > False","fun: (->)input: JAnyoutput: False","fun: (->)input: JAlloutput: > True","fun: (->)input: JNoneoutput: False","fun: (->)input: JOneoutput: > True","fun: (->)input: JAnyoutput: True","fun: (->)input: JAlloutput: > False"] > > -- One problem is that functions do not print as their name. The > call to (show f) in showres simply yields (->) > > -- Another problem is that I cannot manage to separate each string > with a carriage return. > > Any help with these problems is appreciated. > > -} > > test_total_partial = let funs = [isTotalJunc, isPartialJunc] >types = [JNone, JOne, JAny, JAll] >mkdat typ = ApplyArg "somename" (VJunc $ Junc typ > emptySet emptySet) > False showres f t r = "fun: " ++ (show f) ++ "input: " ++ (show t) ++ ^ > "output: " ++ (show r) runtest f t = do { ^ insert a space here? > retval <- f (mkdat t); > return $ (showres f t retval) > } >in > [ (showres f t (f (mkdat t))) | f <- funs, t <- types ] In the case where you want to test a few known functions, you might do something like [(fun1,"fun1"),(fun2,"fun2")] and ... in putStr . unlines $ [showRes fname t (f (mkdat t)) | (f,fname) <- funns, t <- types] Of course, it's very specific, but it will produce better formatted output. Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: [Haskell] specified or not
[moving to the cafe] On Thu, Mar 03, 2005 at 09:39:17AM -0500, Scott Turner wrote: > Is the behavior of evaluating z unspecified? > z = f (0, z) > f x = case x of > (1,1) -> z > _ -> 0 > Hugs and GHC agree that z evaluates to 0. However, if the first line is > changed to > z = f (z,0) > then both implementations loop. In other words, the behavior depends on order > of evaluation, which AFAIK is not specified. The order of pattern matching is specified: pre-order, left to right. In detail: according to the rules of Section 3.17.3 of the Report, the definition of f is equivalent to f x = case x of (x1, x2) -> case x1 of 1 -> case x2 of 1 -> z _ -> 0 _ -> 0 _ -> 0 and hence f (0, anything) = 0 f (undefined, 0) = undefined ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] getting the name of a function for test diagnostic purposes
Am Donnerstag, 3. März 2005 14:28 schrieb Terrence Brannon: > {- > I have written a program (below) to run a test suite for a list of > functions: > > [isTotalJunc, isPartialJunc] > > where each function receives a datum of type ApplyArg whose value slot is > one element at a time of the list of types below: > > [JNone, JOne, JAny, JAll] > > I therefore must run 8 tests (the cross product of functions and types). > > Right now, here is the output: > > *Main> test_total_partial > ["fun: (->)input: JNoneoutput: True","fun: (->)input: JOneoutput: > False","fun: (->)input: JAnyoutput: False","fun: (->)input: JAlloutput: > True","fun: (->)input: JNoneoutput: False","fun: (->)input: JOneoutput: > True","fun: (->)input: JAnyoutput: True","fun: (->)input: JAlloutput: > False"] > > -- One problem is that functions do not print as their name. The > call to (show f) in showres simply yields (->) > > -- Another problem is that I cannot manage to separate each string > with a carriage return. > > Any help with these problems is appreciated. > > -} > > test_total_partial = let funs = [isTotalJunc, isPartialJunc] >types = [JNone, JOne, JAny, JAll] >mkdat typ = ApplyArg "somename" (VJunc $ Junc typ > emptySet emptySet) > False showres f t r = "fun: " ++ (show f) ++ "input: " ++ (show t) ++ > "output: " ++ (show r) runtest f t = do { > retval <- f (mkdat t); > return $ (showres f t retval) > } >in > [ (showres f t (f (mkdat t))) | f <- funs, t <- types ] Well, getting the name of a function, I don't know how to. But as for separating the Strings, what about 'unlines'? Daniel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] getting the name of a function for test diagnostic purposes
{- I have written a program (below) to run a test suite for a list of functions: [isTotalJunc, isPartialJunc] where each function receives a datum of type ApplyArg whose value slot is one element at a time of the list of types below: [JNone, JOne, JAny, JAll] I therefore must run 8 tests (the cross product of functions and types). Right now, here is the output: *Main> test_total_partial ["fun: (->)input: JNoneoutput: True","fun: (->)input: JOneoutput: False","fun: (->)input: JAnyoutput: False","fun: (->)input: JAlloutput: True","fun: (->)input: JNoneoutput: False","fun: (->)input: JOneoutput: True","fun: (->)input: JAnyoutput: True","fun: (->)input: JAlloutput: False"] -- One problem is that functions do not print as their name. The call to (show f) in showres simply yields (->) -- Another problem is that I cannot manage to separate each string with a carriage return. Any help with these problems is appreciated. -} test_total_partial = let funs = [isTotalJunc, isPartialJunc] types = [JNone, JOne, JAny, JAll] mkdat typ = ApplyArg "somename" (VJunc $ Junc typ emptySet emptySet) False showres f t r = "fun: " ++ (show f) ++ "input: " ++ (show t) ++ "output: " ++ (show r) runtest f t = do { retval <- f (mkdat t); return $ (showres f t retval) } in [ (showres f t (f (mkdat t))) | f <- funs, t <- types ] -- Carter's Compass: I know I'm on the right track when, by deleting something, I'm adding functionality. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: Bound threads
Wolfgang Thaller <[EMAIL PROTECTED]> writes: >> Indeed, my brain is melting, but I did it :-) > > Congratulations. How about we found a "Bound-thread-induced brain > melt victims' support group"? The melt was entertaining :-) > Besides simplicity, one of the main reasons for moving our select() > call from the run-time system to the libraries was to avoid the > performance hit of having to call select() every time through the > scheduler loop rather than only once per IO operation. I use epoll when available. It's Linux-specific and allows to register and unregister descriptors separately from waiting. This not only saves process time to set up the array, but also kernel time scanning the array and hooking to files. I've heard BSD kqueue mechanism has similar properties. I unregister descriptors from epoll "lazily": when epoll returned that data is available but no thread was in fact waiting for it. This saves repeated registration when a thread alternates between I/O and computation. When the scheduler determines that it has no thread to wake up immediately, it performs a GC before going to wait if the program did roughly at least half of work until the next normal GC. > Imagine having one or more (unbound) threads that spend most of their > time waiting for IO, and a bunch of (also unbound) threads that do > some computation. If select() is part of the scheduler loop, you will > get a select() call whenever a thread-switch between the computation > threads happens. Actually once the next thread in the "running and I/O" queue is an I/O thread, not in every scheduler iteration. Or more precisely a consecutive span of I/O threads in this queue. epoll_wait takes 0.2 us here, poll takes 1 us, select takes 0.6 us (1 descriptor in each case). I wonder why poll is slower than select. I was thinking about integration with gtk/glib event loop. There are two ways: either we ask glib to poll using a function supplied by us, or we perform polling using glib functions instead of raw epoll / poll / select. The first choice seems better because otherwise callbacks registered at glib were started from the scheduler and this will not work, it's even not clear on behalf of which thread they should run. In this case we must provide a function with an interface of poll(). Without additional support in the runtime (other than making file objects which don't close their underlying file, but this is easy), the function can be implemented by starting a thread for each descriptor, collecting the results, and cancelling threads when some descriptor is ready or when the timeout expires. Let's assume that real poll is used by our scheduler and that no other thread does I/O at the moment, and see what really happens: - the threads are created at the end of the run queue - other threads in the program execute their time slices - each of the newly created threads is marked as waiting for I/O - other threads in the program execute again (ugh) - the scheduler looks at the first I/O thread and makes poll() - all threads whose I/O is ready are woken up - the next running thread is chosen (perhaps one of threads woken up in the previous step) - it notifies the manager thread that glib-poll-emulation is ready - when execution reaches the manager, it kills other threads and reports the result to glib It seems that other than a bunch of context switches there is not much work besides the required minimum. (It gets worse wich epoll, which is suitable for a mostly unchanging set of watched descriptors.) With GHC implementation I think each thread which adds a descriptor will wake up the service thread through a pipe, and later they will wake it up again to unregister files when they become cancelled. >> All threads except the thread performing the fork become unbound. >> [...] > > What happens when fork is called from an unbound thread? Does it > become bound in the child process? No. But in ForkProcess and ForkProcessKillThreads this thread plays the role of the main thread: it receives Unix signals; it receives internal asynchronous signals like heap overflow and deadlock; when it terminates, the process terminates; if it terminates with an unhandled exception, a handler which normally prints the stack trace is called. AtExit handlers are not run though. I don't know what should be done, this got quite hairy. Actually the above termination semantics currently applies only when fork is called with an I/O action as an argument. It can also be called without, like C fork(), and in this case the behavior is ugly: if the new main thread in the child process was not the main thread before, its termination is not special and there will be a deadlock. This should be changed somehow. In any case, when the previous main thread terminates (as it's cancelled cleanly by ForkProcess), it checks whether it's still the main thread. If not, it disappears like normal threads, except that its OS thread will wait on a condition variable fore