Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
Ben, On 29/04/2010, at 6:16 AM, Ben wrote: > [...] > > newtype STAuto s a b = STAuto { unSTAuto : (a, s) -> (b, s) } As Felipe observes in detail, this can be made to work. He uses Read and Show for serialisation, but clearly you can use whatever you like instead. I just wanted to add that one can go to town with the approach: after you understand Felipe's stuff, take a look at Caspi and Pouzet's coalgebraic streams stuff. (I'd recommend looking at both the tech report and the published paper, and there is some Haskell code too.) BTW I was referring (off-list) to the original Arrows paper by John Hughes. cheers peter -- http://peteg.org/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
On Wed, Apr 28, 2010 at 04:16:08PM -0700, Ben wrote: > so i tried state machines of a sort > > newtype STAuto s a b = STAuto { unSTAuto : (a, s) -> (b, s) } > > where the interruptibility would come from being able to save out the > state s. i was not successful, unfortunately, in this level of > generality. the fully-polymorphic state doesn't work, because one > needs to be able to compose arrows, which means composing state, so > like Hughes (see below) one needs some way of nesting states inside > one another. also, to implement delay in ArrowCircuit, one needs to > be able to store in the state s something of type a. this is a > dependency i was not able to model right. You may try encapsulating the state within an existential: {-# LANGUAGE GADTs #-} import Prelude hiding ((.), id) import Control.Category import Control.Arrow data SFAuto a b where SFAuto :: (Read s, Show s) => s -> ((a, s) -> (b, s)) -> SFAuto a b instance Category SFAuto where id = SFAuto () id (SFAuto s f) . (SFAuto r g) = SFAuto (s, r) h where h (x, (s, r)) = let (gx, r') = g (x, r) (fgx, s') = f (gx, s) in (fgx, (s', r')) instance Arrow SFAuto where arr f = SFAuto () (\(x, _) -> (f x, ())) first (SFAuto s f) = SFAuto s f' where f' ((x, y), s1) = let (fx, s2) = f (x, s1) in ((fx, y), s2) instance ArrowChoice SFAuto where left (SFAuto s f) = SFAuto s f' where f' (Right x, s1) = (Right x, s1) f' (Left x, s1) = first Left $ f (x, s1) instance ArrowLoop SFAuto where loop (SFAuto s f) = SFAuto s f' where f' (b, s1) = let ((c, d), s2) = f ((b, d), s1) in (c, s2) Now, if you want to serialize an (SFAuto a b), you may if you know where the original arrow is. I mean, if you have something :: SFAuto a b something = ... and you want to apply it to a huge list, you may A1) 'applyN k', where k is adjustable. A2) Save the results so far, the remaining input and the current state (which is Showable and Readable in my example, but could be an instance of Binary, for example). A3) Go to A1. If anything bad happens, to recover: B1) Read results, input, and last state. B2) 'changeState something stateThatWasRead' B3) Go to A1. Helper functions mentioned above: applyN :: Int -> SFAuto a b -> [a] -> ([b], (SFAuto a b, [a])) applyN 0 sf xs = ([], (sf, xs)) applyN _ sf [] = ([], (sf, [])) applyN n (SFAuto s f) (x:xs) = let (fx, s') = f (x,s) in first (fx :) $ applyN (n-1) (SFAuto s' f) xs changeState :: SFAuto a b -> String -> SFAuto a b changeState (SFAuto _ f) str = SFAuto (read str) f I don't have any idea if this is what you're looking for, but I hope it helps :). Cheers, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, 2010-04-28 at 09:55 -0700, Rogan Creswick wrote: > On Wed, Apr 28, 2010 at 8:19 AM, Duncan Coutts > wrote: > > > > Yes, it means the testing agent (cabal-install or some other > > program/system) can do more than simply run all the tests. It means it > > can enumerate them and not run them (think a GUI or web interface), run > > a subset of tests, run them in parallel etc. > > > > I'm not convinced that this should be cabal's responsibility. "Cabal" should define the interface between testsuite and test runner. Nothing more. Packages should provide collections of tests. Testing agents should provide a test runner to actually run the tests and do something with the results. See for example test-framework which has exactly this decomposition between testsuites (a collection of tests) and a test runner. They are mediated by a common interface. The test-framework package provides both the interface, some adapters for QC/HUnit to provide tests, and also a sample test runner that prints results to the console. Tools like cabal-install that use the interface defined by Cabal can provide a test runner (almost certainly implemented in some other package) and then do something interesting with the results like showing them to the user or uploading them to hackage. Other tools can use other test runners and do other interesting things. > I think we would be better served by leaving this up to the test > frameworks (indeed, test-framework has test filtering capabilities > already). If 'cabal test' simply acts as a thin layer between the > user/invoking system and the test framework, then we could pass > arguments through to the underlying test binary and perform these > tasks using whatever interface that test binary provides. This will > buy us more flexibility in the long run. (I think this is at least a > good place to start -- and matches my interpretation of Thomas's > proposal.) > > If Cabal takes on these responsibilities, then the testing api will be > more constrained -- we won't be able to experiment with new test > formats/methodologies as easily, since any tests will have to meet a > specific API. It is exactly defining this API that should allow flexibility. It means packages can provide tests and have them be used in multiple different ways by different test runners with different purposes and capabilities. If all you can do is run the testsuite and collect the results, that's much more constrained. Note that we're also proposing a lowest-common-denominator testsuite interface that gives all the control to the package author, but means the test runner cannot interpret the results in any interesting way. The main point is to wrap any existing testsuite in a way that allows it to be run automatically and non-iteractively for e.g. hackage testing. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
thanks for the comments, i'll try to respond to them all. but to start off with, let me mention that my ultimate goal is to have a way of writing down causal and robust (restartable) computations which happen on infinite streams of data "in a nice way" -- by which i mean the declarative / whole-meal style ala Bird. loosely, these are functions [a] -> [b] on infinite lists; the causal constraint just means that the output at time (index) t only depends on the inputs for times (indices) <= t. the catch is the robust bit. by robust, i mean i need to be able to suspend the computation, and restart it where it left off (the data might be only sporadically or unreliably available, the computation needs to be able to survive machine reboots.) unfortunately the obvious way (to me) of writing down such suspendible computations is to use explicit state-machines, e.g. to reify function computation as data, and save that. this is unfortunately very piece-meal and imperative. so i tried to turn state-machine computations on streams into an arrow. as an exercise for myself i tried to implement instances of ArrowChoice, ArrowLoop, and ArrowCircuit for other various versions of "stream arrows." i was successful with automatons / mealy machines newtype Auto a b = Auto { unAuto : a -> (b, Auto a b) } functions on infinite lists (Data.Stream) newtype InfSF a b = ISF { unISF : Stream a -> Stream b } and length-preserving functions on finite lists newtype SF a b = SF { unSF : [a] -> [b] } this was promising, if elementary (these are all well-known.) but none of these are particularly interruptible, at least in GHC -- i can't save a mealy machine, and the list versions are not particularly causal. so i tried state machines of a sort newtype STAuto s a b = STAuto { unSTAuto : (a, s) -> (b, s) } where the interruptibility would come from being able to save out the state s. i was not successful, unfortunately, in this level of generality. the fully-polymorphic state doesn't work, because one needs to be able to compose arrows, which means composing state, so like Hughes (see below) one needs some way of nesting states inside one another. also, to implement delay in ArrowCircuit, one needs to be able to store in the state s something of type a. this is a dependency i was not able to model right. perhaps i have entirely the wrong approach -- if anyone can think of a way of writing such a robust program in a declarative style, i would love to know it! of interest are the coalgebraic / comonadic approaches, and the CCA stuff of liu et al. Peter G : i have looked at the original CGI Arrow, it's a nice paper. i don't think i understand all the subtleties, but my impression is that he has a less polymorphic state type, and i don't know if he addressed ArrowCircuit. also he was unable to get it to work, entirely, at least in that paper -- there were some type issues iirc. Chris H : in my state-machine setup, saving the "state" of pure functions is not exactly necessary -- as stream arrows, pure functions lift to stateless gadgets, e.g. lift = map. on the other hand, if i was able to save functions / closures, or whole state of the program, it would certainly suffice (i could use mealy machines or the continuation monad), but is probably more than i need. Peter V, Chris E : the CGI Arrow paper that Peter G mentioned may be of interest to you. the rest of you haskellers -- sorry, this is like the tenth time i've posed this question, in one form or another! i keep on feeling like i've made a little progress, but then Best, Ben On Wed, Apr 28, 2010 at 11:49 AM, Chris Eidhof wrote: > I agree. This would be an extremely useful feature, not only for game > development, but also for web development. We often use continuations as a > way to add state to the web, but this fails for two reasons: whenever the > server restarts, or when we scale to multiple machines. > > However, I think it is not easy to do this: traversing the heap should be > relatively simple, however: what if a function implementation changes? > > An interesting approach is taken by the Clean guys: they use dynamics, which > can store a function, a type representation and the heap to disk. See also > this old thread: > http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html > > -chris > > On 28 apr 2010, at 19:50, Peter Verswyvelen wrote: > >> Interesting topic. I find it a bit annoying that Haskell doesn't >> provide support to save functions. I understand this is problematic, >> but it would be very nice if the Haskell runtime provided a way to >> serialize (part of) the heap, making sure that pointers to compiled >> functions get resolved correctly. >> >> >> >> On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson >> wrote: >>> >>> On Wed, 28 Apr 2010, Ben wrote: >>> I want to save the state of the system to disk, I want to be able to play the game, pick a point to stop, freeze it and turn off the comp
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
I think y'all are talking past each other, a little bit. There are two ways to serialize a function: 1) Serialize the bytecode for the function. 2) Serialize a persistant reference to a function that resides inside the executable. Personally, I think that either strategy is dubious. If you really need this, I would recommend building a DSL to support your specific needs. When I was working in Java I trusted the default serializer about as far as I could physically throw it, and IIRC my associates at the time had the same instinct. Functions in general can contain references to any data, including objects such as MVar's who's behavior is actually determined by unreachable entities. There's no amount of type system magic that can hold off monsters like _|_ or things like lazy bytestrings that are finite but never intended to be fully resident in memory. Or do we intend to serialize unevaluated thunks? Friendly, --Lane On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson wrote: On Wed, 28 Apr 2010, Ben wrote: I want to save the state of the system to disk, I want to be able to play the game, pick a point to stop, freeze it and turn off the computer, and then come back later and resume. Why is that unwise? What are the alternatives? B On Tue, 27 Apr 2010, Ben wrote: slightly off topic, but how does one handle pausing / saving / restarting in the FRP framework, especially the arrowized version? If we're about Arrow FRP, remember that the arrow typeclass includes a function, 'arr', that admits any function as a parameter, and these are in general impossible to serialize to disk. Since Arrow FRP ends up roughly in a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the state of the system. There are a few tactics that would get us around this limitation, but they are rather severe. You could render 'arr' useless in several ways, or you could save all the input to a system and replay it. But I would argue that even if you wanted to do this, "saving an FRP system" is, to me, like "saving a system in the IO monad," (which, there are tactics that would let you do this, too). It's probablematic in part because the FRP system probably has active hooks into the user interface, such as windows and other widgits that it owns, and possibly other devices (such as physical rocket engines). Even if the FRP system is completely pure and can be referenced by a single pointer, it is easily and rightfully aware of specific details of the hardware it is embedded in. So it seems to me that what we actually want, to do complex simulations with persistance, is not an FRP system that interacts with the outside world, but a "self-contained, self-interacting, differential equation hairball." Such a system would be very cool, but I think that the numerical algorithms needed exceed what an FRP system should try to provide. Friendly, --Lane ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe On Wed, 28 Apr 2010, Peter Verswyvelen wrote: As a side note, it's interesting that C# doesn't allow serialization of closures (anonymous delegates). The compiler-generated name assigned to an anonymous delegate can be different after each re-compilation. This is also really annoying in C#/.NET, since one must explicitly add a named method if serialization is needed. So I wander how Clean solves this. I mean, consider data MyData = MD (Int->Int) myFunc x = x+1 myState1 = MyData myFunc myState2 = MyData (\x -> x+1) I can imagine that serializing myState1 is not too difficult, since it should be possible to lookup the name of the compiled function "myFunc". However, what about serializing myState2? The lambda function has no name, and it is not obvious to me how to give it a name that is unique enough to survive a couple of iterations of source code modifications. On Wed, Apr 28, 2010 at 9:56 PM, Gregory Crosswhite wrote: On Apr 28, 2010, at 3:41 PM, Limestra?l wrote: I think the problem with function serialization is that unlike languages which run over a virtual machine, bytecode generated by GHC is platform-specific (just as compilated C or C++) and therefore can run directly on top of the system, which is far faster but less portable. Is this true? I thought that ghc has separate machine code and byte-code modes, and inferred that the latter was platform-independent. Is the latter platform-specific because it is just a different way of organizing different ways of (unlinked) machine code, or because parts of the byte-code depend on things like the size of integers in the compilation machine that are platform-dependent? Also, it is worth noting that Clean supports serialization of values including closures. It's not entirely clear to me how they do this, but looks like some combination of seeing whether a referenced routine is already in the curre
Re: [Haskell-cafe] ANN: CPSA - Cryptographic Protocol Shapes Analyzer
>> We are working towards a version of CPSA with the property that >> whenever it successfully terminates, every possible execution is >> described by its output. However, the current implementation >> occasionally fails to find some executions. > > That is concerning - is it due to ... We have formally specified the algorithm, but we haven't been able to prove the algorithm finds all solutions. In fact, we now have an example in the test suite that shows it misses an answer. The example is in the source distribution in tst/missing-contraction.scm. There should be two answers, but CPSA only finds one. We have a fix you can try out in 2.0.4. In src/CPSA/Lib/Strand.hs, you can change the flag useDisplacement from False to True, and CPSA will find both answers. We don't know if this fix is all one needs to ensure CPSA finds every answer. By the way, the algorithm is in doc/cpsaspec.pdf, which can be build from a source distribution of CPSA. > What is the current status of development both wrt openness and future > direction? Our highest priority is to resolve the correctness issue you just raised. As for openness, the sources are available to you. We haven't thought about other forms of openness. > I'm wondering if you plan to add MQV or other non-trivial primitives. I don't know what MQV is, so I can't say. Thanks for your interest, Thomas. John ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Lazy Parsing (ANN: vcd-0.1.4)
2010/04/28 S. Doaitse Swierstra : > On 27 apr 2010, at 22:12, Jason Dusek wrote: > > So UU parsers can construct input? > > The perform an editing action on the input so it becomes a > sentence of the language recognised. My questions betray a fundamental misunderstanding on my part; reading the above, its clear the parser is constructing strings that match the language, not values that are of the type. -- Jason Dusek ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
As a side note, it's interesting that C# doesn't allow serialization of closures (anonymous delegates). The compiler-generated name assigned to an anonymous delegate can be different after each re-compilation. This is also really annoying in C#/.NET, since one must explicitly add a named method if serialization is needed. So I wander how Clean solves this. I mean, consider data MyData = MD (Int->Int) myFunc x = x+1 myState1 = MyData myFunc myState2 = MyData (\x -> x+1) I can imagine that serializing myState1 is not too difficult, since it should be possible to lookup the name of the compiled function "myFunc". However, what about serializing myState2? The lambda function has no name, and it is not obvious to me how to give it a name that is unique enough to survive a couple of iterations of source code modifications. On Wed, Apr 28, 2010 at 9:56 PM, Gregory Crosswhite wrote: > > On Apr 28, 2010, at 3:41 PM, Limestraël wrote: > >> I think the problem with function serialization is that unlike languages >> which run over a virtual machine, bytecode generated by GHC is >> platform-specific (just as compilated C or C++) and therefore can run >> directly on top of the system, which is far faster but less portable. > > Is this true? I thought that ghc has separate machine code and byte-code > modes, and inferred that the latter was platform-independent. Is the latter > platform-specific because it is just a different way of organizing different > ways of (unlinked) machine code, or because parts of the byte-code depend on > things like the size of integers in the compilation machine that are > platform-dependent? > > Also, it is worth noting that Clean supports serialization of values > including closures. It's not entirely clear to me how they do this, but > looks like some combination of seeing whether a referenced routine is already > in the current executable, then seeing whether it is in a nearby library, and > then finally just-in-type compiling the serialized platform-independent > bytecode into native code. > > Cheers, > Greg > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Control.Exception try and catch
On 28/04/10 14:45, Mads Lindstrøm wrote: Hi From http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-Exception.html#3 "... The difference between using try and catch for recovery is that in catch the handler is inside an implicit block (see "Asynchronous Exceptions") which is important when catching asynchronous exceptions ..." However, 'try' is implemented by calling catch http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/src/Control-Exception-Base.html#try: try :: Exception e => IO a -> IO (Either e a) try a = catch (a>>= \ v -> return (Right v)) (\e -> return (Left e)) Thus, I wonder, why do 'try' not "inherit" the implicit block mentioned above? There's nothing magic going on - the "handler" in the case of try is just (return . Left), and that does indeed get executed with an implicit block. Looking at catch: catch :: Exception e => IO a -- ^ The computation to run -> (e -> IO a) -- ^ Handler to invoke if an exception is raised -> IO a catch io h = H'98.catch io (h . fromJust . fromException . toException) I see no call to 'block'. But maybe it is hidden in H'98.catch? And is H'98.catch == Prelude.catch ? The block is implicit (it's built into the implementation of catch, in fact). Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Benchmarks game updated to ghc 6.12.2
On 28/04/10 21:05, Don Stewart wrote: The benchmarks game has been updated to use 6.12.2 Please dive in and help tweak/improve/spot any regressions. Esp. with respect to multicore flags/options/... chameneos is using -N5, which is probably killing it. Cheers, Simon ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Benchmarks game updated to ghc 6.12.2
The benchmarks game has been updated to use 6.12.2 Please dive in and help tweak/improve/spot any regressions. Esp. with respect to multicore flags/options/... - Forwarded message from Isaac Gouy - Subject: fyi benchmarks game updated to ghc 6.12.2 http://shootout.alioth.debian.org/u64q/haskell.php best wishes, Isaac - End forwarded message - ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
I like this. One area that would be helpful is the ability to run the tests when different compile flags are used. E.g., the HUnit tests have different behaviors when compiled with and without optimization; it would be very handy if I could automate the testing of both cases. I don't believe that testing of multiple compile flags should be done inside Cabal. Instead, the arguments that are passed to `cabal configure' should also be used to build the test programs. This would allow a simple script, or a more complex build system, to handle the testing of both cases. Richard On 10-04-28 9:19 AM, Duncan Coutts wrote: I have previously advocated a library interface as a detailed testsuite interface (in addition to a lowest common denominator interface of stdio+exitcode). That is a test stanza in a package .cabal file would specify a module containing an entry point of the right type (like main but using a more interesting type). That way, cabal or any other tool could run the testsuite and produce results in whatever format it likes. I appreciate the elegance of this method, but it seems to me that it requires dynamic loading, which is currently in a sorry state. Actually it doesn't require dynamic loading. It just requires compiling a stub program that imports the user's library and some test-runner code. Cabal is good at doing that kind of thing already (eg Setup.hs scripts). ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
On Apr 28, 2010, at 3:41 PM, Limestraël wrote: > I think the problem with function serialization is that unlike languages > which run over a virtual machine, bytecode generated by GHC is > platform-specific (just as compilated C or C++) and therefore can run > directly on top of the system, which is far faster but less portable. Is this true? I thought that ghc has separate machine code and byte-code modes, and inferred that the latter was platform-independent. Is the latter platform-specific because it is just a different way of organizing different ways of (unlinked) machine code, or because parts of the byte-code depend on things like the size of integers in the compilation machine that are platform-dependent? Also, it is worth noting that Clean supports serialization of values including closures. It's not entirely clear to me how they do this, but looks like some combination of seeing whether a referenced routine is already in the current executable, then seeing whether it is in a nearby library, and then finally just-in-type compiling the serialized platform-independent bytecode into native code. Cheers, Greg ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
I think the problem with function serialization is that unlike languages which run over a virtual machine, bytecode generated by GHC is platform-specific (just as compilated C or C++) and therefore can run directly on top of the system, which is far faster but less portable. It wouldn't make much sense if, when sending functions through network, the receiver had to have the exact same system as the sender. Back to FRP, now. I was wondering, Ben, which FRP framework you were using. I'm trying to get into the whole FRP stuff, but I don't know which one is better/simpler when you have almost no knowledge about the field. 2010/4/28 Chris Eidhof > I agree. This would be an extremely useful feature, not only for game > development, but also for web development. We often use continuations as a > way to add state to the web, but this fails for two reasons: whenever the > server restarts, or when we scale to multiple machines. > > However, I think it is not easy to do this: traversing the heap should be > relatively simple, however: what if a function implementation changes? > > An interesting approach is taken by the Clean guys: they use dynamics, > which can store a function, a type representation and the heap to disk. See > also this old thread: > http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html > > -chris > > On 28 apr 2010, at 19:50, Peter Verswyvelen wrote: > > > Interesting topic. I find it a bit annoying that Haskell doesn't > > provide support to save functions. I understand this is problematic, > > but it would be very nice if the Haskell runtime provided a way to > > serialize (part of) the heap, making sure that pointers to compiled > > functions get resolved correctly. > > > > > > > > On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson > > wrote: > >> > >> On Wed, 28 Apr 2010, Ben wrote: > >> > >>> I want to save the state of the system to disk, I want to be able to > >>> play the game, pick a point to stop, freeze it and turn off the > >>> computer, and then come back later and resume. Why is that unwise? > >>> What are the alternatives? > >>> > >>> B > >>> > On Tue, 27 Apr 2010, Ben wrote: > > > slightly off topic, but how does one handle pausing / saving / > > restarting in the FRP framework, especially the arrowized version? > >> > >> If we're about Arrow FRP, remember that the arrow typeclass includes a > >> function, 'arr', that admits any function as a parameter, and these are > in > >> general impossible to serialize to disk. Since Arrow FRP ends up roughly > in > >> a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually > the > >> state of the system. There are a few tactics that would get us around > this > >> limitation, but they are rather severe. You could render 'arr' useless > in > >> several ways, or you could save all the input to a system and replay it. > >> > >> But I would argue that even if you wanted to do this, "saving an FRP > system" > >> is, to me, like "saving a system in the IO monad," (which, there are > tactics > >> that would let you do this, too). It's probablematic in part because > the > >> FRP system probably has active hooks into the user interface, such as > >> windows and other widgits that it owns, and possibly other devices (such > as > >> physical rocket engines). Even if the FRP system is completely pure and > can > >> be referenced by a single pointer, it is easily and rightfully aware of > >> specific details of the hardware it is embedded in. > >> > >> So it seems to me that what we actually want, to do complex simulations > with > >> persistance, is not an FRP system that interacts with the outside world, > but > >> a "self-contained, self-interacting, differential equation hairball." > Such > >> a system would be very cool, but I think that the numerical algorithms > >> needed exceed what an FRP system should try to provide. > >> > >> Friendly, > >> --Lane > >> ___ > >> Haskell-Cafe mailing list > >> Haskell-Cafe@haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > > ___ > > Haskell-Cafe mailing list > > Haskell-Cafe@haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Broken ghc documentation links
Hi, I have recently updated Hoogle so it points at specific documentation. If anyone finds any further bugs, please let me know. I'm hoping to go through Hoogle and revise much of it in the near future, and intend to put things in place to stop this happening again (and keep it up to date). Thanks, Neil On Mon, Apr 26, 2010 at 2:15 PM, Ivan Lazar Miljenovic wrote: > Daniel Fischer writes: > >> Am Montag 26 April 2010 13:36:22 schrieb Ivan Lazar Miljenovic: >>> So, the problem is that there are broken links _in Hoogle_; >> >> No, hoogle just sends you to >> http://www.haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Prelude.html#t%3AIO >> , which does exist. It's the 'Source' link in the haddocks that sends you >> to the 404 Not Found. >> It's the same with my local docs, I think it's haddock that got confused by >> the move of the IO definition from base to ghc-prim. > > Yeah, as I've said I mis-read the initial problem (I've fielded a few > queries recently regarding Hoogle not pointing to the 6.12.2 docs and > initially thought this was another one). > > -- > Ivan Lazar Miljenovic > ivan.miljeno...@gmail.com > IvanMiljenovic.wordpress.com > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
I agree. This would be an extremely useful feature, not only for game development, but also for web development. We often use continuations as a way to add state to the web, but this fails for two reasons: whenever the server restarts, or when we scale to multiple machines. However, I think it is not easy to do this: traversing the heap should be relatively simple, however: what if a function implementation changes? An interesting approach is taken by the Clean guys: they use dynamics, which can store a function, a type representation and the heap to disk. See also this old thread: http://www.mail-archive.com/haskell-cafe@haskell.org/msg34054.html -chris On 28 apr 2010, at 19:50, Peter Verswyvelen wrote: > Interesting topic. I find it a bit annoying that Haskell doesn't > provide support to save functions. I understand this is problematic, > but it would be very nice if the Haskell runtime provided a way to > serialize (part of) the heap, making sure that pointers to compiled > functions get resolved correctly. > > > > On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson > wrote: >> >> On Wed, 28 Apr 2010, Ben wrote: >> >>> I want to save the state of the system to disk, I want to be able to >>> play the game, pick a point to stop, freeze it and turn off the >>> computer, and then come back later and resume. Why is that unwise? >>> What are the alternatives? >>> >>> B >>> On Tue, 27 Apr 2010, Ben wrote: > slightly off topic, but how does one handle pausing / saving / > restarting in the FRP framework, especially the arrowized version? >> >> If we're about Arrow FRP, remember that the arrow typeclass includes a >> function, 'arr', that admits any function as a parameter, and these are in >> general impossible to serialize to disk. Since Arrow FRP ends up roughly in >> a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the >> state of the system. There are a few tactics that would get us around this >> limitation, but they are rather severe. You could render 'arr' useless in >> several ways, or you could save all the input to a system and replay it. >> >> But I would argue that even if you wanted to do this, "saving an FRP system" >> is, to me, like "saving a system in the IO monad," (which, there are tactics >> that would let you do this, too). It's probablematic in part because the >> FRP system probably has active hooks into the user interface, such as >> windows and other widgits that it owns, and possibly other devices (such as >> physical rocket engines). Even if the FRP system is completely pure and can >> be referenced by a single pointer, it is easily and rightfully aware of >> specific details of the hardware it is embedded in. >> >> So it seems to me that what we actually want, to do complex simulations with >> persistance, is not an FRP system that interacts with the outside world, but >> a "self-contained, self-interacting, differential equation hairball." Such >> a system would be very cool, but I think that the numerical algorithms >> needed exceed what an FRP system should try to provide. >> >> Friendly, >> --Lane >> ___ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problem about pattern matching.
minh thu schrieb: > 2010/4/28 Magicloud Magiclouds : >> Hi, I have code as below. How come "case" version works wrong and >> gives me "overlap" compiling warning? Thanks. >> if dayOfMonth == firstDayOfMonth >>then v day (x, y) >>else if dayOfMonth == lastDayOfMonth >> then not_ $ v day (x, y) >> else Mider day (x, y) >> >> case dayOfMonth of >>firstDayOfMonth -> v day (x, y) >>lastDay -> not_ $ v day (x, y) >>_ -> Mider day (x, y) > > Hi, > > firstDayIfMonth and lastDay are new variables, not previously bound > variable. This means that trying to pattern match (the value of) > dayOfMonth will always succeed with the first alternative. You can however simulate a 'case' with predefined variables: http://haskell.org/haskellwiki/Case ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
Interesting topic. I find it a bit annoying that Haskell doesn't provide support to save functions. I understand this is problematic, but it would be very nice if the Haskell runtime provided a way to serialize (part of) the heap, making sure that pointers to compiled functions get resolved correctly. On Wed, Apr 28, 2010 at 6:42 PM, Christopher Lane Hinson wrote: > > On Wed, 28 Apr 2010, Ben wrote: > >> I want to save the state of the system to disk, I want to be able to >> play the game, pick a point to stop, freeze it and turn off the >> computer, and then come back later and resume. Why is that unwise? >> What are the alternatives? >> >> B >> >>> On Tue, 27 Apr 2010, Ben wrote: >>> slightly off topic, but how does one handle pausing / saving / restarting in the FRP framework, especially the arrowized version? > > If we're about Arrow FRP, remember that the arrow typeclass includes a > function, 'arr', that admits any function as a parameter, and these are in > general impossible to serialize to disk. Since Arrow FRP ends up roughly in > a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the > state of the system. There are a few tactics that would get us around this > limitation, but they are rather severe. You could render 'arr' useless in > several ways, or you could save all the input to a system and replay it. > > But I would argue that even if you wanted to do this, "saving an FRP system" > is, to me, like "saving a system in the IO monad," (which, there are tactics > that would let you do this, too). It's probablematic in part because the > FRP system probably has active hooks into the user interface, such as > windows and other widgits that it owns, and possibly other devices (such as > physical rocket engines). Even if the FRP system is completely pure and can > be referenced by a single pointer, it is easily and rightfully aware of > specific details of the hardware it is embedded in. > > So it seems to me that what we actually want, to do complex simulations with > persistance, is not an FRP system that interacts with the outside world, but > a "self-contained, self-interacting, differential equation hairball." Such > a system would be very cool, but I think that the numerical algorithms > needed exceed what an FRP system should try to provide. > > Friendly, > --Lane > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, Apr 28, 2010 at 12:55 PM, Rogan Creswick wrote: > On Wed, Apr 28, 2010 at 8:19 AM, Duncan Coutts > wrote: >> >> Yes, it means the testing agent (cabal-install or some other >> program/system) can do more than simply run all the tests. It means it >> can enumerate them and not run them (think a GUI or web interface), run >> a subset of tests, run them in parallel etc. >> > > I'm not convinced that this should be cabal's responsibility. > > I think we would be better served by leaving this up to the test > frameworks (indeed, test-framework has test filtering capabilities > already). If 'cabal test' simply acts as a thin layer between the > user/invoking system and the test framework, then we could pass > arguments through to the underlying test binary and perform these > tasks using whatever interface that test binary provides. This will > buy us more flexibility in the long run. (I think this is at least a > good place to start -- and matches my interpretation of Thomas's > proposal.) That is more or less how I intended my proposal to be read, the caveat being that I intentionally said very little about the detailed test suite interface. I agree that we should leave much up to the testing frameworks. If we start implementing facilities in Cabal to pick and choose specific tests from inside test suites, we're essentially writing yet another test framework into Cabal; I've been specifically discouraged from doing that since I began discussing this proposal on the list. I am increasingly of the opinion that we should just provide a simple, stdout/exit code interface and let test frameworks handle the rest: If developers want continuous integration with existing testing tools, the can use a framework that supports the output format those tools use, and pipe that output to stdout to be captured by Cabal. Then they can turn whichever tool they want loose on the output file. If developers want to independently run subsets of their tests, they can give them independent test stanzas in the .cabal file. Either they put the tests in different executables, or the test framework can provide command-line options for turning tests on and off. Those are the big two usage scenarios we've discussed for the detailed test interface, and I think these examples demonstrate why I think it may be unnecessary. -- Thomas Tuegel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
If the goal is continuous integration, perhaps it would be sufficient to require "cabal test" to return an error code of 0 if all tests succeed, and something else if any of them fail; it can additionally print whatever output it wants in either case. The continuous integration system would then run "cabal test" after the build, and if it succeeded (error code 0) say nothing, and if it failed (error code something else) it would report that the build failed and show the output from "cabal test" to give details to the developer. Cheers, Greg On Apr 28, 2010, at 12:55 PM, Rogan Creswick wrote: > On Wed, Apr 28, 2010 at 8:19 AM, Duncan Coutts > wrote: >> >> Yes, it means the testing agent (cabal-install or some other >> program/system) can do more than simply run all the tests. It means it >> can enumerate them and not run them (think a GUI or web interface), run >> a subset of tests, run them in parallel etc. >> > > I'm not convinced that this should be cabal's responsibility. > > I think we would be better served by leaving this up to the test > frameworks (indeed, test-framework has test filtering capabilities > already). If 'cabal test' simply acts as a thin layer between the > user/invoking system and the test framework, then we could pass > arguments through to the underlying test binary and perform these > tasks using whatever interface that test binary provides. This will > buy us more flexibility in the long run. (I think this is at least a > good place to start -- and matches my interpretation of Thomas's > proposal.) > > If Cabal takes on these responsibilities, then the testing api will be > more constrained -- we won't be able to experiment with new test > formats/methodologies as easily, since any tests will have to meet a > specific API. > > While I agree that we need standardization, I think that we should > achieve that by using compatible output formats and compatible (user) > interfaces (and enforcing those with tests, schema checkers, etc..). > I don't see many benefits to baking this functionality into cabal when > it could be done separately. > > --Rogan > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
Richard G. schrieb: > I think that formatted plain-text output would be much better than XML, > something that is human-readable and relatively easy to parse via > machine. Something similar to the GHC error output would work well > because developers are familiar with it. > > Test : > > > > E.g., > > Test 1:Passed > src/Some/File.hs:23 > > Test 2:Failed > src/Some/File.hs:27 > Expecting `4'; received `5'. > > Test 3:Error > src/Some/OtherFile.hs:39 This is the format Emacs parses and lets you jump right to the according file and position. > Unexpected exception. > > This would keep the complexity low in Cabal and allow for easy > transformation to XML. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, Apr 28, 2010 at 8:19 AM, Duncan Coutts wrote: > > Yes, it means the testing agent (cabal-install or some other > program/system) can do more than simply run all the tests. It means it > can enumerate them and not run them (think a GUI or web interface), run > a subset of tests, run them in parallel etc. > I'm not convinced that this should be cabal's responsibility. I think we would be better served by leaving this up to the test frameworks (indeed, test-framework has test filtering capabilities already). If 'cabal test' simply acts as a thin layer between the user/invoking system and the test framework, then we could pass arguments through to the underlying test binary and perform these tasks using whatever interface that test binary provides. This will buy us more flexibility in the long run. (I think this is at least a good place to start -- and matches my interpretation of Thomas's proposal.) If Cabal takes on these responsibilities, then the testing api will be more constrained -- we won't be able to experiment with new test formats/methodologies as easily, since any tests will have to meet a specific API. While I agree that we need standardization, I think that we should achieve that by using compatible output formats and compatible (user) interfaces (and enforcing those with tests, schema checkers, etc..). I don't see many benefits to baking this functionality into cabal when it could be done separately. --Rogan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Installing ghc in an OpenSolaris Zone
Hello Christin, http://www.haskell.org/ghc/download_ghc_6_10_4.html#x86solaris is supposed to work under open solaris, too. it does actually, quite nicely too, in the *global* zone. It's just when I try to install it into a separate zone the install fails. Have you managed to install it into a zone yourself? Best regards Günther ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
On Wed, 28 Apr 2010, Ben wrote: I want to save the state of the system to disk, I want to be able to play the game, pick a point to stop, freeze it and turn off the computer, and then come back later and resume. Why is that unwise? What are the alternatives? B On Tue, 27 Apr 2010, Ben wrote: slightly off topic, but how does one handle pausing / saving / restarting in the FRP framework, especially the arrowized version? If we're about Arrow FRP, remember that the arrow typeclass includes a function, 'arr', that admits any function as a parameter, and these are in general impossible to serialize to disk. Since Arrow FRP ends up roughly in a form of: FRP a b c = a b (c, FRP a b c), an Arrow instance is actually the state of the system. There are a few tactics that would get us around this limitation, but they are rather severe. You could render 'arr' useless in several ways, or you could save all the input to a system and replay it. But I would argue that even if you wanted to do this, "saving an FRP system" is, to me, like "saving a system in the IO monad," (which, there are tactics that would let you do this, too). It's probablematic in part because the FRP system probably has active hooks into the user interface, such as windows and other widgits that it owns, and possibly other devices (such as physical rocket engines). Even if the FRP system is completely pure and can be referenced by a single pointer, it is easily and rightfully aware of specific details of the hardware it is embedded in. So it seems to me that what we actually want, to do complex simulations with persistance, is not an FRP system that interacts with the outside world, but a "self-contained, self-interacting, differential equation hairball." Such a system would be very cool, but I think that the numerical algorithms needed exceed what an FRP system should try to provide. Friendly, --Lane ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, Apr 28, 2010 at 1:24 AM, Richard G. wrote: > I think that formatted plain-text output would be much better than XML, > something that is human-readable and relatively easy to parse via machine. > Something similar to the GHC error output would work well because > developers are familiar with it. I don't think we need to be limited to a single output format. It's a simple thing to have continuous integration (or cabal) invoke tests with a flag/option to output in a specific format. XML is useful because there are a number of mature tools that already expect xml -- we don't need to reinvent the wheel to get some of the capabilities that developers in other languages are enjoying if our tools use some of the same formats (despite the issues that may exist with those formats..). I like your suggestion for an emacs/dev-readable format, and it can coexist with xml and other "snazzier" outputs (such as the default format for test-framework, which uses many little tricks to draw and erase progress bars / etc.) --Rogan > > Test : > > > > E.g., > > Test 1:Passed > src/Some/File.hs:23 > > Test 2:Failed > src/Some/File.hs:27 > Expecting `4'; received `5'. > > Test 3:Error > src/Some/OtherFile.hs:39 > Unexpected exception. > > This would keep the complexity low in Cabal and allow for easy > transformation to XML. > > Richard G. > > On 10-04-08 8:30 PM, Rogan Creswick wrote: >> >> On Thu, Apr 8, 2010 at 5:53 AM, Duncan Coutts >> wrote: >>> >>> I think it's important to be able to convert into standard or custom >>> formats. I've no idea if JUnit XML would make sense as the native >>> format. It's plausible. >>> >> >> I hadn't really thought about cabal, itself, being a consumer for test >> results -- but I like your (Duncan's) points about defining a testing >> interface, and keeping it extensible. >> >> For the record: I don't think junit xml is a good choice for a native >> format :), but I do think it's a good format to start with simply >> because there are many tools that can consume it already. >> >> --Rogan >> >> >>> Duncan >>> >>> ___ >>> Haskell-Cafe mailing list >>> Haskell-Cafe@haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> ___ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, 2010-04-28 at 10:42 -0400, Thomas Tuegel wrote: > On Wed, Apr 28, 2010 at 4:54 AM, Duncan Coutts > wrote: > > On 28 April 2010 09:24, Richard G. wrote: > >> I think that formatted plain-text output would be much better than XML, > >> something that is human-readable and relatively easy to parse via machine. > >> Something similar to the GHC error output would work well because > >> developers are familiar with it. > > > > I have previously advocated a library interface as a detailed > > testsuite interface (in addition to a lowest common denominator > > interface of stdio+exitcode). That is a test stanza in a package > > .cabal file would specify a module containing an entry point of the > > right type (like main but using a more interesting type). > > > > That way, cabal or any other tool could run the testsuite and produce > > results in whatever format it likes. > > I appreciate the elegance of this method, but it seems to me that it > requires dynamic loading, which is currently in a sorry state. Actually it doesn't require dynamic loading. It just requires compiling a stub program that imports the user's library and some test-runner code. Cabal is good at doing that kind of thing already (eg Setup.hs scripts). > One way or another, cabal will need to provide a data structure it expects > test suites to use for results. Is there a substantial advantage to a > library interface, versus providing Read/Show instances for the test > result data structure? Yes, it means the testing agent (cabal-install or some other program/system) can do more than simply run all the tests. It means it can enumerate them and not run them (think a GUI or web interface), run a subset of tests, run them in parallel etc. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Seeking the correct quote
Bradford Larsen wrote: I don't have the book handy (it was from the library), but I seem to remember reading something along those lines in ``Datatype-Generic Programming: International Spring School, SSDGP 2006, Nottingham, UK, April 24-27, 2006, Revised Lectures'', edited by Backhouse, Gibbons, Hinze, and Jeuring. The spirit is there in quotes like "The term ‘generic programming’ means different things to different people, because they have different ideas about how to achieve the common goal of combining flexibility and safety. To some people, it means parametric polymorphism; to others, it means libraries of algorithms and data structures; to another group, it means reflection and meta-programming; to us, it means polytypism, that is, type-safe parametrization by a datatype " and "Moreover, a parametrization is usually only called ‘generic’ programming if it is of a ‘non-traditional’ kind; by definition, traditional kinds of parametrization give rise only to traditional programming, not generic programming. Therefore, ‘genericity’ is in the eye of the beholder, with beholders from different programming traditions having different interpretations of the term." But nothing 'snappy'. Ah well. Jacques ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, Apr 28, 2010 at 4:54 AM, Duncan Coutts wrote: > On 28 April 2010 09:24, Richard G. wrote: >> I think that formatted plain-text output would be much better than XML, >> something that is human-readable and relatively easy to parse via machine. >> Something similar to the GHC error output would work well because >> developers are familiar with it. > > I have previously advocated a library interface as a detailed > testsuite interface (in addition to a lowest common denominator > interface of stdio+exitcode). That is a test stanza in a package > .cabal file would specify a module containing an entry point of the > right type (like main but using a more interesting type). > > That way, cabal or any other tool could run the testsuite and produce > results in whatever format it likes. I appreciate the elegance of this method, but it seems to me that it requires dynamic loading, which is currently in a sorry state. One way or another, cabal will need to provide a data structure it expects test suites to use for results. Is there a substantial advantage to a library interface, versus providing Read/Show instances for the test result data structure? > As you suggest in your other post, it would make sense to adapt > test-framework to implement the interface specified by Cabal. I agree, as well; this is essentially the approach I took in my proposal. -- Thomas Tuegel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: FRP for game programming / artifical life simulation
I want to save the state of the system to disk, I want to be able to play the game, pick a point to stop, freeze it and turn off the computer, and then come back later and resume. Why is that unwise? What are the alternatives? B On Tue, Apr 27, 2010 at 9:28 PM, Christopher Lane Hinson wrote: > > I'm not sure exactly what you want to do. It should certainly be easy to > "freeze" an FRP program by lying about the amount of time that is passing > and witholding all events. Do you want to save an FRP system instance to > disk (generally unwise), or something else (what?). > > Friendly, > --Lane > > On Tue, 27 Apr 2010, Ben wrote: > >> slightly off topic, but how does one handle pausing / saving / >> restarting in the FRP framework, especially the arrowized version? >> i've only been able to do this via explicit (or monadic) >> state-passing, e.g. imperative / piecemeal versus declarative / >> wholemeal, which seems against the spirit of FRP. >> >> b >> ___ >> Haskell-Cafe mailing list >> Haskell-Cafe@haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Control.Exception try and catch
Hi From http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-Exception.html#3 "... The difference between using try and catch for recovery is that in catch the handler is inside an implicit block (see "Asynchronous Exceptions") which is important when catching asynchronous exceptions ..." However, 'try' is implemented by calling catch http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/src/Control-Exception-Base.html#try: try :: Exception e => IO a -> IO (Either e a) try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e)) Thus, I wonder, why do 'try' not "inherit" the implicit block mentioned above? Looking at catch: catch :: Exception e => IO a -- ^ The computation to run -> (e -> IO a) -- ^ Handler to invoke if an exception is raised -> IO a catch io h = H'98.catch io (h . fromJust . fromException . toException) I see no call to 'block'. But maybe it is hidden in H'98.catch? And is H'98.catch == Prelude.catch ? /Mads ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On Wed, Apr 28, 2010 at 4:30 AM, Richard G. wrote: > I think that, rather than having Cabal try to combine the results of > different frameworks, Cabal should specify interfaces that frameworks need > to conform to. > > E.g., rather than integrating test-framework into Cabal so that HUnit works > with it, modify HUnit so it emits the format that Cabal wants. And modify > test-framework to emit the format that Cabal wants so, if someone can't > convert their test suite to the CabalTest format, test-framework can act as > an intermediary and handle the conversion of output. I think this is what we've ultimately decided to do, although we have yet to decide exactly what format Cabal should expect test results to be in. I realize that it's a little difficult to follow this discussion, since the proposal was in a state of flux. I think you can read my proposal at the GSoC site, but the proposal submission form kinda mangled my formatting. There is a public Google Documents version of my proposal at https://docs.google.com/Doc?docid=0AZzNFnSY9FOeZGd6MnQ4cWNfM2Q2N2J0OWZn&hl=en which should be up-to-date and contain all the information you need. -- Thomas Tuegel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is XHT a good tool for parsing web pages?
Hi Ivan, > Uwe Schmidt writes: > > The HTML parser in HXT is based on tagsoup. It's a lazy parser > > (it does not use parsec) and it tries to parse everything as HTML. > > But garbage in, garbage out, there is no approach to repair illegal HTML > > as e.g. the Tidy parsers do. The parser uses tagsoup as a scanner. > > So what is parsec used for in HXT then? for the XML parser. This XML parser also deals with DTDs. This parser only accepts well formed XML, everything else gives an error (not just a warning like HTML parser). tagsoup and the HTML parser do not deal with DTDs, so they can't be used for a full (validating) XML parser. Regards, Uwe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What do _you_ want to see in FGL?
Henning Thielemann writes: > Ivan Miljenovic schrieb: > >> So you don't want the labels to be part of the actual datatype? And >> for users to then have to deal with any labels they want themselves? > > No, you would continue to provide labelled and unlabelled graphs, where > unlabelled graphs (or just Graphs) are the base type and labelled graphs are > > data LabelledGraph node edge = >LabelledGraph Graph (Map Node node) (Map (Node,Node) edge) > > This is a matter of separation of concerns. Sure, it means that you need > to split the graph algorithms into their parts: each algorithm into an > unlabelled and a labelled part. If there are algorithms that make no > sense on labelled graphs, then you need only the first part. I'm hesitant to do such a thing for the simple reason that it will involve duplicate work... It might be possible, by having two classes that do the same thing (Foo and FooLabelled), but I'm not sure how well this would scale. >> If so, I don't think this is feasible; some of the nice parts of FGL >> IMHO are how it deals with labels (admittedly, I've had to write and >> use my own "((Int,a) -> a') -> g a b -> g a' b" function because it >> doesn't have one...). Removing this would be a step backwards. >> >> How exactly is it bad/a pain to have to deal with specifying "g () >> ()", especially since there are some pre-defined "unlabelled" graph >> type and function aliases? > > For problems that do not need labels, why shall I cope with them? Ummm... I fail to see how having labels would make FGL harder to use just because you have to do "gr () ()" rather than just "gr" in your types. > I expect that you quickly run into the need for type extensions, I was planning on using associated types to state what the node type was. > if you define a graph type class that have only unlabelled graphs as > instance. For instance: > >> instance SpecialGraph (gr () ()) where > > is not Haskell 98, instead > >> instance (IsUnit a) => SpecialGraph (gr a a) where >> >> class IsUnit a where toUnit :: a -> () >> instance IsUnit () where toUnit = id > > would be Haskell 98, but is certainly more complicated. Not sure what you're doing here... But isn't that what newtypes are for? > This may also answer your question, how hard you should try to stay > Haskell 98. My experience is, that with a proper design of a library you > can reduce the need for type extensions. This makes your code more > portable and easier to understand. I don't plan on going overboard, but I am not going to go out of my way to avoid extensions (sane ones; there are no plans on using IncoherentInstances or something like that!). Yes, it means that it won't compile on a non-GHC Haskell implementation; but how many people actually use any other compiler full time? My understanding was that the other Haskell compilers still being worked on (JHC and UHC) didn't fully implement Haskell98 either. -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] What do _you_ want to see in FGL?
Ivan Miljenovic schrieb: > So you don't want the labels to be part of the actual datatype? And > for users to then have to deal with any labels they want themselves? No, you would continue to provide labelled and unlabelled graphs, where unlabelled graphs (or just Graphs) are the base type and labelled graphs are data LabelledGraph node edge = LabelledGraph Graph (Map Node node) (Map (Node,Node) edge) This is a matter of separation of concerns. Sure, it means that you need to split the graph algorithms into their parts: each algorithm into an unlabelled and a labelled part. If there are algorithms that make no sense on labelled graphs, then you need only the first part. > If so, I don't think this is feasible; some of the nice parts of FGL > IMHO are how it deals with labels (admittedly, I've had to write and > use my own "((Int,a) -> a') -> g a b -> g a' b" function because it > doesn't have one...). Removing this would be a step backwards. > > How exactly is it bad/a pain to have to deal with specifying "g () > ()", especially since there are some pre-defined "unlabelled" graph > type and function aliases? For problems that do not need labels, why shall I cope with them? I expect that you quickly run into the need for type extensions, if you define a graph type class that have only unlabelled graphs as instance. For instance: > instance SpecialGraph (gr () ()) where is not Haskell 98, instead > instance (IsUnit a) => SpecialGraph (gr a a) where > > class IsUnit a where toUnit :: a -> () > instance IsUnit () where toUnit = id would be Haskell 98, but is certainly more complicated. This may also answer your question, how hard you should try to stay Haskell 98. My experience is, that with a proper design of a library you can reduce the need for type extensions. This makes your code more portable and easier to understand. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell Weekly News?
2010/4/28 Ivan Lazar Miljenovic : > minh thu writes: > >> 2010/4/28 Ivan Lazar Miljenovic : >>> Joe Fredette writes: That said, if any of you have time machines/time dilation devices in the works, I'm happy to beta test. >>> >>> Don't be silly, you don't need more time, you need more _you_ >>> (i.e. clones); after all, nothing ever goes wrong with clones! :p >> >> Don't want to dismiss your comment but about clones and time machines, >> the only good source of information is their creators, Kelvin and >> Hobbes. > > You mean Calvin? Damn, of course. > Anyway, the transmogrifier was _much_ better! Cardboards and abstractions ... seems like programming :) Thu ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell Weekly News?
minh thu writes: > 2010/4/28 Ivan Lazar Miljenovic : >> Joe Fredette writes: >>> That said, if any of you have time machines/time dilation devices in >>> the works, I'm happy to beta test. >> >> Don't be silly, you don't need more time, you need more _you_ >> (i.e. clones); after all, nothing ever goes wrong with clones! :p > > Don't want to dismiss your comment but about clones and time machines, > the only good source of information is their creators, Kelvin and > Hobbes. You mean Calvin? Anyway, the transmogrifier was _much_ better! -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell Weekly News?
2010/4/28 Ivan Lazar Miljenovic : > Joe Fredette writes: >> That said, if any of you have time machines/time dilation devices in >> the works, I'm happy to beta test. > > Don't be silly, you don't need more time, you need more _you_ > (i.e. clones); after all, nothing ever goes wrong with clones! :p Don't want to dismiss your comment but about clones and time machines, the only good source of information is their creators, Kelvin and Hobbes. Thu ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell Weekly News?
Joe Fredette writes: > That said, if any of you have time machines/time dilation devices in > the works, I'm happy to beta test. Don't be silly, you don't need more time, you need more _you_ (i.e. clones); after all, nothing ever goes wrong with clones! :p -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is XHT a good tool for parsing web pages?
Uwe Schmidt writes: > The HTML parser in HXT is based on tagsoup. It's a lazy parser > (it does not use parsec) and it tries to parse everything as HTML. > But garbage in, garbage out, there is no approach to repair illegal HTML > as e.g. the Tidy parsers do. The parser uses tagsoup as a scanner. So what is parsec used for in HXT then? -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Getting used and available memory
Hi On Tue, 2010-04-27 at 14:55 -0700, Don Stewart wrote: > We could bind to Rts.c in the GHC runtime, and get all the stats > programmatically that you can get with +RTS -s That would be nice. /Mads ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] happstack/SOAP
Hi I do not have an example for you, but I do have some text conversion functions you may find useful. I have attached the text conversion functions in a file. /Mads On Mon, 2010-04-26 at 09:46 +, Johannes Waldmann wrote: > Hi - I'm looking for an example/demo happstack server > that handles SOAP requests. - Thanks, J.W. > > > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe {-# OPTIONS -Wall -XOverloadedStrings #-} module TextConversion ( soapXmlUtf8, soapXmlToString , soapContentType , E.DecodingException , E.EncodingException ) where import qualified Data.ByteString.Lazy as BS import qualified Data.ByteString.Lazy.Char8 as BsC8 import qualified Data.Encoding as E import qualified Data.Encoding.UTF8 as E import Text.Regex import Text.Parsec import Text.Parsec.ByteString.Lazy -- soapXmlUtf8, soapXmlToString, bsToUtf8, bsToString, StringToUtf8Bs may throw DecodingException -- or EncodingException -- |Converts a SOAP request to UTF8. If the request contains a XML header, -- the text encoding is set to UTF8. soapXmlUtf8 :: String-- ^The content type as seen in the HTTP header -> BS.ByteString -> BS.ByteString soapXmlUtf8 contentType = bsToUtf8 (encoding contentType) . setUtf8EncodingInXmlHeader -- |Converts a SOAP request to String. If the request contains a XML header, -- the text encoding is set to UTF8. soapXmlToString :: String-- ^The content type as seen in the HTTP header -> BS.ByteString -> String soapXmlToString contentType = bsToString (encoding contentType) . setUtf8EncodingInXmlHeader bsToUtf8 :: String -> BS.ByteString -> BS.ByteString bsToUtf8 enc = stringToUtf8Bs . bsToString enc bsToString :: String -> BS.ByteString -> String bsToString enc bs = E.decodeLazyByteString (E.encodingFromString enc) bs stringToUtf8Bs :: String -> BS.ByteString stringToUtf8Bs = E.encodeLazyByteString E.UTF8 -- *** HTTP Header -- |Produces a HTTP content type header from a charector encoding soapContentType :: Maybe String -- ^ If nothing then it defaults to ISO-8859-1 -> String soapContentType = maybe ("application/soap+xml;charset=" ++ httpDefaultEncoding) id -- |Extracts charector encoding from a HTTP content type header encoding :: String -> String encoding httpContentType = case matchRegex (mkRegex "charset=([^; ]*)") httpContentType of Just (x:_) -> x _ -> httpDefaultEncoding -- Default charset=ISO-8859-1. See: -- http://www.w3.org/Protocols/rfc2616/rfc2616-sec3.html#sec3.7.1 -- http://www.w3.org/International/O-HTTP-charset httpDefaultEncoding :: String httpDefaultEncoding = "ISO-8859-1" -- *** XML Header -- http://www.w3.org/TR/REC-xml/#TextEntities setUtf8EncodingInXmlHeader :: BS.ByteString -> BS.ByteString setUtf8EncodingInXmlHeader xml = let replaceEnc (name, value) | name == "encoding" = (name, "UTF-8") | otherwise = (name, value) in case parse headerParser "" xml of Left _ -> xml Right (attrs, rest) -> BS.append (mkHeader $ map replaceEnc attrs) rest mkHeader :: [(String, String)] -> BS.ByteString mkHeader attrs = let mkAttr (name, value) = " " ++ name ++ "=\"" ++ value ++ "\"" in BsC8.pack ("\n") headerParser :: Parser ([(String, String)], BS.ByteString) headerParser = do _ <- string "" endPos <- getInput return (attrs, endPos) attrParser :: Parser (String, String) attrParser = do name <- many1 letter spaces _ <- char '=' spaces _ <- char '"' value <- many $ noneOf "\"" _ <- char '"' spaces return (name, value) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Problem about pattern matching.
2010/4/28 Magicloud Magiclouds : > Hi, I have code as below. How come "case" version works wrong and > gives me "overlap" compiling warning? Thanks. > if dayOfMonth == firstDayOfMonth > then v day (x, y) > else if dayOfMonth == lastDayOfMonth > then not_ $ v day (x, y) > else Mider day (x, y) > > case dayOfMonth of > firstDayOfMonth -> v day (x, y) > lastDay -> not_ $ v day (x, y) > _ -> Mider day (x, y) Hi, firstDayIfMonth and lastDay are new variables, not previously bound variable. This means that trying to pattern match (the value of) dayOfMonth will always succeed with the first alternative. Think of parsing command line argument, using the last alternative as a fall-through : args <- getArgs case args of ["--help"] -> ... ["--run-tests"] -> ... x -> putStrLn $ "unknow args " ++ concat x What would happen if the last alternative (with the x) was put in first position ? Cheers, Thu ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is XHT a good tool for parsing web pages?
Hi John and Malcom, > I know that the HaXml library has a separate error-correcting HTML > parser that works around most of the common non-well-formedness bugs > in HTML: > Text.XML.HaXml.Html.Parse > > I believe HXT has a similar parser: > Text.XML.HXT.Parser.HtmlParsec > > Indeed, some of the similarities suggest this parser was originally > lifted directly out of HaXml (as permitted by HaXml's licence), > although the two modules have now diverged significantly. The HTML parser in HXT is based on tagsoup. It's a lazy parser (it does not use parsec) and it tries to parse everything as HTML. But garbage in, garbage out, there is no approach to repair illegal HTML as e.g. the Tidy parsers do. The parser uses tagsoup as a scanner. The table driven approach for inserting missing closing tags is indeed taken from HaXml. Malcom, I hope you don't have a patent on this algorithm. Regards, Uwe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
On 28 April 2010 09:24, Richard G. wrote: > I think that formatted plain-text output would be much better than XML, > something that is human-readable and relatively easy to parse via machine. > Something similar to the GHC error output would work well because > developers are familiar with it. I have previously advocated a library interface as a detailed testsuite interface (in addition to a lowest common denominator interface of stdio+exitcode). That is a test stanza in a package .cabal file would specify a module containing an entry point of the right type (like main but using a more interesting type). That way, cabal or any other tool could run the testsuite and produce results in whatever format it likes. As you suggest in your other post, it would make sense to adapt test-framework to implement the interface specified by Cabal. Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Problem about pattern matching.
Hi, I have code as below. How come "case" version works wrong and gives me "overlap" compiling warning? Thanks. if dayOfMonth == firstDayOfMonth then v day (x, y) else if dayOfMonth == lastDayOfMonth then not_ $ v day (x, y) else Mider day (x, y) case dayOfMonth of firstDayOfMonth -> v day (x, y) lastDay -> not_ $ v day (x, y) _ -> Mider day (x, y) -- 竹密岂妨流水过 山高哪阻野云飞 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
I think that, rather than having Cabal try to combine the results of different frameworks, Cabal should specify interfaces that frameworks need to conform to. E.g., rather than integrating test-framework into Cabal so that HUnit works with it, modify HUnit so it emits the format that Cabal wants. And modify test-framework to emit the format that Cabal wants so, if someone can't convert their test suite to the CabalTest format, test-framework can act as an intermediary and handle the conversion of output. Richard G. On 10-04-06 5:03 PM, Gregory Crosswhite wrote: Rather that starting from scratch, you should strongly consider adapting something like test-framework to this task, as it already has done the heavy work of creating a way to combine tests from different frameworks into a single suite and includes such features as displaying a progress bar during the QuickCheck tests. Furthermore, it is easily extendable to support new kinds of tests; for example, I found that it was relatively straightforward to add a new kind of "statistical" test to make sure that the average value of a function where where it should be. Cheers, Greg ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: GSoC: Improving Cabal's Test Support
I think that formatted plain-text output would be much better than XML, something that is human-readable and relatively easy to parse via machine. Something similar to the GHC error output would work well because developers are familiar with it. Test : E.g., Test 1:Passed src/Some/File.hs:23 Test 2:Failed src/Some/File.hs:27 Expecting `4'; received `5'. Test 3:Error src/Some/OtherFile.hs:39 Unexpected exception. This would keep the complexity low in Cabal and allow for easy transformation to XML. Richard G. On 10-04-08 8:30 PM, Rogan Creswick wrote: On Thu, Apr 8, 2010 at 5:53 AM, Duncan Coutts wrote: I think it's important to be able to convert into standard or custom formats. I've no idea if JUnit XML would make sense as the native format. It's plausible. I hadn't really thought about cabal, itself, being a consumer for test results -- but I like your (Duncan's) points about defining a testing interface, and keeping it extensible. For the record: I don't think junit xml is a good choice for a native format :), but I do think it's a good format to start with simply because there are many tools that can consume it already. --Rogan Duncan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Lazy Parsing (ANN: vcd-0.1.4)
On 27 apr 2010, at 22:12, Jason Dusek wrote: > So UU parsers can construct input? The perform an editing action on the input so it becomes a sentence of the language recognised. > The presence of an > empty list in the 2nd slot of the tuple is the only > indicator of errors? The parser wants to see a natural number, whch is a non-empty list of digits. So it inserts a single digit, which is any character from the range '0'-'9'. Since no default value is given here, it takes the first one from the range: '0'. Furthermore you get a list of errors, which tell you which correcting steps were taken. There is a special combinator with which you can ask for the errors produced since the last time you asked, and which you can use to control further parsing. > > For parsing datatypes without a sensible default value, > what happens? If you do nothing you get a less sensible default value; you may however provide (lower costs) extra alternatives which will be taken by the correcting process. There is a cost model which can be used to control the correction process. Tokens have a specific insertion cost and a specific deletion cost with which you can play. Usually this is not necessary. The typical process is that at first you do not pay attention to the correction process, and once you see things you really do not want, you provide an extra alternative, or rule out some alternatives by increasuig costs. In the UHC token like "if" have a high cost, since we think there is very little chance that people will forget to write them. A ')' can have a lower insertion and deletion cost, since people are more likely to have too many or not enough of them. Doaitse > > -- > Jason Dusek ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Re: Haskell Weekly News?
David Sankel wrote: > I'm wondering if a monetary incentive would keep the person who does this > work more accountable. I personally would be willing to contribute to > continue getting this service. I wonder if there are others as well. Maybe Flattr http://flattr.com/ fits the bill concerning monetary appreciation. Regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe