[Haskell-cafe] Simulation and GHC Thread Scheduling

2009-05-09 Thread Thomas DuBuisson
All, I have a simple Haskell P2P library that I've been playing with in simulations of 20 to 600 nodes. To run the simulation there is a Haskell thread (forkIO) for every node in the system, one that starts up all the nodes and prints the info (so prints aren't mangled), and one that acts as the

[Haskell-cafe] Re: Why is Bool no instance of Num and Bits?

2009-05-09 Thread Stefan Monnier
[...] unsafe [PerformIO ...] looks safer to me. Hmmm Stefan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Darcs as undo/redo system?

2009-05-09 Thread Stefan Monnier
I have thought about applications of patch theory like this as well. I could imagine applying it to the undo stack in GIMP. Allowing you to undo things on different layers. I think one of the things you Don't know about the GIMP, but in Emacs, you can select a region of text and undo just

Re: [Haskell-cafe] Generating Haskell with associated types (and kind annotations)

2009-05-09 Thread Manuel M T Chakravarty
Hi Dan, I was wondering whether anyone had any suggestions on a good way to generate repetitive code with associated types and kind annotations. I'd like to use TH but as far as I understand, it doesn't support this yet (I think associated types are in HEAD but not kinds), I implemented type

Re: [Haskell-cafe] Darcs as undo/redo system?

2009-05-09 Thread John A. De Goes
Una Merge does real-time merging and has per user undo. And it can do lots of stuff that seems darcs-like, though I don't know enough about darcs to say for sure (e.g. moving a user's own edits after other edits). http://www.n-brain.net/una_merge.html Regards, John A. De Goes

Re: [Haskell-cafe] is value evaluated?

2009-05-09 Thread Lennart Augustsson
But testing for something being evaluated has to be in the IO monad, or else you're going to break the semantics. On Fri, May 8, 2009 at 4:14 PM, Don Stewart d...@galois.com wrote: Andy Gill has been advocating programmatic access to the 'is evaluated' status bit for years now. 'seq' becomes

Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-09 Thread Stephan Friedrichs
Neil Mitchell wrote: [...] Which is a shame, having Bits on Bool seems entirely logical, having Num a superclass of Bits seems a little less clear. There are two default implementations in Bits bit i = 1 `shiftL` i x `testBit` i = (x .. bit i) /= 0 which rely on Num

Re: [Haskell-cafe] GC

2009-05-09 Thread Jason Dagit
On Fri, May 8, 2009 at 2:37 PM, Andrew Coppin andrewcop...@btinternet.comwrote: John Lask wrote: on the other hand a function to release pool memory to the OS down to the current active level should (I hope) be easily implementable, and quickly incorporated into application where required,

Re: [Haskell-cafe] Generating Haskell with associated types (and kind annotations)

2009-05-09 Thread Neil Mitchell
Hi I guess I should write the skeleton of the code I want to generate, get HSE to parse it, and then replace the parts I want to change of the AST with what I need? Is there a nicer way (TH-like?) to get the modified AST into GHC than prettyprinting the AST again and asking GHC to compile

Re: Can HLint help spot space leaks? (was: Re: [Haskell-cafe] Generating Haskell with associated types (and kind annotations))

2009-05-09 Thread Neil Mitchell
Hi Jason, Hi Neil, A bit off-topic, but your post reminded me:  Does HLint currently help the user find space leaks?  For example, does it recommend strict folds instead of lazy folds?  I looked at the FAQ but this was not listed.  I don't really know how feasible this is. It spots when you

Re: [Haskell-cafe] Writing a compiler in Hakell

2009-05-09 Thread Mads Lindstrøm
Hi Doaitse Doaitse Swierstra wrote: Dear Rouan, on http://www.cs.uu.nl/wiki/HUT/WebHome you will find a collection of tools which may help you to construct a compiler. As an example you will find a Tiger compiler constructed with the uulib tools and the uuagc attribute grammar

Re: [Haskell-cafe] Simulation and GHC Thread Scheduling

2009-05-09 Thread Neil Davies
Thomas You can build your own scheduler very easily using what is already there. As with any simulation the two things that you need to capture are dependency and resource contention. Haskell does both the dependency stuff beautifully and the resource contention. Using STM you can even get

[Haskell-cafe] haskell - main function

2009-05-09 Thread applebiz89
Could anyone look at this segment of code; it's not compiling wondering if anyone could correct me as to why. Thanks Code: -- Film as datatype type Title = String type Director = String type Year = Int type Fan = String data Film = Film Title Director Year [Fan] -- List of films

Re: [Haskell-cafe] Simulation and GHC Thread Scheduling

2009-05-09 Thread Neil Brown
properly, the slight variation is actually a good test). What I would like to know is are there any plans for GHC to incorporate user-definable scheduler? What exactly is it that you want from a user-definable scheduler? Do you want co-operative scheduling in your program, or do you want

