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

2006-12-11 Thread Andreas Rossberg

S.M.Kahrs wrote:

let data Bar = ... in  ...

If you allow this you need to be very careful about type equality.   
When is Bar equal to Bar?

If it's inside a recursive function, does each invocation get its
own Bar?  (In SML the answer is yes.) 


Not really.
In SML the answer used to be a clear "no", that is: in the 1990
definition. However, that proved to be a matter of type-unsoundness,
and Claudio Russo came up with an example that used this feature to
break the type system. Having said this, this was based on the way the
type system was defined in the language definition, the problem did not
show up in implementations (which therefore failed to implement the
language standard :-).

The problem was fixed in the 1997 language standard.
But there the answer isn't "yes" either, it is more like: "whatever it
is, you cannot tell", though technically it is still "no".


Mh, technically, isn't it likewise "neither"? As you say, types are only 
generated statically, and are erased in the dynamic semantics, so how is 
it a "no" more than a "yes"?


As an aside (sorry if this is getting far too OT), in Alice ML we extend 
SML with dynamic types, and local types in fact *are* dynamically 
generative. This seemed to be the most natural semantics (and the only 
correct one in the presence of dynamic linking).



In the static semantics, a local datatype in SML is fresh.
However, this freshness is a static freshness, at compile time,
and every time the code is run the same "type name" (a uniqueness tag
for types) will be used: there is no run time type-checking, the type
name is generated once, at compile time.


Well, this is sort of true for types defined in functor bodies as well, 
still they are generative. The only semantical difference I see is that 
its local types are allowed to escape scope, and are (statically) 
renamed upon each application of the functor. No difference with respect 
to the dynamic semantics, however.



However, that type name is not allowed to leak to the outside, i.e.
not only is the identifier Bar not visible outside, the type of the
value returned by the let-expression must not contain the type name
associated with Bar. Thus, if a let-expression with a local datatype is
evaluated twice, it does not really matter whether it uses the same or a
different type name because encapsulation ensures
that these type names do not interfere with each other in any way.

In a nutshell: local types are not worth the trouble they cause.


I'm not quite sure how this follows from your explanation. :-) Don't you 
just need the same standard 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

Lennart Augustsson wrote:


let data Bar = ... in  ...


If you allow this you need to be very careful about type equality.  When 
is Bar equal to Bar?
If it's inside a recursive function, does each invocation get its own 
Bar?  (In SML the answer is yes.)


Can you give an example of how this would be observable in SML? AFAICS, 
there is no way to tell the difference, because generative type names 
are not allowed to escape their scope. (You can observe dynamic 
generativity of exception constructors, though.)


If you decide the answer is no, then 
is the beta rule still valid?


I 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] Dynamic binding

2005-06-23 Thread Andreas Rossberg

Ralf Lammel wrote:



"dynamic binding" is just the OOO way of saying
"calling a first-class function").


Let me presume that dynamic binding 
was meant here in the sense of late binding


Yes.


in the sense of subtyping polymorphism.


No, as far as I read it, "dynamic" or "late binding" is orthogonal to 
subtyping, or typing in general. It is just that most typed OO languages 
lump these concepts together.


For me, "dynamic" or "late" binding just means calling (or more 
generally, accessing) something that is not determined statically. That 
is precisely what first-class functions provide.


Objects just turn more complex uses of this idiom into a language 
concept. Operationally, objects are equivalent to records of first-class 
functions. They usually come with more flexible typing and more 
efficient implementation, though.



(First-class function seems to refer to currying or what?)


No, constructing closures, and passing them around as values (currying 
is merely a particularly convenient special case of this).



