Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread Fergus Henderson
On 23-Jun-2004, Hal Daume III <[EMAIL PROTECTED]> wrote: > On Wed, 23 Jun 2004, Fergus Henderson wrote: > > > On 23-Jun-2004, MR K P SCHUPKE <[EMAIL PROTECTED]> wrote: > > > This may not be the right answer to the question (which is of > > > course lets w

Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread Fergus Henderson
On 23-Jun-2004, Ketil Malde wrote: > > Thirdly, profiling seems to be incompatible with the use of ghci; there > > doesn't seem to be any easy way to build a workspace so that you can > > get stack traces and use ghci in that workspace at the same time. > > You can compile with: -prof -auto-all -

Re: [Haskell] modern language design, stone age tools

2004-06-23 Thread Fergus Henderson
On 23-Jun-2004, MR K P SCHUPKE <[EMAIL PROTECTED]> wrote: > This may not be the right answer to the question (which is of > course lets write a debugger) - But I have never used a debugger, > and find them more or less the most unfriendly and useless things So how do you debug problems like "Prelu

[Haskell] modern language design, stone age tools

2004-06-22 Thread Fergus Henderson
\begin{gripe} Seeing as Haskell is apparently such a popular language these days, I don't suppose a working debugger would be too much to ask for, would it? Or even just a decent call stack trace when a program terminates with an exception? In case you're wondering, yes I have already tried using

Re: Haskell naming conventions

2003-12-28 Thread Fergus Henderson
ll interfaces are really quite a bit more general than Java interfaces, particularly when you consider common extensions such as multi-parameter type classes, constructor classes, and functional dependencies. So I think it would not help to use the word "interface". -- Fergus Henderson

Re: Annotating Expressions

2003-12-16 Thread Fergus Henderson
hing, none of those solve all the problems that Meacham is trying to solve (numbers 1 and 2 in his original mail). -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a le

Re: Annotating Expressions

2003-12-16 Thread Fergus Henderson
> Bool occurs v (Lam v1 e) = v == v1 || occurs v e occurs v (Ap x y) = occurs v x || occurs v y occurs v (LetRec bindings e) = any (\(vi,ei)->v==vi || occurs v ei) bindings || occurs v e occurs v (Var v1) = v == v1 -- Fergus Henderson <[EMAIL PRO

Re: pattern-matching extension?

2003-12-07 Thread Fergus Henderson
o call it properly. So it would be nice to have a way of doing dynamic class cast, rather than just dynamic type cast. However, there are some theoretical difficulties with dynamic type class cast. In particular, it has some nasty interactions with dynamic loading. If you dynamically load a n

Re: incompatible signatur syntax within instance definition

2003-12-07 Thread Fergus Henderson
eclaration, which has already been constained, and cannot be constrained again. With Haskell 98, it is a fresh type variable, for which the constraint is necessary. Try renaming the type variable as "b" in the inner declaration: the following should work both with and without -fglasgow-exts.

Re: Arbitrary precision reals?

2003-03-25 Thread Fergus Henderson
_sqrt_ui would be an interface to GMP's mpf_sqrt_ui() function, which takes as input an mpf_t and a precision and produces an mpf_t as output. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal

Re: simulating dynamic dispatch

2003-03-20 Thread Fergus Henderson
instance declarations (for obvious > reasons). You can use instance declarations for whichever ground types you need, e.g. instance FooBar Int where ... instance FooBar String where ... -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that t

Re: data vs. newtype, abstractly

2003-03-18 Thread Fergus Henderson
defined as mkD x = x `seq` D x in which case I think it would behave exactly the same as mkN. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <http://www

Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
ng about the `instance' declarations, right? Yes -- the fact that Haskell has separate instance declarations, as opposed to making this information part of the `data' declaration. In most OO languages inheritence relations need to be specified in the type definition. -- Fergus Henderso

Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
{1999}, location = {Auckland}, publisher ={Springer-Verlag}, isbn = {981-4021-54-7}, editor = {J. Edwards}, } -- Fergus Henderson <[EMAIL PROTECTED]> |

Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
ccurate and informative to say that both Haskell and OO languages dispatch on the dynamic type of a value. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habi

Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Fergus Henderson
ost mainstream OOP languages don't. For example C#, Eiffel and Ada-95 don't, if I recall correctly. Sather does support it, but Sather is hardly mainstream (the language is just about dead these days). GNU C++ used to support it, with the "signature" extension, but doe

Re: dynamic types

2003-01-14 Thread Fergus Henderson
ype safety. So it is not safe to allow the use of `fromDynamic' if you are executing untrusted code. > Maybe in Haskell 2. Yes, it would be nice to have a built-in, type-safe, version of Dynamic in Haskell 2. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always

Re: diff in Haskell: clarification

2002-11-21 Thread Fergus Henderson
The Mercury distribution includes a Mercury version of Myer's algorithm: it's in the directory `samples/diff'. You might find it easier to translate from Mercury to Haskell than from C to Haskell. (Then again, you might not ;-) -- Fergus Henderson <[EMAIL PROTECTED]> | "I h

Re: UTF-8 library

2002-08-09 Thread Fergus Henderson
elf to being only implementable on Posix systems. However, systems which don't have 8-bit bytes are getting very very rare nowadays -- it might well be reasonable for Haskell, like Posix, to limit itself to only being implementable on systems where C's `char' is exactly 8 bits. -- Fer

Re: Storable tuples and what is 'alignment'?

2002-08-09 Thread Fergus Henderson
hat rather than defining it yourself. Defining offsetof() yourself is an error if is included, because you are stepping on the implementation's namespace. Furthermore, the definition there is not standard-conforming C code, since it dereferences a null pointer. -- Fergus Henderson <[EMAIL

Re: can't write instance Storable

2002-08-01 Thread Fergus Henderson
er of type `Ptr MPI_Rank', but needs to call `peek' with a parameter of type `Ptr MPI_Rank_Type'. You need to use `castPtr' to convert between the two pointer types. I think the following (untested) code should do it: peek addr = do r <- peek (castPtr addr)

Re: [Fwd: F#]

2002-05-31 Thread Fergus Henderson
nly true that being verifiable is likely to cost some performance. But I don't think it would be difficult to implement. For the Mercury compiler's .Net back-end, there's a --verifiable option which controls whether the generated IL code is verifiable or not. -- Fergus Henderson

Re: uniqueness typing

2002-03-15 Thread Fergus Henderson
27;s. In particular, Clean supports uniqueness polymorphism, whereas Mercury only supports overloading on uniqueness. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit The University of Melbourne | of excellence is a lethal habit" WWW: <ht

Re: Another H'98 Report query

2002-01-31 Thread Fergus Henderson
he union of the entities exported by the individual > items of the list. > > I see no reason to disallow duplicates at the subordinate level if > they are permitted otherwise. Well, disallowing duplicates here may improve error detection, catching some unintentional typos and cut-and

Re: if-then-else inside a "do"

2002-01-29 Thread Fergus Henderson
away the return value: h :: IO () h = do x <- return () -- other things This example is the same as h :: IO () h = do let x = () -- other things -- Fergus Henderson <[EMAIL PROTECTED]> | "I

Re: type specs not making it in to functions

2002-01-28 Thread Fergus Henderson
:: C a => a -> Int -- type var `a' introduced here... foo :: Int quux :: String foo = 42 quux = "hello world" bar x = foo (undefined :: a)-- ... and used here. which means that this feature can be used in ways that have the pote

Re: varying number of arguments restriction

2001-10-31 Thread Fergus Henderson
e number of arguments, and since requiring this helps the compiler give better error messages and/or catch errors earlier, I think it makes good sense to do so. -- Fergus Henderson <[EMAIL PROTECTED]> | "... it seems to me that 15 years of The University of Melbourne | email

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-15 Thread Fergus Henderson
n. With the latter, compilers can't issue such warnings without getting too many false positives. The whole idea of letting you omit method definitions for methods with no default and having calls to such methods be run-time errors is IMHO exceedingly odd in a supposedly strongly typed language,

Re: macros. Was: Arrow notation, etc.

2001-10-14 Thread Fergus Henderson
y are just an efficiency hack, and one which is already looking somewhat dated -- a bit like the "register" keyword in C. This is quite different to the kind of macros that would allow you to extend the language syntax to support things like arrow notation or views. -- Fergus Henderso

Re: Namespaces (was Re: GUI Library Task Force)

2001-10-11 Thread Fergus Henderson
g > nuisance, especially since ghc (seems to) lack an environment variable > that it looks at to get command line options every time it runs > (HUGSFLAGS, I think it was for Hugs). Well, I wouldn't be invoking ghc manually anyway; I'd put the commands to invoke ghc in a script o

Re: Application letters at the Haskell workshop: suggestion

2001-09-25 Thread Fergus Henderson
tch error-1 -> 1 where a _ = raise error-1 b n = b n Should this program return 1, or loop? Giving this program deterministic behaviour requires specifying the order of evaluation. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known

Re: type classes and generality

2001-07-09 Thread Fergus Henderson
On 09-Jul-2001, Alexander V. Voinov <[EMAIL PROTECTED]> wrote: > Hi All, > > Fergus Henderson wrote: > > Ah, now I think I understand your problem. You want to `random' to > > generate random numbers that span all the possible values of the type > >

Re: type classes and generality

2001-07-09 Thread Fergus Henderson
. So by induction you can't generate any non-integers. I'd advise you to add an extra "Random t" class constraint to those parts of your application that rely on generating random numbers. If you find yourself using `Real t, Random t' frequently, you can use a derived class for that:

Re: type classes and generality

2001-07-09 Thread Fergus Henderson
per an instance of Random.Random if the underlying type is an instance of Real instance Real r => Random.Random (WrapReal r) where ... Then you can use the wrapper type whenever you want to get a random number. -- Fergus Henderson <[EMAIL PROTECTED]> | "I

Re: Haskell 98 Report

2001-05-31 Thread Fergus Henderson
signature,.." > > Fergus Henderson, June 2001 > > Is this definition of reuse in Haskell quotable?-) Sure, feel free to go ahead and quote it (you just did already ;-). But it's taken a little out of context. Certainly I wouldn't recommend that as a method o

Re: Haskell 98 Report

2001-05-31 Thread Fergus Henderson
but include it in the next version of Haskell. (It would be good for someone, perhaps Simon P-J., to keep a list of issues like this which have been left out of Haskell 98 due to backwards compatibility concerns, so that they don't get forgotten about when it comes to time for the next versio

Re: Unicode

2001-05-25 Thread Fergus Henderson
bit, since the distinction between these is not always clear. Is there a way to convert a Haskell String into a UTF-16 encoded byte stream without writing to a file and then reading the file back in? -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that

Re: Templates in FPL?

2001-05-23 Thread Fergus Henderson
be able to do a lot of it using ordinary Haskell syntax with just some additional annotation that directs the compiler to evaluate part of the program at compile time. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit

Re: Integers to Ints

2001-05-16 Thread Fergus Henderson
ed that one in March 1998. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___

Re: BAL paper available

2001-05-15 Thread Fergus Henderson
ay. The right solution, IMHO, is to extend nhc and other Haskell compilers to support multiparameter type classes, not to try to shoehorn things that don't fit into Haskell 98. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit

Re: CA proposal by D.Thurston

2001-05-14 Thread Fergus Henderson
ould not find it from http://haskell.org It was posted to the haskell-cafe list, and is available from the archives of that list: <http://haskell.org/pipermail/haskell-cafe/2001-February/000331.html>. -- Fergus Henderson <[EMAIL PROTECTED]> | &quo

Re: User defined Ix instances potentially unsafe

2001-05-07 Thread Fergus Henderson
lementation, other than the standard reserved words, so I think even using a name like `__unchecked_index' here would not be 100% strictly Haskell 98 compatible. I think it would be good enough in practice, though. For Haskell 200X, where strict backwards compatibility is not required, uncheck

Re: polymorphic recursion (was: Re: Implict parameters and monomorphism)

2001-05-06 Thread Fergus Henderson
me programs as the > existing Haskell algorithm? (assuming an arbitrary user-defined iteration > limit, and suitable type annotations for the existing Haskell algorithm). Yes, I believe so. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit

Re: Implict parameters and monomorphism

2001-05-05 Thread Fergus Henderson
e process may fail to terminate for certain ill-typed programs. The Mercury compiler uses a user-configurable iteration limit, and rejects programs for which type inference exceeds this limit. In practice this is very very rare. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always kn

Re: Contexts in Existential Types

2001-03-13 Thread Fergus Henderson
aration. test.m: 1: Warning: interface for module `test' does not export anything. test.m:012: Inferred :- func anyA = (test:anyCharable). test.m:013: Inferred :- func recoverA = character. test.m:014: Inferred :- some [C] (func x((test:anyCharable)) = C => (test:charab le(C))). Note that the typ

Re: Synonym Type Constructors

2001-02-19 Thread Fergus Henderson
f those existential philosphical debates about terminology ;-) Personally I would describe the type constructors introduced by type synonym declarations as "real", but not "first class". -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the p

Re: Types from values using existential types?

2001-02-11 Thread Fergus Henderson
blem, but not the second. We develop a representation that solves | both problems: it offers logarithmic access to each individual element | and it captures the shape invariants in the type, where they can be | checked by the compiler. One interesting feature of our solution is | that it transl

Re: Types from values using existential types?

2001-02-09 Thread Fergus Henderson
SquareMatrix type_for_n element_type new_matrix n f = SquareMatrix n f :: SquareMatrix Dummy element_type but this relies a couple of extensions to standard Haskell, at least one of which is not supported by any existing Haskell implementation. I think there might also be some stuf

Re: Detail: laziness in show

2001-02-09 Thread Fergus Henderson
for functions explicitly, rather than using `import ShowFunctions', otherwise it might have taken much longer to figure out what was going on. But I wondered afterwards whether it might be better for Hugs to use x `seq` show x rather than show x whe

Re: names, modules, types

2001-02-08 Thread Fergus Henderson
comprehensions rather than monad comprehensions. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. _

Re: binary files in haskell

2001-02-08 Thread Fergus Henderson
n a 16-bit machine just by computing all arithmetic operations modulo 256. There is no requirement that Word8 be physically 8 bits, just that it represents an 8-bit quantity. Indeed, I think ghc uses this technique, representing Word8 as a full machine word (e.g. 32 bits for x86, of which the topmost

Re: Problem with functional dependencies

2001-01-03 Thread Fergus Henderson
tances is not able to handle such constraints, so for such examples, the current implementation of the compiler reports "sorry, not implemented: constraints may only constrain type variables".) -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursui

Re: Haskell Language Design Questions

2000-12-29 Thread Fergus Henderson
c/docs/latest/set/sec-exception.html>. There's also a paper or two on that. I hope you'll forgive the self-citation, but the only one for which I happen to have a reference on-hand is this one: A semantics for imprecise exceptions. Simon Peyton-Jones, Al

Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2000-12-25 Thread Fergus Henderson
:- module enum_t. :- interface. :- instance enum(t). :- end_module enum_t. :- implementation. :- module enum_t. :- implementation. :- instance enum(t) where [ ... ]. :- end_module enum_t. -- Fergus Hende

Re: Union Types for Haskell!?

2000-11-24 Thread Fergus Henderson
e to infer a union type there, and the point where the types become inconsistent is only when the union type is later used in a context that requires one particular type. Reporting the error at that point of use is likely to make it harder to find the problem, since it is further away from the place

Re: Hugs and Linux

2000-11-10 Thread Fergus Henderson
hey gave it a new major number). But Hugs probably doesn't use that much of the interface to readline (e.g. there's no support for command-line completion, except the default file-name completion), so the difference *might* not matter. It's certainly worth a try ;-) Cheers,

