Re: Haskell and the NGWS Runtime

2000-08-10 Thread Tyson Dowd

On 10-Aug-2000, Brent Fulgham <[EMAIL PROTECTED]> wrote:
> > You can download it here:
> > http://msdn.microsoft.com/net/#sdk
> > 
> > There is a C# compiler and runtime environment in the SDK.
> > 
> 
> Thanks for the link!  Unfortunately, its click-through
> license forbids disassembly, reverse engineering, and a
> raft of other endeavors that one should be allowed if they
> were truly interested in global acceptance.  

Unfortunately this is pretty standard stuff for proprietary
software.  I have certainly made it clear to Microsoft that
licensing conditions are a significant impediment to them being taken
seriously by academics.

> [stuff about poorly written C# stuff]

I think most of the C# press has been written to impress VB and C++
programmers.  I also find it shockingly written and hopelessly
uninformed.  But I'm sure the intended audience thinks it's just
wonderful.

> > Microsoft spent around $2M funding a bunch of groups working 
> > on research and industrial programming languages to give 
> > feedback on their work. (Haskell, Mercury, ML, Scheme, Oberon,
> > Eiffel, Python, Oz, etc...)  While they acknowledged from the
> > start that getting any changes (apart from tailcall) into 
> > version 1 was pretty unlikely, they have been listening, 
> > taking notes, and even now the C# folks are getting
> > excited about the idea of putting generics into the language.
> > 
> Well, that sounds good.  Are you speaking from personal knowledge
> here?  My concern is that although they may have spoken with
> these various teams, I really don't see much in C# that looks
> like they took any of the comments to heart.  In fact, it looks
> like they took J++, changed the name, and added a few nasty things
> (like labeled "gotos").

They didn't really want any feedback on C#.  C# was always going to be
what it is, another simple object-oriented C derivative language.
I'm kind of annoyed they released C# at the same time as all this other
stuff, because everyone is focusing on the "new language" when the real
interesting stuff is under the hood.

What is underneath C# is a runtime system that can run lots of different
languages.  That's what they wanted the feedback on.  C# is just one
language that runs on it, MS will also run C++ (well a lot of it) and VB
on it.  Other vendors will run their own languages on it.  You get cross
language debugging, data-level interoperability, unified memory
management, etc.  It's a bit like the JVM without the insistance that it
be 100% Java.

Oh, yes I am speaking from personal knowledge.  Mercury got some of that
funding. 

> In fact, if they were interested in learning anything, why
> did they solicit feedback so late in the game?

There's often some sort of assumption that because they are rich and
powerful, they are also omnipotent.  By the time they figured out they
should do this, got a budget for it, shortlisted the groups, 
flew around the world and explained it to 20 different groups, signed
non-disclosure agreements, and gave out the work they had done so far,
quite a bit of time had passed.

> The thing that really bothers me is that they claim that ".NET
> will be available on Windows (C) and other systems".  But they
> have no reference implementations available for non-Windows (C)
> environments.  When Sun released Java, we had Unix and Windows
> versions available right away, and the Linux Blackdown port
> shortly thereafter.

Yes, but real support for Linux has been very slow in coming from Sun,
as Linux is a competitor.  

I don't really expect MS to release a non-Windows implementation.
But I wouldn't be the least bit surprised if they decide to pay someone
to do a Linux version (possibly even an open source version).

> Thanks for your feedback, Tyson, but I'm afraid I still don't
> see much to recommend it.  And .NET's heavy dependence on older
> MS technologies (such as COM objects, etc.) is especially
> distasteful.

AFAIK there is no dependence on COM.  There is builtin COM interop, in
much the same way that you can have CORBA interop in Java.  (You
shouldn't believe everything you read on Slashdot).

Of course apps might depend on COM, but that's a different issue.

I'm not trying to convince anyone to use it.  That's Microsoft's
job.  I'm mostly interested in fostering the good ideas that are in .NET
and making sure they become popular and widespread.  I'd love it if Sun
took the good bits and put them straight into JVM 2.

-- 
   Tyson Dowd   # 
#  Surreal humour isn't everyone's cup of fur.
 [EMAIL PROTECTED]# 
http://www.cs.mu.oz.au/~trd #




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Tyson Dowd

On 10-Aug-2000, Theodore Norvell <[EMAIL PROTECTED]> wrote:
> Thanks to Nigel for answering my question
> 
> Tyson Dowd wrote:
> > > Microsoft indicates that C# will not support "genericity", through
> > > even anything as crude as C++'s templates, so it is unlikely that
> > > they will seek to support functional programming languages in the
> > > short term.  Perhaps this limitation is part of the impetus for the
> > > Mondrian variant.

Please be careful with attribution, I did not write that.

-- 
   Tyson Dowd   # 
#  Surreal humour isn't everyone's cup of fur.
 [EMAIL PROTECTED]# 
http://www.cs.mu.oz.au/~trd #




Re: GC in embedded systems (was Re: Haskell and the NGWS Runtime)

2000-08-10 Thread Manuel M. T. Chakravarty

Adrian Hey <[EMAIL PROTECTED]> wrote,

> My objection to the use of GC (and by implication all current Haskell
> implementations) in embedded systems would be that if your program is
> sufficiently complex/powerful that it can't be implemented as some kind
> of _finite_ state machine, then it can never be part of a robust system
> (which has finite memory resources). Put simply, if you don't know how
> much memory you need, how can you ever be confident you have enough?
> 
> Hmm, now having written that, I'm wondering how the Erlang community
> addressed this problem. I believe Erlang is targeted at applications
> which I would class as 'embedded'.
> 
> Anybody know the answer?

Erlang applications are characterised as being soft-realtime
applications:

  http://www.erlang.org/faq/x847.html#SOFT-REALTIME

In one sentence, I would characterise this as ``it is fast
enough most of the time.''  This seems to be good enough for
many (most?) embedded systems.

I see your point about insisting on finite state machines,
but as the functionality expected from embedded systems
increases, this ideal viewpoint will become increasingly
infeasible in practice.

Manuel




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Manuel M. T. Chakravarty

Byron Hale <[EMAIL PROTECTED]> wrote,

> At 06:46 PM 8/10/2000 -0400, you wrote:
> >What bothers me most about C# is that although, at first glance, it seems 
> >to be a variation on Java, it doesn't follow the spirit of Java in at 
> >least one important respect.
> >
> >Specifically, one common advantage of both Haskell and Java is that they 
> >encourage higher-order abstraction:  Haskell through functional 
> >abstraction, and Java through eliminating explicit pointers and memory 
> >management and enforcing object orientation through the use of classes.
> >
> >However, according to the C# Language Reference (at 
> >http://msdn.microsoft.com/vstudio/nextgen/technology/csharpdownload.asp), 
> >"For developers who are generally content with automatic memory management 
> >but sometimes need fine-grained control or that extra iota of performance, 
> >C# provides the ability to write "unsafe" code. Such code can deal 
> >directly with pointer types, and fix objects to temporarily prevent the 
> >garbage collector from moving them." [Section 1.2]
> 
> Other issues aside, garbage collection is not the only form of automatic 
> memory management. Also, garbage collection is unlikely to satisfy any need 
> for automatic memory management in real-time systems for the foreseeable 
> future because an extra thread on a single processor is still 
> non-deterministic. 

I am far from being an expert on realtime systems, but AFAIK
the important thing is to be able to guarantee that a given
operation executes in a given bounded time frame.  In other
words, it need not be deterministic as long as the
indeterminism is within predictable bounds, ie, guaranteed
to be sufficiently small.  So by guaranteeing that the extra
thread can take only a fixed amount of time, it should be
possible to meet the realtime constraint, shouldn't it?

Manuel




Re: GC in embedded systems (was Re: Haskell and the NGWS Runtime)

2000-08-10 Thread Byron Hale

At 05:21 AM 8/11/2000 +0100, you wrote:
>On Fri 11 Aug, Byron Hale wrote:
> > Also, garbage collection is unlikely to satisfy any need
> > for automatic memory management in real-time systems for the foreseeable
> > future because an extra thread on a single processor is still
> > non-deterministic.
>
>I'm not sure this is true, doesn't it depend on the scheduling strategy?
>I've written a lot of code for single and multiple processor DSP systems,
>and typically have multiple threads (on 1 processor).
>But they are still entirely deterministic.
>
>Regards
>--
>Adrian Hey


I don't mean that threads are non-deterministic, but that the execution 
time of a GC thread seems to be non-deterministic. Large collections need 
more time than small ones and the time required is some function of the 
store to be collected, is it not?  If the store to be collected is created 
at a greater rate than it can be collected, then a garbage-collected system 
would seem to be be expected to crash eventually.

ML-Kit has implemented some work on compile-time memory management using 
regions. I wonder if that might not be more practical than garbage 
collection, in real-time systems.

Best Regards,

Byron Hale
[EMAIL PROTECTED]






Re: Haskell and the NGWS Runtime

2000-08-10 Thread Lyndon While

At 6:46 pm -0400 10/8/2000, Benjamin Leon Russell wrote:
>Somebody once wrote that a clearly written, well-documented program 
>that doesn't work is usually more valuable than a badly written, 
>poorly-documented program that does work because it can easily be 
>fixed and reused.

Who wrote this?

Is it just a rumour or is there a reference that I can give to my students?

--
Lyndon While


Email  - [EMAIL PROTECTED],-_|\
Phone  - +61 8 9380 2720/ \
Fax- +61 8 9380 1089*_,-._/
Web- http://www.cs.uwa.edu.au/~lyndonv




GC in embedded systems (was Re: Haskell and the NGWS Runtime)

2000-08-10 Thread Adrian Hey

On Fri 11 Aug, Byron Hale wrote:
> Also, garbage collection is unlikely to satisfy any need 
> for automatic memory management in real-time systems for the foreseeable 
> future because an extra thread on a single processor is still 
> non-deterministic.

I'm not sure this is true, doesn't it depend on the scheduling strategy?
I've written a lot of code for single and multiple processor DSP systems,
and typically have multiple threads (on 1 processor).
But they are still entirely deterministic.

BTW, I've never really understood how it is that garbage collection is
a separate thread in Java (as I've heard it is, but I have never used Java).
The implication is that somehow Java progs keep running while garbage
collection is performed concurrently.

Is this true? If so how does this work?

It seems to be a hard thing to do if the GC uses pointer some variant of
mark-sweep and pointer reversal. I guess if reference counting and fixed
cell size was used this could be possible, but this won't work with cyclic
data structures.

My objection to the use of GC (and by implication all current Haskell
implementations) in embedded systems would be that if your program is
sufficiently complex/powerful that it can't be implemented as some kind
of _finite_ state machine, then it can never be part of a robust system
(which has finite memory resources). Put simply, if you don't know how
much memory you need, how can you ever be confident you have enough?

Hmm, now having written that, I'm wondering how the Erlang community
addressed this problem. I believe Erlang is targeted at applications
which I would class as 'embedded'.

Anybody know the answer?

It seems a sad irony if the memory management techniques used to implement
declarative languages (which are designed to ensure program 'correctness',
aren't they?) also ensure program 'flakeyness' at run time (on real machines). 

Regards
-- 
Adrian Hey





Re: Haskell and the NGWS Runtime

2000-08-10 Thread Manuel M. T. Chakravarty

Ketil Malde <[EMAIL PROTECTED]> wrote,

> "Manuel M. T. Chakravarty" <[EMAIL PROTECTED]> writes:
> 
> > A good analysis of were C# fits re Java and C++ is at
> > 
> >   http://slashdot.org/article.pl?sid=00/08/09/1612254&mode=thread
> 
> Wherein we read:
> 
> > One new feature that I mentioned already was that of copy-by-value
> > objects. This seemingly small improvement is a potentially huge
> > performance saver! With C++, one is regularly tempted to describe the
> > simplest constructs as classes, and in so doing make it safer and
> > simpler to use them. For example, a phone directory program might
> > define a phone record as a class, and would maintain one PhoneRecord
> > object per actual record. In Java, each and every one of those objects
> > would be garbage collected!
> 
> Now, is this really such a big problem?  Is it a problem because of
> Java's mark-and-sweep, and if so, couldn't you apply a better GC?

That's exactly what I thought.  I mean why don't they read a
couple of research papers?  It is not so that they are the
first to run into these problems.  At a related issue, have a
look at the memory management in the Realtime Java spec that
Sun is just about to finalise.  It seems they want to ignore
the existence of generational and concurrent GC altogether
*sigh*

Manuel




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Antony Courtney

Benjamin Leon Russell wrote:
> 
> [example of an unsafe method in C#]
>
> Taken to an extreme, this ability could encourage some programmers to
> ignore the spirit of higher-level abstraction and focus back on The Old
> Way (TOW):  rampant pointer-level optimization to squeeze out that extra
> iota of performance at the expense of clarity.  

But Java also has a way to do "rampant pointer-level optimization":  You declare
a method as "native" and then implement it in C.  

Any sensible programmer will recognize the loss of portability, safety and
abstraction when writing a native method in Java, and will only do so when
absolutely necessary.  The same should go for "unsafe" methods in C#, UNSAFE
modules in Modula-3, and "unsafePerformIO" in various Haskell implementations.

C# simply provides a mechanism to write native methods within the C# language
directly instead of dropping down to C.  I haven't looked too closely at C#, but
I would imagine that even unsafe C# has less "implementation defined" pitfalls
than C and other features useful for systems hacking (e.g. exceptions), and
therefore even "unsafe" C# might be a better language for doing the kinds of
low-level systems hacking that Java only permits you to do in C.  This was
certainly true for "unsafe" modules in Modula-3.  

Remember, too, that not every program is written as an application on a PC.  The
requirement in Java that native methods be implemented in another language
caused serious problems for the JavaOS and embedded / JVM-on-a-chip efforts. 
How do you write a device driver for a memory-mapped device in 100% pure Java? 
You can't.  The "unsafe" provision in C# might make C# a more viable language
for such systems.

-antony

-- 
Antony Courtney  
Grad. Student, Dept. of Computer Science, Yale University
[EMAIL PROTECTED]  http://www.apocalypse.org/pub/u/antony




Re: doubles

2000-08-10 Thread Ralf Muschall

Sebastian Schulz <[EMAIL PROTECTED]> writes:

> John Peterson wrote:
> > Or you can just set USE_DOUBLE_PRECISION in options.h if you want to

I did that (to be precise, I had to do it every time when building
hugs :-(  ).

pi::Double is defined by the prelude as primPiDouble, and this
seems to be hardcoded to 3.1415926535 in old hugsen (I just looked
into verion 990121).

. Consequently, 
pi-4*atan 1
gives
-8.97930619e-11 :: Double
which looks reasonable (for appropriate values of "reasonable").

> Same question as to Jan :
> how many significant digits will that change give me?

Maybe none, depending on the version.
990525 says pi=4*atan 1.

It seems I should upgrade as well (my installed one is here is still 990121).

Ralf




RE: Why is the following not lazy?

2000-08-10 Thread Sigbjorn Finne


Hi,

you'll need to loosen up your data dependencies a little.
Consider the following expression,

   let action = a1 >> a2 >> ... >> an in runI action

'runI' forces the evaluation of an IState, which according
to your (>>=) defn, action's IState will be the one that 'an'
evaluates to/returns.

Hence, in your particular example, you won't see any output
until 'an' has been evaluated ==> no output will appear until
the end of the input has been seen.

One way out is to define (>>=) as follows:

   (I c1) >>= fc2 = I $ \s0 -> 
   let (r,s1)   = c1 s0
   (I c2)   = fc2 r
   (r2, s2) = c2 (s1{io=return ()})
 in
 (r2, IState { io = io s1 >> io s2})

or, redefine your monad to distinguish between output &
the (threaded) interaction state.

hth
--sigbjorn


> -Original Message-
> From: Sengan [mailto:[EMAIL PROTECTED]]
> Sent: Thursday, August 10, 2000 16:54
> To: [EMAIL PROTECTED]
> Subject: Why is the following not lazy?
> 
> 
> I'm writing a program that involves the use of an interaction
> Monad. However it seems to be insufficiently lazy to provide
> any interaction. The following code is derived from my original
> but highly simplified. Why is "works" lazy, but "main" is not?
> 
> Thanks for any help
> 
> Sengan
> 
> > module Main(main) where
> > import IO
> 
> --
> --
> 
> > works
> >   = hGetContents stdin >>= \input ->
> > foldr (>>) (return ()) $ map putStr $ lines input
> 
> --
> --
> 
> > main
> >   = hGetContents stdin >>= \input ->
> > runI $ foldr (>>) (return "") $ map output $ lines input
> 
> > data IState = IState { io :: IO () }
> 
> > data I a= I (IState -> (a, IState))
> 
> > instance Monad I where
> >return k   = I $ \s  -> (k,s)
> >(I c1) >>= fc2 = I $ \s0 -> let (r,s1) = c1 s0
> >I c2   = fc2 r in
> >c2 s1
> 
> > runI (I c) = let (result, state) = c (IState $ return ()) in
> >  io state >> return ()
> 
> > output string
> >   = I $ \s -> (string, s { io = (io s) >> putStr (string ++ "\n") })
> 




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Byron Hale

At 06:46 PM 8/10/2000 -0400, you wrote:
>What bothers me most about C# is that although, at first glance, it seems 
>to be a variation on Java, it doesn't follow the spirit of Java in at 
>least one important respect.
>
>Specifically, one common advantage of both Haskell and Java is that they 
>encourage higher-order abstraction:  Haskell through functional 
>abstraction, and Java through eliminating explicit pointers and memory 
>management and enforcing object orientation through the use of classes.
>
>However, according to the C# Language Reference (at 
>http://msdn.microsoft.com/vstudio/nextgen/technology/csharpdownload.asp), 
>"For developers who are generally content with automatic memory management 
>but sometimes need fine-grained control or that extra iota of performance, 
>C# provides the ability to write "unsafe" code. Such code can deal 
>directly with pointer types, and fix objects to temporarily prevent the 
>garbage collector from moving them." [Section 1.2]
>
>Taken to an extreme, this ability could encourage some programmers to 
>ignore the spirit of higher-level abstraction and focus back on The Old 
>Way (TOW):  rampant pointer-level optimization to squeeze out that extra 
>iota of performance at the expense of clarity.  But wasn't the whole point 
>of higher-level abstraction to leave this level of optimization to more 
>intelligent compilers so that the programmer could focus on writing clear, 
>reusable code?  Why allow us to get TOW'ed back (pardon the pun)?
>
>Somebody once wrote that a clearly written, well-documented program that 
>doesn't work is usually more valuable than a badly written, 
>poorly-documented program that does work because it can easily be fixed 
>and reused.  It just seems that allowing programmers the ability to 
>manipulate pointers directly is virtually hiding a Pandora's Box in C#.
>
>--Benjamin L. Russell
>[EMAIL PROTECTED]
>[EMAIL PROTECTED]

Other issues aside, garbage collection is not the only form of automatic 
memory management. Also, garbage collection is unlikely to satisfy any need 
for automatic memory management in real-time systems for the foreseeable 
future because an extra thread on a single processor is still 
non-deterministic. Furthermore, embedded systems tend to be commodities, 
hence multiple processors are rare. In fact, a developer is lucky to have a 
general stack machine in an embedded system. Everything is typically based 
on the end price.

So maybe it would be even better to be able to just turn off garbage 
collection altogether in some applications, if one had an alternative form 
of automatic memory management.

Best Regards,

Byron Hale
[EMAIL PROTECTED]





Why is the following not lazy?

2000-08-10 Thread Sengan

I'm writing a program that involves the use of an interaction
Monad. However it seems to be insufficiently lazy to provide
any interaction. The following code is derived from my original
but highly simplified. Why is "works" lazy, but "main" is not?

Thanks for any help

Sengan

> module Main(main) where
> import IO



> works
>   = hGetContents stdin >>= \input ->
> foldr (>>) (return ()) $ map putStr $ lines input



> main
>   = hGetContents stdin >>= \input ->
> runI $ foldr (>>) (return "") $ map output $ lines input

> data IState = IState { io :: IO () }

> data I a= I (IState -> (a, IState))

> instance Monad I where
>return k   = I $ \s  -> (k,s)
>(I c1) >>= fc2 = I $ \s0 -> let (r,s1) = c1 s0
>I c2   = fc2 r in
>c2 s1

> runI (I c) = let (result, state) = c (IState $ return ()) in
>  io state >> return ()

> output string
>   = I $ \s -> (string, s { io = (io s) >> putStr (string ++ "\n") })




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Craig Dickson

Benjamin Leon Russell wrote:

> However, according to the C# Language Reference,
> "For developers who are generally content with
> automatic memory management but sometimes need
> fine-grained control or that extra iota of
> performance, C# provides the ability to write
> “unsafe” code. Such code can deal directly with
> pointer types, and fix objects to temporarily
> prevent the garbage collector from moving them."
> [Section 1.2]

I hadn't known that. Guess I didn't read far enough, or perhaps it wasn't
covered in the book I was reading. I agree that this is likely to be abused.

Craig






Re: Haskell and the NGWS Runtime

2000-08-10 Thread Benjamin Leon Russell

What bothers me most about C# is that although, at first glance, it seems to be a 
variation on Java, it doesn't follow the spirit of Java in at least one important 
respect.

Specifically, one common advantage of both Haskell and Java is that they encourage 
higher-order abstraction:  Haskell through functional abstraction, and Java through 
eliminating explicit pointers and memory management and enforcing object orientation 
through the use of classes.

However, according to the C# Language Reference (at 
http://msdn.microsoft.com/vstudio/nextgen/technology/csharpdownload.asp), "For 
developers who are generally content with automatic memory management but sometimes 
need fine-grained control or that extra iota of performance, C# provides the ability 
to write “unsafe” code. Such code can deal directly with pointer types, and fix 
objects to temporarily prevent the garbage collector from moving them." [Section 1.2]

Witness the following example [Section 1.2]:

-- quoted text begins --
using System;
class Test
{
unsafe static void WriteLocations(byte[] arr) {
fixed (byte *p_arr = arr) {
byte *p_elem = p_arr;
for (int i = 0; i < arr.Length; i++) {
byte value = *p_elem;
string addr = int.Format((int) p_elem, "X");
Console.WriteLine("arr[{0}] at 0x{1} is {2}", i,  
addr, value);
p_elem++;
}
}
}
static void Main() {
byte[] arr = new byte[] {1, 2, 3, 4, 5};
WriteLocations(arr);
}
}
-- quoted text ends --

Even though the method is marked "unsafe," it allows direct pointer manipulation in 
iterating over the elements and writing out the index, value, and location of each.

The reference adds, "Here is one possible output of the above program:

arr[0] at 0x8E0360 is 1
arr[1] at 0x8E0361 is 2
arr[2] at 0x8E0362 is 3
arr[3] at 0x8E0363 is 4
arr[4] at 0x8E0364 is 5

Of course, the exact memory locations are subject to change." [Section 1.2]

Taken to an extreme, this ability could encourage some programmers to ignore the 
spirit of higher-level abstraction and focus back on The Old Way (TOW):  rampant 
pointer-level optimization to squeeze out that extra iota of performance at the 
expense of clarity.  But wasn't the whole point of higher-level abstraction to leave 
this level of optimization to more intelligent compilers so that the programmer could 
focus on writing clear, reusable code?  Why allow us to get TOW'ed back (pardon the 
pun)?

Somebody once wrote that a clearly written, well-documented program that doesn't work 
is usually more valuable than a badly written, poorly-documented program that does 
work because it can easily be fixed and reused.  It just seems that allowing 
programmers the ability to manipulate pointers directly is virtually hiding a 
Pandora's Box in C#.

--Benjamin L. Russell
[EMAIL PROTECTED]
[EMAIL PROTECTED]

On Thu, 10 Aug 2000 10:46:04 -0700
 "Craig Dickson" <[EMAIL PROTECTED]> wrote:
> 
> 
> 
> More like "Microsoft Java", but of course they never
> mention Java, as if
> hoping that people will read all this tripe and not
> notice the similarities.
> 
> I had a most exquisite sense of down-the-rabbit-hole a
> few weeks ago when I
> browsed through a Microsoft book on C#. I kept running
> into all this stuff
> about how C# was a revolutionary next-generation OO
> language, better than
> C++, but all the programming samples looked only
> trivially different from
> Java, which of course they never mentioned, as if the
> book had arrived from
> some parallel universe in which James Gosling was
> assassinated by Richard
> Stallman after inventing Gosling Emacs, and had thus
> never invented Java. I
> had to put the book down after a little while because I
> felt like I'd lose
> my mind if I kept going.
> 
> I don't really mind them inventing a variation on Java.
> Either it will take
> off or it won't, and I don't really care either way. But
> I just wish they'd
> admit what they're doing, and stop treating us all as if
> we're so stupid
> that if they don't _tell_ us that C# is a Java
> derivative, we won't notice.
> 
> 




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Fergus Henderson

On 10-Aug-2000, Theodore Norvell <[EMAIL PROTECTED]> wrote:
> With Haskell# or Mondrian: Can I use C# to create an instance of
> a Haskell class? Can I use Haskell to extend a C# abstract class?
> I suspect the answer to both these questions is currently no.

I'm not sure either, but I think the answer is no.

A related question to which I do know the answer is "Can I use Mercury
to create an instance of a Haskell class, or vice versa?".
And the answer to that one, despite Mercury and Haskell having a
very similar concept of "class", is still no.  So there's still a long
way to go.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Fergus Henderson

On 10-Aug-2000, Brent Fulgham <[EMAIL PROTECTED]> wrote:
> I hope they at least get rid of
> the hungarian notation while they are at it. 

Yes, thankfullly they have indeed done that.  That one got a round of
applause even from the (mostly) Microsoft faithful who attended PDC,
when it was mentioned in one of the sessions there.

> > Microsoft spent around $2M funding a bunch of groups working 
> > on research and industrial programming languages to give 
> > feedback on their work. (Haskell, Mercury, ML, Scheme, Oberon,
> > Eiffel, Python, Oz, etc...)  While they acknowledged from the
> > start that getting any changes (apart from tailcall) into 
> > version 1 was pretty unlikely, they have been listening, 
> > taking notes, and even now the C# folks are getting
> > excited about the idea of putting generics into the language.
>
> Well, that sounds good.  Are you speaking from personal knowledge
> here?

Yes, Tyson and I, as well as researchers from other groups, visited
Redmond several times.  Note that tailcall was in already by the time
outside researchers were approached, so I don't know of any technical
suggestions made by outside researchers that have yet been acted on.
However, the fact that they have been asking for our suggestions and
taking notes is at least an improvement.  I guess the really
interesting bit will be to see what goes in version two.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: monadic source of randomness

2000-08-10 Thread Dana Harrington

>>> Does anybody know of work using monads to encapsulate a source of
>>> random numbers?

>> Is the global random number generator, in section
>> 17.3 of the Haskell 98 library report, the sort of thing you're after?

> No; that appears to embed a generator in the IO monad. Not what I'd
> hoped for.

I'm not sure if this is what you are looking for but since I consider the
IO monad overkill I use a state monad:

  newtype Rand a = Rand (StdGen -> (a,StdGen))

Of course you don't have to use StdGen, and the monad takes care of
threading the generator through your code.  Generating random numbers is
accomplished by

  rand :: (Random r) => Rand r
  rand = Rand random

Dana





Re: Haskell and the NGWS Runtime

2000-08-10 Thread Theodore Norvell

Thanks to Nigel for answering my question

Tyson Dowd wrote:
> > Microsoft indicates that C# will not support "genericity", through
> > even anything as crude as C++'s templates, so it is unlikely that
> > they will seek to support functional programming languages in the
> > short term.  Perhaps this limitation is part of the impetus for the
> > Mondrian variant.

That they are not supporting templates ala C++ can only be a good thing.
It leaves the door open for something closer to Haskell's or ML's
styles of genericity. This is certainly something that the functional
language community can contribute to the world of mainstream imperative
programming languages, and thence to the bulk of software development.
Yes, I know it's been done; for example pizza; but pizza is not a widely
adopted standard. If C# adopts parametric polymorphism and either type
classes or ML style modules, and C# becomes more than a
proprietary language, then it could make a contribution to getting
some of the ideas developed by the functional community into the
mainstream.

With Haskell# or Mondrian: Can I use C# to create an instance of
a Haskell class? Can I use Haskell to extend a C# abstract class?
I suspect the answer to both these questions is currently no.
If future versions of .NET and Haskell variants change that, it will
be very interesting.

Cheers,
Theodore Norvell


Dr. Theodore Norvell[EMAIL PROTECTED]
Electrical and Computer Engineering http://www.engr.mun.ca/~theo
Engineering and Applied SciencePhone: (709) 737-8962
Memorial University of Newfoundland  Fax: (709) 737-4042
St. John's, NF, Canada, A1B 3X5




Re: doubles

2000-08-10 Thread Jan Skibinski


> 
> Aha . And how many digits will GHC offer me?

I would think that you will get the same number of digits
as is available for C - unless some bits are reserved
for something special, which I am not aware of.
For example, in some implementations of Smalltalk the most
significant bit is used as a flag to distinquish between
a reference to an object and an unboxed integer, hence their
integers are one bit shorter than in C.

Jan
  





Re: doubles

2000-08-10 Thread Sebastian Schulz

John Peterson wrote:
> 
> Or you can just set USE_DOUBLE_PRECISION in options.h if you want to
> rebuild hugs.
> 
>   John

Same question as to Jan :
how many significant digits will that change give me?

regards
seb



-- 

  | Sebastian Schulz
  May the source be with you! | mailto:[EMAIL PROTECTED]  





Re: doubles

2000-08-10 Thread Sebastian Schulz

Jan Skibinski wrote:
> 
> 1. What you see printed and what is used in internal
>computations are two different things.

In HUGS I can see 6 digits. How many are used in the intrnal
computation?

> 2. But Hugs'es Double is the same as Float, anyway.
>This used to be a low priority for Mark.


Aha . And how many digits will GHC offer me?

seb
-- 

  | Sebastian Schulz
  May the source be with you! | mailto:[EMAIL PROTECTED]  





Re: Haskell and the NGWS Runtime

2000-08-10 Thread Craig Dickson

Brent Fulgham wrote:

> Thanks for the link!  Unfortunately, its click-through
> license forbids disassembly, reverse engineering, and a
> raft of other endeavors that one should be allowed if
> they were truly interested in global acceptance.

Well, this _is_ Microsoft, after all.

> Of course, a few hops up the chain you might run across Joshua
> Trupin's execrable description of the C# language.  Really one
> of the worst articles I've ever read.  You will get such
> wisdom as:
>
> "It's [C#] a little like taking all the good stuff in
> Visual Basic (C) and adding it to C++, while trimming off some
> of the more arcane C and C++ traditions."

More like "Microsoft Java", but of course they never mention Java, as if
hoping that people will read all this tripe and not notice the similarities.

I had a most exquisite sense of down-the-rabbit-hole a few weeks ago when I
browsed through a Microsoft book on C#. I kept running into all this stuff
about how C# was a revolutionary next-generation OO language, better than
C++, but all the programming samples looked only trivially different from
Java, which of course they never mentioned, as if the book had arrived from
some parallel universe in which James Gosling was assassinated by Richard
Stallman after inventing Gosling Emacs, and had thus never invented Java. I
had to put the book down after a little while because I felt like I'd lose
my mind if I kept going.

I don't really mind them inventing a variation on Java. Either it will take
off or it won't, and I don't really care either way. But I just wish they'd
admit what they're doing, and stop treating us all as if we're so stupid
that if they don't _tell_ us that C# is a Java derivative, we won't notice.

> If you're like me, you might be wondering what exactly the
> "good stuff" allegedly contained within Visual Basic (C) might
> be.  Well, one such element is apparently the labeled "goto".

My impression is that C#'s use of labeled gotos is extremely restricted. (I
could be wrong.) The only reference to gotos that I found in a Microsoft
Press book on C# is its use in jumping to the start of one case in a switch
from another case in the same switch. This is actually useful, since it is a
better solution than "falling through" from one case to another, as is
sometimes done in C, C++, and Java (but which cannot be done in C#, since
the "break" required in those languages is implicit in C# -- also a good
thing). It's a better solution because (1) it doesn't look like a mistake
when you see it in someone else's code; (2) it is more flexible, since the
case you're going to doesn't have to be positioned directly below the case
you're coming from.

Now, if it turns out that C#'s goto can be used for any other purposes, I
will be much less happy about it.

> Joshua is also quick to highlight another:
>
> "What's one of the most annoying things about working in C++?
> It's gotta be remembering when to use the -> pointer indicator,
> when to use the :: for a class member, and when to use the dot."
>
> Hmm.  I guess stating precisely what you mean is a bad feature
> for programming languages.

Well, claiming that the -> vs. . thing is one of the "most annoying things
about working in C++" is pretty silly, but only because it's so trivial, not
because "stating precisely what you mean is a bad feature". C#, like Java,
doesn't need -> because there's no distinction between having a reference to
an object vs. having a pointer to an object. And C++ overloads so many
things that it's sort of silly to complain that getting rid of the
double-colon scoping operator reduces clarity. The double-colon was
unnecessary to begin with.

> The thing that really bothers me is that they claim that ".NET
> will be available on Windows (C) and other systems".  But they
> have no reference implementations available for non-Windows (C)
> environments.  When Sun released Java, we had Unix and Windows
> versions available right away, and the Linux Blackdown port
> shortly thereafter.

True, but then Sun is a Unix vendor, so of course they had to support it,
and Windows is 90% of the market, so they had to support that too.
Microsoft's incentive to support anything other than Windows is unclear to
me, to say the least. I interpret "other systems" to mean Windows CE, and
will believe otherwise only when a less ambiguous announcement is made.

Craig






Re: doubles

2000-08-10 Thread John Peterson

Or you can just set USE_DOUBLE_PRECISION in options.h if you want to
rebuild hugs.

  John




Re: doubles

2000-08-10 Thread Jan Skibinski



On Thu, 10 Aug 2000, Sebastian Schulz wrote:

> Hi!
> 
> How can I use Doubles which are more exact than six digits?
>  For example HUGS gives me :
> 
> >1,23456789
> 1.23457

1. What you see printed and what is used in internal
   computations are two different things.
2. But Hugs'es Double is the same as Float, anyway.
   This used to be a low priority for Mark.
> 
> I want to rotate coordinates with eulerian matrizes and I'm using the pi
> from the Prelude ( 6 digits).
> After about 1000 360°-rotations I have an error of about 0.1% ; but I
> want it more exact.

Try compilers or STHugs instead.

Jan






doubles

2000-08-10 Thread Sebastian Schulz

Hi!

How can I use Doubles which are more exact than six digits?
 For example HUGS gives me :

>1,23456789
1.23457

I want to rotate coordinates with eulerian matrizes and I'm using the pi
from the Prelude ( 6 digits).
After about 1000 360°-rotations I have an error of about 0.1% ; but I
want it more exact.
Thanks for your help.

regards 
Seb

-- 

  | Sebastian Schulz
  May the source be with you! | mailto:[EMAIL PROTECTED]  





RE: Haskell and the NGWS Runtime

2000-08-10 Thread Brent Fulgham

> You can download it here:
>   http://msdn.microsoft.com/net/#sdk
> 
> There is a C# compiler and runtime environment in the SDK.
> 

Thanks for the link!  Unfortunately, its click-through
license forbids disassembly, reverse engineering, and a
raft of other endeavors that one should be allowed if they
were truly interested in global acceptance.  

Of course, a few hops up the chain you might run across Joshua 
Trupin's execrable description of the C# language.  Really one 
of the worst articles I've ever read.  You will get such
wisdom as:

"It's [C#] a little like taking all the good stuff in
Visual Basic (C) and adding it to C++, while trimming off some
of the more arcane C and C++ traditions."

If you're like me, you might be wondering what exactly the 
"good stuff" allegedly contained within Visual Basic (C) might
be.  Well, one such element is apparently the labeled "goto".
Joshua is also quick to highlight another:

"What's one of the most annoying things about working in C++?
It's gotta be remembering when to use the -> pointer indicator,
when to use the :: for a class member, and when to use the dot."

Hmm.  I guess stating precisely what you mean is a bad feature
for programming languages.  I hope they at least get rid of
the hungarian notation while they are at it. 

> Microsoft spent around $2M funding a bunch of groups working 
> on research and industrial programming languages to give 
> feedback on their work. (Haskell, Mercury, ML, Scheme, Oberon,
> Eiffel, Python, Oz, etc...)  While they acknowledged from the
> start that getting any changes (apart from tailcall) into 
> version 1 was pretty unlikely, they have been listening, 
> taking notes, and even now the C# folks are getting
> excited about the idea of putting generics into the language.
> 
Well, that sounds good.  Are you speaking from personal knowledge
here?  My concern is that although they may have spoken with
these various teams, I really don't see much in C# that looks
like they took any of the comments to heart.  In fact, it looks
like they took J++, changed the name, and added a few nasty things
(like labeled "gotos").

In fact, if they were interested in learning anything, why
did they solicit feedback so late in the game?

> I understand your sentiment.  Those of use working on the
> .NET stuff with Microsoft are also uncomfortable about the
> situation.  However I'm sure that everyone involved is doing
> what they think is the best thing overall.  Don't forget that
> many groups developed a .NET and a JVM backend at the same time
> using Microsoft's money!

Hah!  Expect your next round of funding to have more strings
attached.  :-)

The thing that really bothers me is that they claim that ".NET
will be available on Windows (C) and other systems".  But they
have no reference implementations available for non-Windows (C)
environments.  When Sun released Java, we had Unix and Windows
versions available right away, and the Linux Blackdown port
shortly thereafter.

Thanks for your feedback, Tyson, but I'm afraid I still don't
see much to recommend it.  And .NET's heavy dependence on older
MS technologies (such as COM objects, etc.) is especially
distasteful.

Regards,

-Brent





RE: Haskell and the NGWS Runtime

2000-08-10 Thread Doug Ransom

Interesting results might be generated if Microsoft were to provide the
entire C# team and the team designing the virtual machine 2 weeks to learn
Haskell and play with it.  



-Original Message-
From: Tyson Dowd [mailto:[EMAIL PROTECTED]]
Sent: Wednesday, August 09, 2000 9:26 PM
To: Brent Fulgham
Cc: [EMAIL PROTECTED]
Subject: Re: Haskell and the NGWS Runtime


On 09-Aug-2000, Brent Fulgham <[EMAIL PROTECTED]> wrote:
> 
> Hopefully that won't be the case.  However, I feel uncomfortable with
> the whole .NET/C# situation.  Like clockwork, MS releases yet another
> new product that they claim will change the world.  Meanwhile, there is
> no C# implementation available, and the entire .NET framework as
> described in their various white papers seems so large and complex
> that probably only Microsoft will be capable of producing a working
> implementation in any reasonable amount of time.

You can download it here:
http://msdn.microsoft.com/net/#sdk

There is a C# compiler and runtime environment in the SDK.

They used to say that only proprietary companies could possibly write
something so large and complex as an operating system.  It could never
be done, for example, by a bunch of volunteers...

> Microsoft indicates that C# will not support "genericity", through
> even anything as crude as C++'s templates, so it is unlikely that
> they will seek to support functional programming languages in the
> short term.  Perhaps this limitation is part of the impetus for the
> Mondrian variant.

They did add a tailcall instruction largely at the behest of certain
functional language researchers at MSR Cambridge.

They have developed a prototype C# implementation (and hence .NET
runtime) with generics too.

> When Microsoft decides to stop playing games, and works with the
> rest of the developer community to build on existing standards for
> their products I will start to pay attention.  Until then, I will
> not waste one minute of time working to support any of their 
> nefarious new products whose true aim is to prevent alternative 
> platforms from gaining widespread acceptance and use.

Microsoft spent around $2M funding a bunch of groups working on research
and industrial programming languages to give feedback on their work.
(Haskell, Mercury, ML, Scheme, Oberon, Eiffel, Python, Oz, etc...)
While they acknowledged from the start that getting any changes
(apart from tailcall) into version 1 was pretty unlikely, they have
been listening, taking notes, and even now the C# folks are getting
excited about the idea of putting generics into the language.

I understand your sentiment.  Those of use working on the .NET stuff
with Microsoft are also uncomfortable about the situation.  However
I'm sure that everyone involved is doing what they think is the best
thing overall.  Don't forget that many groups developed a .NET and a JVM
backend at the same time using Microsoft's money!

-- 
   Tyson Dowd   # 
#  Surreal humour isn't everyone's cup of fur.
 [EMAIL PROTECTED]# 
http://www.cs.mu.oz.au/~trd #




Erlang User Conference, October 3, Stockholm

2000-08-10 Thread Bjarne Däcker


Call for Participation

Erlang users and other interested parties are invited to 
the Sixth Erlang/OTP User Conference which will take place 
in Älvsjö, Stockholm, on the 3rd of October. 

All information, conference program, how to register, where 
to go, how to pay, etc. etc. can be found in

http://www.erlang.se/euc/00/

The conference program covers applications, implementations,
and developments followed by a conference dinner on a
traditional steam ship cruising in the Stockholm archipelago.

Welcome and best regards,

Bjarne Däcker
Computer Science Laboratory
Ericsson Utvecklings AB
Box 1505
125 25 Älvsjö - Stockholm
Sweden




Re: Haskell and the NGWS Runtime

2000-08-10 Thread Keith Wansbrough

Florian Hard <[EMAIL PROTECTED]> writes:

> How did they say on segfault.org:
> 
>Microsoft plans to expand Marketese in the future, adding a pound sign
>to every language currently in their suite of compilers and a plus
>sign to every acronym currently used to describe Microsoft technology.
> 
>http://www.segfault.org/story.phtml?mode=2&id=39897e26-060c53e0
> 
> :-)


Please:   #  -  hash / octothorp(e)
  £  -  pound
 C#  -  C sharp

Three different characters.  Down with American cultural imperialism.


--KW 8-)
-- 
Keith Wansbrough <[EMAIL PROTECTED]>
http://www.cl.cam.ac.uk/users/kw217/
Cambridge University Computer Laboratory.





Re: monadic source of randomness

2000-08-10 Thread Fergus Henderson

On 09-Aug-2000, Carl R. Witty <[EMAIL PROTECTED]> wrote:
> Norman Ramsey <[EMAIL PROTECTED]> writes:
> 
> > Does anybody know of work using monads to encapsulate a source of 
> > random numbers?  A quick web search suggested Haskell 98 did not take
> > this path.  I'd be curious for any insights why, or any suggestions
> > about a `randomness monad'.
> 
> My guess as to why Haskell 98 does not provide a stand-alone
> "randomness monad" is that monads are annoying (impossible in general)
> to combine.

Another reason is that some people favour an approach using the
`Random.split' function in preference to using a monad.
Using a monad imposes a sequence on things, whereas using the
`Random.split' function, you can distribute a sequence of random
numbers to several function calls without imposing any sequence.
The resulting code is thus more symmetric and (at least in theory)
more easily parallelizable.

(However, little work has been done on ensuring good randomness of
sequences generated using `Random.split', so if you need high quality
randomness then I would not advise that approach at this point in time.)

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.