(Did you miss a "polymorphic" before function? That would explain it.


I don'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!  -- TB
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Dynamic binding

2005-06-23 Thread Andreas Rossberg

Andrew Ward wrote:
In Simon Thompson's The Craft of Functional Programming Second Edition, 
page 226, it is mentioned that Laufer (1996) describes a Haskell 
extension to allow dynamic binding. I was wondering if this has been 
implemented as an extension in any of the haskell compilers, or variants?


Definitely. GHC and Hugs implement it, don't know about the others.

But note that you do not necessarily need it. Often a simple first-class 
function, or a record thereof, is enough (in fact, "dynamic binding" is 
just the OOO way of saying "calling a first-class 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.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] translation of "kind"

2005-06-20 Thread Andreas Rossberg

Ralf Hinze wrote:


I'ld prefer "der Kind" (and avoid situtations that allowed confusion
with "das Kind")


Honestly, this is truly horrible (sorry, Peter). Just try to read it
aloud: "der Kind des Typkonstruktors ...".


Indeed. Moreover, my impression is that 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
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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

2005-04-27 Thread Andreas Rossberg
Andre Pang wrote:
data RankN  = RankNEq (forall a. Eq a => a -> a -> Bool)
| RankNOrd (forall a. Ord a => a -> a -> Bool)
data Exists = forall a. Eq a => ExistsEq (a -> a -> Bool)
| forall a. Ord a => ExistsOrd (a -> a -> Bool)
So, the RankN type uses rank-2 polymorphism to "hide" the expression 
inside the type, whereas the Exists type uses existentially quantified 
types instead.  The two seem pretty equivalent to me, since the data 
constructors have the same type.  However, I can't help but feel that 
I'm missing something fundamental about a difference between them.  Are 
the two completely isomorphic?  Is there some advantage or disadvantage 
to using one over the other?
They don't have the same type. The types are
  RankNEq  :: (forall a.Eq a => a->a->Bool) -> RankN
  ExistsEq :: forall a.Eq a => (a->a->Bool -> Exists)
These are quite different beasts.
The difference really shows up when you *use* (deconstruct) them:
  g (RankNEq f) = (f 4 5, f True False)
This allows the embedded function to be used polymorphically. But:
  h (ExistsEq f) = ???
Here, you cannot use 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 those possible thingies!  -- TB
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] MPTCs and type inference

2005-04-26 Thread Andreas Rossberg
Thanks for the detailed explanation that helped clearing up the smog in 
my head. I reckoned that once more the MR was to blame, at least for 
part of it.

in particular, when I compare with the single parameter case:
  class C 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.
The inference steps for this case are much the same except, that the
inferred type for "p" now will be: "a -> ()", provided that we can
solve the constraint "C a".  Because we have assumptions about "a" in
the environment (namely it is mentioned in the type of the varible
"x") we cannot generalize the type of "p".  It therefore remains
monomorphic, and the constraint "C a" is propagated to the type of
"c2".
To be more precise, p is not polymorphic *in the variables mentioned by 
the constraint* - the overall type of p could still be polymorphic, 
without changing the outcome.

My understanding now is as follows: a constraint is captured by a 
declaration if at least one of the type variables mentioned in the 
constraint is generalised in the respective type scheme. Is that a 
correct interpretation?

Of course, this is not the only possible rule. Alternatively, 
generalisation could always capture *all* unresolved constraints. For 
example, the type of p in c2 could be C a => a->() 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 local quantifier.

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


[Haskell] MPTCs and type inference

2005-04-25 Thread Andreas Rossberg
This may well be stupidity on my side, but some experiments with multi 
parameter type classes got me slightly confused. Can somebody explain 
the following behaviour to me?

  class D a b where fd :: a -> b -> ()
  d1 x = let p = fd x in ()
  d2 x = let p y = fd x y in ()
GHC derives the following types:
  d1 :: D a b => a -> ()
  d2 :: a -> ()
Hugs rejects d1 on the grounds that the type is ambiguous, but agrees on 
the type of d2. I do not understand where the context disappears to in 
this example - in particular, when I compare with the single parameter case:

  class C 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
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


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