Re: Passing an environment around

2000-11-08 Thread Fergus Henderson
read-safe. An alternative is to store the values of the implicit parameters in thread-local storage rather than global storage. But this is more complicated. It may also be less efficient on some targets (depending on how efficiently thread-local storage is imple

Re: First class modules

2000-11-08 Thread Fergus Henderson
biguity to arise within a single function: foo = show (read "whatever") This expression is fundamentally ambiguous unless you somehow disambiguate what type it is that you are trying to read. I don't see how first class modules could solve that. -- Fergus Henderson <[EMAI

Re: Overloaded function and implicit parameter passing

2000-10-23 Thread Fergus Henderson
y comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is

Re: How does one find lazyness bottlenecks?

2000-10-12 Thread Fergus Henderson
ed to be garbage collected. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Usability of M$ specs [was: Haskell and the NGWS Runtime]

2000-09-14 Thread Fergus Henderson
ocumentation format, which can only be browsed on a Windows system (in fact I think it even has to be W2k, IIRC). -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit&

Re: help, classes!

2000-09-13 Thread Fergus Henderson
ll. About the best you can do is to create your own `EqMonad' class, which is like `Monad' except that it has an `Eq a' constraint on the type variable. Then use `EqMonad' instead of `Monad'. You can't use the `do' syntax, and you can't reuse the library routin

Re: Inferring types

2000-09-08 Thread Fergus Henderson
efault default list (Integer, Double) which satifies the constraint in question, namely `Num a'. If you define `p' as a syntactic function, e.g. p x y = x + y or p x = (+) x rather than via p = (+) then the monomorphism restriction does not apply, and so the ty

Re: inference question

2000-09-01 Thread Fergus Henderson
than it is. > For some reason, _explicitly_ typing it is okay. Yes. That's because of rule 1 (b) in 4.5.5. Another work-around is to make `x' a function rather than a variable: let x _ = cmethod . fromNat $ 1 in 0 -- Fergus Henderson <[EMAIL PROTECTED]> | "I

Re: Haskell compilers targetting Wintel platforms, or microsoft's ".NET"...

2000-08-29 Thread Fergus Henderson
T". Does > anybody out there knows about existing Haskell compilers generating code > for the ".NET", or native code for WinTel platforms ? There was a long discussion of this quite recently on this list. You can find the archive for this list on www.haskell.org. Search for

Re: Haskell and the NGWS Runtime

2000-08-15 Thread Fergus Henderson
> code in C#. > > Ah, a testable hypothesis! If you are right, then you should be able to > provide an example of a language that meets the requirements of writing > both low-level kernel code and most user applications equally well for > the bulk of the programmers

Re: Haskell and the NGWS Runtime

2000-08-11 Thread Fergus Henderson
that's the worst part. In Lynx and Opera, it *seems* to be correctly rendered. Unfortunately it is missing all of the crucial links to the actual slides! Of course there is no easy way you could tell this, except by having seen the same site already with IE, or by examining the site'

Re: Haskell and the NGWS Runtime

2000-08-11 Thread Fergus Henderson
On 11-Aug-2000, R.S. Nikhil <[EMAIL PROTECTED]> wrote: > > -Original Message- > > From: Fergus Henderson [mailto:[EMAIL PROTECTED]] > > Sent: Friday, August 11, 2000 4:18 AM > > ... > > > > In particular <http://commnet.pdc.mscorpevents.c

Re: Haskell and the NGWS Runtime

2000-08-11 Thread Fergus Henderson
s any indication, they have a long way to go before they'll be "walking the walk". -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Haskell and the NGWS Runtime

2000-08-11 Thread Fergus Henderson
er, I think it is fair to say that Microsoft have done their homework on this issue. I have not yet done any benchmarking of their GC yet. The reason for that is that currently the Mercury to IL code generator generates code which does many unnecessary allocations which we know how to eliminate, so be

Re: Haskell and the NGWS Runtime

2000-08-10 Thread Fergus Henderson
l no. So there's still a long way to go. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Haskell and the NGWS Runtime

2000-08-10 Thread Fergus Henderson
hnical 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 PROTE

Re: monadic source of randomness

2000-08-10 Thread Fergus Henderson
ence. 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 thi

Re: Haskell and the NGWS Runtime

2000-08-03 Thread Fergus Henderson
;. I guess one could argue that the costs of most other things pale in comparison to the costs of having lazy evaluation as the default ;-) -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Haskell and the NGWS Runtime

2000-08-02 Thread Fergus Henderson
On 02-Aug-2000, Carl R. Witty <[EMAIL PROTECTED]> wrote: > Fergus Henderson <[EMAIL PROTECTED]> writes: > > > > The compiler hooks into GHC by translating Core into GOO > > > and then after some source to source transformations it > > > can

Re: Haskell and the NGWS Runtime

2000-08-02 Thread Fergus Henderson
or a given language, you also need to implement a > > certain API. Now my information on this is mostly second-hand, > > but as I understand it, this API pretty much assumes that your > > language is a fairly typical imperative language, with constructs > > like loops, etc.

Re: Haskell and the NGWS Runtime

2000-08-01 Thread Fergus Henderson
h constructs like loops, etc. So it is fairly easy to implement this API for imperative languages, but not nearly so easy to implement it for functional languages or other non-traditional languages. In addition, I think your compiler also needs to support attributes? P.S. My research group has re

Re: Classes

2000-07-27 Thread Fergus Henderson
cope of instance declarations, it is hard to define "these" in "these > are the only instances of class C". If a type class is not exported from a module, then only that module can contain instances of that type class. So the type checker could perhaps handle that case specially. On the other hand, it would be problematic if simply exporting some previously private entity could change whether the module is type-correct. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Precision problem

