Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Ryan Ingram
So, the Haskell98 solution to this is: class StringableList a where listToString :: [a] - String -- now [a] is of the proper form; T = [], a is a type variable instance StringableList a = Stringable [a] where toString = listToString -- now to make an instance for Stringable [Char] --

Re: [Haskell-cafe] List as input

2008-10-15 Thread Janis Voigtlaender
leledumbo wrote: module Main where import Data.List -- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = [] qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater

Re: [Haskell-cafe] ANNOUNCE: Salsa: A .NET Bridge for Haskell

2008-10-15 Thread Manuel M T Chakravarty
Great! Thanks for putting the code out! Manuel ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] List as input

2008-10-15 Thread leledumbo
module Main where import Data.List -- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = [] qsortOpt x = qsortOpt less ++ [pivot] ++ qsortOpt greater where pivot = x

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread apfelmus
Janis Voigtlaender wrote: Derek Elkins wrote: Agreed. I'm extremely tired of the I haven't heard this term therefore it must be 'scary' and complicated and beyond me attitude. Such people need to stop acting like five year old children. Not that it has much to do with the debate, but the

Re: [Haskell-cafe] Re: 2008-10-12 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread wren ng thornton
Simon Marlow wrote: Don Stewart wrote: * GHC.Prim was moved, Nobody should be importing GHC.Prim, use GHC.Exts instead. This is oft declared, but as things stand I don't think it's a tenable position. If someone's bothering to dig as far as GHC.Exts then it's very likely they're

Re[2]: [Haskell-cafe] Flexible instances

