[Haskell-cafe] Different behavior of GHC 6.10.1 and Hugs (Sep 2006)

2010-04-03 Thread Vladimir Reshetnikov
Hi list, GHC 6.10.1: Prelude> :t let f x y = return x == return y in f let f x y = return x == return y in f :: (Eq (m a), Monad m) => a -> a -> Bool Hugs (Sep 2006): Hugs> :t let f x y = return x == return y in f ERROR - Ambiguous type signature in inferred type *** ambiguous type : (Eq (a b),

[Haskell-cafe] Why there is not standard Monoid instance for ZipList a?

2009-10-16 Thread Vladimir Reshetnikov
I find the following instance very convenient: import Data.Monoid import Control.Applicative instance Monoid a => Monoid (ZipList a) where mempty = pure mempty mappend = liftA2 mappend -

Re: [Haskell-cafe] Monotype error

2009-10-15 Thread Vladimir Reshetnikov
See our previous discussion on this topic here: http://www.nabble.com/Fwd:-Unification-for-rank-N-types-td23942179.html Thanks, Vladimir On Wed, Oct 14, 2009 at 10:35 PM, Martijn van Steenbergen < mart...@van.steenbergen.nl> wrote: > Dear café, > > {-# LANGUAGE Rank2Types #-} >> {-# LANGUAGE Im

[Haskell-cafe] List comprehensions and impredicative rank-N types

2009-06-11 Thread Vladimir Reshetnikov
Hi, Consider the following definitions: --- {-# LANGUAGE RankNTypes, ImpredicativeTypes #-} foo :: [forall a. [a] -> [a]] foo = [reverse] bar :: [a -> b] -> a -> b bar fs = head fs --

[Haskell-cafe] Re: Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
#-} f :: [forall a. t a -> t a] -> t b -> t b f = foldr (\g -> (.) g) id --- What is the reason for this? Thanks, Vladimir On 6/9/09, Vladimir Reshetnikov wrote: > Hi, > > I have the following code: > -

[Haskell-cafe] Unification for rank-N types

2009-06-09 Thread Vladimir Reshetnikov
Hi, I have the following code: --- {-# LANGUAGE RankNTypes #-} f :: ((forall a. a -> a) -> b) -> b f x = x id g :: (forall c. Eq c => [c] -> [c]) -> ([Bool],[Int]) g y = (y [True], y [1]) h :: ([Bool],[Int]) h = f g ---

Re: [Haskell-cafe] Question on rank-N polymorphism

2009-06-07 Thread Vladimir Reshetnikov
dless of their element types. Thanks Vladimir On 6/7/09, Zsolt Dollenstein wrote: > On Sun, Jun 7, 2009 at 9:17 AM, Vladimir > Reshetnikov wrote: >> Hi Zsolt, >> >> It does not compiles with GHC without type annotations. > > It does with mine: The Glorious Glasgo

[Haskell-cafe] Question on rank-N polymorphism

2009-06-06 Thread Vladimir Reshetnikov
Hi, I have the following code: fs g = (g fst, g snd) examples = (fs fmap, fs liftA, fs liftM, fs id, fs ($(1,"2")), fs ((,)id), fs (:[]), fs repeat) ---

Re: [Haskell-cafe] Trouble with types

2009-06-01 Thread Vladimir Reshetnikov
Montag 01 Juni 2009 14:44:37 schrieb Vladimir Reshetnikov: >> Hi, >> >> I tried this code: >> >> --- >> f, g :: a -> a >> (f, g) = (id, id) >> --- >> >> Hugs: OK >> >> GHC: >

[Haskell-cafe] Trouble with types

2009-06-01 Thread Vladimir Reshetnikov
Hi, I tried this code: --- f, g :: a -> a (f, g) = (id, id) --- Hugs: OK GHC: Couldn't match expected type `forall a. a -> a' against inferred type `a -> a' In the expression: id In the expression: (id, id) In a pattern binding:

[Haskell-cafe] GHCi vs. Hugs (record syntax)

2009-05-31 Thread Vladimir Reshetnikov
Hi, I tried to evaluate this expression: head[[]{}] GHCi: [] Hugs: ERROR - Empty field list in update What is the correct behavior? Thanks, Vladimir ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskel

[Haskell-cafe] (no subject)

2009-05-31 Thread Vladimir Reshetnikov
Hi, Seems that Haskell allows to specify "dummy" type variables in a declaration of a type synonym, which do not appear in its right-hand side. This can lead to interesting effects, which appears differently in GHC and Hugs. I would like to know, what behavior is correct according to the haskell 9

[Haskell-cafe] Which type variables are allowed in a context?

2009-05-31 Thread Vladimir Reshetnikov
Hi, Consider this (a bit pathological) Haskell code: -- class A a where foo :: A (b d) => a (c b) -- GHC compiles it successfully, but Hugs rejects it: Ambiguous type signature in class declaration *** ambiguous type : (A

[Haskell-cafe] Question on kind inference

2009-05-31 Thread Vladimir Reshetnikov
Hi, Consider this Haskell code: --- class A a where foo :: a b class B a class (A a, B a) => C a --- GHC compiles it without errors, but Hugs rejects it: "Illegal type in class constraint". What is the co

[Haskell-cafe] Hugs vs. GHCi

2009-05-29 Thread Vladimir Reshetnikov
Hi, The following expression evaluates to 1 in GHCi, but results in an error in Hugs: let f x = let g y = [x,y] in (g 1, g []) in 1 What is the correct behavior? Thanks Vladimir ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell

[Haskell-cafe] Strange behavior of float literals

2008-04-05 Thread Vladimir Reshetnikov
, Vladimir Reshetnikov (aka nikov), Microsoft MVP ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe