Re: [Haskell] Num is such a fat and greedy class

2006-12-11 Thread Andreas Rossberg
tandard scoping restriction as for existential types? (Which they basically are, as we know.) Why do you consider it troublesome? - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Num is such a fat and greedy class

2006-12-11 Thread Andreas Rossberg
think with the scoping restrictions in place the beta rule would not be affected. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] ___ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Re: GHC Error question

2006-12-06 Thread rossberg
[EMAIL PROTECTED] wrote: > > I'm afraid I may disagree about the quantification. Also, I'm cautious > about the phrase "ML and Haskell". In GHC 6.4, local type variables > behave pretty much like those in ML (actually, GHC 6.2 was closer). In > GHC 6.6, the behavior is completely different! > > Reg

Re: [Haskell] Dynamic binding

2005-06-23 Thread Andreas Rossberg
;t understand what you mean. Polymorphism is about typing. Late binding is not dependent on typing (there are untyped OO languages, for example). Cheers, - Andreas [Followups to Haskell Cafe] -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! --

Re: [Haskell] Dynamic binding

2005-06-23 Thread Andreas Rossberg
ss function"). In typical functional programming style, you need the general thing only rarely. Cheers, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! -- TB ___ Haskell mailing list Haskell@haskell

Re: [Haskell] translation of "kind"

2005-06-20 Thread Andreas Rossberg
hat many Germans rather tend to say "die Kind" instead when they have to, maybe because that is the gender you have for "Sorte", "Art", and "Gattung". -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! -- TB _

Re: [Haskell] Rank-N types vs existential types

2005-04-27 Thread Andreas Rossberg
se f at all (well, except with undefined). The type is not polymorphic in "a" on the RHS, it is abstract! You'd need to encapsulate a value of the same type (or a constructing function) as well to this type useful. -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of tho

Re: [Haskell] MPTCs and type inference

2005-04-26 Thread Andreas Rossberg
gt;() without a being quantified. That looks a bit more uniform in the face of MPTCs and would allow more programs, because contexts induced by dead code in form of an unused declaration could be forgotten consistently, not just when some of its free variables happen to be bound by a

[Haskell] MPTCs and type inference

2005-04-25 Thread Andreas Rossberg
a where fc :: a -> a -> () c1 x = let p = fc x in () c2 x = let p y = fc x y in () where c1 :: C a => a -> () c2 :: C a => a -> () is inferred, as I would expect. -- Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! -- TB _

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Andreas Rossberg
rincipal type (due to the lack of row polymorphism), so its type must be derivable from context - which might involve a type annotation. BTW, I'd prefer r.l as well. A section like (.l) could then give you the equivalent of #l. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] Let'

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-04 Thread Andreas Rossberg
Andreas Rossberg, [EMAIL PROTECTED] Let's get rid of those possible thingies! -- TB ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] Gallopping Tab characters

2004-01-26 Thread Andreas Rossberg
es would go to "\t" and " ", which your algorithm would reject. If the editor does the replacement consistently everywhere (like I would expect) then it would not change the meaning of a "well-indented" program. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED]

Re: [Haskell] Re: Use of tab characters in indentation-sensitive code

2004-01-26 Thread Andreas Rossberg
e that. With this solution, tab width is irrelevant and indentation may include whatever Unicode has. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids; I mean if Pac Man affected us as kids, we would all be running around in darkened rooms, munching

Re: Type classes and code generation

2003-06-17 Thread Andreas Rossberg
rse, for most practical programs, the optimization you have in mind would be possible. I doubt compilers generally do it globally, though, because it requires whole program analysis, i.e. does not interfer well with separate compilation (beside other reasons). | Andreas -- Andreas Rossberg, [EMA

Re: forall quantifier

2003-06-04 Thread Andreas Rossberg
ent classify :: [Classifier a] -> [a] -> [[a]] Cheers, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids; I mean if Pac Man affected us as kids, we would all be running around in darkened rooms, munching magic pills, and l

Re: beginner's questions - fix f

2001-07-24 Thread Andreas Rossberg
this example it is easy to infer how to transform arbitrary recursive definitions. Even generalising it to mutual recursion is not difficult (and left as an exercise to the reader ;-). All the best, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect ki

Re: Implict parameters and monomorphism

2001-05-03 Thread Andreas Rossberg
tance Num T where fromInteger n = T n (+) (T _) (T _) = T 0 x :: T -- try removing this type signature x = 1 + 2 main = putStr (show x) - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids. If Pac Man affected us as kids, we w

Re: Implict parameters and monomorphism

2001-05-02 Thread Andreas Rossberg
it. To me it seems overly restrictive to rule out perfectly correct programs for the sole reason of potentially surprising space/time behaviour. After all it is not forbidden to write Haskell programs with obscure space leaks. -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't

Re: help wanted with type error message

2001-04-04 Thread Andreas Rossberg
iting > type T = Row [] Int Cheers, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids. If Pac Man affected us as kids, we would all be running around in darkened rooms, munching pills, and listening to repetitive music." ___

Re: Inferring from context declarations

2001-02-22 Thread Andreas Rossberg
ymorphically recursive functions. Wasn't this one motivation to allow general polymorphic recursion in Haskell - that it is in the language anyway? - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids. If Pac Man affected us as kids, we would all be

Re: Inferring from context declarations

2001-02-21 Thread Andreas Rossberg
/www.cs.chalmers.se/~rjmh/ Hope this helps, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids. If Pac Man affected us as kids, we would all be running around in darkened rooms, munching pills, and listening to repetitive music." ___

Re: Inferring from context declarations

2001-02-21 Thread Andreas Rossberg
is potentially infinite. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] "Computer games don't affect kids. If Pac Man affected us as kids, we would all be running around in darkened rooms, munching pills, and listening to repetitive music." _

