Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Luke Palmer
On Dec 18, 2007 7:31 AM, Cristian Baboi [EMAIL PROTECTED] wrote: Here is some strange example: module Hugs where aa::Int aa=7 cc:: (Int-Int)-(Int-Int-Int)-Int-(Int-Int) cc a op b = \x- case x of { _ | x==aa - x+1 ; _- a x `op` b } f::Int-Int f(1)=1 f(2)=2 f(_)=3 g::Int-Int

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
What I should have been told about upfront: - the syntax for an expression - the syntax for a block Don't see your point. - the adhoc syntax rules (how to distinguish among a tuple and a pharanthesized expression and how to find the start and end of a block for example ) Oh, that's

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Ketil Malde
Cristian Baboi [EMAIL PROTECTED] writes: Here is some strange example: module Hugs where aa::Int aa=7 Small note, it's common to use spaces around the :: and = I've never really noticed before. cc :: (Int-Int) - (Int-Int-Int) - Int - (Int-Int) cc a op b = \x- case x of { _ | x==aa -

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean
Miguel Mitrofanov wrote: There's a third way, too, and I haven't seen anybody mention it yet I've noticed it, but there are some problems with this representation, so I decided not to mention it. It's OK as far as we don't want functions working on two areas - I don't see, how we can

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov [EMAIL PROTECTED] wrote: What I should have been told about upfront: - the syntax for an expression - the syntax for a block Don't see your point. The point is the syntax is introduced as transformation of layout form to non layout

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Miguel Mitrofanov
class Shape a where { intersect :: Shape b = a - b - Bool } data Shape a = { intersect :: Shape b = a - b - Bool } in fact, the syntax is rather similar, too! :) Um, well, and how are you going to implement it? ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] list utilities -- shouldn't these be in the hierarchical libs somewhere?

2007-12-18 Thread Jules Bean
Thomas Hartman wrote: I found http://haskell.cs.yale.edu/haskell-report/List.html had many useful one off type list functions such as subsequences and permutations which are nowhere to be found in hoogle, Data.List, or the haskell hierarchical libs Weird. It's not very many. Other

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean
Miguel Mitrofanov wrote: class Shape a where { intersect :: Shape b = a - b - Bool } data Shape a = { intersect :: Shape b = a - b - Bool } in fact, the syntax is rather similar, too! :) Um, well, and how are you going to implement it? Yes, exactly. My only point is There

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Cristian, On Dec 18, 2007 10:53 AM, Cristian Baboi [EMAIL PROTECTED] wrote: - the lambda expressions can be written (input) but cannot be printed (output) Yes, since two different lambda expressions can denote the same function. I just want the sistem to be able to print one of these

[Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Jon Fairbairn
Cristian Baboi [EMAIL PROTECTED] writes: What I should have been told about upfront: - the syntax for an expression Since there are only declarations and expressions, the syntax of an expression involves pretty much all of the language, so it would be difficult to tell it upfront. - the

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Jules Bean
Cristian Baboi wrote: On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov [EMAIL PROTECTED] wrote: What I should have been told about upfront: - the syntax for an expression - the syntax for a block Don't see your point. The point is the syntax is introduced as transformation of layout

[Haskell-cafe] Re: data vs newtype

2007-12-18 Thread ChrisK
Jonathan Cast wrote: So there is a program (or, rather, type) you can write with newtype that can't be written with data: newtype T = T T That compiles, and anything of type T is ⊥. But it breaks my mental model of what the compiler does for newtypes. I always think of them as differently

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
- the syntax for an expression - the syntax for a block Don't see your point. The point is the syntax is introduced as transformation of layout form to non layout form. As a user, I just want to be able to spot the basic components of a source file without thinking about

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn [EMAIL PROTECTED] wrote: Cristian Baboi [EMAIL PROTECTED] writes: - the syntax for a block Not sure what you mean by block. do a - [1..10] b - [3,4] return (a,b) is an expression... you can write that same expression as do {a -

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 12:25:18 +0200, Miguel Mitrofanov [EMAIL PROTECTED] wrote: - the syntax for an expression - the syntax for a block Don't see your point. The point is the syntax is introduced as transformation of layout form to non layout form. As a user, I just want to be able to

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Miguel Mitrofanov
- the lambda expressions can be written (input) but cannot be printed (output) This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one lambda expression from another (all it can do with one is apply it to something).

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Ketil Malde
Cristian Baboi [EMAIL PROTECTED] writes: I mean anything that you can put between { }, and between ; Okay, there you have it then: the syntax for a block is a {, followed by elements separated by ;s and terminated by a }. Perhaps you are really asking about how the layout rule works? (Which

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Cristian Baboi
Thank you very much! On Tue, 18 Dec 2007 12:17:54 +0200, Jules Bean [EMAIL PROTECTED] wrote: Cristian Baboi wrote: On Tue, 18 Dec 2007 10:29:43 +0200, Miguel Mitrofanov [EMAIL PROTECTED] wrote: - what guarantees are made by the LANGUAGE that an IO action (such as do putStrLn Hello

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Miguel Mitrofanov
As a user, I just want to be able to spot the basic components of a source file without thinking about transformation rules. Well, most users are. Are what ? Sorry if I've confused you. English isn't my native language. Are able, of course. Have you asked them all ? If you're

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 12:49:52 +0200, Miguel Mitrofanov [EMAIL PROTECTED] wrote: - the lambda expressions can be written (input) but cannot be printed (output) This is a fundamental property of the language. A lambda expression is programme and at runtime the system doesn't know one

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Jules Bean
Cristian Baboi wrote: What guarantees that by running the main, the string Hello world will be printed exactly twice ? The semantics of IO, and the guarantees of the runtime. IO specifies that () means compose two actions to make a larger action which does the first actions, then the

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Peter Lund
On Tue, 2007-12-18 at 12:53 +0200, Cristian Baboi wrote: The semantics of IO, and the guarantees of the runtime. IO specifies that () means compose two actions to make a larger action which does the first actions, then the second action. [do {a; a;} is notation for a a] The RTS

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Spencer Janssen
On Tuesday 18 December 2007 01:31:59 Cristian Baboi wrote: A few days ago, for various reasons, I've started to look at Haskell. At first I was quite impressed, after reading some FAQ, and some tutorials. Evrything was nice and easy ... until I've started writing some code on my own. What I

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Miguel Mitrofanov
Yes, and Haskell can do it also. But C, I guess, can't print out a source code for a function (well, there can be some weird dialects of C I'm not aware about). Haskell can't do it either. Well, LISP can, if I remember it right. Only in an interpreter, if I remember it right.

Re: [Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Ketil Malde
Miguel Mitrofanov [EMAIL PROTECTED] writes: Well, LISP can [print functions], if I remember it right. Only in an interpreter, if I remember it right. I think Emacs used to print #function or something for functions. It seems to keep around the reresentation now. Anyway, LISP has a bunch of

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Jules Bean
Felipe Lessa wrote: On Dec 18, 2007 7:51 AM, Jules Bean [EMAIL PROTECTED] wrote: class Shape a where { intersect :: Shape b = a - b - Bool } Shouldn't this be class Shape a where whatever class (Shape a, Shape b) = Intersectable a b where intersect :: a - b - Bool With your

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Felipe Lessa
On Dec 18, 2007 7:51 AM, Jules Bean [EMAIL PROTECTED] wrote: class Shape a where { intersect :: Shape b = a - b - Bool } Shouldn't this be class Shape a where whatever class (Shape a, Shape b) = Intersectable a b where intersect :: a - b - Bool With your definition I don't

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread C.M.Brown
If however, you *really* want to keep your shapes as being seperate types, then you'll want to invoke the class system (note, not the same as OO classes). class Shape a where area :: a - Int newtype Circle = C Int instance Shape Circle where area (C r) = pi * r^2 newtype

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Tillmann Rendel
Felipe Lessa wrote: class Shape a where whatever class (Shape a, Shape b) = Intersectable a b where intersect :: a - b - Bool This looks nice at first sight, but is it usefull in practice? I can somehow express the type any shape wich is intersectable with a given other shape,

[Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Cristian Baboi
Haskell strengts as I see them: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several platforms - it has a community - it is free Is there anything you would like to add ?

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Lutz Donnerhacke
* Tillmann Rendel wrote: My conclusion: To make Haskell a better OO language Haskell is not an OO language and never should be. (Since it's not the goal of Haskell to be any OO language at all this may not be a problem) Ack. ___ Haskell-Cafe

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Reinier Lamers
Cristian Baboi wrote: Haskell strengts as I see them: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several platforms - it has a community - it is free Is there anything you would like to

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Alex Sandro Queiroz e Silva
Hallo, Cristian Baboi escreveu: From your list, I agree to add some pattern matching abilities to mine, but that it all. Keep using Haskell and resend your list in six months. -alex ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Jules Bean
Cristian Baboi wrote: Haskell strengts as I see them: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several platforms - it has a community - it is free Is there anything you would like to

[Haskell-cafe] Multiple statements with Where

2007-12-18 Thread insertjokehere
Hi all, I am having problems adding multiple definitions with where for example in my code --A parser for recognising binary operations parseBinaryOp :: String - String - [(Expr, Expr, String)] parseBinaryOp op str | (elem op binops) (notElem '(' (snd bm)) (notElem ')' (snd bm))

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Cristian Baboi
On Tue, 18 Dec 2007 15:33:55 +0200, Reinier Lamers [EMAIL PROTECTED] wrote: Cristian Baboi wrote: Haskell strengts as I see them: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Jules Bean
insertjokehere wrote: Hi all, I am having problems adding multiple definitions with where for example in my code --A parser for recognising binary operations parseBinaryOp :: String - String - [(Expr, Expr, String)] parseBinaryOp op str | (elem op binops) (notElem '(' (snd bm))

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Matthew Brecknell
insertjokehere wrote: where bm = bracketMatch str nstr = words (snd (bracketMatch str)) It looks like you have set your editor to make tabs look like four spaces. Haskell compilers are required to interpret tabs as being equivalent to eight spaces, so it

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Tillmann Rendel
insertjokehere wrote: --A parser for recognising binary operations parseBinaryOp :: String - String - [(Expr, Expr, String)] parseBinaryOp op str | (elem op binops) (notElem '(' (snd bm)) (notElem ')' (snd bm)) (elem nstr!!1 binops) = [(EInt 1, EInt 1, HERE!)] You want (elem (nstr

[Haskell-cafe] Foldable Rose Trees

2007-12-18 Thread Dominic Steinitz
I've been trying to re-label nodes in a rose tree without re-inventing wheels (although I'm beginning to wish I had). I've got as far as this but haven't yet cracked the general case for Traversable. Any help would be much appreciated. Thanks, Dominic. *Main let (p,_) = runState (unwrapMonad

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Henning Thielemann
On Tue, 18 Dec 2007, Cristian Baboi wrote: Haskell strengts as I see them: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several platforms - it has a community - it is free Is

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann
On Tue, 18 Dec 2007, Benja Fallenstein wrote: Hi Cristian, On Dec 18, 2007 10:53 AM, Cristian Baboi [EMAIL PROTECTED] wrote: - the lambda expressions can be written (input) but cannot be printed (output) Yes, since two different lambda expressions can denote the same function. I

[Haskell-cafe] Re: New to Haskell

2007-12-18 Thread Jon Fairbairn
Cristian Baboi [EMAIL PROTECTED] writes: On Tue, 18 Dec 2007 11:56:36 +0200, Jon Fairbairn [EMAIL PROTECTED] wrote: Cristian Baboi [EMAIL PROTECTED] writes: - the syntax for a block Not sure what you mean by block. do a - [1..10] b - [3,4] return (a,b) is an expression... you

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread jerzy . karczmarczuk
Concerning the subject: The End of WHAT? Cristian Baboi writes: Reinier Lamers wrote: Cristian Baboi wrote: Haskell strengts as I see them: ... - it has a compiler ... Is there anything you would like to add ? Higher-order functions, purity, pattern-matching, no-nonsense syntax,

[Haskell-cafe] Re: Foldable Rose Trees

2007-12-18 Thread apfelmus
Dominic Steinitz wrote: I've been trying to re-label nodes in a rose tree without re-inventing wheels (although I'm beginning to wish I had). I've got as far as this but haven't yet cracked the general case for Traversable. Solution 1) Data.Tree is already an instance of Traversable. :)

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Henning, On Dec 18, 2007 3:53 PM, Henning Thielemann [EMAIL PROTECTED] wrote: Since this was discussed already here, I summed it up in: http://www.haskell.org/haskellwiki/Show_instance_for_functions I find the discussion under theoretical answer unsatisfying. The property that a Show

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
On Dec 18, 2007 4:50 PM, Benja Fallenstein [EMAIL PROTECTED] wrote: Further, even with extensionality, we can (with compiler support) in principle have Show instances other than enumerating the graph. Now that I said it, I'm starting to doubt we even need compiler support beyond what we have

Re: [Haskell-cafe] list utilities -- shouldn't these be in the hierarchical libs somewhere?

2007-12-18 Thread Twan van Laarhoven
Jules Bean wrote: Thomas Hartman wrote: I found http://haskell.cs.yale.edu/haskell-report/List.html had many useful one off type list functions such as subsequences and permutations which are nowhere to be found in hoogle, Data.List, or the haskell hierarchical libs Weird. It's

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann
On Tue, 18 Dec 2007, Benja Fallenstein wrote: Hi Henning, On Dec 18, 2007 3:53 PM, Henning Thielemann [EMAIL PROTECTED] wrote: Since this was discussed already here, I summed it up in: http://www.haskell.org/haskellwiki/Show_instance_for_functions I find the discussion under

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak
If the semantics of a language says that a function f is equivalent to a function g, but there is a function h such that h(f) is not equivalent to h(g), then h cannot be a function. Therefore that language cannot be a (purely) functional language. That is the pure and simple reason why

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Henning, On Dec 18, 2007 5:17 PM, Henning Thielemann [EMAIL PROTECTED] wrote: The mathematical definition of function I know of, says that functions are special relations, and relations are sets of pairs. Their is nothing about intension. That's the standard definition in set theory, but

[Haskell-cafe] MonadFix

2007-12-18 Thread Joost Behrends
Hi, since about three weeks i am learning Haskell now. One of my first excercises is to decompose an Integer into its primefactors. I already posted discussion on the solution to the problem 35 in 99 excercises. My simple algorithm uses a datatype DivIter of 4 named fields together with the core

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Paul, On Dec 18, 2007 5:18 PM, Paul Hudak [EMAIL PROTECTED] wrote: If the semantics of a language says that a function f is equivalent to a function g, but there is a function h such that h(f) is not equivalent to h(g), then h cannot be a function. Sure. Therefore that language cannot

[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread Joost Behrends
Henning Thielemann lemming at henning-thielemann.de writes: - it is lazy with class - it is strongly typed - it has automatic memory management - it has a standard library - it has a compiler - it is available on several platforms - it has a community - it is free There MUST be

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak
Benja Fallenstein wrote: Not so fast :-) Caveat one, there may be useful ways to for functions to implement Show that don't conflict with extensionality (i.e., the property that two functions are equal if they yield the same results for all inputs). Sure, and I suppose one way to do this

[Haskell-cafe] Re: New to Haskell: The End

2007-12-18 Thread apfelmus
Joost Behrends wrote: it has MONADS Interestingly, this is not even a language feature, it just happens that the concept of monads can be expressed in Haskell. (Ok, ignoring syntactic sugar in form of do-notation for the moment. And ignoring that constructor classes have been introduced

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
On Dec 18, 2007 6:01 PM, Paul Hudak [EMAIL PROTECTED] wrote: Well, my caveat was that the Haskell designers wanted it this way. So you are essentially rejecting my caveat, rather than creating a new one. :-) I mean, I reject the answer They wanted it this way because I think the answer should

[Haskell-cafe] Re: Foldable Rose Trees

2007-12-18 Thread Dominic Steinitz
Solution 1) Data.Tree is already an instance of Traversable. :) Yes it's all there but I would have missed the fun of trying to do it myself ;-) Plus the data structure I actually want to re-label isn't quite a rose tree. Solution 2) The key observation is that you the instances for rose

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Sterling Clover
Don't think the Haskell's Overlooked Object System paper has been posted to this thread yet: http://homepages.cwi.nl/~ralf/OOHaskell/paper.pdf --s On 12/18/07, Lutz Donnerhacke [EMAIL PROTECTED] wrote: * Tillmann Rendel wrote: My conclusion: To make Haskell a better OO language Haskell

[Haskell-cafe] A Show instance for simple functions

2007-12-18 Thread Benja Fallenstein
Hi all, Below is a program that implements Show for functions whose type is composed of only (-) and type variables (or, more precisely, of (-) and (State Int Term), but any type composed of (-) and type variables can obviously be specialized to that). (-fglasgow-exts is needed only for the

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

2007-12-18 Thread Andre Nathan
Hello On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote: Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :) I'm trying to finish the process tree construction but I guess I'll need some help again. My idea is to have a function that would

[Haskell-cafe] [ANN] Wadler talk in San Francisco on Jan 9, 2008

2007-12-18 Thread Keith Fahlgren
Hi all, Philip Wadler will be in San Francisco for POPL '08 so the Bay Area Functional Programmers have asked him to reprise his ICFP '07 talk Well-typed programs can’t be blamed. He's been good enough to set us up with a proper room in the ACM conference hotel. The meeting will take place in the

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Henning Thielemann
On Tue, 18 Dec 2007, Benja Fallenstein wrote: Hi Henning, On Dec 18, 2007 5:17 PM, Henning Thielemann [EMAIL PROTECTED] wrote: The mathematical definition of function I know of, says that functions are special relations, and relations are sets of pairs. Their is nothing about

Re: [Haskell-cafe] MonadFix

2007-12-18 Thread Daniel Fischer
Am Dienstag, 18. Dezember 2007 17:26 schrieb Joost Behrends: Hi, since about three weeks i am learning Haskell now. One of my first excercises is to decompose an Integer into its primefactors. I already posted discussion on the solution to the problem 35 in 99 excercises. My simple

Re: [Haskell-cafe] MonadFix

2007-12-18 Thread Marc A. Ziegert
Am Dienstag, 18. Dezember 2007 schrieb Joost Behrends: snip fix f is the least fixed point of the function f, i.e. the least defined x such that f x = x. What does least mean here ? There is nothing said about x being a variable of an instance of Ord. And why fix has not the type a - (a

[Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Cristian Baboi
This is what I understand so far ... Suppose we have these two values: a) \x-x + x b) \x-2 * x Because these to values are equal, all functions definable in Haskell must preserve this. This is why I am not allowed to define a function like h :: (a-b) - (a-b) h x = x The reasons are very

Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Philip Weaver
On Dec 18, 2007 1:00 PM, Cristian Baboi [EMAIL PROTECTED] wrote: This is what I understand so far ... Suppose we have these two values: a) \x-x + x b) \x-2 * x Because these to values are equal, all functions definable in Haskell must preserve this. This is why I am not allowed to define

Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
Extensionality says that the only observable properties of functions are the outputs they give for particular inputs. Accepting extensionality as a Good Thing implies that enabling the user to define a function that can differentiate between f x = x + x and g x = 2 * x is a Bad Thing. Note that