2004-03-04 Thread Andreas Rossberg
Simon Peyton-Jones wrote:
| Actually, #l is just syntactic sugar for (\{l=x,...}->x), which
implies
| that you might need type annotations.
Yes I was wrong to say that there are no implicitly-defined record
selectors; (#l r) is exactly that.  Syntactically I'd prefer (r.l); but
regardless, it's a syntactic construct distinct from function
application, which must be monomorphic.
I'm not sure I parsed your sentence correctly, but in SML, (#l r) indeed 
*is* a function application, and #l is a perfectly normal function, as 
its desugared form reveals. It just fails to have a principal 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's get rid of those possible thingies!  -- TB

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


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

2004-03-04 Thread Andreas Rossberg
Simon Peyton-Jones wrote:
If the big bug-bear is record selectors, let's focus on them
exclusively.  I now think that ML got it right. ML records are simply
labelled tuples.
Note that this is true only for SML, not for Caml.

So just as (Bool,Int) is an anonymous type, so is
{x::Bool, y::Int}.  Indeed (Bool,Int) is just shorthand for {#1::Bool,
#2::Int}.
A bit of nitpicking: (Bool,Int) would be shorthand for {1::Bool,2::Int}. 
In SML, labels may be numeric or alpha-numeric. OTOH, the hash is the 
projection operator (ASCII art for \pi), which can be used for both 
kinds of labels:

  #2 (x,y,z)
  #b {a=x, b=y, c=z}
Actually, #l is just syntactic sugar for (\{l=x,...}->x), which implies 
that you might need type annotations.

There are
no implicitly-defined record selectors either: you have to use pattern
matching for that.
Or projection using #.

Cheers,

	- Andreas

--
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
George Russell wrote:

> The most flexible but safe solution is to simply define the indentation
> as the sequence of indentation characters used. Two consecutive lines
> are indented consistently whenever one indentation is a prefix of the
> other. Hence you may freely mix different indentation characters, but
> you must be consistent across lines. Any decent editor should be 
able to
> ensure that.

Well no they won't, because some editors might replace blocks of 8 spaces
at the start of a line with TABs (or something like that), meaning that
8 and 7 spaces 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]
"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 listening to repetitive electronic music."
- Kristian Wilson, Nintendo Inc.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


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

2004-01-26 Thread Andreas Rossberg
George Russell wrote:
Graham Klyne wrote (according to Wolfgang Thaller, snipped):
 > I think that compilers should issue a warning when indentation that
 > determines the scope of a construct is found to contain tab characters.
In an ideal world, TAB characters would never have been put into ASCII, and
this would be my preferred solution.  However, since there would be some 
people
who would object to such purity, a better alternative might be
(a) to allow
m TABs followed by n spaces
at the start of lines.
(b) to denote the indention of the line by the two numbers (m,n).
(c) to give an error message when comparing two indentions 
(m1,n1),(m2,n2) where
neither m1<=m2,n1<=n2, nor m1>=m2,n1>=n2.

Incidentally Unicode allows far more possibilities for fun with 
indentation (for example
half-spaces, IIRC).
The most flexible but safe solution is to simply define the indentation 
as the sequence of indentation characters used. Two consecutive lines 
are indented consistently whenever one indentation is a prefix of the 
other. Hence you may freely mix different indentation characters, but 
you must be consistent across lines. Any decent editor should be able to 
ensure 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
 magic pills, and listening to repetitive electronic music."
 - Kristian Wilson, Nintendo Inc.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Type classes and code generation

2003-06-17 Thread Andreas Rossberg
Bayley, Alistair wrote:
When it's applied, the compiler will know the types of the arguments, won't
it?. Which means that you would generate a version of double for each
(applied) instance of Num. I don't doubt that there's a good reason this is
not done: code bloat? or are there simply some expressions that can't be
statically resolved?
I suppose I was thinking: is the language design sufficiently clever that
it's *always* possible for the compiler to infer the type instance in use,
or are there some situations where it's not possible to infer the instance,
so some kind of function dispatch mechanism is necessary?
This almost is an FAQ. Short answer: in general it is impossible to 
determine statically which instances/dictionaries are needed during 
evaluation. Their number may even be infinite. The main reason is that 
Haskell allows polymorphic recursion.

Consider the following (dumb) example:

f :: Eq a => [a] -> Bool
f [] = True
f (x:xs) = x == x && f (map (\x -> [x]) xs)
The number of instances used by f depends on the length of the argument 
list! Determining that statically is of course undecidable. If the list 
is infinite, f will use infinitely many instances (potentially, 
depending on lazy evaluation).

Another (non-Haskell-98) feature that prevents static resolution of type 
class dispatch are existential types, which actually provide the 
equivalent to "real" OO-style dynamic dispatch.

Of course, 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, [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 listening to repetitive electronic music."
 - Kristian Wilson, Nintendo Inc.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: forall quantifier

2003-06-04 Thread Andreas Rossberg
Ketil Z. Malde wrote:
I have a function declared as:

  anova2 :: (Fractional c, Ord b)
=> [a->b] -> (a->c) -> [a] -> [Anova1 c]
where the first parameter is a list of classifiers.  I could simplify
it, I guess, to something like
  classify :: Eq b => [a->b] -> [a] -> [[[a]]]
   ^^^
Isn't this one list too many?
  classify cs xs = ...

where for each classifying function in cs, I would get the xs
partitioned accordingly.  E.g.
  classify [fst,snd] [(1,0), (1,2), (2,0)] 

would yield

  [ [(1,0), (1,2)], [(2,0)] -- classified by `fst`
  , [(1,0), (2,0)], [(1,2)]] -- classified by `snd`
Now, obviously, the problem is that fst and snd, being passed in a
list, needs to be of the same type; this complicates classifying a
list of type [(Int,Bool)], for instance?.
What you'd need would be an existential type of the form

   classify :: [exists b. Eq b => a->b] -> [a] -> [[a]]

Such a type is not available directly in Haskell, but only through an 
auxilary data type:

  data Classifier a = forall b. Eq b => Classifier (a -> b)

Using that you should be able to implement

   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 listening to repetitive electronic music."
 - Kristian Wilson, Nintendo Inc.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: beginner's questions - fix f

2001-07-24 Thread Andreas Rossberg

Bob Koutsky wrote:
> 
> remainder a b = if a < b then a
>  else remainder (a-b) b
> 
> fix f = f (fix f)
> 
> Rewrite remainder using fix so that it is not recursive.
> 
> 
> Function fix left me completely puzzled. With help of hugs I found out that
> its type is "( a -> a ) -> a", but I have absolutely no idea how it could
> be used to do anything useful.

Function fix is a so-called fixpoint operator. Theory says that you can
formulate any computable function using only non-recursive definitions
plus fix.

> Can somebody provide me
> with an example how to use fix for something just a bit useful, if possible
> to rewrite remainder?

Try:

remainderF self a b = if a < b then a else self (a-b) b

remainder = fix remainderF

>From 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 kids.
 If Pac Man affected us as kids, we would all be running around in
 darkened rooms, munching pills, and listening to repetitive music."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Implict parameters and monomorphism

2001-05-03 Thread Andreas Rossberg

Lennart Augustsson wrote:
> 
> But most importantly, this was a bad example.  There was a much better
> one posted on this mailing list a while ago.  Does anyone remember it?

No, but this should do it:

data T = T Int

instance Show T where
show (T n) = show n

instance Eq

instance 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 would all be running around in
 darkened rooms, munching pills, and listening to repetitive music."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Implict parameters and monomorphism

2001-05-02 Thread Andreas Rossberg

John Hughes wrote:
> 
> I think it's important to have a simple model of how many
> times expressions are evaluated. Function bodies are clearly
> evaluated many times, once for each call, but non-function
> bindings should be evaluated at most once to respect
> call-by-need semantics.

Maybe I misinterpret the Haskell Report but I thought it does not even
demand call-by-need evaluation (it only speaks of non-strict semantics).
So why have a special rule in the language definition to support
something cbn-ish for this particular case? As long as the Report does
not specify any execution model the MR looks rather arbitrary to me.

> Breaking the monomorphism restriction in ANY case makes both
> space and time cost of evaluation unpredictable, and brittle
> when program changes elsewhere introduce or remove an implicit
> parameter. It isn't good enough to say `the chances are' that
> a program has, for example, linear time and constant space
> complexity: the programmer should be able to convince himself
> of such properties.

Why isn't it good enough if the compilers give warnings then? The Report
could even require 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 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."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: help wanted with type error message

2001-04-04 Thread Andreas Rossberg

Norman Ramsey wrote:
> 
> > data Formula f => Row a = Row (f a, Weight)
> > type Weight = Float
> 
> Hugs rejects this program:
> 
> ERROR "hard.lhs" (line 14): Undefined type variable "f"

Right, f is not bound in the declaration of Row. Only the occurances of
type variables after the type constructor are binding occurances.

The fix is to turn Row into a binary constructor:

> data Formula f => Row f a = Row (f a, Weight)

BTW, contexts have no real meaning in data declarations - the
declaration above does not prevent you from writing

> 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."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Inferring from context declarations

2001-02-22 Thread Andreas Rossberg

Lennart Augustsson wrote:
> 
> Incidentally, this has nothing to do with allowing polymorphic recursion
> on functions in Haskell.  It could be done earlier too, but then it had
> to be encoded using a class and instance declaration.

I would argue that methods are in fact polymorphically 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 running around in
 darkened rooms, munching pills, and listening to repetitive music."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Inferring from context declarations

2001-02-21 Thread Andreas Rossberg

George Russell wrote:
> 
> I'm sorry if this is a FAQ, but I'm curious to know why Haskell (or at least, GHC 
>and Hugs)
> doesn't seem able to use contexts on variables at the front of data declarations.

There has been some discussion on contexts on data declarations during
the Haskell 98 standardization process. See:

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=302

I think this discussion also lead John Hughes to write his paper on
"Restricted Datatypes in Haskell" which is available from his homepage:

http://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."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Inferring from context declarations

2001-02-21 Thread Andreas Rossberg

George Russell wrote:
> 
> (3) Simon Peyton Jones' comments about dictionary passing are a red herring,
> since they assume a particular form of compiler.  Various (MLj, MLton)
> ML compilers already inline out all polymorphism. Some C++ compilers/linkers
> do it in a rather crude way as well, for templates.  If you can do it,
> you can forget about dictionary passing.

Such monomorphisation is not possible for Haskell in general, because it
allows polymorphic recursion. As a consequence, the number of
dictionaries constructed for a given program also 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."

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Doing IO in foldr repeats lines?

2001-01-23 Thread Andreas Rossberg

Ian Lynagh wrote:
> 
> > main :: IO()
> > main = do _ <- foldl foo (return 14) ["qq\n", "ww\n", "ee\n"]
> >   putStr ""
> 
> > foo :: IO Int -> String -> IO Int
> > foo io_l s = do l <- io_l
> > () <- putStr s
> > io_l
> 
> prints (with both GHC and hugs):
> 
> qq
> ww
> qq
> ee
> qq
> ww
> qq
> 
> and I really don't understand why. Is the code re-evaluated every time
> foldl is expanded or something?

Nobody seems to have answered yet, so I try to explain it.

Look at your definition of foo: it actually duplicates its argument
action io_l. For the first application io_l is (return 14). Let's call
that io_l0. The resulting action is

io_l1 = do { l <- return 14; () <- putStr "qq"; return 14 }

which is passed at the next application. The result is

io_l2 = do { l <- do { l <- return 14; () <- putStr "qq"; return 14 }
   ; () <- putStr "ww"
   ; do { l <- return 14; () <- putStr "qq"; return 14 }
   }

This can be reformulated as

io_l2'= do { l  <- return 14
   ; () <- putStr "qq"
   ; l  <- return 14
   ; () <- putStr "ww"
   ; l  <- return 14
   ; () <- putStr "qq"
   ; return 14
   }

And so on. Finally the complete action (io_l3) is executed by running
main and produces the output you observe.

Hope this helps,

- Andreas

-- 
Andreas Rossberg, [EMAIL PROTECTED]

:: be declarative. be functional. just be. ::

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



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, [EMAIL PROTECTED]

:: be declarative. be functional. just be. ::

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: class instance with nested types

2000-10-27 Thread Andreas Rossberg

Matthias Höchsmann wrote:
> 
> > type Sequence a = [a]
> > data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> > type Forest a = Sequence (Tree a)
> 
> i want to construct a class Xy
> 
> > class Xy s a where
> >  test :: s a -> a
> 
> [...]
> 
> > instance  ([] Tree) Char where
> > test x@(N a xs):txs = a

To make it syntactically correct this should at least be something like

> instance Xy ([] Tree) Char where
> test (N a xs:txs) = a

But the real problem is in the expression ([] Tree), which is the same
as writing [Tree]. 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.

What you are trying to say is probably something like this:

> instance Xy (\a . [Tree a]) Char  -- not Haskell

But unfortunately there are no lambdas on the type level - they would
render the type system undecidable. For the same reason it is not
allowed to use a type synonym in an instance declaration:

> instance Xy Forest Char   -- illegal

The only thing you can do is turning Forest into a data type:

> data 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. ::

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Higher-order function application

2000-08-23 Thread Andreas Rossberg

"Ch. A. Herrmann" wrote:
> 
> the problem is that we loose much of the strength the Haskell type
> system provides and a lot of programming errors will remain
> undetected.

Moreover, it is completely incompatible with polymorphic typing and type
inference, because you overload notation. Consider for example a
definition like

f x y = x y

How do you want to type this if actually application syntax can mean
many different things? Using your rules, f could be typed

f :: (a -> b) -> a -> b
f :: (a -> b) -> (c -> a) -> (c -> b)
f :: (a -> b, c -> d) -> (a,c) -> (b,d)
f :: (a -> b -> c) -> (a,b) -> c
f :: (a -> b) -> [a] -> [b]
...

all of which are incompatible. Also note that operators like (+) usually
have no special status in functional languages, they are ordinary
functions. So giving them special typing rules is a bad idea. Similarly,
types like [] should have no special meaning besides being predefined.

It's better to say what you mean, overloading is your enemy! (Well, not
counting Haskell style "overloading" through type 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

"Frank A. Christoph" wrote:
> 
> It seems to me that a compiler would be an ideal candidate for being written
> in an imperative language. The number of times GHC has been too slow and
> memory-hungry for me indicates that Haskell is not suitable for writing
> anything as general-purpose as a compiler.
>
> Food for thought. :) I'm in an equivocal mood tonight...