Re: Doing IO in foldr repeats lines?

2001-01-23 Thread Andreas Rossberg
} This can be reformulated as io_l2'= do { l <- return 14 ; () <- putStr "qq" ; l <- return 14 ; () <- putStr "ww" ; l <- return 14 ; () <- putStr "qq"

Re: class instance with nested types

2000-10-27 Thread Andreas Rossberg
I mumbled: > > This is not a legal type expression, since Tree is a > type constructor, not a ground type, so you cannot apply it to the list > constructor. The other way round, of course: you cannot apply the list constructor to it. - Andreas -- Andreas Rossberg, [EMA

Re: class instance with nested types

2000-10-27 Thread Andreas Rossberg
a Tree a = N a (Forest a) deriving (Ord,Eq,Show) > data Forest a = Forest [Tree a] > instance Xy Forest Char where > test (Forest (N a xs:txs)) = a HTH, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] :: be declarative. be functional. just be. :: ___

Re: Higher-order function application

2000-08-23 Thread Andreas Rossberg
e classes, which I wouldn't call overloading in the first place.) BTW, this sort of notational overloading used in maths has always been a good source of confusion for students, IMHO. All the best, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] :: be declarative. be functional. just be. ::

Compiler implementation and FP [Was: Re: Clean and Haskell]

2000-01-13 Thread Andreas Rossberg
s come in handy sometimes (eg. for unification) -- like always. Compilers like OCaml or SML/NJ are very fast, even though they have to perform quite some complex stuff. And they are `mostly functional'. (And please: not another flame war about the definition of `functional'.) -

Re: OO in Haskell

1999-10-06 Thread Andreas Rossberg
Kevin Atkinson wrote: > > On Tue, 5 Oct 1999, George Russell wrote: > > > Perhaps I'm being stupid. (It certainly wouldn't be the first time!) > > But what does OO give me that I can't get with existential types (in > > datatype definitions) and multiparameter type classes? The latter seem > >

Re: Units of measure

1999-08-26 Thread Andreas Rossberg
accordingly might be possible with MPTCs, I think. The hard problem is that you cannot establish equalities like Prod a (Quot b a) = b Sigh. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] :: be declarative. be functional. just be. ::

Re: Units of measure

1999-08-26 Thread Andreas Rossberg
-- OK: Quot Metres Seconds a = m /$ (s *$ s) -- OK: Quot Metres (Prod Seconds Seconds) x = m -$ s -- error It would be nicer if Haskell had infix type constructors:  newtype a :* b = Prod Float newtype a :/ b = Quot Float Cheers,

Re: The dreaded layout rule

1999-08-12 Thread Andreas Rossberg
kell's, because I couldn't get Yacc's error productions to work properly in all cases). For Haskell 2(000) I would suggest removing all but the first 4 tokens from the list above. - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] :: be declarative. be functional. just be. ::

Re: Haskell 98 progress...

1998-11-23 Thread Andreas Rossberg
haracter matching for -}. (Modulo nesting, as now.) Sorry for interrupting, but how are inner comments opened then? By character by character matching for {- ? So is this legal {- bla {-- blabla -} bla -} ? Regards, - Andreas -- Andreas Rossberg, [EMAIL PROTECTED] :: be declarative. be functional. just be. ::

Re: Simon's H98 Notes

1998-10-22 Thread Andreas Rossberg
Frank A. Christoph wrote: > > >Standard ML does not allow this. One important aspect of the SML module > >system actually is its strong separation from the core language. > > Not that old saw again...! Ocaml separates the two as well. Well, the new let-module feature undermines the separation

Re: Simon's H98 Notes

1998-10-21 Thread Andreas Rossberg
Frank A. Christoph wrote: > > Local imports might be useful, though. Objective Caml 2.00 has finally > caved in and followed Standard ML in allowing expression-local modules. Standard ML does not allow this. One important aspect of the SML module system actually is its strong separation from th

Haskell 98 - The Underbar

1998-10-19 Thread Andreas Rossberg
Ralf Hinze wrote: > >* make '_' lexically a valid identifier character anywhere >* but disallow identifiers starting with '_' > > Thus '___' would lex as '___' but then be rejected. '_' on its own remains a > wild-card pattern, and illegal in expressions. > > > ] `_' is a special case w

Re: Multi-parameter type classes

1998-06-30 Thread Andreas Rossberg
Simon L Peyton Jones wrote: > > GHC 3.02 supports multi-parameter type classes, but I have been > guilty of not documenting precisely what that means. > > I've now summarised the extensions, informally but I hope > precisely, at > > http://www.dcs.gla.ac.uk/multi-param.html That does n

Wadler's prettier printer

1998-05-13 Thread Andreas Rossberg
Hello, thinking about whether the pretty printer proposed by Wadler requires some changes to be efficient in a strict language, I stumbled over the the last case defining `flatten': flatten (x :<|> y) = flatten x I wonder why it is necessary here to recurse on x. The only point were a

Re: Punning: Don't fix what ain't broken.

1998-02-12 Thread Andreas Rossberg
Tommy Thorn wrote: > > Koen Claessen: > > This brings us to another issue. Doesn't the following definition look > > a bit awkward? > > > > R{ x = x } > > Definitely wierd. The left and right-hand side denotes two different > things, which AFAIK is the only place where `=' behaves like this.