2008-10-15 Thread Bulat Ziganshin
Hello Albert, Wednesday, October 15, 2008, 7:51:06 AM, you wrote: Illegal instance declaration for `Stringable [Char]' (All instance types must be of the form (T a1 ... an) where a1 ... an are distinct type *variables* Just in case: n=0 for instance Eq Blah, i.e., T a1 ...

[Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread oleg
Lennart Augustsson wrote: I was just pointing out that the mechanism for doing the OO thing exists in Haskell too, albeit looking a little different. Indeed there is a mechanism for doing OO in Haskell -- several of them. Most of them have nothing to do with Existentials. In the OHaskell

[Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Mauricio
Hi, I'm wrapping a library where functions take as parameters pointers to a few standard structs (as, well, all C libraries). I would like to ensure that only pointers of correct structs are passed to those functions. What is the Haskell way to do that? My idea is to do something like this:

Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Bulat Ziganshin
Hello Vivek, Wednesday, October 15, 2008, 3:39:54 PM, you wrote: i think that practical answer is suggestion to use `case` instead: case () of _ | x 5 - do abc def ... | x==5 - do ... | otherwise - do ... it's pretty common

Re: [Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Bulat Ziganshin
Hello Mauricio, Wednesday, October 15, 2008, 5:40:16 PM, you wrote: newtype SomeStruct = SomeStruct () data SomeStruct = SomeStruct looks even simpler. you don't need to shell around () since you anyway will not use its value :) -- Best regards, Bulat

[Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Creighton Hogg
So in my quest to create bindings to BlueZ in Haskell, I've hit a bit of a snag: sockets programming. In C, you can use the standard sockets library and just pass around addresses as arrays of 6 bytes instead of arrays of 4 bytes like you normally would. The problem I'm having is that in

[Haskell-cafe] ICFP09: Call for Workshop Proposals

2008-10-15 Thread Matthew Fluet (ICFP Publicity Chair)
CALL FOR WORKSHOP PROPOSALS ICFP 2009 14th ACM SIGPLAN International Conference on Functional Programming 31st August - 2nd September, 2009 Edinburgh, Scotland

Re: [Haskell-cafe] Type safety in foreign pointer

2008-10-15 Thread Stuart Cook
On Thu, Oct 16, 2008 at 12:53 AM, Bulat Ziganshin [EMAIL PROTECTED] wrote: data SomeStruct = SomeStruct You can even go one step further and do data SomeStruct which will prevent you from accidentally trying to the dummy constructor. However, you'll need {-# LANGUAGE EmptyDataDecls #-}

[Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Simon Michael
Does that help? It helps me a lot. I never clearly understood that there are these two different layout modes in my code (coddled by haskell-mode!) This will cut down some more guesswork. Thanks! ___ Haskell-Cafe mailing list

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread John Lato
I'd like to thank everyone who replied to my OP, and also perhaps clarify one point. I wasn't trying to be argumentative or negative about any work people have done to make Haskell approachable for OO programmers (or any other programmers, for that matter). I simply wanted to know what others

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread David Leimbach
On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED] wrote: I'd like to thank everyone who replied to my OP, and also perhaps clarify one point. I wasn't trying to be argumentative or negative about any work people have done to make Haskell approachable for OO programmers (or any

Re: [Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Jules Bean
Simon Michael wrote: Does that help? It helps me a lot. I never clearly understood that there are these two different layout modes in my code (coddled by haskell-mode!) This will cut down some more guesswork. Thanks! There is a new indentation module which does much better at the

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Lennart Augustsson
The (=) operation for the state monad can be implemented with no understanding at all. Just watch djinn make the code for it. And djinn doesn't understand the state monad, I promise. :) -- Lennart 2008/10/15 David Leimbach [EMAIL PROTECTED]: On Wed, Oct 15, 2008 at 8:08 AM, John Lato

Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Bulat Ziganshin
Hello David, Wednesday, October 15, 2008, 7:16:09 PM, you wrote: I've read a lot of the Monad tutorials, and I feel like I only get most of it to be 100% honest.  The State Monad still boggles my mind a little bit.  I understand what it's supposed to do and I get the idea about how it works.

RE: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Mitchell, Neil
Hi I didn't understand Monads until I read this: http://www.haskell.org/haskellwiki/Monads_as_Containers It took me quite a long time to get them too, but slowly over time it will sink in. Thanks Neil From: [EMAIL PROTECTED] [mailto:[EMAIL

Re: [Haskell-cafe] Re: Linking and unsafePerformIO

2008-10-15 Thread wren ng thornton
Mauricio wrote: What I actually want to use that way are build time configs. For instance, 'isThisLibraryThreadSafe' or 'maximumNumberOfBigObjects'. Actually, I don't know why people allow build time options at all. We always use the best set of options, and the alternatives are there just to

Re: [Haskell-cafe] I do not want to be a bitch, but ghc-6.8.3 and haskell binary policy are really horrible.

2008-10-15 Thread Jules Bean
John Van Enk wrote: Could you, perhaps, outline a little more of what you're trying to do? I'm having a hard time seeing what exactly you're doing, and why you can't use the package provided by your distribution. We'd love to help you, but you're not being very clear with what your problem

Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Daniel Fischer
Am Mittwoch, 15. Oktober 2008 13:39 schrieb Ramaswamy, Vivek: Hello All~ I have just started with Haskell, and I must confess; I am in love with it. However one area that I am really confused about is indentation. Lets take a look at if-else if- else block. The way I understand it:

Re: [Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Jules Bean
Ramaswamy, Vivek wrote: Hello All~ I have just started with Haskell, and I must confess; I am in love with it. However one area that I am really confused about is indentation. Lets take a look at if-else if- else block. Important point 1. There are two contexts in haskell programs. Layout

Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread David Menendez
On Wed, Oct 15, 2008 at 6:05 AM, [EMAIL PROTECTED] wrote: Regarding existentials, the web page http://okmij.org/ftp/Computation/Existentials.html demonstrates how to systematically eliminate existentials. In fact, the object encoding via existentials can be easily transformed into

Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread George Pollard
Thanks to all that replied (Derek Ryan for the major understanding, Albert Luke also)*. I guess I was getting confused with the error message: (All instance types must be of the form (T a1 ... an) I was interpreting this with Stringable/Enum as T and [Char]/Blah as a1. Now I have clarity! I

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread John Lato
Albet Lai wrote: John Lato wrote: Are you advocating introducing existential types to beginning Haskellers? I think something with the scary name existential quantification would greatly increase the head'splodin' on the learnin' slope. OOP(*) advocates introducing existential types to

[Haskell-cafe] Re: 2008-10-12 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Simon Marlow
wren ng thornton wrote: Simon Marlow wrote: Don Stewart wrote: * GHC.Prim was moved, Nobody should be importing GHC.Prim, use GHC.Exts instead. This is oft declared, but as things stand I don't think it's a tenable position. If someone's bothering to dig as far as GHC.Exts then it's

Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread Lennart Augustsson
What do you mean by need? From a theoretical or practical perspective? We don't need them from a theoretical perspective, but in practice I'd rather use existentials than encodinging them in some tricky way. On Wed, Oct 15, 2008 at 11:05 AM, [EMAIL PROTECTED] wrote: The web page begs a

Re: [Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Creighton Hogg
On Wed, Oct 15, 2008 at 12:26 PM, Bryan O'Sullivan [EMAIL PROTECTED] wrote: On Wed, Oct 15, 2008 at 6:54 AM, Creighton Hogg [EMAIL PROTECTED] wrote: Is there a way around this that I just haven't seen, or should I write a patch to Network to add an extra constructor to SockAddr and code to

[Haskell-cafe] Haskell newbie indentation query.

2008-10-15 Thread Ramaswamy, Vivek
Hello All~ I have just started with Haskell, and I must confess; I am in love with it. However one area that I am really confused about is indentation. Lets take a look at if-else if- else block. The way I understand it: {--} if something then do something 1 something2 else if nothing

[Haskell-cafe] Re: Multi-line string literals are both easy /and/elegant in Haskell

2008-10-15 Thread Simon Marlow
Don Stewart wrote: mjm2002: On 10/13/08, Andrew Coppin wrote: Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-} Yes and no. There's dons' compiled-constants pkg which has a solution:

Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread wren ng thornton
John Lato wrote: Are you advocating introducing existential types to beginning Haskellers? I think something with the scary name existential quantification would greatly increase the head'splodin' on the learnin' slope. Certainly there's a place for them, but I wouldn't want to see new Haskell

Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Anton Tayanovskyy
Thanks for the portable solution. I'd also like to know how is the following different from -XFlexibleInstances with [Char]? Stronger, weaker, same thing? {-# OPTIONS -XTypeSynonymInstances #-} class Stringable a where toString :: a - String instance Stringable String where

Re: [Haskell-cafe] Network trouble: what to do?

2008-10-15 Thread Bryan O'Sullivan
On Wed, Oct 15, 2008 at 6:54 AM, Creighton Hogg [EMAIL PROTECTED] wrote: Is there a way around this that I just haven't seen, or should I write a patch to Network to add an extra constructor to SockAddr and code to handle it? Linux and Windows support Bluetooth sockets, but they have

Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Yitzchak Gale
Derek Elkins wrote: In general, to encode OO... turns out all you needed was recursive bounded existential quantification. Do you have a reference for that? Thanks, Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
The instance selection for an interface is done at run-time and this is inherently necessary. The instance (in a different sense) selection for type classes is almost always resolvable statically. In Haskell 98 In both cases, the dispatch is inherently dynamic, and in both cases, most

[Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
leaders and pioneers: if you know one language, picking up others should be easy, they just differ in syntax. I have heard it, and I used to believe it. Now I think it's only true provided the one language you know is suitably advanced (and currently non-existent, I think). It all depends

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash
The equivalent won't compile in Haskell, because the actual return type does matter, and *is determined by the calling code*. Our fictional GetListOfData can't return a List or a Mylist depending on some conditional, in fact it can't explicitly return either one at all, because the actual

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 11:56 -0700, Daryoush Mehrtash wrote: The equivalent won't compile in Haskell, because the actual return type does matter, and *is determined by the calling code*. Our fictional GetListOfData can't return a List or a Mylist

[Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin
I like Parsec. I use it for everything. But it does have one irritating problem. Consider the following parser: expressions = many1 expression Suppose this is the top-level parser for my language. Now suppose the user supplies an expression with a syntax error half way through it. What I

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote: Suppose this is the top-level parser for my language. snip Does anybody know how to fix this irratiting quirk? I can see why it happens, but not how to fix it. One of: expressions = many1 (try expression | myFail) where myFail = {- eat your way

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 20:22 +0100, Andrew Coppin wrote: I like Parsec. I use it for everything. But it does have one irritating problem. Consider the following parser: expressions = many1 expression Suppose this is the top-level parser for my language. I always wrap my top-level

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote: Suppose this is the top-level parser for my language. Now suppose the user supplies an expression with a syntax error half way through it. What I *want* to happen is for an error to be raised. What *actually* happens is that Parsec just ignores all

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread brian
On Wed, Oct 15, 2008 at 2:22 PM, Andrew Coppin [EMAIL PROTECTED] wrote: So if + is not a valid token, but the user writes x = 1; y = 2; z = 3 + z; w = 4; then what my program receives back is x = 1; y = 2; z = 3 You said you expect one or more 'expression'. It looks as if your expression can

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin
Philippa Cowderoy wrote: expressions = do es - many1 expression eof return es Ah - so eof fails if it isn't the end of the input? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Philippa Cowderoy
On Wed, 15 Oct 2008, Andrew Coppin wrote: Philippa Cowderoy wrote: expressions = do es - many1 expression eof return es Ah - so eof fails if it isn't the end of the input? eof = notFollowedBy anyChar (assuming I've got the identifiers right,

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Andrew Coppin
Philippa Cowderoy wrote: On Wed, 15 Oct 2008, Andrew Coppin wrote: Philippa Cowderoy wrote: expressions = do es - many1 expression eof return es Ah - so eof fails if it isn't the end of the input? eof = notFollowedBy anyChar

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash
Would you please explain this a bit more: the various unfortunate consequences of type erasure in Java are avoided by the fact that Haskell types lack constructors, so the user never expects to be able to conjure up a value of an unknown type. Thanks, daryoush On Wed, Oct 15, 2008 at 12:04

Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Bulat Ziganshin
Hello Daryoush, Wednesday, October 15, 2008, 10:56:39 PM, you wrote: If you notice  java generics has all sort of gotchas (e.g. http://www.ibm.com/developerworks/java/library/j-jtp01255.html).  I large prob;em of OOP languages with generics is interaction between those two types of

[Haskell-cafe] Cairo and dialog oddities on Windows using glade.

2008-10-15 Thread Jefferson Heard
Maybe I'm doing something wrong. I've created several dialog boxes in Glade, and I'm calling Gtk.runDialog on them when a user clicks the mouse in my main window. On Linux, they work mostly right, but the insertion point never shows in the Gtk.Entry areas and the dialog itself comes up without

Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Daryoush Mehrtash
I am having hard time understanding this statement: Haskell types lack constructors, so the user never expects to be able to conjure up a value of an unknown type. I am not sure how say in a Java language a constructor can conjure up a value of an unknown type. daryoush On Wed, Oct 15, 2008

[Haskell-cafe] Re: Haskell newbie indentation query.

2008-10-15 Thread Simon Michael
I'm trying that one now. Thanks for the tip! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Cabal package with library and tests

2008-10-15 Thread Mauricio
Hi, I'm writing a Cabal package, using main=defaultMain in Setup.hs. It has a library, and I want to also build a few executables so I can test the library. How am I supposed to do that? My attempt was to create 'executable' sections for those tests. However, I don't know how to include the main

Re: [Haskell-cafe] Very silly

2008-10-15 Thread Tommy M. McGuire
Jason Dagit wrote: On Mon, Oct 13, 2008 at 8:32 PM, Tommy M. McGuire [EMAIL PROTECTED] mailto:[EMAIL PROTECTED] wrote: Java (and presumably C#) generics are very much like a weakened version of normal parametric polymorphism. I'm curious, in what way are they weakened? That's a good

Re: [Haskell-cafe] Cabal package with library and tests

2008-10-15 Thread Sean Leather
I'm writing a Cabal package, using main=defaultMain in Setup.hs. It has a library, and I want to also build a few executables so I can test the library. How am I supposed to do that? My attempt was to create 'executable' sections for those tests. However, I don't know how to include the main

Re: [Haskell-cafe] Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-15 Thread Henning Thielemann
Ryan Ingram schrieb: On Mon, Oct 13, 2008 at 2:04 AM, J. Garrett Morris [EMAIL PROTECTED] wrote: Indeed - MTL seems to have been rewritten at some point in the past to prefer exhaustive enumeration to overlap. Indeed, and I actually think this is a weakness of the current implementation.

Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Karl Mazurak
Yitzchak Gale wrote: Derek Elkins wrote: In general, to encode OO... turns out all you needed was recursive bounded existential quantification. Do you have a reference for that? I'm not sure if this is precisely what Derek had in mind, but Bruce, Cardelli, and Pierce did a comparison of

Re: [Haskell-cafe] What I wish someone had told me...

2008-10-15 Thread Dan Weston
I suspect that more has been done since 1997. Isn't that pre-Oleg? Karl Mazurak wrote: Yitzchak Gale wrote: Derek Elkins wrote: In general, to encode OO... turns out all you needed was recursive bounded existential quantification. Do you have a reference for that? I'm not sure if this is

Re: [Haskell-cafe] Flexible instances

2008-10-15 Thread Henning Thielemann
George Pollard schrieb: I'm a little confused. Why is this allowed: data Blah = Blah instance Eq Blah where x == y = True But not this: class Stringable a where toString :: a - String instance Stringable [Char] where toString = id (Resulting in:)

Re: [Haskell-cafe] An irritating Parsec problem

2008-10-15 Thread Evan Laforge
Here's what I have in one file: -- | Parse the text of an event with the given parser @[EMAIL PROTECTED] parse :: (Monad m) = P.CharParser () a - String - Derive.DeriveT m a parse p text = do (val, rest) - case P.parse (p_rest p) text of Left err - Derive.throw $ parse

[Haskell-cafe] Re: Repair to floating point enumerations?

2008-10-15 Thread Henning Thielemann
David Roundy schrieb: Why not look for a heuristic that gets the common cases right, rather than going with an elegant wrong solution? After all, these enumerations are most often used by people who neither care nor know how they're implemented, but who most likely would prefer if haskell

Re: [Haskell-cafe] 2008-10-13 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Henning Thielemann
Don Stewart schrieb: numeric-prelude-0.0.4 Easy: Lanuage pragma My question was still not answered: I used the non-existing pragma LANGUAGE_HOW_CAN_WE_ENABLE - I hoped it would be ignored, but it was parsed and made GHC fail. Why? Bug or feature?

Re: [Haskell-cafe] List as input

2008-10-15 Thread Toby Hutton
On Wed, Oct 15, 2008 at 5:44 PM, leledumbo [EMAIL PROTECTED] wrote: module Main where import Data.List -- quicksort of any list qsort [] = [] qsort (x:xs) = qsort(filter(x) xs) ++ [x] ++ qsort(filter(=x) xs) -- optimized quicksort, uses middle element as pivot qsortOpt [] = []

Re: [Haskell-cafe] List as input

2008-10-15 Thread Dan Weston
Google median order statistic. E.g. this is an interesting (and colorful) discussion: http://ocw.mit.edu/NR/rdonlyres/Electrical-Engineering-and-Computer-Science/6-046JFall-2005/60D030CD-081D-4192-9FB5-C220116E280D/0/lec6.pdf Toby Hutton wrote: On Wed, Oct 15, 2008 at 5:44 PM, leledumbo

Re: [Haskell-cafe] Re: Repair to floating point enumerations?

2008-10-15 Thread David Roundy
On Wed, Oct 15, 2008 at 11:25:57PM +0200, Henning Thielemann wrote: David Roundy schrieb: Why not look for a heuristic that gets the common cases right, rather than going with an elegant wrong solution? After all, these enumerations are most often used by people who neither care nor know

Re: [Haskell-cafe] 2008-10-13 Hackage status with GHC 6.10 release candidate

2008-10-15 Thread Don Stewart
schlepptop: Don Stewart schrieb: numeric-prelude-0.0.4 Easy: Lanuage pragma My question was still not answered: I used the non-existing pragma LANGUAGE_HOW_CAN_WE_ENABLE - I hoped it would be ignored, but it was parsed and made GHC fail. Why? Bug or feature? Feature.

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread wren ng thornton
Daryoush Mehrtash wrote: I have had an unresolved issue on my stack of Haskell vs Java that I wonder if your observation explains. If you notice java generics has all sort of gotchas (e.g. http://www.ibm.com/developerworks/java/library/j-jtp01255.html). I somehow don't see this discussion in

[Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Kalashnikov
I'm supposed to write a function isPrime that checks whether or not a given integer is a prime number or not. The function has to use recursion. The only advice I was given, was to use a helper function. I still have no clue how to do it :confused: I'm new to Haskell by the way..please help..

Re: [Haskell-cafe] List as input

2008-10-15 Thread Toby Hutton
On Thu, Oct 16, 2008 at 9:01 AM, Dan Weston [EMAIL PROTECTED] wrote: Google median order statistic. E.g. this is an interesting (and colorful) discussion:

Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Bulat Ziganshin
Hello Kalashnikov, Thursday, October 16, 2008, 2:41:05 AM, you wrote: I'm supposed to write a function isPrime that checks whether or not a given integer is a prime number or not. The function has to use recursion. The only advice I was given, was to use a helper function. seems that russian

Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread wren ng thornton
Henning Thielemann wrote: I long thought that it is unnecessary use of type system extensions to require multi-parameter type classes for simple monads and its transformer versions. I thought it would be enough to have atomar monads like ST, IO and Identity, and monads like State, Reader,

Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Jonathan Cast
On Wed, 2008-10-15 at 13:01 -0700, Daryoush Mehrtash wrote: I am having hard time understanding this statement: Haskell types lack constructors, so the user never expects to be able to conjure up a value of an unknown type. I am not sure how say in a Java language

Re: [Haskell-cafe] Monadic Floating Point [was: Linking and unsafePerformIO]

2008-10-15 Thread Ariel J. Birnbaum
On Wednesday 15 October 2008 05:21:04 John Dorsey wrote: Should all floating point numerals be in the IO Monad? I'm deviating from the thread's topic, but I tend to agree with this one. Maybe not IO directly, but some kind of STM-style monad, at least (that is, FP operations are composable but

[Haskell-cafe] Rewrite rules

2008-10-15 Thread George Pollard
Section 8.13.2 of the GHC manual[1] states: GHC keeps trying to apply the rules as it optimises the program. For example, consider: let s = map f t = map g in s (t xs) The expression s (t xs) does not match the rule map/map, but GHC will substitute for s and t, giving an

[Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Simon Michael
I'm pleased to announce the first release of hledger, a command-line accounting tool similar to John Wiegley's c++ ledger. hledger generates simple ledger-compatible transaction account balance reports from a plain text ledger file. It's simple to use, at least for techies. This has been my

[Haskell-cafe] (OT) Humorous definition for fixed points?

2008-10-15 Thread Corey O'Connor
I was just reminded of one of the joke definitions of recursion: recursion: see recursion. Perhaps there is a similar one for fixed points? To learn about fixed points find the fixed point of the process: Given somebody learn about fixed points from them. Course, my understanding of fixed points

Re: [Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Don Stewart
simon: I'm pleased to announce the first release of hledger, a command-line accounting tool similar to John Wiegley's c++ ledger. hledger generates simple ledger-compatible transaction account balance reports from a plain text ledger file. It's simple to use, at least for techies.

Re: [Haskell-cafe] ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Jason Dagit
On Wed, Oct 15, 2008 at 5:01 PM, Simon Michael [EMAIL PROTECTED] wrote: I'm pleased to announce the first release of hledger, a command-line accounting tool similar to John Wiegley's c++ ledger. hledger generates simple ledger-compatible transaction account balance reports from a plain text

Re: [Haskell-cafe] Improving MTL instances

2008-10-15 Thread Antoine Latter
On Wed, Oct 15, 2008 at 5:55 PM, wren ng thornton [EMAIL PROTECTED] wrote: Doing it that way removes the polymorphism that MonadState, MonadReader, etc offer to clients. For example, the backwards-state monad[1] is a MonadState but not a StateT (without extra plumbing). There are other

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Derek Elkins
On Wed, 2008-10-15 at 14:45 -0400, Stefan Monnier wrote: The instance selection for an interface is done at run-time and this is inherently necessary. The instance (in a different sense) selection for type classes is almost always resolvable statically. In Haskell 98 In both cases, the

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Derek Elkins
On Wed, 2008-10-15 at 08:16 -0700, David Leimbach wrote: On Wed, Oct 15, 2008 at 8:08 AM, John Lato [EMAIL PROTECTED] wrote: I'd like to thank everyone who replied to my OP, and also perhaps clarify one point. I wasn't trying to be argumentative or negative

Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Richard O'Keefe
On 16 Oct 2008, at 9:01 am, Daryoush Mehrtash wrote: I am not sure how say in a Java language a constructor can conjure up a value of an unknown type. ... Class anUnknownClass; Object anInstance; anInstance = anUnknownClass.getConstructor().newInstance(); If you know that the

Re: Re[2]: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Richard O'Keefe
On 16 Oct 2008, at 12:09 pm, Jonathan Cast wrote: I am not sure how say in a Java language a constructor can conjure up a value of an unknown type. Well, that's the point. It can't, in Haskell or in Java. If you understand that --- that you can't call the default constructor of a class

[Haskell-cafe] Re: ANN: hledger 0.1, command-line accounting tool

2008-10-15 Thread Simon Michael
Thanks Jason! Glad you liked it. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: What I wish someone had told me...

2008-10-15 Thread Stefan Monnier
Would you please explain this a bit more: the various unfortunate consequences of type erasure in Java are avoided by the fact that Haskell types lack constructors, so the user never expects to be able to conjure up a value of an unknown type. Even if Haskell had Java-style constructors, it

Re: [Haskell-cafe] List as input

2008-10-15 Thread leledumbo
The compiler doesn't know what kind of list you are trying to read, sort, and print. So, the type must be specific? Then why it's possible to call the sorting function with any list? I'm curious as to why taking the pivot from the middle is an 'optimized' version. Consider if it's used in a

Re: [Haskell-cafe] Writing a function isPrime using recursion.

2008-10-15 Thread Nathan Bloomfield
At the risk of doing someone's homework... A naive solution is to do trial division by all integers from 2 up to sqrt n. {- isPrime :: Integer - BoolisPrime n | n 2 = False | otherwise = f 2 n where f k n = if k isqrt then True else undefined -- exercise for the reader -}

Re: [Haskell-cafe] Monadic Floating Point [was: Linking and unsafePerformIO]

2008-10-15 Thread Duncan Coutts
On Thu, 2008-10-16 at 01:24 +0200, Ariel J. Birnbaum wrote: On Wednesday 15 October 2008 05:21:04 John Dorsey wrote: Should all floating point numerals be in the IO Monad? I'm deviating from the thread's topic, but I tend to agree with this one. Maybe not IO directly, but some kind of

Re: [Haskell-cafe] List as input

2008-10-15 Thread Brandon S. Allbery KF8NH
On 2008 Oct 16, at 0:53, leledumbo wrote: The compiler doesn't know what kind of list you are trying to read, sort, and print. So, the type must be specific? Then why it's possible to call the sorting function with any list? A function may have a polymorphic type; this allows its actual

Re: [Haskell-cafe] Object-oriented programming, Haskell and existentials

2008-10-15 Thread Kim-Ee Yeoh
re: the importance of existential-cleansing On the one hand, it's easy to concur that existentials are simpler than the alternatives, the tortuous elimination of CC Shan's translucent existential being a case in point. And it's also easy to dismiss such caprice as a penchant for Houdinian