[OK, I'll jump in :-)]

Of course, the first sentence is an invalid generalization. It may (or
may not -- I hope time will prove you wrong and Haskell code will
improve performance-wise) be true that Haskell is not suitable for
writing compilers. But this does not imply that FPLs in general are not
suitable for writing compilers -- or even less suitable than imperative
languages...

It seems to be folklore in the FP community that functional languages
are perfect for this task. After all, it is what they are mainly used
for :-|. I wouldn't dare writing such a beast without pattern matching,
higher-order functions, a powerful type system, and strong support for
recursion -- things imperative languages usually lack completely. OTOH I
have to admit that imperative features 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'.)

- Andreas

-- 
Andreas Rossberg, [EMAIL PROTECTED]

:: be declarative. be functional. just be. ::



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
> > to me much more powerful, since I can add dancing and singing methods
> > to objects without having to go back to the original class definition.
> 
> 1) Dynamic types.  You can't cast up.

You certainly mean to cast down (casting upwards corresponds to the
application of the existential constructor).

Down casts could be done. This would mean that each existential
constructor had to carry dynamic type information and there would be a
special pattern matching construct that checks this. One could argue
whether this feature is desirable or worthwhile in the presence of
parametric polymorphism and algebraic data types.

> 2) More specific types, you can't _easilly_ call the more general type.
> For example in OO this is very commen:
> 
> class Base
>   virtual foo()
> do stuff
> 
> class Derived, extends Base
>   foo()
> call Base::foo()
> doo stuff