2000-07-25 Thread Fergus Henderson
On 25-Jul-2000, Julian Assange <[EMAIL PROTECTED]> wrote: > Fergus Henderson <[EMAIL PROTECTED]> writes: > > > Jon Fairbairn was talking about Haskell. MSVC is a C/C++ compiler, > > not a Haskell compiler. For C and C++, there are many many areas of

Re: The type of zip

2000-07-24 Thread Fergus Henderson
erful technique; I think that using reflection you can do quite a lot in the language that in Haskell currently seems to instead be done with external preprocessors (e.g. "Deriv", or whatever it is called now). -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known

Re: Precision problem

2000-07-23 Thread Fergus Henderson
most always due to the program depending on one of those areas, rather than due to the compiler not conforming to the standard. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: Precision problem

2000-07-18 Thread Fergus Henderson
be a step in the wrong > direction. If all the platforms that GHC target use the same IEEE arithmetic and representation for Float/Double, why does GHC need to use Rational to represent floating pointer values? -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known th

Re: Precision problem

2000-07-18 Thread Fergus Henderson
rounding, overflow, etc., and of course it might vary from platform to platform, or from compiler to compiler, or perhaps even from run to run; but nevertheless, Haskell or any other language which aims to be referentially transparent, for any given program execution the sum should be the same each

