Re: incompatible signatur syntax within instance definition
On 09-Dec-2003, Christian Maeder <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > >Or were you referring to the fact that variables which are already > >constrained can't be constrained again? IMHO that is a feature too. > >It doesn't make sense to constrain a variable at any point other than > >the point where that variable is introduced. > > Indeed, repeating a constraint should be no error (at most a warning) > and be it only to let "ghc -fglasgow-exts" except [accept] more programs > than ghc does without extensions. Allowing repeated constraints would not be sufficient for that. The fact that the two type variables in the case originally posted happened to have the same constraint is somewhat coincidental; in Haskell 98, the inner variable might have absolutely no relationship with the outer variable. Consider the following example: data MyType a = MkMyType a class Foo a where foo :: a -> Int instance Foo (MyType a) where foo _ = bar (42::Int) where bar :: a -> a bar x = x This is legal in Haskell 98, because the `a' in the inner declaration is implicitly universally quantified. But if the scope of the outer type variable `a' extends over the inner type declaration, then the inner `a' will not be locally universally quantified, and the call to `bar' will be a type error, because the `a' in the head of the instance declaration will in general be different than `Int'. data MyType a = MkMyType a class Foo a where foo :: a -> Int instance Foo (MyType a) where foo _ = bar (42::Int) where bar :: a -> a bar x = x Indeed, the scoping of type variables can affect the meaning of programs, not just their legality. Consider the following variation: data MyType a = MkMyType a class Foo a where foo :: a -> String instance Num a => Foo (MyType a) where foo _ = bar 42 where bar :: Num a => a -> String bar x = show x If the scope over the outer `a' does not extend over the inner `a', then the implicit `fromInteger 42' will be resolved by the defaulting rules to `fromInteger 42 :: Int'. But if the outer `a' extends over the inner `a', then it will be `fromInteger 42 :: a'. These could have different semantics, e.g. if called in the following context. data MyNum = MyNum instance Eq MyNum where _ == _ = True instance Num MyNum where fromInteger _ = MyNum instance Show MyNum where show MyNum = "MyNum" main = print (foo (MkMyType MyNum)) With Haskell 98, this program will print "42". With ghc and your proposed change to allow multiple qualifications, it would print "MyNum". With ghc as it stands, you get an error, because the variable `a' is qualified multiple times. So, to summarize, this particular ghc extension is not a pure extension. It can change the legality or even the semantics of Haskell 98 code. Allowing repeated constraints won't change that. Given that allowing repeated constraints isn't sufficient to solve that problem, I don't think it is a good idea to allow them. P.S. I note that ghc 5.02.2 enables this extension always, regardless of the setting of -fglasgow-exts. That seems like a bug to me. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: incompatible signatur syntax within instance definition
On 08-Dec-2003, Christian Maeder <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > >I think the issue here is that in ghc (with -fglasgow-exts), > >the "a" here refers to the same type variable "a" in the > >top of the instance declaration, which has already been > >constained, and cannot be constrained again. > > Is that a bug or a feature? A feature. It's called "scoped type variables". See <http://www.haskell.org/ghc/docs/6.2/html/users_guide/type-extensions.html#SCOPED-TYPE-VARIABLES>: "The type variables in the head of a class or instance declaration scope over the methods defined in the where part.". Or were you referring to the fact that variables which are already constrained can't be constrained again? IMHO that is a feature too. It doesn't make sense to constrain a variable at any point other than the point where that variable is introduced. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: FWD: Re: GHC FFI Return Type Bug
On 08-Aug-2001, Fergus Henderson <[EMAIL PROTECTED]> wrote: > Sigbjorn Finne <[EMAIL PROTECTED]> wrote: > > > > "Julian Seward (Intl Vendor)" <[EMAIL PROTECTED]> writes: > > > > > > | > char fooble ( ... ) > > > | > { > > > | >return 'z'; > > > | > } > > > | > > > > | > on an x86, 'z' will be returned at the lowest 8 bits in %eax. What I > > > | > don't know is, is the C compiler obliged to clear the upper 24 bits of > > > | > %eax, or does that onus fall on the callee? > > The upper 24 bits of eax must be cleared in the callee. > The caller can assume that they are zero. > > I don't know if this is documented anywhere, but that is the convention > which GNU C follows (on all architectures -- the C front-end internally > promotes the return type from "char" to "int"). I can point you to > the exact line of code in the GNU C front-end if you really want. > > I think this is required by traditional K&R C code, which does things > like calling such functions without declaring them. On further investigation it appears that although what I wrote is true for GNU C, it seems to *not* be true for GNU C++, which was being used in the code in the original bug report. I'm not sure why that is. The C++ front-end has some code similar to the code in the GNU C front-end, to promote function return types, but the code seems to not get used. I don't know whether that is deliberate or not. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: FWD: Re: GHC FFI Return Type Bug
Sigbjorn Finne <[EMAIL PROTECTED]> wrote: > > "Julian Seward (Intl Vendor)" <[EMAIL PROTECTED]> writes: > > > > | > char fooble ( ... ) > > | > { > > | >return 'z'; > > | > } > > | > > > | > on an x86, 'z' will be returned at the lowest 8 bits in %eax. What I > > | > don't know is, is the C compiler obliged to clear the upper 24 bits of > > | > %eax, or does that onus fall on the callee? The upper 24 bits of eax must be cleared in the callee. The caller can assume that they are zero. I don't know if this is documented anywhere, but that is the convention which GNU C follows (on all architectures -- the C front-end internally promotes the return type from "char" to "int"). I can point you to the exact line of code in the GNU C front-end if you really want. I think this is required by traditional K&R C code, which does things like calling such functions without declaring them. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: GHC HQ are looking for a Linux-IA64 box
On 12-Mar-2001, Julian Seward (Intl Vendor) <[EMAIL PROTECTED]> wrote: > > Does any kind person have an IA64 box, running Linux, on which we could > have an account? You might want to check out SourceForge: <http://ia-64.sourceforge.net/>. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: Overloaded function and implicit parameter passing
On 23-Oct-2000, José Romildo Malaquias <[EMAIL PROTECTED]> wrote: > - cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > - cut here ... > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 ... > Would anybody comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
Re: Wanted: mmap or other fast IO
On 16-Feb-2000, Simon Marlow <[EMAIL PROTECTED]> wrote: > > The easiest way is to declare mmap as a foreign function using foreign > import, then build a little wrapper around it. Unfortunately you won't be > able to turn the resulting memory into an array (even a ByteArray), since > these are assumed to live in GHC's heap I'm curious: why do you make that assumption? If I write code that defines some big array whose contents are known at compile time, it would be nice if ghc would allocate that array at compile time, in read-only memory, rather than allocating it on the heap at run-time. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
Re: Existential types, save me now?
On 22-Nov-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote: > > > Is this supposed to be a heterogenous list, > > or a homogeneous list? > > Sorry, I should have been a tad less terse: it's intended to be > a homogeneous list, else the maximum wouldn't be well-typed. Oh, of course -- you're quite correct. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
Re: Existential types, save me now?
On 22-Nov-1999, Alex Ferguson <[EMAIL PROTECTED]> wrote: > > Here's some of the threatened examples: > > > data OrdFuncExist = OE (Ord a => Char -> a) > That's not the syntax for a existential type, that's the syntax for a universally quantified type with rank-2 polymorphism. With that syntax, the argument of `OE' must be a polymorphic function with type `forall a . Ord a => Char -> a'. I think the syntax for what you want is data OrdFuncExist = Ord a => OE (Char -> a) > > data OrdListExist = OLE (Ord a => [a]) Is this supposed to be a heterogenous list, or a homogeneous list? That is, must the elements all have the same type `a', or is the choice of `a' supposed to be allowed to vary for each element? If you want a homogeneous existentially quantified list, then use data OrdListExist = Ord a => OLE [a] But I suspect you want a heterogenous existentially quantified list. In that case, you should use something like this: data AnyOrd = Ord a => MkAnyOrd a data OrdListExist = [AnyOrd] > > emap :: OrdFuncExist -> [Char] -> OrdListExist > > emap (OE f) l = OLE (map f l) You'll probably need something along the lines of emap (OE f) l = OLE (map (MkAnyOrd . f) l) > The other problem: > > > emax :: OrdListExist -> OrdListExist > > emax (OLE l) = OLE [maximum l] > > Now, I think I see why this doesn't work: but any ideas on how to fix? Hmm, I'm not sure exactly what you're trying to achieve here... but perhaps you just need to add instance Ord AnyOrd where compare (MkAnyOrd x) (MkAnyOrd y) = compare x y to make it work. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
Re: haskell operator precedence
Libor Skarvada, you wrote: > > > > infixr 0 `foo` > > > infixr 0 `bar` > > I do not see any problem here. [...] > But if we mix the associativity like > infixl 0 `foo` > infixr 0 `bar` > then the parsing of the expression above is not unique, and eg. Hugs > complains > ERROR "tmp.hs" (line 7): Ambiguous use of operator "foo" with "bar" Ah. Thank you for reading my mind. Now why can't ghc and Hugs do that? ;-) ;-) Sorry about that. (I really should think a bit harder before mailing this list, lest I make a habit of looking really silly...) -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.
haskell operator precedence
Hi, Is the following legal Haskell? > infixr 0 `foo` > infixr 0 `bar` > > x `foo` y = "foo(" ++ x ++ "," ++ y ++ ")" > x `bar` y = "bar(" ++ x ++ "," ++ y ++ ")" > dubious a b c = a `foo` b `bar` c According to the grammar in the Haskell report, I don't think it is. However, ghc-0.24 (ancient, I know) and Hugs 1.3 both accept it without complaint. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED] | -- the last words of T. S. Garp.