I guess what you mean by "more specific types" is inheritance. This is
not directly related to types, though. You are right, Haskell does only
provide a very weak form of inheritance, namely default methods. On the
other hand, many people consider inheritance a doubtful feature.

> 3) Encapsulation.  You can't have private and protected members.  Some
> of this can be done using modules.  However it is more work.

Maybe, but I think it's good to have this separation of concepts:
classes provide a certain form of polymorphism, encapsulation is
something completely different that should be dealt with uniformingly,
i.e. by the module system. However, it would be nice if Haskell had a
more powerful module language.

> 4) Cleaner more natural syntax.

>From an abstract language point of view, there certainly is nothing
natural or even clean in having this special case syntax for the first
argument:

x.f y z

compared to

f x y z

In particular, it does not scale to methods where the first parameter
does not happen to be of the type to dispatch on (or where there
actually are zero or multiple such xs, cf. the binary method and multi
dispatch problems in OOP).

For certain problem domains however it might appear to be natural to
think in terms of objects that receive messages. But I'm not sure
whether this has to be reflected in syntax too much. Haskell is not an
object-oriented language. You can express most things that you can
express in OO languages but they will look a bit different. And
sometimes of course it will be more painful - but no single language can
be equally well-suited for every application.

> Unfortunately Haskell, like Java in some ways, is also a simple language.