Re: [Haskell-cafe] haskell - main function

2009-05-09 Thread Jeremy Shaw
At Sat, 9 May 2009 04:54:13 -0700 (PDT), applebiz89 wrote: Could anyone look at this segment of code; it's not compiling wondering if anyone could correct me as to why. Thanks There is a ton of things wrong with that code. I have attached a version that at least compiles, but there are

Re: [Haskell-cafe] haskell - main function

2009-05-09 Thread Mads Lindstrøm
Hi applebiz89 wrote: Could anyone look at this segment of code; it's not compiling wondering if anyone could correct me as to why. Thanks Code: -- Film as datatype type Title = String type Director = String type Year = Int type Fan = String data Film = Film Title Director Year [Fan]

Re: [Haskell-cafe] is value evaluated?

2009-05-09 Thread Brandon S. Allbery KF8NH
On May 8, 2009, at 16:31 , Sittampalam, Ganesh wrote: Brandon S. Allbery KF8NH wrote: Unless it catches exceptions itself (which strikes me as a bad idea; it becomes a trivial way to ignore exceptions, leading to bad programming practices) either they're handled inside the _|_ (in which case it

Re: [Haskell-cafe] Question concerning Haskell Foundation

2009-05-09 Thread Duncan Coutts
On Thu, 2009-05-07 at 18:13 -0500, Vasili I. Galchin wrote: sorry should read With Haskell Platform 1) Can we still publish/push up packages to Hackage? E.g. now I am trying to get Graham Lyle's Swish (semantic web package) cabalized. 2) Will Hackage go away? Hackage and the

Re: [Haskell-cafe] cabal parse problems

2009-05-09 Thread Duncan Coutts
On Wed, 2009-05-06 at 19:37 -0500, Vasili I. Galchin wrote: are them some CLI switches I can enable in order to better determine what parse error is?? The problem is that we're using a parser that has no support for producing parse errors (Text.ParserCombinators.ReadP). The only reason we're

Re: [Haskell-cafe] runhaskell CLI parameters

2009-05-09 Thread Duncan Coutts
On Tue, 2009-05-05 at 22:39 -0500, Vasili I. Galchin wrote: Hello, I have forgotten the runhaskell CLI parameters ... sigh. In particular I want to a local build of a set of of package: runhaskell Setup.hs configure --user??? I just did a runhaskell -? which didn't tell me

Re: [Haskell-cafe] Simulation and GHC Thread Scheduling

2009-05-09 Thread Thomas DuBuisson
On Sat, May 9, 2009 at 6:28 AM, Neil Brown nc...@kent.ac.uk wrote: properly, the slight variation is actually a good test).  What I would like to know is are there any plans for GHC to incorporate user-definable scheduler? What exactly is it that you want from a user-definable scheduler?  Do

[Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread michael rice
Why doesn't this work? Michael data Maybe a = Nothing | Just a instance Monad Maybe where     return = Just     fail   = Nothing     Nothing  = f = Nothing     (Just x) = f = f x      instance MonadPlus Maybe where     mzero = Nothing     Nothing

RE: [Haskell-cafe] is value evaluated?

2009-05-09 Thread Sittampalam, Ganesh
Brandon S. Allbery KF8NH wrote: On May 8, 2009, at 16:31 , Sittampalam, Ganesh wrote: Brandon S. Allbery KF8NH wrote: Unless it catches exceptions itself (which strikes me as a bad idea; it becomes a trivial way to ignore exceptions, leading to bad programming practices) either they're

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Thomas DuBuisson
Because you're looking for: Just 3 = return . (+1) or more simply Just 3 = Just . (+1) or more generally: return 3 = return . (+1) The second argument of (=) is supposed to be of type (Monad m = a - m b) but (+1) ishe of type (Num a = a - a). Wre is the monad in that? Thomas On Sat, May 9,

Re: [Haskell-cafe] haskell - main function

2009-05-09 Thread Tillmann Rendel
applebiz89 wrote: becomeFan :: Title - fanName - [Film] - [Film] becomeFan _ _ [] = [] becomeFan Title fanName ((Film Title Director Year fan):xs) | filmName == title = (Film Title Director Year fanName:fan) : xs | otherwise = (Film Title Director Year fan) : becomeFan Title fanName

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Daniel Peebles
I think you're looking for fmap/liftM here. The type of = is: (=) :: (Monad m) = m a - (a - m b) - m b so it's trying to make your function (1+) return m b, which in this case should be a Maybe. Clearly, (1+) doesn't return a Maybe, so it breaks. Another options is to do return . (1+) to lift

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Henning Thielemann
On Sat, 9 May 2009, michael rice wrote: Prelude Just 3 = (1+) fmap (1+) (Just 3) or Just 3 = return . (1+) or, with consistent order of functions return . (1+) = Just 3 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Neil Brown
Hi, (1+) :: Num a = a - a For the bind operator, you need something of type a - Maybe b on the RHS, not simply a - a. You want one of these instead: fmap (1+) (Just 3) liftM (1+) (Just 3) Alternatively, you may find it useful to define something like: (*) = flip liftM so that you can

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Brandon S. Allbery KF8NH
On May 9, 2009, at 15:31 , michael rice wrote: Prelude Just 3 = (1+) interactive:1:0: No instance for (Num (Maybe b)) arising from a use of `it' at interactive:1:0-14 Possible fix: add an instance declaration for (Num (Maybe b)) In the first argument of `print', namely `it'

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Tillmann Rendel
michael rice wrote: Prelude Just 3 = (1+) Let's check the types. Prelude :t (=) (=) :: (Monad m) = m a - (a - m b) - m b Prelude :t Just 3 Just 3 :: (Num t) = Maybe t Prelude :t (1 +) (1 +) :: (Num a) = a - a Renaming the variables in the type of (1 +) gives: (1 +) :: (Num

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Vasyl Pasternak
Hi, Haskell expects the function with type (a - m b) in the right side of (=), but you put there function with type (a - a): try: :t (Just 3 =) (Just 3 =) :: (Num a) = (a - Maybe b) - Maybe b and: :t (1+) (1+) :: (Num a) = a - a You should put (1+) into Maybe monad, just do return.(1+), so

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Alexander Dunlap
On Sat, May 9, 2009 at 12:31 PM, michael rice nowg...@yahoo.com wrote: Why doesn't this work? Michael data Maybe a = Nothing | Just a instance Monad Maybe where     return = Just     fail   = Nothing     Nothing  = f = Nothing     (Just x) = f = f x

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Bas van Gijzel
Hey Michael, If you would look at the type of =, it would give (=) :: (Monad m) = m a - (a - m b) - m b and specifically in your case: (=) :: Maybe a - (a - Maybe b) - Maybe b You are applying Just 3 as first argument, which is correct, but then supply a partially applied function (1+) which

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Miguel Mitrofanov
Types. (=) :: Monad m = m a - (a - m b) - m b (1+) :: Num a = a - a So, the typechecker deduces that 1) a is the same as m b, and 2) a (and m b, therefore) must be of class Num Now, Just 3 :: Num t = Maybe t and the typechecker learns from that that m a must be the same as Maybe t,

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Austin Seipp
Excerpts from michael rice's message of Sat May 09 14:31:20 -0500 2009: Why doesn't this work? Michael data Maybe a = Nothing | Just a instance Monad Maybe where     return = Just     fail   = Nothing     Nothing  = f = Nothing     (Just x) = f = f

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Daniel Fischer
Am Samstag 09 Mai 2009 21:31:20 schrieb michael rice: Why doesn't this work? Michael [mich...@localhost ~]$ ghci GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help Loading package ghc-prim ... linking ... done. Loading package integer ... linking ... done. Loading package base

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Miguel Mitrofanov
On 10 May 2009, at 00:30, Brandon S. Allbery KF8NH wrote: On May 9, 2009, at 15:31 , michael rice wrote: Prelude Just 3 = (1+) That (a - m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying hard to find a way to do what you want, so it

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Brandon S. Allbery KF8NH
On May 9, 2009, at 18:03 , Miguel Mitrofanov wrote: On 10 May 2009, at 00:30, Brandon S. Allbery KF8NH wrote: On May 9, 2009, at 15:31 , michael rice wrote: Prelude Just 3 = (1+) That (a - m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Brandon S. Allbery KF8NH
On May 9, 2009, at 18:16 , Brandon S. Allbery KF8NH wrote: That's the only way I can get the error he got; if it uses Maybe as the monad then why is the Maybe on the *inside* in the error message? Clearly it bound m to something else, and ((-) r) is the only other one I can think of

Re: [Haskell-cafe] cabal parse problems

2009-05-09 Thread Vasili I. Galchin
Thanks .. very interesting on the cabal parsers. I somehow got around my problem ... forgot how though. Vasili On Sat, May 9, 2009 at 10:48 AM, Duncan Coutts duncan.cou...@worc.ox.ac.ukwrote: On Wed, 2009-05-06 at 19:37 -0500, Vasili I. Galchin wrote: are them some CLI switches I can enable

Re: [Haskell-cafe] Just 3 = (1+)?

2009-05-09 Thread Cory Knapp
... There have been 12 replies to this question, all of which say the same thing. I'm glad we're so happy to help, but does Just 3 = return . (+1) Need to be explained by 12 different people? fmap (trying to++) $ Just help -- :D Cory Why doesn't this work? Michael [mich...@localhost ~]$