Re: [Haskell-cafe] Haskell purity and printing

2007-12-18 Thread Nicolas Frisby
This is a fine warning you both point out, but I would suggest that it distracts from the OP's question. The previous, germane discussion holds if we assume that i) both f and g have type Integer - Integer, ii) the compiler writer is not out to get us, and iii) the GMP library, if used by that

[Haskell-cafe] Re: MonadFix

2007-12-18 Thread Joost Behrends
Daniel Fischer daniel.is.fischer at web.de writes: Am Dienstag, 18. Dezember 2007 17:26 schrieb Joost Behrends: Hi, since about three weeks i am learning Haskell now. One of my first excercises is to decompose an Integer into its primefactors. I already posted discussion on the

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

2007-12-18 Thread Andre Nathan
On Tue, 2007-12-18 at 16:47 -0200, Andre Nathan wrote: I'm trying to finish the process tree construction but I guess I'll need some help again. I guess I could do away with StateT and just pass the PsMap around as a parameter, but I guess that wouldn't be the haskell way... I think my code is

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

2007-12-18 Thread Daniel Fischer
Am Dienstag, 18. Dezember 2007 19:47 schrieb Andre Nathan: Hello On Mon, 2007-12-17 at 21:22 -0200, Andre Nathan wrote: Thanks everyone for the great suggestions. The code is much cleaner now (not to mention it works :) I'm trying to finish the process tree construction but I guess I'll

[Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread Brad Larsen
Hi there list, How would one go about creating a new type for a subset of the integers, for (contrived) example just the even integers? I was thinking of making a new type newtype EvenInt = EvenInt Integer but the problem with this is that it accepts any integer, even odd ones. So to

Re: [Haskell-cafe] New to Haskell: The End

2007-12-18 Thread Jonathan Cast
On 18 Dec 2007, at 7:28 AM, [EMAIL PROTECTED] wrote: Concerning the subject: The End of WHAT? Cristian Baboi writes: Reinier Lamers wrote: Cristian Baboi wrote: Haskell strengts as I see them: ... - it has a compiler ... Is there anything you would like to add ? Higher-order functions,

Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread gwern0
On 2007.12.18 21:07:25 -0500, Brad Larsen [EMAIL PROTECTED] scribbled 0.6K characters: Hi there list, How would one go about creating a new type for a subset of the integers, for (contrived) example just the even integers? I was thinking of making a new type newtype EvenInt = EvenInt

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Paul Hudak
Benja Fallenstein wrote: I mean, I reject the answer "They wanted it this way" because I think the answer should be, "They wanted it this way because They looked at substituting equals under a lambda, and They saw it was good" ;-) Your version of the answer is in fact correct, but is

Re: [Haskell-cafe] Creating a type for a subset of the integers

2007-12-18 Thread Jules Bean
Brad Larsen wrote: Hi there list, How would one go about creating a new type for a subset of the integers, for (contrived) example just the even integers? I was thinking of making a new type newtype EvenInt = EvenInt Integer but the problem with this is that it accepts any integer, even

Re: [Haskell-cafe] New to Haskell

2007-12-18 Thread Benja Fallenstein
Hi Paul, On Dec 19, 2007 6:54 AM, Paul Hudak [EMAIL PROTECTED] wrote: Your version of the answer is in fact correct, but is just an elaboration of the original one. So, I don't see what your point is... Ok, sorry, I'll try again... I'm trying to say that in my opinion, it's important to