Java is much more complex than most people realize. And Haskell is far
from being a simple language either. So adding even more features
requires compelling reasons, in particular, if there are already ways to
achieve the same effect without too much extra effort.

But of course, in comparison with C++ any language looks simple. ;-)

> I would like to be able to do the things in Haskell that I can do in C++
> but currently Haskell's type system is too simple to allow me to do
> them.

You are mixing up things a little bit. The Haskell type system
definitely is not simple. It is likely to be the most complex and
powerful type system of any major language around. The reason why there
are things that you can do in C++ but not in Haskell is that C++ does
not press typing that much. Templates for example are not really type
checked. That gives you flexibility at the price of safety or early
error detection.

Another aspect you mentioned in one of your postings is state. Again
this is not directly related to the expressiveness of Haskell's type
system. C++, like most other languages, simply ignores state in its type
system. So of course you won't have any problem as far as typing is
concerned. Haskell does capture the use of state in its types - being a
curse and a blessing.

Best regards,

- Andreas






Re: Units of measure

1999-08-26 Thread Andreas Rossberg

"D. Tweed" wrote:
> 
> Isn't the issue a bit weirder than this in that you've also got pure
> numbers which ought be usable with the same operators (*$,etc)

You are right, I overlooked that. But this is not even the most serious
problem, overloading the operators 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