Re: Library conventions

2000-06-26 Thread Fergus Henderson
ntally confusing since it is not clear what the meaning of `Left' and `Right' is. I much prefer using a separate type defined as e.g. data Result error val = ResultError error | ResultOK val This tends to lead to much more readable code. -- Fergus Henderson <[EMAIL PROTECTE

Re: "Boxed imperatives" to implement pure functions (Was: Inverse Indices)

2000-06-06 Thread Fergus Henderson
t; ix -> elt -> ST s () | thawSTArray :: Ix ix => Array ix elt -> ST s (STArray s ix elt) | freezeSTArray :: Ix ix => STArray s ix elt -> ST s (Array ix elt) | unsafeFreezeSTArray :: Ix ix => STArray s ix elt -> ST s (Array ix elt) -- Fergus Hen

Re: mode in functions

2000-06-02 Thread Fergus Henderson
On 02-Jun-2000, Ketil Malde <[EMAIL PROTECTED]> wrote: > Fergus Henderson <[EMAIL PROTECTED]> writes: > > > An interactive command line tool and a programming language intended > > for writing non-trivial applications have very different requirements. > > For

Re: mode in functions

2000-06-02 Thread Fergus Henderson
e ... = (sort mode) ... rather than by passing in a sort function. If they did that, then I wouldn't be able to make `foo' use my own sort function. (Note that using `Char' rather than an enumeration doesn't help with this problem.) -- Fergus Henderson <[EMAIL PRO

Re: mode in functions

2000-06-02 Thread Fergus Henderson
language intended for writing non-trivial applications have very different requirements. For the former, brevity may well be more important than readability, but for the latter it is definitely the other way around. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known tha

Re: mode argument

2000-06-02 Thread Fergus Henderson
On 01-Jun-2000, Ketil Malde <[EMAIL PROTECTED]> wrote: > Fergus Henderson <[EMAIL PROTECTED]> writes: > > >> Again, `Positive' would not do, it should be something like > >> QuotRem_Positive, and so on. > > > This is a problem with H

Re: unsafeinterleaveIO

2000-06-01 Thread Fergus Henderson
rface that all Mercury implementations must support. I strongly urge that a standard FFI should be seen as an important goal for Haskell-2. If Haskell does not have a standard FFI, then programmers who are concerned about not being locked into a single compiler will turn to other languages that d

Re: mode argument

2000-05-31 Thread Fergus Henderson
t; f x y = remP ((remO x b)*(remO x b)) b > Maybe, Char is better? No, IMHO Char would definitely not be better. In this case, I think separate functions would be best, a single function with a properly typed mode argument second best, and a single function with a `Char' mode argument worst. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: unsafeinterleaveIO

2000-05-30 Thread Fergus Henderson
On 30-May-2000, George Russell <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > > (If nothing at all can be guaranteed, then no-one should be using those > > features, and they should be removed from the Hugs/ghc extension libraries. > > But it should be possi

Re: unsafeinterleaveIO

2000-05-30 Thread Fergus Henderson
aranteed, then no-one should be using those features, and they should be removed from the Hugs/ghc extension libraries. But it should be possible to make some guarantees.) -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.

Re: import List(..)

2000-05-22 Thread Fergus Henderson
always* refer to their prelude definitions. That may well be the *easiest* thing to do, but the question we should be asking is what is the *best* thing to do. The easiest thing has been tried already, and -- dare I say it -- found wanting! -- Fergus Henderson <[EMAIL PROTECTED]> |

Re: import List(..) ?

2000-05-21 Thread Fergus Henderson
On 21-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Sun, 21 May 2000 17:26:13 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > > But being able to import and/or re-export such symbols is necessary > > if you want to be able to i

Re: import List(..) ?

2000-05-21 Thread Fergus Henderson
ernative prelude. > Must the type of Main.main be Prelude.IO something, or it can be a > replacement of IO? The latter does not have a semantics, so it must > be the former. Right. But an alternative prelude could define a function run :: AltPrelude.ReplacementForIO

Re: import List(..) ?

2000-05-20 Thread Fergus Henderson
ust syntactic sugar for `ListType'. The list type could then by defined in the Prelude using ordinary Haskell syntax: data ListType t = ListNil | ListCons t (ListType t) Then these symbols could be mentioned in import and export lists using the existing syntax. I don't have

Re: how to replace Num.fromInteger 2

2000-05-20 Thread Fergus Henderson
On 20-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Sat, 20 May 2000 20:45:47 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > > For the next version of Haskell, I propose changing the wording to > > > > The in

Re: how to replace Num.fromInteger 2

2000-05-20 Thread Fergus Henderson
On 20-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Sat, 20 May 2000 20:45:47 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > This is somewhat ambiguous; if it is really intended that unary - > > always refer to the negate func

Re: how to replace Num.fromInteger 2

2000-05-20 Thread Fergus Henderson
ax for such types, even though it would make good sense to do so. So again, for the next version of Haskell I propose the wording be changed to make it clear that the `>>' and `>>=' in the translation for `do' expressions need not refer to the methods defined in the

  1   2   3   4   5   >