[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-16 Thread Gleb Alexeyev
Mauricio wrote: After you pointed my dumb mistake, I was able to build the first example -- without any of the extensions! Haskell can be misterious some times. Strange enough, I can't get the original (and, to my eyes, equal) problem to work. Indeed Haskell can be misterious sometimes. Now

[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Gleb Alexeyev
Mauricio wrote: Hi, I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well: --- import Data.Ratio ; main = do { printNumber - let { print :: (Num n,Show n) = n - IO () ; print n = do { putStrLn $ show n}

Re: [Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Ryan Ingram
I suggest you start using let in your do blocks; both of these problems are solvable with let. Binding with - instead of let makes the type system work harder, and will generally require type annotations extensions for polymorphic results. And it's almost never what you want, anyways; you don't

[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Mauricio
I have this problem trying to define a function inside a do expression. I tried this small code to help me check. This works well: I guess you intended to call printNumber in the quoted snippet? (...) {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ImpredicativeTypes #-} After you pointed my dumb

[Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Mauricio
Thanks, everything works now. What should I read to better understand the difference for the type system between using - and 'let'? That is not intuitive for me. About layout, I used to filter my code to better fit everyone taste before posting to this list. The filter stoped working due to

Re: [Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Lennart Augustsson
The - binding is lambda binding (look at how it desugars). Lambda bindings are monomorphic without any type extensions. The monadic 'let' binding is like regular 'let', so it's a point where the type checker does generalization, and so you get (possibly) polymorphic bindings from let. --

Re: [Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Ryan Ingram
Here's the desugaring: do { pattern - expression ; rest } desugars to expression = \temp - case temp of pattern - do { rest } _ - fail Pattern match failure (where temp is a fresh variable not used elsewhere, and the failure message usually includes source position) Whereas do {

Re: Type errors in Haskell programming languages - Plz help

2003-11-05 Thread s_mazanek
Hello. The code is as follows - -- Code starts -- entry :: [Char] - [(Char,Int)] entry list = do t - getGroups list mergeGroups t getGroups :: [Char] - [(Char,Int)] mergeGroups :: [(Char,Int)] - [(Char,Int)] -- Code Ends -- You probably mean: entry

Re: Type errors in Haskell programming languages - Plz help

2003-11-05 Thread Karthik Kumar
Thanks Steffen. This one worked. Cheers Karthik. --- [EMAIL PROTECTED] wrote: Hello. The code is as follows - -- Code starts -- entry :: [Char] - [(Char,Int)] entry list = do t - getGroups list mergeGroups t getGroups :: [Char] - [(Char,Int)]

Re: type errors

1998-07-01 Thread Ralf Hinze
Ok, I did not reconize this solution, it seems to me the (nearly) proper one. But why not write: class = Dictionary dict where delete :: (Eq key, Ord key) = key - dict key dat - dict key dat ... So one could avoid multiparamter classes at all. The two types key and dat

Re: type errors

1998-07-01 Thread Simon L Peyton Jones
Actually I think you would be better off with a class like this: class (Eq key, Ord key) = Dictionary dict key where delete :: key - dict dat - dict dat search :: key - dict dat - (key, SearchResult dat, dict dat) searchList :: [key] - dict dat -

RE: type errors

1998-07-01 Thread Mark P Jones
| delete :: (Dictionary dict key dat) = key - dict - dict | | It would not *always* result in ambiguity. For example, consider | | instance Dictionary (MyDict dat) Int dat where ... | | f :: MyDict dat - MyDit dat | f d = delete (3::Int) d | | Here, the polymorphism in

Re: type errors

1998-07-01 Thread Alastair Reid
Simon PJ wrote: So, I now think that the existing rule (all class variables must appear in each class-operation type signature) is probably the right one, but on stylistic rather than technical grounds. I feel very uneasy about this style of argument - a language designed this way becomes

Re: type errors

1998-07-01 Thread Simon L Peyton Jones
| class (Eq key, Ord key) = Dictionary dict key dat where |delete :: key - dict - dict | ... | the first error: | | Class type variable `dat' does not appear in method signature | delete :: key - dict - dict | | Why does ghc expect that I use all of the type

Re: type errors

1998-06-30 Thread Simon L Peyton Jones
The ghc compiler complains about 2 type errors in the following code: data SearchResult a = Found a | Fail class (Eq key, Ord key) = Dictionary dict key dat where delete :: key - dict - dict search :: key - dict - (key,SearchResult dat,dict) searchList :: [key] -

Re: type errors

1998-06-30 Thread Martin Stein
Ambiguous type variable(s) `key', `dict' in the constraint `Dictionary dict key a10v' arising from use of `searchList' at Dtest2.hs:11 In an equation for function `searchList': searchList (x : xs) d = let

Re: type errors

1998-06-30 Thread Philip Wadler
You're right. The restriction is excessive. Thanks for pointing this out. Probably we should only require that at least one of the class variables is constrained. Why even require this? (All x) = x - x uses the class `All' which restricts its argument not one whit. -- P

Re: type errors

1998-06-30 Thread Simon L Peyton Jones
The ghc compiler complains about 2 type errors in the following code: data SearchResult a = Found a | Fail class (Eq key, Ord key) = Dictionary dict key dat where delete :: key - dict - dict search :: key - dict - (key,SearchResult dat,dict) searchList :: [key] -

RE: type errors

1998-06-30 Thread Mark P Jones
| class (Eq key, Ord key) = Dictionary dict key dat where |delete :: key - dict - dict | ... | the first error: | | Class type variable `dat' does not appear in method signature | delete :: key - dict - dict | | Why does ghc expect that I use all of the type

Re: type errors

1998-06-30 Thread Martin Stein
Actually I think you would be better off with a class like this: class (Eq key, Ord key) = Dictionary dict key where delete :: key - dict dat - dict dat search :: key - dict dat - (key, SearchResult dat, dict dat) searchList :: [key] - dict dat - ([(key,SearchResult