Tom Pledger wrote:
> 
> Where do units of measure fit into a type system?

In Haskell this should be quite easy. Off my head I would suggest
something like

class Unit a where
unit  :: Float -> a
value :: a -> Float

newtype Metres  = Metres Float
newtype Seconds = Seconds Float

instance Unit Metres where
unit = Metres
value(Metres x) = x
instance Unit Seconds where
unit = Seconds
value(Seconds x) = x

newtype Prod a b = Prod Float
newtype Quot a b = Quot Float

instance (Unit a, Unit b) => Unit(Prod a b) where
unit = Prod
value(Prod x) = x
instance (Unit a, Unit b) => Unit(Quot a b) where
unit = Quot
value(Quot x) = x

infix 7 *$, /$
infix 6 +$, -$

(+$) :: (Unit a) => a -> a -> a
(-$) :: (Unit a) => a -> a -> a
(*$) :: (Unit a, Unit b) => a -> b -> Prod a b
(/$) :: (Unit a, Unit b) => a -> b -> Quot a b
x +$ y = unit(value x + value y)
x -$ y = unit(value x - value y)
x *$ y = Prod(value x * value y)
x /$ y = Quot(value x / value y)

m  = Metres 5
s  = Seconds 2
m' = m +$ m -- OK: Metres
m2 = m *$ m -- OK: Prod Metres Metres
v  = m /$ s -- 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,

- Andreas

-- 
Andreas Rossberg, [EMAIL PROTECTED]

:: be declarative. be functional. just be. ::





Re: The dreaded layout rule

1999-08-12 Thread Andreas Rossberg

Simon Marlow wrote:
> 
> > Does it mean that the following expressions would be illegal?
> >
> > if cond then do proc1; proc2 else do proc3; proc4
> > (case e of Just x -> x > 0; Nothing -> False)
> 
> Unfortunately, yes.
> 
> > Now one can forget about {} and use layout everywhere. He would no
> > longer be able to forget or he would have to split some expressions
> > into indented lines, even when they are unambiguous in one line.

You could just enumerate all keywords that allow/enforce insertion of }.
A suitable list for Haskell 98 might be:

in
where
)
]
module
type
data
newtype
class
instance
default

In fact I think that this would be the cleanest and simplest rule. (At
least that is how I once implemented layout similar to Haskell'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

Simon Peyton-Jones wrote:
> 
> *  Comments *start* with a lexeme, as previously discussed, and I think
>this is fine.
> 
> *  The opening lexeme may be '--', '---' etc for ordinary comments, or
>'{-' for nested comments
> 
> * Note that '{--' is not a lexeme at all, so the maximal munch rule won't
>   munch it.  Hence '{--' lexes as '{-' followed by stuff; it does start
>   a nested comment.
> 
> * Nested comments are closed, as in all earlier Haskells, by character by
>   character 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 quite a bit,
because any expression can now contain arbitrary module code -- the
module system no longer rests on top of the core language.

> I imagine that it could be translated into SML along these lines
> (excuse my rusty SML):
> 
>   structure M = struct ... val y = ref  ... end;
>   structure X =
> struct
>   fun f(x,y) = M.y := y; ... !M.y ...
> end;
> 
> Or maybe not.  I'm not sure of the extent of the feature, but I get the 

Not really. First of all, f will not be re-entrant (e.g. recursion won't
work). You had to save and restore the previous value. But that's not
all: consider the following (admitedly contrieved) code for example

let rec f x = let module M = struct exception E end
  in match x with M.E -> ()
| _   -> f M.E

A call like f(some_exn) will not terminate because M.E is different on
each recursion. You can observe similar effects using references. The
point here is that modules (and all the generative objects in it, like
references, exceptions, modules, etc.) are really created at runtime,
while without the let-module feature, all module instances are
determined at compile time.

Also, the main motivation for introducing it was to allow functor
applications that depend on polymorphic type variables. I think these
cannot be translated (as far as typing is concerned).

(In case somebody is still interested. But this has far left the scope
of the Haskell list now.)


> You're right, though.  I meant expression-local imports, like
> 
>   local open M
>   in ...

\begin{nitpicking}

You probably mean

let open M
in ...

\end{nitpicking}

And I agree, these are very useful sometimes (although I wouldn't call
that import).

- Andreas





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 the core language.

- Andreas





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 whatever option one chooses. So I can see no real
> ] advantage in disallowing identifiers starting with '_'.

IMHO the simplest rule would be to allow '_' anywhere a lowercase letter
is
allowed. And "_" becomes just an ordinary keyword.

Cheers,
- Andreas





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 not seem to be the correct URL. I had better luck with:

http://www.dcs.gla.ac.uk/~simonpj/multi-param.html


- Andreas





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
doc (x:<|>y) is constructed is in the function `group':

group z   = flatten z :<|> z

So the x above is always flat already. Wouldn't the equation

flatten (x :<|> y) = x

suffice? Doing recursion here seems to be unnecessary overhead. In
particular, it prevents structure sharing between alternatives when
grouping, because flatten rebuilds the whole doc tree (which might be
more of a problem without laziness).

Am I missing something?


- Andreas





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.
> Wouldn't `<-' have been a better choice?  `<-' bindings are never
> recursive, thus `R{ x <- x } is less surprising, as the two x's can't
> be the same.


What about using constructor syntax: R{ X x } ?

Not to be taken too seriously...

- Andreas