Re: FW: Haskell 98: partition; and take,drop,splitAt
On 15-Mar-2000, George Russell <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > [snip] > > For FLOOR_{F->I}(NaN), the result is defined as a NaN: > [snip] > > But in both cases this doesn't really make much sense to me, > > since here the result type of the operation is an integer rather > > than floating point type. I guess the earlier part of 6.1 does > > shed a little extra light: > > The less elevated source of "man floor" tells me that although of > course floor returns an integer, it returns it represented as a double. > So perhaps that's the idea. Or maybe I'm talking rubbish and it > says explicitly in the standard that FLOOR_{F_I} returns something > of integer type. Yes, `FLOOR_{F->I}', which is my Latex-style ASCII-ization of what appears in the standard as `FLOOR' with a subscript `F->I', is a function from floating point to integer. That is the one which should correspond with Haskell's `floor' function, which according to the Haskell 98 Report has type floor :: (RealFrac a, Integral b) => a -> b LIA-2 also has a separate floor function named `FLOOR_{F->F}'; this one is a function from floating point to floating point, and as such corresponds to C's floor() function. -- 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: newtypes
On 17-Mar-2000, Tom Pledger <[EMAIL PROTECTED]> wrote: > Marcin 'Qrczak' Kowalczyk writes: > > Thu, 16 Mar 2000 14:38:30 -0500, Chris Okasaki <[EMAIL PROTECTED]> pisze: > > > > > How are these two statements reconciled for recursive > > > types such as > > > > > > newtype Foo = F Foo > > > > IMHO simply the only value of this type is bottom. [...] > > Shouldn't applying (\(F _) -> ()) differentiate between bottom and > (F bottom)? No. See 4.2.3: | Unlike algebraic datatypes, the newtype constructor N is unlifted, | so that N _|_ is the same as _|_. > Do the two statements reconcile trivially in this case, into > "Foo has the same representation as Foo"? Yes. So the representation of Foo is unspecified. -- 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: speed and size of compiled Haskell code
On 16-Mar-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > I wonder if someone could tell me more about the speed and size of compiled > Haskell code. ... > What about Haskell 98 versus (I anticipate) Haskell 2 There should be no significant differences as far as performance goes between Haskell 98 and whatever the next revision of Haskell is called. -- 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: The return of the Void [Was: newtypes]
On 17-Mar-2000, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > > newtype Void = Void Void deriving Show > > > Hugs and hbc accept it without complaining. (I haven't got nhc installed.) > > nhc98 reports > > > Error when renaming:: > Newtype Main.B is circular. > Newtype Main.A is circular. > Newtype Main.Void is circular. > > which seems reasonable to me. Why? The Haskell report explicitly allows recursive newtype definitions. So why is it reasonable for a compiler to reject them? As a question of language design, it might well be reasonable. But I think the issue here is conformance, and I think it is clear that nhc98 does not conform to the specification in the Haskell 98 Report. -- 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: The return of the Void [Was: newtypes]
On 16-Mar-2000, Patrik Jansson <[EMAIL PROTECTED]> wrote: > On Thu, 16 Mar 2000, Chris Okasaki wrote: > > newtype Foo = F Foo ... > Hugs and hbc accept it without complaining. (I haven't got nhc installed.) > > What is interesting is that ghc loops when trying to compile this > definition! (Ghc folks, consider this a bug report, details below!) ghc is not the only compiler to have this problem. I tried code analagous to this out on the Mercury compiler, and it turned out that like ghc, the Mercury compiler went into an infinite loop. Fortunately the problem was fairly simple, so I've fixed it already. Thanks for the devious test case, though ;-) -- 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: The return of the Void [Was: newtypes]
On 17-Mar-2000, Malcolm Wallace <[EMAIL PROTECTED]> wrote: > > The Haskell report explicitly allows recursive newtype definitions. > > So why is it reasonable for a compiler to reject them? > > nhc98 rejects circular newtypes which are semantically bottom, like > newtype Void = Void Void > newtype A = A B > newtype B = B A > because it cannot find a representation for them. I would suggest that it is not trying hard enough ;-) Clearly Hugs manages to find a representation for such types. Why does nhc98 have such difficulty finding a representation for them? Indeed, pretty much any representation will do. > What is unreasonable about that? > > > But I think the issue here is conformance, and I think it is > > clear that nhc98 does not conform to the specification in the > > Haskell 98 Report. > > Well, I'm not sure that the specification is entirely clear on this > point. It states that a newtype uses the same representation as the > type it renames. nhc98 claims that if there is no representation for > the type, it can't continue. There's a big difference between there being no representation for a type, and the representation for a type being unspecified. In this case, the representation is the same as itself, i.e. unspecified. Note that the Haskell report does not specify how the unit type `()' is represented either. Does nhc98 reject that too? -- 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.
== and hyperstrictness
On 21-Mar-2000, Sven Panne <[EMAIL PROTECTED]> wrote: > Example: length is strict in its argument, but the following > function is hyperstrict (at least according to my definition :-) : > >len :: Eq a => [a] -> Int >len [] = 0 >len (x:xs) | x == x = 1 + len xs > > This 'x == x' is folklore for getting rid of some space leaks, > AFAIK. Actually, that raises an interesting question: should instances of `==' be required to be hyperstrict in cases where they return `True'? The Haskell report is silent on this issue. Suppose Sven implements his `len' function as above, and furthermore implements a library which depends on this function being hyperstrict. Suppose next that I implement an instance of `==' that returns `True' without evaluating the arguments, and then finally suppose a third programmer called say Joe comes along and uses my type with Sven's library. If it breaks, who is to blame? -- 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: == and hyperstrictness
On 22-Mar-2000, Qrczak <[EMAIL PROTECTED]> wrote: > On Wed, 22 Mar 2000, Fergus Henderson wrote: > > > Actually, that raises an interesting question: > > should instances of `==' be required to be hyperstrict > > in cases where they return `True'? > > Certainly no. > > First, using (==) for that purpose is a hack. OK, you convinced me on that point. Thanks. > > Suppose Sven implements his `len' function as above, and furthermore > > implements a library which depends on this function being hyperstrict. > > It generally cannot depend on it. Strictness only improves efficiency and > narrows cases when a function is defined, but it can never improve > correctness. There is no code that requires strictness to work at all. Sometimes efficiency is important, and it is quite possible for a function to depend on strictness for reasonable performance. -- 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: == and hyperstrictness
On 22-Mar-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > I'm not convinced that it [hseq] should exist at all. Much can be archieved > by adding strictness flags to data definitions, or at most suitable > problem-specific functions / classes. It should not be *very* important > to evaluate exactly what one has in mind - the essence of laziness > is that it is not harmful - except perfomance... It's good when the > compiler can infer itself where laziness can be safely eliminated. `hseq' would sometimes be useful in conjunction with exception handling, for ensuring that some sub-expression was fully evaluated within the scope of an exception handler, rather than being lazily evaluated with some parts of the evaluation occurring outside the scope of the exception handler. -- 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: Some questions
On 27-Mar-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > Hi, > > Suppose a denotes a type variable. > > 1.Can I then say: Bool is of type a ? No. That would be a category error. `Bool' _is a_ type, but it doesn't _have a_ type. Only _values_ have types, but `Bool' is a type, not a value, and types don't have types. Instead, types and type constructors have "kinds"; you could for example say `Bool' has kind `*' (the kind of all types), as oppose to `List', which has kind `* -> *' (the kind of type constructors which take a type as their parameter and give you back a type). Note that Haskell doesn't have any explicit syntax for kinds; the syntax using asterisks (`*') is used in the Haskell Report, but it is not part of Haskell syntax and cannot be used in Haskell programs. Nor does Haskell have any kind variables. > 2. I suppose I can say that True is of type Bool. Yes. > However True is not itself a type, isn't it? That's correct. > I suppose that I cannot say that True is of type a, isn't it ? Well, you can certainly say that `True' is of type `Bool', and in certain circumstances you can also say that `True' is of type `a' -- this would imply that `a' was bound to `Bool'. > So True is a "value" but not a "type value" , isn't? Right. > 3. Now consider the type of state transformers ST s a : in the > above s is a type variable that ranges over the values(?) of type > State . No; s is a type variable that ranges over the _types_ of kind `*'. > Since IO a = ST RealWorld a , I deduce that RealWorld > is not a type variable (because the first letter is a capital) but a > very specific type Correct. > : i.e. RealWorld is of type State No, RealWorld is a type of kind `*'. I'm not sure where `State' came from. > and RealWorld itself contains values Yes; at very least, it must contain bottom. > but not of type State ; Indeed, the values in the `RealWorld' type are of type `RealWorld', not of type `State'. > shouldn't I then say > that s ranges over "type values " of type state instead of > "values" of type State. You should say that s ranges of types of kind `*'. > 4. Consider the type f :: a -> b -> c. Since you're asking about terminology: `f :: a -> b -> c' is not a type, it is a _type signature_. `a -> b -> c' is a type and `f :: a -> b -> c' is a type signature which declares `f' to have the type `forall a,b,c . a -> b -> c'. > Can I say that f is of type a -> b > since b is a more general type than the type b -> c The short answer is no. There are several issues here. One is that you need to be careful about the scopes of type variables; if `f' has type `a -> b -> c', then that type is _not_ an instance of the type `a -> b' if `a' and `b' denote the same type variables in both types. Another issue is that a type signature such as `f :: a -> b -> c' declares `f' to have the polymorphic type `forall a,b,c . a -> b -> c', which is different from the polymorphic type `forall a,b . a -> b'. Every instance of the former is an instance of the latter, but not vice versa. > And if this is true I suppose that "being of type " is a transitive relation >among types, isn't? No. It doesn't even make sense to say that a type "is of type" some other type. However, you can say that a type is an instance of some other type, meaning that you can obtain the first type by some binding of the type variables in the second type. This "instance of" relation is transitive. -- 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: Additions to the FFI API
ime_t POSIX typedef DIR POSIX typedef sigjmp_buf POSIX typedef clock_t POSIX typedef dev_t POSIX typedef gid_t POSIX typedef ino_t POSIX typedef mode_t POSIX typedef nlink_t POSIX typedef off_t POSIX typedef pid_t POSIX typedef size_t POSIX typedef ssize_t POSIX typedef uid_t POSIXtypedef cc_t POSIXtypedef speed_t POSIXtypedef tcflag_t POSIX typedef size_t POSIX typedef ssize_t If you're going to provide any of these, then you should provide at least the ANSI C types ptrdiff_t, size_t, wchar_t, FILE, fpos_t, clock_t, and time_t. You should strongly consider providing the other ANSI C types jmp_buf, sig_atomic_t, div_t, and ldiv_t, not because they would be particularly useful, but simply because the additional implementation effort required would be quite trivial. va_list is probably the most problematic, since it is often dependent on the particular C compiler. Of the POSIX types, probably all of them except the ones in are worth doing if any of them are. > 3. Byte order > === > For the really dirty stuff one needs to know the byte order of the > underlying architecture: > >data ByteOrder = SmallEndian | BigEndian -- are there more esoteric ones? >byteOrder :: ByteOrder Yes, there are more esoteric ones. Furthermore it's generally a bad idea to write code that relies on byte ordering. I don't see any reason for the Haskell FFI to encourage this. -- 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: Additions to the FFI API
On 28-Mar-2000, Fergus Henderson <[EMAIL PROTECTED]> wrote: > For prior art, see the `Interfaces.C' package in normative Annex E of > the Ada 95 standard (available via www.ada.org). Sorry, that URL is not correct. In fact that is the American Dentists Association (ADA) home page, not the Ada programming language (Ada) home page ;-) The one I was thinking of is , which does have a link to the Ada 95 standard. But <http://lglwww.epfl.ch/Ada/> is a better URL to give, since that has the Ada 95 rationale as well as the Ada 95 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: Some questions
On 27-Mar-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > 1. In Haskell there are 2 sorts of variables : variables that range over values of >a specific type and "type variables". > > e.g.in fact n = n * fact (n - 1) (the factorial function n ranges over the values >of type Int. > > and in the typeST s a where s and a are variables that only range over >types > > Am I correct? Yes. > 2. I would first like to come back to the type signature > >f :: a -> b > > I can say the type of f is a -> b , isn't it? Well, people often do say that, but it is a little sloppy; if you want to be precise, it is more correct to say that the type of `f' is `forall a,b . a -> b'. > But a and b are both variables. Question > > can I replace the General type b by the type c -> d ? In general that transformation does not preserve type-correctness. Changing `b' to `c -> d' in the type signature might change a type-correct program into an ill-typed one. For example, if the program contains foo :: Int -> Int foo x = f x then changing the type signature of `f' to `f :: a -> c -> d' would mean that the previously type-correct call to `f' here would now become a type error. -- 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: Additions to the FFI API
or details. There is some hope that the new C 99 standard will also eventually be available for a similar price. > > POSIX typedef DIR > > [...] > > POSIX typedef ssize_t > > Those should probably go into the Posix libs, not the basic FFI lib. Yes, that is a good idea. > > > [...] 3. Byte order [...] > > Yes, there are more esoteric ones. > > Could you give examples? I know that there are e.g. 4! = 24 ways to > arrange the bytes of a 32bit int, but... Well, the GNU C source has numerous different configuration macros regarding endianness, e.g. BYTES_BIG_ENDIAN WORDS_BIG_ENDIAN FLOAT_WORDS_BIG_ENDIAN BITS_BIG_ENDIAN Apparently these do not always agree. For example, BYTES_BIG_ENDIAN and WORDS_BIG_ENDIAN disagree on the 1750a, fx80, gmicro, and pdp11 targets. > > Furthermore it's generally a bad idea to write code that relies on > > byte ordering. I don't see any reason for the Haskell FFI to > > encourage this. > > It's not a matter of encouragement, but a matter of necessity: There > are a lot of binary file formats out in the real world, and you really > need to know if some swapping is needed or not. You can read/write things byte at a time, and choose whichever byte order you want. For example, the following routine reads in a 16-bit unsigned integer encoded in big-endian format from a file. /* error checking omitted in the interests of simplicity */ uint16 read_big_endian_uint16(FILE *fp) { uint8 c0, c1; c0 = getc(fp); c1 = getc(fp); return (c0 << 8) | c1; } Note that this code works regardless of the endianness of the CPU it is running on. -- 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: Additions to the FFI API
On 28-Mar-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Tue, 28 Mar 2000 12:26:34 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > > It would be fine to have a `typedef void *HsStablePtr'. But it is important > > that you do not lose static type information when exporting Haskell functions > > to C. So a parameter of type `StablePtr Int' on the Haskell side should get > > converted to a pointer to an opaque struct type, e.g. `struct HsStablePtrInt *' > > in C, not to just plain `HsStablePtr'. > > What would StablePtr (b -> [Maybe Int] -> IO (Integer, b)) map to? For type constructors like `->', `[]', and `Maybe', which (unlike StablePtr) don't have any C equivalent, I think you probably need to drop the structure, and just keep the top-level type constructor, thus mapping that type to just `struct HsStablePtrFunc *'. It would be nice if more of the structure could be preserved, but I don't see any way to do that in C mangling the Haskell type names into C identifiers, which would make it exceedingly cumbersome to use, and I think would also break the Haskell substitutability properties anyway. Still, just making sure that Haskell types with distinct top-level type constructors get mapped to distinct C types is probably enough to catch most of the type errors. > > > BTW, Ptr is probably not fully polymorphic, e.g. > > > what should be the mapping for > > > > > >Ptr (b -> [Maybe Int] -> IO (Integer, b)) > > > ? > > > > It should be a pointer to whatever the mapping for > > `b -> [Maybe Int] -> IO (Integer, b)' is. > > There is no mapping for the latter type. Then there should be no mapping for the former type either. But I don't see why that means that Ptr is not fully polymorphic; it just means that not all instances of `Ptr t' have corresponding types in C. -- 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: Additions to the FFI API
On 28-Mar-2000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> wrote: > Sven Panne <[EMAIL PROTECTED]> wrote, > > 1) Although the Haskell 98 report states that Char should be a Unicode > >character, a plain char is used here. No implementation uses Unicode so > >far, and char is what one wants most of the time, anyway. > > As already pointed out by others, I guess, this one will > bite us one day. So maybe, we should say that `HsChar' > corresponds to `wchar_t' The ANSI/ISO C standard does not guarantee that `wchar_t' will be Unicode, or even that it will be large enough to hold Unicode. I believe that the Unicode consortium recommends against using `wchar_t' for Unicode if you want portable code. > and use `CChar' on the Haskell-side > whenever we want to guarantee that we use 8bit characters. > > 3) Stable pointers are passed as addresses by the FFI, but this is only > >because a void* is used as a generic container in most APIs, not because > >they are real addresses. To make this special case clear, a separate C > >type is used here. Foreign objects are a different matter: They are > >passed as real addresses, so HsAddr is appropriate for them. > > Yes, but it is not enough to say that `HsStablePtr' is > probably a `void *'. We have to guarantee that (I guess, we > also have to guarantee it for `HsAddr'). If a system > doesn't implement exactly this mapping, all bindings to C > code using C-style polymorphism (see my favourite `glist.h' > example from previous email re this topic) will break > anyway. If, as I suggested, `StablePtr Foo' maps to `struct HsStablePtrFoo *', C-style polymorphism using `void *' will still work. You just need `StablePtr t' where `t' is a type variable to map to `void *'. > > 4) The following standard types are so ubiquitous that they should probably > >be included, too: (any further types wanted?) > > > > Haskell type | C type > > -+--- > > CSize| size_t > > CSSize | ssize_t > > COff | off_t > > CPtrdiff | ptrdiff_t > > Surely a good idea to include those, but as Fergus said, > then it would be good to include as many of the ANSI C types > as possible. Which ones can we do without running the risk > that they are implemented as structs by some C system. The following ANSI/ISO C 89 types are guaranteed to be integer types: wchar_t ptrdiff_t size_t sig_atomic_t The following are guaranteed to be arithmetic types: clock_t time_t Note that in C 99, the complex number types are arithmetic types, so it is technically legal for a C 99 implementation to define e.g. clock_t as `double _Complex'... but in practice that is unlikely (for backwards compatibility with C 89, not to mention programmer sanity), so I think we can ignore that possibility. -- 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: Additions to the FFI API
On 28-Mar-2000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> wrote: > [EMAIL PROTECTED] (Marcin 'Qrczak' Kowalczyk) wrote, > > What woyld GtkText* map to? GtkText is a typedef to an opaque struct. > > One idea that we discussed is that `GtkText*' would map to > `Ptr GtkText', where `GtkText' is opaque und would indeed be > implemented as > > newtype GtkText = GtkText () > > This way, we wouldn't try to model Haskell's type system in > C or the other way around, but just increase type safety by > using types such as `GtkText' as Skolem variables that only > match with themselves in Haskell's type checker. Yes -- that kind of thing, plus the equivalent for the other direction (exporting Haskell to C), is what I was getting at when I stressed the importance of preserving static type information across the FFI boundary. > As Sven pointed out, it was suggested that we collect some > experience with this definition before including it into the > FFI standard proposal. The next version of C->HS will > support `Ptr a' to gather some experience with its use. Great! > PS: This proposal does not address the problem of cross-FFI > type consistency raised by Fergus. It only makes the > Haskell binding of C code more type safe. Actually it does address one half of the cross-FFI type safety problems I was talking about. The other half is just doing the same thing (or at least as much of it as is possible) for the C binding of Haskell code. I wasn't suggesting that you try to address the more difficult issue of providing full access to compound C data types from Haskell or vice versa. That would be a nice bonus, but it's a lot harder to implement. I'd be happy if you keep compound data types as opaque when viewed from the other side of the FFI interface. I just want them to be as type-safe as possible. Debugging problems that turn out to be due to type errors across a language interfacing boundary is in my experience difficult and time-consuming, because such bugs often manifest themselves in difficult ways (e.g. seg fault in the HLL code) and because the debugging tools generally don't have great support for debugging across the language interfacing boundary. -- 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: Additions to the FFI API
On 28-Mar-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Tue, 28 Mar 2000 20:14:26 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > > For type constructors like `->', `[]', and `Maybe', which (unlike > > StablePtr) don't have any C equivalent, I think you probably need > > to drop the structure, and just keep the top-level type constructor, > > thus mapping that type to just `struct HsStablePtrFunc *'. > > What about StablePtr SomeUserDefinedTypeConstructor? `struct HsStablePtrSomeUserDefinedTypeConstructor *'. Actually on second thoughts I think that should perhaps be just `struct HsSomeUserDefinedTypeConstructor *' and likewise for all the other mappings from `StablePtr' types; since the FFI always(?) requires the use of StablePtrs when passing compound types, I think there is no need to put `StablePtr' in the C type name. Does that sound reasonable? > There is no corresponding C type defined anywhere. So let the FFI generator declare one. There's no need to define it; leaving it undefined means that the type remains opaque. > > Still, just making sure that Haskell types with distinct top-level > > type constructors get mapped to distinct C types is probably enough > > to catch most of the type errors. > > IMHO it's not worth the conceptual complication of such arbitrary > decisions. It's not typesafe anyway. Well, that is a judgement call I guess. But personally I'd be happy to pay a little conceptual complication in the FFI if it saves me a few afternoons in the debugger wondering why my program is seg faulting. -- 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: runtime optimization of haskell
On 28-Mar-2000, S. Alexander Jacobson <[EMAIL PROTECTED]> wrote: > The issue is not just generating the data for a particular running > instance, but rather: > 1. generating the data from all/many running instances on user machines > 2. sending that data back to the developer for analysis > 3. generating useful reports on aggregate data > > Jacob Nielsen says that data from 5 users is enough to address most user > porblems so the above may be overkill, but I think it depends on the > problem you want to solve (performance optimization being somewhat more > complex). > > In any case, the point is to collect data on behavior of the code under > real life operating conditions rather than the test conditions of the lab. The difficulty with this is that there is a significant cost associated with collecting such data, and under real life operating conditions the real life users generally don't want to pay that cost. -- 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: Additions to the FFI API
On 28-Mar-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Tue, 28 Mar 2000 20:37:24 +1000, Fergus Henderson <[EMAIL PROTECTED]> pisze: > > > The ANSI/ISO C standard does not guarantee that `wchar_t' will be > > Unicode, or even that it will be large enough to hold Unicode. > > I believe that the Unicode consortium recommends against using > > `wchar_t' for Unicode if you want portable code. > > It also does not guarantee that char is ASCII, nevertheless Haskell > assumes that it is. Well, it is reasonable to make some assumptions which go beyond what ANSI/ISO C guarantees. I just want to be sure that you understand what assumptions you are making, so that if you do make such assumptions they are deliberate trade-offs rather than accidental non-portabilities. Having `char' be ASCII is very widespread, so assuming that is probabably a good trade-off; I don't see much likelihood of people wanting to port Haskell to EBCDIC environments. Having `wchar_t' be Unicode is not so widespread; indeed on some Unix systems what `wchar_t' represents depends on the current locale. > And allows int to be 128 bits, where Haskell does not have such type. Haskell allows Int to be 128 bits. But more importantly, the Haskell implementor who is implementing a Haskell<->C FFI can presumably add additional types to their Haskell implementation. However, they won't have the same freedom to add additional types to the C implementation. > The Haskell FFI will not be portable to every > ANSI C anyway. > > We should probably explicitly specify additional assumptions about > the C implementation. Yes, that would be a very good idea. > It's probably not very important to what type Char maps to. It maps > to HsChar, which can be char or wchar_t or int or whatever, as they > are mostly compatible in C. It's easier to explicitly specify fewer > assumptions about exact correspondence of types, and provide conversion > functions instead (for Haskell) and rely on implicit conversions > between integral types (for C) - than to try to find whether Char > should be mapped to char or wchar_t. Leaving the exact representation of HsChar unspecified seems quite reasonable to me. Note that the exact representation of HsInt certainly needs to be unspecified. So making HsChar's reprentation unspecified would be no great loss. > OTOH CChar and CWChar could be any types which: > - map to C types which have the same physical layout as char and > wchar_t respectively, ... > So for example CChar could be Int8 and CWChar could be Int32, ... > We could be more strict and make CChar and CWChar some more distinct > types, not synonyms to other integral types, newtypes say, and > guarantee that they map to char and wchar_t exactly. I think that is a very good idea. CChar and CWChar should be distinct types in Haskell, not type synonyms, otherwise it would be easy to accidentally write non-portable code that makes assumptions about how they are represented. > It would not > give much to guarantee exact correspondence on the C side. It would > give only one thing if I understand it: foreign exported functions > using CChar etc. will have proper C sygnatures in the *_stub.h file. > Will have exactly predictable C types, and not some compatble types. > Which makes sense if somebody wants to use C function pointers > with them. In the Mercury implementation, there are quite a lot of times where we take the address of a function exported from Mercury to C. I imagine the same might well be common for code interfacing Haskell with C. So I think it is worth getting that right. Another case where getting the exact types might be important is if you are interfacing Haskell code with C++. In C++, you might use overloading, and if the types generated by the Haskell FFI vary depending on platform or the Haskell implementation, this could cause your code to break when you try to port it. This situation is probably a lot rarer, but it's another point to consider. > So the question is: must CChar, CInt, CLong etc. map (in foreign > exported C type signatures) exactly to char, int, long etc., or it's > enough that they point to some physically compatible types (which > work even with mismatched function signatues)? I recommend the former. -- 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: multilingual programs
On 29-Mar-2000, D. Tweed <[EMAIL PROTECTED]> wrote: > On Wed, 29 Mar 2000, Matthias Mann wrote: > > > Has anybody some experience on what's the best way to write programs that > > may interact in multiple languages? > > > > My first thought was to extract all texts from the source and put them > > into a big list or array. The program then accesses the list > > corresponding to the selected language. > > Any other (better) ideas? Should inputs, e.g. answers to yes-no-questions, be > > handled the same? > > Not sure if this is a better idea, but the approach that, from what I can > gather, a lot of the GNU programs use is equivalent to replacing every > literal string in the text with roughly > > (lookup language "the string") One issue that you need to consider is that the word ordering may be different in different languages. So for a message like You have 3 apples. which in Haskell you might format using code such as this msg :: Int -> Fruit -> String msg num fruit = "You have" ++ show num ++ " " ++ show (plural_name (fruit)) the correct translation in some other language might have the number occurring after the fruit name. In C, this is handled using position parameters in printf() format strings (not standard C, but an X/open extension): | The printf() functions can handle a format string that enables the | system to process elements of the parameter list in variable order. In | such a case, the normal conversion character % (percent sign) is | replaced by %digit$, where digit is a decimal number in the range from | 1 to NL_ARGMAX. Conversion is then applied to the specified argument, | rather than to the next unused argument. This feature provides for | the definition of format strings in an order appropriate to specific | languages. For Haskell you would need to do something similar. -- 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: No more additions to the FFI API...
On 28-Mar-2000, Andy Gill <[EMAIL PROTECTED]> wrote: > > Don't mean to be rude chaps, but is there any way you can > have this conversation without flooding haskell.org? > > How about a mailing list, on haskell.org, for FFI issues? Well, I certainly understand that not everyone is interested in reading all of the details in this FFI thread. But on the other hand, I don't think we should create a new mailing list for every new thread that generates a lot of discussion. Perhaps we could create a single new mailing list called say `[EMAIL PROTECTED]' for long-running discussions? -- 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: Additions to the FFI API
On 29-Mar-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Wed, 29 Mar 2000 15:00:46 +1000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> >pisze: > > > > 6) Add HsBool with a mapping to an arbitrary integral C type, see Fergus' > > >point about a Haskell API. (Should we guarantee that False maps to 0 and > > >True to something <>0?) > > > > We don't make any guarantees for the mapping of Haskell _values_ > > to C _values_ for any other type. > > Of course we do. (HsInt)42 means 42 and nothing else. I guess this implies that Haskell implementations that use tags on Ints (e.g. to distinguish non-pointers from pointers, for GC) must apply a conversion to get from Haskell `Int' to C `HsInt' or vice versa. Fair enough... -- 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: Additions to the FFI API
On 29-Mar-2000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> wrote: > The code > > void *p; > struct foo *x; > struct bar *y; > > p = x; /* (1) */ > y = x; /* (2) */ > > compiles at (1) without problems, but gives a warning at > (2). Actually whether it is an error or a warning is implementation-dependent. Some C compilers, for example lcc, will report an error for this. Likewise `gcc -pedantic-errors' will report an error. The code is not strictly conforming C, and the C standard requires the compiler to issue a diagnostic, but a diagnostic can be either an error or a warning. (The only thing the C 99 standard requires an error for is the #error directive.) > I think that's actually a good idea. In fact, as this does > not raise a compile time error, but only a warning, it > doesn't prevent you at all from doing nasty things at the C > side (if you entertain such thoughts), As noted above, with some C compilers it is an error, but in that case you can easily avoid the error by inserting a cast, so I think your point still holds. -- 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: improving error messages
On 30-Mar-2000, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > | What do you think of improving the error messages like > | Prelude.take: negative argument > | (for say, take (-1) [(0,'b'),(1,'a')] ) > > That would be splendid. But I don't see how to do it. > > take :: Int -> [a] -> [a] > > Since take is polymorphic in a, I can't print a member of the > list. If you want to define your own take > > mytake :: Show a => Int -> [a] -> [a] > > that's fine, but it's a different function. Well, there's two separate issues here. One issue is what exception is thrown. One this issue, you are absolutely right: there is no way for the exception thrown to expose any information about the value or type of the argument, without breaking some of the nice properties that Haskell possesses. The other issue is what error message the implementation prints out if such an exception is not caught (as is _always_ the case for implementations which don't support ghc's `Exception' module or something equivalent). And on this issue, Haskell semantics don't impose any constraints. The message that the implementation prints out can be as informative as the implementor is capable of. There is no conceptual difficulty with a Haskell implemention printing out a full stack trace, complete with the values of all of the arguments. Of course, modifying an existing implementation to do so may well be by no means trivial, but it's just a matter of programming... If you really don't see how it could be done, I'd be happy to sketch the outline of a possible implementation. -- 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: ServiceShow for error messages
On 31-Mar-2000, Keith Wansbrough <[EMAIL PROTECTED]> wrote: > Sergey writes: > > [sketch of how to implement better error messages] > The problem with this is that there is a performance penalty to be > paid for overloading a function in this way. ... > Perhaps this could be turned on with a debugging option > but in general it would be a Very Bad Thing performance-wise. Certainly in cases where there is a trade-off between performance and good error messages, it is appropriate to use a compiler option to allow the programmer to select what they want. The Mercury compiler, for example, does exactly this: if you compile without debugging enabled, then error messages for uncaught exceptions include only the exception object and its type, whereas if you compile with debugging enabled then you also get a full stack trace, and furthermore if you then run the program under the Mercury debugger, then you can also browse the arguments of any of the calls on the call stack. While laziness does complicate things significantly, the same kind of thing would certainly be possible for Haskell too. -- 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: ServiceShow class for messages
On 31-Mar-2000, Marc van Dongen <[EMAIL PROTECTED]> wrote: > S.D.Mechveliani ([EMAIL PROTECTED]) wrote: > > [ error messages printing their aguments ] > > Printing the argument of a function as part of an error > message may lead to infinite error messages. Well, of course if the argument is large (let alone infinite), you don't want to print it all out, just part of it. And of course you don't want to evaluate the argument any further than it is already evaluated. But this is quite doable. -- 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: error messages
On 31-Mar-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > > Now, what should Prelude.take > think of Prelude.take (-1) (x:y:z:xs), > > how could it decide to display x ? > The compiler does not know whether show x > would lead to the infinite printing. > > Example: take (-1) (x,"a","b","c") where x = 'a':x That's a bad example, since it is not type-correct. I presume you meant take (-1) [x,"a","b","c"] where x = 'a':x In that case, I would recommend that the implementation display the second argument to take as [a, "a", "b", "c"] where a = 'a':a > I wonder whether this is possible. Yes, it is possible. -- 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: Untrusted code
On 06-Apr-2000, Chris Angus <[EMAIL PROTECTED]> wrote: > I was wondering if there was any way to run code which possibly > threw an error in any version of Haskell. > > e.g. > > efficient3rdPartyAlgorithm :: Int -> Int > myOwnSlowAlgorithm :: Int -> Int > > i.e. the idea is you run the efficent version and if > falls over you run your own version. In ghc this is possible, using the "Exception" library. See the ghc documentation for details. However, that question is different to the topic of running untrusted code, as you mention in your subject line. AFAIK, none of the existing Haskell implementations have any support for running untrusted code in a Java-like sandbox. Instead, AFAIK all of them permit code to use operations like `unsafePerformIO'. Well, Hugs and ghc do have options do disable extensions, like `unsafePerformIO'; if you run code with extensions disabled, that will, I believe, serve as a fairly secure sandbox, although AFAIK no-one has done any detailed security analysis of Haskell implementations or the Haskell standard library. But the drawback is that if you use those options, then you also can't make use of safe extensions like the "Exception" library (well, I think it's secure, but that's just my first guess, I haven't really thought about it much). There's no option which just disables unsecure extensions. -- 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: `deriving', newtype
On 25-Apr-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Which meaning of deriving Show would you choose? If the first, then > the new rule becomes "any class can be derived for newtypes giving > such-and-such effect, except Show and Read which are processed as in > Haskell98". If the second, the old rule has to be changed to include > "among Haskell98's derivable classes, Show and Read apply only to data, > not to newtype". I would recommend choosing the first. One reason for this is that defining the second behaviour manually is easier than defining the first behaviour manually. -- 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: a newbie's question about something related to runST
On 26-Apr-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > Hi, > > First I give the following primitive operations > > newVar :: a -> ST s (MutVar s a) > > readVar :: MutVar s a -> ST s a > > writeVar :: MutVar s a -> a -> ST s () > > Next consider the function > > f :: MutVar s a -> Mut Var s a > > f v = runST (newVar v `thenST` \w -> > > readVar w) > > 1. What is the type given to newVar v by the typechecker? Let's see... `v' has type `MutVar s a', and after renaming apart `newVar' has type `forall a2,s2 . a2 -> ST s2 (MutVar s2 a2)', so, substituting `Mutvar s a' for `a2', we see that `newVar v' has type `forall s2 . ST s2 (MutVar s2 (MutVar s a))'. -- 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: a newbie's question about something related to runST
On 26-Apr-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > > runST :: forall s. (ST s a) -> a It would be clearer to write that as runST :: (forall s. ST s a) -> a rather than relying on the relative precedences of `.' and `->'. > give runST the type signature > > >runST :: exists s . ( ST s a ) -> a > > and technically we have also a bounded variable s. What is the reason for > choosing > > forall against exists ? `forall' means that the variable can be instantiated by the caller, but not by the callee. `exists' means the opposite, that the variable can be instantiated by the callee, but not the caller. If a function has a universally quantified type such as `forall s . ', then the function definition must be polymorphic in `s', but the caller can call it with `s' bound to some particular instance. For `exists', it is the other way around, the caller must be polymorphic in `s' but the function definition could bind it to some particular instance. If some Haskell implementation supported `exists' in that position, and runST were declared with `exists' rather than `forall', then the following example would be well-typed: data MyStore = MyStore side_effect :: STRef MyStore Int -> Int -> () side_effect ref new_val = runST arg where arg :: exists s . ST s () arg = clobber_it clobber_it :: ST MyStore () clobber_it = writeSTRef ref new_val Note here how the definition `arg = clobber_it' binds the existentially quantified variable `s' to `MyStore'. This allows the side effect to escape the ST monad. You could then go ahead and use this nasty side_effect: main = print (runST nasty) nasty :: ST MyStore Int nasty = do x <- newSTRef 1 dummy <- newSTRef (side_effect x 42) readSTRef x This might print either 1 or 42, depending on whether side effect in the construction of the unused `dummy' variable was optimized out. Ouch! -- 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: updating file
On 27-Apr-2000, Jan Skibinski <[EMAIL PROTECTED]> wrote: > > currentSecond = second $ unsafePerformIO localDateTime > > where `localDateTime' has been defined via primitive > call to C: > > localDateTime :: IO DateTime > > To my distress the clock stopped after the first call to > `currentSecond'. I took me much more than just few seconds > to realize that the problem was not related to any > bug in the C code, but in the signature of > `currentSecond': > > currentSecond :: Int > > This is all fine and dandy if `currentSecond' is within `where' > clause, because it will be always evaluated afresh. It might happen to work with current Haskell implementations, but I don't think there's any guarantee of that. -- 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: When is it safe to cheat?
On 28-Apr-2000, Jan Skibinski <[EMAIL PROTECTED]> wrote: > > When can I safely cheat haskell compiler/interpreter > by pretending that I perform pure computations, > when in fact they are not? That depends on what degree of safety and portability you want. If you want the greatest degree of both of those, then currently the only safe answer is "never". The Haskell 98 Report does not standardize `unsafePerformIO', and so there are no guarantees about whether future implementations will have such a function, or what it would do, or when it would be safe. -- 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: When is it safe to cheat?
On 28-Apr-2000, Frank Atanassow <[EMAIL PROTECTED]> wrote: > Jan Skibinski writes: > >When can I safely cheat haskell compiler/interpreter > >by pretending that I perform pure computations, > >when in fact they are not? Here is a real example, > >from my Md5Digest module which works fine in Hugs: > > I don't understand what is impure about the MD5 example, but the time example > is clearly state-dependant. I think the bottom line is that unsafePerformIO > has no semantics beside the fact that it _forgets_ the effectful semantics of > the inner expression, I think you should stop a bit earlier, and just say that the bottom line is that unsafePerformIO has no semantics, period. It's certainly not guaranteed that `unsafePerformIO' will "forget" the effects of the inner expression. It might, of course, but then again it might not. > and since we don't have an operational semantics for > Haskell, you can in principle expect any "bad" use of unsafePerformIO to fail. Yes, and you can in principle expect that any use of unsafePerformIO might be "bad" for some future implementation. > For example, even if you try to suspend the evaluation by guarding the > expression with a (), as Nigel explained, a smart compiler could recognize > that a function of type () -> a is denotationally equivalent to a constant > of type a. Actually that is not true in general, since the `()' type has two values, namely `()' and bottom. But in specific circumstances a compiler could perform optimizations like that. -- 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: When is it safe to cheat?
On 28-Apr-2000, Erik Meijer <[EMAIL PROTECTED]> wrote: > Hi Jan, > > > When can I safely cheat haskell compiler/interpreter > > by pretending that I perform pure computations, > > when in fact they are not? > > If the computation is not pure, you cannot pretend it is. Indeed. And if the computation were pure, then why would it have `IO' in its type in the first place? ;-) > > Here is a real example, > > from my Md5Digest module which works fine in Hugs: > > > > digest :: String -> String > > digest string > > = unsafePerformIO ( > > marshall_string_ string >>= \x1 -> > > prim_Md5Digest_digest x1 >>= \x2 -> > > unmarshall_string_ x2 >>= \x3 -> > > return x3 > > ) > > I gues that for digest it holds that > > s1 == s2 > ==> > digest s1 == digest s2 > > The only reason that the underlying function is impure is that is allocates > memory to marshall its argument and then calls a C function. These > side-effects don't influence the result of computing digest I'm not familiar with Jan's Md5Digest module, or the various functions that it calls. But I remain unconvinced that your argument above need hold in general. Certainly there is nothing in the Haskell 98 Report that guarantees it, and last time I looked there was nothing in the ghc manual that guarantees it either. A Haskell implementation is free to assume that something of type `String' has no side effects at all (not just no side effects that alter the return value), and it may perform optimizations that rely on this. If you break that invariant, then the compiler may break your program. No doubt it works with the current version of ghc, but who knows what optimizations some future version of ghc may have? If implementations are to provide `unsafePerformIO', then really they ought to document when it can safely be used. Current implementations don't do an adequate job of that, AFAIK. -- 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: your mail
On 29-Apr-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > > Is it possible to interrogate the typechecker > from within a Haskell program You can of course invoke a Haskell typechecker (e.g. Hugs) as a separate process. Why do you ask? What kind of questions do you want to ask the type checker? -- 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: Performance, and algorithms
On 30-Apr-2000, Ian Jackson <[EMAIL PROTECTED]> wrote: > I've been using GHC's profiling support. This gives me information > about numbers of `allocations' (which I presume refers to memory > allocations) and does indeed point the finger at the part of the > program that I most suspected anyway. > > I think the program is using too much CPU rather than too much memory > because (a) my machine doesn't thrash and (b) the test case I'm using > is not very large. Thrashing is determined by the amount of live memory. Allocations measure that amount of memory which is allocated, but in general not all of the allocated memory will remain live. Memory allocations that subsequently become garbage don't influence the working set size much, but they do influence CPU usage, since it takes quite a bit of CPU do the allocation and/or to garbage collect it afterwards. > * I added a reasonable amount of added strictness in `obvious' kind of > places, but with no visible effect on performance. Does adding > strictness help with CPU use as well as with memory use ? Where is it > most beneficial to add strictness ? It's most beneficial to add strictness annotations on data structures. Compilers for lazy functional languages tend to do a reasonably good job of inferring strictness of functions, but a lousy job of inferring strictness of data constructors. > * Most of my program is in a state-threading monad of my own (built > out of normal functional pieces). The main program (which is in the > IO monad) invokes the `grind handle on state machine' function, > passing the action to perform and the initial state and getting the > new state back. Is this good, bad, or ugly ? That sounds OK to me. > * In particular, the bit of code that seems to be slow is the part > responsible for updating a part of the state whose type is broadly > speaking > >Array (x,y) [value] ... > In C I would have just had one big flat array and updated it in > place. How can I get a Haskell compiler to do the same ? With ghc, you can use the `STArray' type defined in the `ST' module. > * I really wanted a simple, flat, strict type rather than the lazy, > nested [value]. I'm only using a list because I want to do a zipWith > on it in the update function. Also, the manual says that an Array is > not strict in its contents, which doesn't seem helpful to me. Rather than using Haskell's list type, which is lazy, you can define your own strict list type data List t = Nil | Cons !t !(List t) You can easily write a zipWith function for this type. -- 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: Impasse for math ...
On 02-May-2000, Jerzy Karczmarczuk <[EMAIL PROTECTED]> wrote: > For me it is obvious that Simon PJ, the Oregon Strong Team, > Lennart, and others who actively work/ed *on the language > itself* have different priorities! Changing a mature > programming language is dangerous, everybody knows that > (in particular if one teaches it...). > > == > > I believe that the situation will get unblocked with the > birth of the *successor* to Haskell. Well, Mercury is not really intended as a successor to Haskell -- more like a competitor ;-). But if people work on the design of math class hierarchy for Haskell, this work might eventually find its way into Mercury, even if it doesn't make it into Haskell. Mercury has a Haskell-like type class system, but its current standard library, which predates the adoption of type classes in Mercury, does not use type classes at all. So in the medium to long term, we are planning on developing a new standard library for Mercury, one which does make appropriate use of type classes. The design of this new library is completely up for grabs at this point. We'd like to smooth the transition as much as possible, so probably the names in the new library will match those in our existing library, but as far as the class hierarchy is concerned, there are no backwards compatibility constraints at all. -- 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: your mail
On 02-May-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > > > > On 29-Apr-2000, Jan Brosius <[EMAIL PROTECTED]> wrote: > > > > > > Is it possible to interrogate the typechecker > > > from within a Haskell program > > > > You can of course invoke a Haskell typechecker (e.g. Hugs) as a separate > > process. > > > > Why do you ask? What kind of questions do you want to ask the type > > checker? > > Suppose in some function definition some variable is of type A s a and I > want to do something like this : if the type variable of the first parameter > in A s a is s then do this if not then do something else. That particular example seems nonsensical: you're asking if `s' is `s'? The answer would always be "yes". More generally, you can use the `Dynamic' module (a Hugs/ghc extension) to perform dynamic type tests, so long as the type that you are testing is an instance of the `Typeable' type class. > It should be some sort of program flow during compilation before the code is > generated. If you're worried about efficiency, with a little bit of partial evaluation, a good compiler should be able to optimize away dynamic type checks in cases where the type is known at compile time. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit WWW: <http://www.cs.mu.oz.au/~fjh> | of excellence is a lethal habit" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
Re: recent summary for basAlgPropos discussion
On 05-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Harmless for hackers, advanced for snobs > > I am going to prove (can I ?) that basAlgPropos is so. > The approach is: do not mention advanced features in the hacker > program, and the program would not bite you. ... > Few explicit categories, many implicit ones > --- > AddSemigroup ... Ring, EuclideanRing ... are the explicit > categories - there are provided the *classes* for them. > > How the hacker uses them? One simply takes (+) from Additive, > (*) from Multiplicative, dimRem from EuclideanRing > - instead of Num, Integral of old Haskell-98. > When one wants the instance for the type T with, say, (*), > one needs to declare for it > instance Set T -- skip implementation ! > instance Multiplicative T where (*) = ... Personally I think it is bad that Haskell allows this. The Haskell report says the following: | If no binding is given for some class method then the corresponding | default class method in the class declaration is used (if present); | if such a default does not exist then the class method of this | instance is bound to undefined and no compile-time error results. But I think it would be better if the last two lines were replaced with | if such a default does not exist then a compile-time error results. The existence of this loop-hole compromises Haskell's static type safety. > Also one writes, for example, zero x > instead of zero `asTypeOf` x. The latter is clearer. This change reduces program readability, IMHO. I also agree with Marcin 'Qrczak' Kowalczyk's arguments on this issue. > Is simplicity possible? > --- > Some people say here, that this is impossible, that the compilation > errors become the run-time ones ... > I do not see, so far, in what way these matters may occur serious. > For the critics, it is a good point to provide some schematic > examples. OK. Consider the following scenario. Alfred defines a type `T' and writes such a vacuous instance declaration for `Set T'. This is part of a large library package that Alfred has written. Meanwhile, Betty has written another library package that provides functions on `set a'. Charles writes a program using both Alfred's and Betty's libraries. Being pressed for time (aren't we all?), Charles does not test his program very thoroughly. Instead, since his program type-checks, and it's late Friday evening and already past the deadline, he ships his program to Duncan. On Monday morning, Charles is surprised to find an angry message from Duncan saying that the program didn't work. Of course, Duncan doesn't give Charles enough information to duplicate the problem, so Charles wastes most of Monday trying to get the appropriate information from Duncan so that he can reproduce the bug. Finally he does so, and is able to reproduce the problem. After a fair amount of time debugging, he is able to track the problem down. But he still can't solve it! The problem is that in order to solve it, he needs to modify Alfred's library package. For a variety of reasons, doing that could be difficult. Firstly, he might not have source code. Secondly, even if he did have source code, there may be copyright issues -- he might not have legal permission to modify it. Thirdly, even if he did have source code, and permission to modify it, it may be problematic to do so, since (a) now he will have to ship Duncan the modified version of the library, and (b) this may lead to maintenance difficulties if Alfred later releases a new version of his library. -- 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: basAlgPropos. Skipping class methods
On 06-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Fergus Henderson <[EMAIL PROTECTED]> writes on 6 May 2000 > > > Personally I think it is bad that Haskell allows this. > > The Haskell report says the following: > > | If no binding is given for some class method then the corresponding > | default class method in the class declaration is used (if present); > | if such a default does not exist then the class method of this > | instance is bound to undefined and no compile-time error results. > > > But I think it would be better if the last two lines were replaced > > with > > > > | if such a default does not exist then a compile-time error results. > > > > The existence of this loop-hole compromises Haskell's static type > > safety. > > If this happens, there will appear more definitions in the > application programs like >instance Foo (C a) where foo = dummy_of_some_kind > -- or maybe= error "..." That would be a good thing. It would make the original programmer and anyone else reading the code more aware of the danger that such incomplete instance declarations constitute. > Because it is wrong for the standard classes to pretend for *all* > their operations to have a real sense in *all* the user instances. > The user may know better one's situation, one may rely on the > standard operation op1 and ignore another standard op2, having > some replacement for it, maybe, in other, user class, or maybe, not > exploiting it at all. The programmer is free to do so, but doing so is risky, and so if that is really what they want, they should have to write it out explicitly, so that they and future maintainers will remain aware of the risk. > On this subject, Bart Demoen <[EMAIL PROTECTED]> writes > > >> I am quite happy with not getting a compile-time error for > >> non-implemented class methods, as long as I get a compile-time > >> error when I try to use a non-implemented class method. > > Maybe, it is the best approach? As Marcin 'Qrczak' Kowalczyk, this approach is in general not possible. > >> Also one writes, for example, zero x > >> instead of zero `asTypeOf` x. > > > The latter is clearer. This change reduces program readability, IMHO. > > I also agree with Marcin 'Qrczak' Kowalczyk's arguments on this issue. > > The expression zero `asTypeOf` x > still is, *formally*, not a constant, it depends on x and means > certain map applied to x. `asTypeOf` is effectively a builtin language construct that just happens to be implemented as a function in the standard Prelude (because it can be). It is even mentioned explicitly in the main part of the Haskell report (specifically in 4.3.4), not just in the part describing the Prelude. Anyone who is truly familiar with Haskell will know exactly what it does. On the other hand, `zero' and the other functions that take unnecessary dummy arguments in your proposal do not have the same status. > The same is zero x > Also zero x is shorter. Shorter does not imply more readable. > Finally, with class Foo a where cardinality :: Int > your approach is impossible. > We are still forced to introduce a sample (dummy) argument >class Foo a where cardinality :: a -> Int Dummy arguments are sometimes needed. But the less often they are needed, the better, IMHO. Incidentally, this is an area where Mercury is more expressive than Haskell. In Mercury, dummy arguments are still needed sometimes. But using Mercury's mode system, you can express in the function's declaration the fact that it depends only on the argument's type, not on its value, by using the mode `unused' rather than `in': :- typeclass foo(A) where [ func cardinality(A::unused) = (int::out) ]. The compiler's static checking will enforce this mode declaration; it would be a compile-time error to define an instance of this typeclass for which the cardinality function examined the value of its argument. -- 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: basAlgPropos. Skipping class methods
On 06-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > > > Consider the following scenario. Alfred defines a type `T' > > and writes such a vacuous instance declaration for `Set T'. > > This is part of a large library package that Alfred has written. > > Meanwhile, Betty has written another library package that provides > > functions on `set a'. Charles writes a program using both Alfred's > > and Betty's libraries. Being pressed for time (aren't we all?), > > Charles does not test his program very thoroughly. Instead, since > > his program type-checks, and it's late Friday evening > > [..] > > Rather long thing. The impression is that the trouble is in > "late Friday evening" and such things, that may happen with > *everything*, independently on whether this thing is based on > basAlgPropos or it is just in Haskell-98. I try to understand it: >Alfred.hs [or .o ?] : >type T a = ... >instance Set (T a) where baseSet = vacuous... >... >Betty.hs [.o]:f :: Set a => a -> T a ... >... In my example, Betty's code does not use anything from Alfred's code. In particular it does not use `T'. So it should be something like this instead: Betty.hs [.o]:f :: Set a => a -> Int ... >Charles.hs [.o]:import Alfred >import Betty ... >... The key point is that Charles.hs contains a call to Betty's function, passing it Alfred's type: foo :: Alfred.T -> ... foo x = ... (Betty.f x) ... > What you are saying is that setting things like > baseSet = error "dummy_baseSet" > for T a > creates the problems because Charles may like to exploit > essentially the result of baseSet on say T Bool. > Right? Not exactly. Charles just wants to call Betty's function `f'. Charles has never even heard of `baseSet'. Betty is the one that wants to exploit the result of baseSet. But Betty's code is polymorphic; she doesn't want to exploit baseSet for type `T Bool', she wants to exploit it for a value of type `Set a => a'. Betty has never even heard of the type `Alfred.T'. > This critic looks strange: searching for problems where there are > not any. > Alfred defined *his* user type T and *his* Set instance for it. > And Charles dislikes this instance. > Why basAlgPropos is guilty? Because basAlgPropos encouraged the poor coding style that Alfred used. How, I hear you ask? That coding style was the only easy option. The only alternative would have been for Alfred to define instances of a whole lot of methods that he doesn't understand and doesn't intend to use, and that would have been both time-consuming and error-prone. > The same is with any other libraries. No, libraries written in a good style won't force their users to define instances of lots of methods that they don't understand and don't intend to use. > For example, writing the above program Alfred.hs under > basAlgPropos, a good hacker has to put in documentation > " >The program Alfred was compiled without -fadvancedAlgebra: >the standard advanced algebra operations are put dummy. > " If Alfred was a really good hacker, he would realize that defining incomplete instance declarations like this will quite likely cause trouble for the users of his library, and so he will prefer to give proper instance declarations. It's almost always better to fix a bug rather than simply documenting it. But, suppose Alfred does document his code like this. Then how is Charles to know whether passing Alfred.T to Betty.f will be safe? Perhaps Charles reads Betty's documentation. Now, some of the time Betty will simply not have documented whether her library depends on the standard advanced algebra operations. In that case, if Charles is being cautious, then he cannot use Betty's library at all. Other times, Betty may have documented that her library does not depend on the standard advanced algebra operations. In that case, Charles can go ahead and use Betty's library. But then the next version of Betty's library may well use those operations! Betty will need to be very careful to document this change in the release notes. Of course, by this time Charles will have moved on to another job, and there will be a new programmer Edward who is maintaining Charles' program. Edward will need to go through the WHOLE PROGRAM looking for any place where it calls Betty's functions with an argument that
Re: fix
On 06-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > To my > > >> Alfred defined *his* user type T and *his* Set instance for it. > >> And Charles dislikes this instance. > >> Why basAlgPropos is guilty? > > Marcin Qrczak Kowalczyk <[EMAIL PROTECTED]> writes > > > Because it unnecessarily forced him to define a Set instance, and to > > do it early. > > Alfred is not forced to define this Set instance for his T. > If he skips the key-fadvancedAlgebra, > > the compiler has to insert the default one automatically - if it > finds that the program exploits it. > Why not assume this, for example? If the default instance simply defines all methods as bottom, then it doesn't help; in the scenario that I outlined, Charles will still have the same problem when he passes `Alfred.T' to `Betty.f'. -- 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: basAlgPropos. Why sample argument
On 07-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> writes > > > Sample arguments are bad, because: > > [5 points follow] > > But they are only for snobs. That doesn't matter; we don't want to add a bad feature, regardless of who is likely to use it. > > 1. They present a confusing interface. This looks like a function, > > but the real meaning is a constant. Neither mathematics nor > > programming languages treat zero as a function from any unused > > number to the zero value. > > zero `asTypeOf` xis also a function applied to x. >Where is the difference? See my earlier mail: `asTypeOf' is essentially a language construct. > > 5. They hurt performance, Not always they can be optimized out. > > Why? zero `asTypeOf` x is as likely to be optimized as zero x. That is not true. The reason is that `asTypeOf' is a (standard Prelude) function, whereas `zero' is a class method. Since `asTypeOf' has a trivial definition, any half-decent optimizing compiler will inline it. Specializing class methods, on the other hand, is more difficult. > If for the former, the instance of `zero' is defined simply and can > be, say in-lined, then the latter can too. That is pretty much true. The problem comes when the compiler *can't* figure out statically which instance of `zero' this code will call. > basAlgPropos introduces `zero x' because > * Haskell has problems with constants in methods, in particular > `asTypeOf` is often needed, I don't buy that argument. > * `zero x' fits the aim of implicit dynamic domains. This one is much more interesting. -- 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: When is it safe to cheat?
On 10-May-2000, Sverker Nilsson <[EMAIL PROTECTED]> wrote: > > Relevance for Haskell would be that you wouldnt be able to fork a > program written in C into a protected environment (functional > sandbox?) and know that its result would depend only on its input > arguments. So you couldnt safely do this thru an ordinary Haskell > function call that could be cached for example. Well, you don't have that guarantee anyway. C has many areas of undefined and/or unspecified behaviour. There is no guarantee that C code will be deterministic. So do operating system ABIs. Even hardware architectures often have areas of undefined and/or unspecified behaviour. To give you a practical example: on SPARCs, the contents of uninitialized stack slots are unspecified, and in practice they are nondeterministic. This happens because the SPARC's register windows get flushed to the stack when a context switch occurs, and the timing of context switches is in general nondeterministic. If you write a C program that examines uninitialized stack slots -- for example one using a conservative garbage collector -- then the program's exact behaviour can be nondeterministic. (This has bitten me in the past.) -- 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: how to replace Prelude
On 12-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > > Sorry for easy question, > who could explain please, can Haskel work with the user-provided > prelude instead of standard? Name your prelude something different than "Prelude", e.g. "SDM_Prelude". Then every module which wants to use this prelude rather than the standard prelude should begin with the following two lines: import qualified Prelude import SDM_Prelude SDM_Prelude itself should start with import qualified Prelude and it can then define its own `+' in terms of `Prelude.+'. -- 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(..) ?
On 15-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > I am again stuck. Who could help, please? > >module T >where >import Prelude ( tail, (.) ) -- List(..) ? At first glance, I didn't see what the problem was. But having tried it myself, I see why you're having difficulty. There's simply no valid syntax in Haskell 98 for naming the list type constructor (`[]') in a module import or export list! Following the grammar in the Haskell 98 Report, :exports -> ( export1 , ... , exportn [ , ] ) (n>=0) :export -> qvar :| qtycon [(..) | ( qcname1 , ... , qcnamen )] (n>=0) :| qtycls [(..) | ( qvar1 , ... , qvarn )] (n>=0) :| module modid :qcname -> qvar | qcon : :qtycon -> [modid .] tycon :tycon -> conid :conid -> large {small | large | digit | ' } we see that the name of a (possibly qualified) type constructor in an export list is a `qtycon', which is an optionally module qualified `tycon', which is just a `conid', and a `conid' is just an identifier starting with a capital letter. The same is true for module imports. The problem is that although the grammar for types includes a nonterminal `gtycon' which includes syntax for various special type constructors, :gtycon -> qtycon :| () (unit type) :| [] (list constructor) :| (->) (function constructor) :| (,{,}) (tupling constructors) the grammar for import and export lists use `tycon' and `qtycon' (respectively) rather than `gtycon'. Is there any particular reason for this, or is this just a defect in the Haskell 98 report? Would changing `qtycon' to `gtycon' in the grammar production for `export' cause any problems? Likewise, how about changing `tycon' in the grammar production for `import' to say `gutycon', defined by gutycon -> tycon | () (unit type) | [] (list constructor) | (->) (function constructor) | (,{,}) (tupling constructors) ? For Haskell implementations that follow the report, I don't see any easy work-around for this problem. The only thing you can do is to use `import qualified Prelude' rather than `import Prelude(...)'. The good news is that ghc (4.04) does not follow the Haskell 98 report -- it accepts the following code, apparently as an extension to Haskell 98 (even without `-fglasgow-exts'): module Example(Prelude.[](..)) where import Prelude([](..)) Similarly, it also accepts module Example(Prelude.[]((:), [])) where import Prelude([]((:), [])) -- 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: user Prelude
On 15-May-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > ... only several days ago I have realized or recalled that it is > possible to replace some algebraic part of Prelude-98 with the > user prelude. Someone, - thanks for the help, - had confirmed > this recently: use import qualified Prelude > import MyPrelude > > Probably, this makes the implementation easy. > A small problem remains, for example, with the code like >case xs >of > [Prelude.Just] -> [Prelude.True] > (Prelude.Just) Prelude.: xs -> Prelude.Nothing Prelude.: ys > > I expect, it would not be good to repeat the definitions of > data Maybe, data Bool > in MyPrelude. Right. Instead, you can simply re-export them: module MyPrelude(Prelude.Maybe(..), Prelude.Bool(..)) where import qualified Prelude Then you can go ahead and use these in code that uses your standard Prelude: module Example where import qualified Prelude import MyPrelude conj :: Bool -> Bool -> Bool conj True x = x conj False _ = False -- 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(..) ?
On 15-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > On Mon, 15 May 2000, S.D.Mechveliani wrote: > > >import Prelude ( tail, (.) ) -- List(..) ? > > [](..) or []([],(:)) > And also: ()(..) or ()(()) > > AFAIR the report says that : is a special syntax that always refers to the > Prelude thing, for consistency with the rest of the list syntax. But in > GHC (:) must be imported like other constructors, where other list > constructions are indeed magical - hmm, I guess GHC is not right here and > should always understand (:). The report is actually a bit unclear: it says that `:' is a special syntax, and it gives a definition of `:' in the Prelude, but it doesn't actually say that `:' always refers to the Prelude version. It's not clear from the report what is supposed to happen if you write import Prelude () nil :: [a] nil = [] or import Prelude () cons :: a -> [a] cons h t = h : t The report says "every name explicitly mentioned by the source code must be either defined locally or imported from another module" (5.3.3), but it seems that the special syntax `[]' and `:' are not "names" (2.4), so I guess this rule does not apply to them. However, it would help a lot if the report was clearer about this point. The existing implementations I tried behave differently. Hugs allows the first example, but rejects the second, which seems quite inconsistent. ghc rejects them both, which is at least consistent, but goes against my interpretation of 5.3.3. Also, that approach is not a complete solution unless you also extend the syntax of imports and exports to allow (:) and [] to be explicitly imported and exported, as ghc seems to have done. If you take this approach but omit the extension, then `import Prelude (...)' becomes unusable, and instead you have to just use `import qualified Prelude'. -- 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: Type of minimumBy
On 17-May-2000, Keith Wansbrough <[EMAIL PROTECTED]> wrote: > Moving this thread to the Haskell list... > > Summary: the Haskell 98 Report claims > > minimumBy :: (a -> a -> Ordering) -> [a] -> a > > but Hugs and GHC implement > > minimumBy :: (a -> a -> a) -> [a] -> a > minimumBy = foldl1 > > Carl writes: > > > Sigbjorn Finne <[EMAIL PROTECTED]> writes: > > > > > This a doc bug on the GHC (and Haskell report) side - > > > Hugs98's List.minimumBy type is the right one (and also > > > the type of the *defn* in the Lib Report.) The Haskell Library Report is clearly inconsistent here. > > mimimumBy :: (a -> a -> Ordering) -> [a] -> a > > > > seems much more useful than > > > > mimimumBy = foldl1 > > maximumBy = foldl1 > > > > Why do you say the latter is "right"? Hmm... Take a look at 7.6 in the Haskell Library Report: | 7.6 The "By" operations | |By convention, overloaded functions have a non-overloaded counterpart |whose name is suffixed with "By". ... |The "By" variants are as follows: [...] maximumBy, minimumBy. OK, based on this, all we need to do is to look up the type of `minimum', and figure out the corresponding type for the non-overloaded counterpart. So, consulting the section A.1 of Haskell Report, we find that the type of `minimum' is | minimum :: Ord a => [a] -> a But the correct type for the non-overloaded counterpart of this is not so clear, because `Ord' has a bunch of different methods: |class (Eq a) => Ord a where |compare :: a -> a -> Ordering |(<), (<=), (>=), (>) :: a -> a -> Bool |max, min :: a -> a -> a |-- Minimal complete definition: |-- (<=) or compare It is not clear which of these should be used as the parameter for "By" variant. I see three alternatives: (1) Section 7.6 does gives us a hint: |... when the "By" function replaces |an Ord context by a binary predicate, the predicate is assumed to |define a total ordering. Here the phrase "binary predicate" suggests we should use something of type `a -> a -> Bool'. So perhaps we should use `<='. (2) On the other hand, the other "By" variants of functions that take something constrained by `Ord', i.e. `insertBy' and `sortBy', use an argument of type `a -> a -> Ordering'. So for consistency `minimumBy' should do the same. This is probably a more compelling argument. (3) The Haskell Libary Report's _definition_ of those functions gives us yet another alternative, using a parameter of type `a -> a -> a', i.e. `min' for `minimumBy' and `max' for `maximumBy'. This interpretation is apparently supported by the status quo amongst implementations (at least Hugs and ghc). But it is somewhat inconsistent with the choice made for `insertBy' and `sortBy', and as Carl Whitty argued, it is not very useful, since in that case `minimumBy' and `maximumBy' become just alternative names for `foldl1'. Of these three solutions, I personally favour (2), unless there a significant amount of code for the existing implementations would be broken if they changed, which I suspect is unlikely. If solution (3) is adopted, the above-quoted phrase "binary predicate" from 7.6 should be replaced by "comparison function": ... when the "By" function replaces an Ord context by a comparison function, the comparison function is assumed to define a total ordering. Likewise that paragraph should be reworded if solution (2) is adopted. -- 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: how to replace Num.fromInteger 2
7;) on the arguments to be monads. As Haskell currently stands there is no way to use the monad syntax 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 standard Prelude. Comments? -- 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: how to replace Num.fromInteger 2
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 function define in the Prelude, it really > > ought to be written as > > > > The special form -e denotes prefix negation, the only prefix operator in >Haskell , and is > > syntax for Prelude.negate (e). > > > > IMHO it is better to state that all such names mentioned in the report > refer to Prelude versions, than to clutter the report with explicit > Prelude qualification everywhere. Looking at the report again, I see that in fact it does do this: | 3 Expressions | |In this section, we describe the syntax and informal semantics of Haskell |expressions, |including their translations into the Haskell kernel, where appropriate. ... |Free variables and constructors used in these translations refer to entities |defined by the Prelude. To avoid clutter, we use True instead of Prelude.True or |map |instead of Prelude.map. (Prelude.True is a qualified name as described in Section |5.3.) So I retract that criticism. Sorry, I didn't notice that section of the report first time around. -- 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: how to replace Num.fromInteger 2
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 integer literal i is equivalent to fromInteger i. Normally > > fromInteger is a method in the standard Prelude class Num (see Section > > 6.4.1), but it is also possible for modules to use `import qualified > > Prelude' and then define their own fromInteger function or method, > > or import fromInteger from another module. > > Such breakage of lexical scoping is generally dangerous and bad > language design (like using C preprocessor); not because it is a > change, but in itself. > > I would be disappointed if code like: > bad x = -x > where > negate = ... > did not use standard meaning of unary negation. You raise a good point about accidental redefinition for cases like this. But the current definition of Haskell doesn't just prevent accidental redefinition, it also prevents deliberate redefinition. Wouldn't it be better if we could somehow allow deliberate redefinition, so people like S.D.M. could design alternative preludes, while still preventing all or at least almost all cases of accidental redefinition? I think it would. One way to achieve this would be simply to define all the syntactic constructs to expand to calls to functions with a long prefix that people are unlikely to define accidentally. For example, rather than defining the `do' syntax to call `>>' directly, it could be defined to call say `__builtin_do_syntax__BIND__', which would be defined in the standard Prelude to call `>>'. Similarly, unary minus could be defined in terms of `__builtin_negation_syntax__NEGATE__', which would be defined in the standard Prelude to call `negate'. I understand why you would be disappointed if code like bad x = -x where negate = ... did not use standard meaning of unary negation. But if the code looks like bad x = -x where __builtin_negation_syntax__NEGATE__ = ... then it's much more obvious that something funny is going on here. If you would still complain about this, I would say that it is a small price to pay in order for people to be able to define alternative preludes. -- 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: When is it safe to cheat?
On 10-May-2000, Sverker Nilsson <[EMAIL PROTECTED]> wrote: > Fergus Henderson wrote: > > To give you a practical example: on SPARCs, the contents of > > uninitialized stack slots are unspecified, and in practice they are > > nondeterministic. This happens because the SPARC's register windows > > get flushed to the stack when a context switch occurs, and the timing > > of context switches is in general nondeterministic. If you write a C > > Which OS on the Sparc are you referring to? SunOS. > Seems to me that this OS doesn't support transparent context > switches. Yes. Off-hand, I'm not sure whether this is merely a flaw of the OS or whether it is due to the hardware. I guess comp.arch would be the place to go to find people who know the answer to that. -- 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: user Prelude
On 15-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Mon, 15 May 2000 08:53:21 +0400 (MSD), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > > > I expect, it would not be good to repeat the definitions of > > data Maybe, data Bool > > in MyPrelude. > > 1. import qualified Prelude >import Prelude (Bool(..), Maybe(..), etc.) > > 2. import Prelude hiding (Num(..), Integral(..), etc.) Both of these solutions require more work from the user of the alternative Prelude. The approach that I suggested, namely re-exporting Bool(..) and Maybe(..) from the alternative prelude, is better because the extra work is done by the implementor of the alternative prelude, which means it only needs to be done once, rather than once for every time you use the alternative prelude. -- 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(..) ?
On 20-May-2000, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote: > Of course, that doesn't solve the problem! Sergey essentially wants to > replace the entire prelude, special syntax and all. There are lots > of small but important things under the heading of special syntax: > > Explicit lists [a,b,c] > List comprehensions > Numeric constants (1 means 'fromInteger 1') > do notation > > Here is an idea for an extension to Haskell 98 to support this. Suppose > we added a pragma, or compiler flag, that let us say where the special > syntax should come from: > > module M where > import Prelude () > import {-# SYNTAX #-} MyPrelude > > Here, I've expressed it as a pragma. The idea is that wherever we have > a special syntax think, like [Int], it means 'S.[] Int', where S is > either 'Prelude' or, if there's a SYNTAX pragma, the module specified > in the pragma. ... > I don't think this would be too hard to implement in GHC. Now I think > about it, it's rather attractive. I wonder what other people think? I like this proposal. I'm not rapt about the particular syntax you've chosen for it, though. I think I'd prefer something that was part of the language syntax proper, rather than a pragma. Perhaps module M where import Prelude () import syntax MyPrelude where `syntax' here would be treated as a special-id (like `qualified')? Or how about just module M where import prelude MyPrelude ? > That module had jolly well better export all the things > needed to support special syntax (which we'd need to enumerate). It may be best to check that requirement lazily: the module would only be _required_ to export the things needed for those parts of the syntax which the importing module actually uses. This would make it easier to develop an alternative prelude in a step-by-step manner. > Note that if we chose to do this, we'd want the ability to have '[]' in > export lists, so that MyPrelude was able to explicitly export '[]', so that > the SYNTAX lookup would find it. So we'd also have to extend the syntax of > import and export lists as Fergus suggests. But this facility would only > be useful for (the) module intended to be imported with {-# SYNTAX #-} Another alternative to this would be to simply define the `[]' and `:' constructors as syntactic sugar for `ListNil' and `ListCons', and to define the `[]' list type constructor as just 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 any particular preference as to which of those two solutions is adopted, but I thought the alternative worth mentioning. -- 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(..) ?
On 21-May-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > Sat, 20 May 2000 13:13:22 -0700, Simon Peyton-Jones <[EMAIL PROTECTED]> pisze: > > > Explicit lists [a,b,c] > > List comprehensions > > Numeric constants (1 means 'fromInteger 1') > > do notation > > > > Here is an idea for an extension to Haskell 98 to support this. > [...] > > It has small problems (and IMHO nobody should need to replace the > list type etc.). > > What about string literals - do they refer to Prelude list type or > the replacement? For consistency, I would recommend the latter. > The first is a bit inconsistent, the second does > not allow optimizations. Why do you say the second does not allow optimizations? Surely the compiler can perform exactly the same optimizations, if it just makes those optimizations conditional on this feature not being used. If you don't use the feature, you don't pay for it! Of course a compiler could also do better, and perform the same kind of optimizations even if an alternative prelude was used, so long as those optimizations still make sense. That might be a little more difficult to implement, since the optimizations would have to be done in a slightly more general way. But I don't see it as being infeasible. > If list comprehensions are translated literally as the report says, > they don't allow optimizations too, unless the compiler is smart > enough to optimize the translation. Currently GHC does not optimize > concatMap (\x -> [x]) into identity. The issue here is the same. GHC can do exactly the same optimizations it currently does, if it just makes them conditional on this feature (the `{#- SYNTAX -#}' pragma, or whatever syntax is chosen for it) not being used. If the feature is used, then it would have to use the translation in the report, and then optimization might be a bit harder; but optimization is still possible, it's just a quality of implementation issue. > If the programmer says: > data [a] = () | a:[a] > data () = [] > is [1,2,3] a type error (because it gets translated to 1:2:3:[])? > > If he says: > data X= Int:Stop > data Stop = [] > is [1] permitted? > > Is this permitted: > type (,) = Prelude.[] > type [] = Either > f :: (,) ([Int] String) > f = [Left 5, Right "foo"] So far no-one has proposed allowing special symbols such as `[]', `()', or `:' in definitions -- only in import and export lists. So with the current proposals, those examples would all be syntax errors. Unless someone can suggest a good reason why there would be some benefit in allowing people to define those symbols, I see no reason to do so. But being able to import and/or re-export such symbols is necessary if you want to be able to implement an alternative 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 t -> Prelude.IO t and then `main' could be defined using `run' main = run (...) so I don't see that as being a problem. -- 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(..) ?
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 implement an alternative prelude. > > No: they can be simply always available, just as \ and let. OK, I guess that would work too. Just to elaborate a little: with this suggestion, I suppose the following module would be legal: module Foo(List, nil, cons) where import Prelude () type List t = [t] nil = [] cons = (:) Neither Hugs nor ghc currently allow this; Hugs complains about `:' being undefined (but allows it if the definition of cons is replaced with e.g. `cons = cons'), while ghc complains about both `:' and `Prelude.[]' not being in scope. But looking at the Haskell report, I think your suggestion looks like it is the correct interpretation of the current wording, and Hugs and ghc are wrong. The current wording is as follows: | 5.5.3 Closure | |Every module in a Haskell program must be closed. That is, every name explicitly |mentioned |by the source code must be either defined locally or imported from another module. |Entities that the compiler requires for type checking or other compile time |analysis need |not be imported if they are not mentioned by name. Note that `:' and `[]' are not names (see 2.4). P.S. On a related note, Hugs and ghc both allow the following module module Bar(List(..)) where type List = [] without complaint, but according to the Haskell report (5.2) the syntax `(..)' should only be used for algebraic data types, not for type synonyms. -- 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(..)
On 22-May-2000, Koen Claessen <[EMAIL PROTECTED]> wrote: > I think there are two separate issues here: ... > 2. Syntactic sugar which is translated away using prelude > functions. ... > Issue number 2 is completely different and unrelated. Note > that this also includes normal prelude functions without > special syntax (such as >>=, return, mfail, fromInteger, > etc.). What happens in general when one uses this special > notation in a module which redefines these operators? I > think the easiest thing to do is just to make the > translation *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]> | "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
On 30-May-2000, George Russell <[EMAIL PROTECTED]> wrote: > "Ronald J. Legere" wrote: > > > > SUMMARY: How about a supplement to the standard that contains the > > 'standard' extensions that everyone uses. > One problem I have with this is that "unsafe" operations, being unsafe, > are difficult to fit in with the rest of the language. For example > a common use of unsafePerformIO is to set up global variables: > > counter :: MVar Int > counter = unsafePerformIO(newMVar 0) > > What exactly does this mean? I presumably want only one counter for the > whole program. But what is a program? Suppose "counter" is declared as > part of a "where" clause in a bigger function. Is the compiler allowed > to lift it so that there is only one counter, or should it create only one? > And so on. I think the current situation, where such functions are only > supplied as extensions with "caveat emptor" implied, is probably best. I have to say that the current situation, where the Hugs/ghc documentation for these features is worse than non-existent, is certainly far from the best imaginable. The Hugs/ghc implementors should bite the bullet and explicitly document exactly what is guaranteed about the behaviour of these features. Likewise for the implementors of any other Haskell implementations which support such features. (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 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: unsafeinterleaveIO
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 possible to make some guarantees.) > What on earth is a guarantee? GHC is a research project. I don't expect to > be able to sue Microsoft or the University of Glasgow [...] I was not talking about a legal guarantee. Just some documentation that explains the intended specification. Providing library procedures without providing a specification for them is fundamentally bad practice. -- 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: mode argument
On 01-Jun-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Why people do not complain on the mode argument outside of Haskell: > `zip -r ...' `unzip -t xxx.zip' `tar xvfz xxx.tar.gz' > ? People do indeed complain about Unix's habit of using cryptic option sequences like `-r', `-t' or `xvfz'. Why do you thing long options (e.g. `--recursive', rather than `-r') were invented? Short options like `-r' are useful for interactive use. But if you're programming (e.g. writing shell scripts), then you really ought to use the long versions instead, since it makes the code much more readable. Unfortunately for historical reasons the long options are not as portable as the short options, for many standard Unix commands. But hopefully that will change over time. > Patrik Jansson <[EMAIL PROTECTED]> writes on 31 May 2000 > > J> On the contrary - you only need one character N instead of threee 'n' if > J> you use a datatype with two constructors N and (whatever you like for > J> the other case). > J> But the length of the argument is not that interesting here - you can have > J> long names for the constructors of the "mode" datatype and still use short > J> local abbreviations. > > 'n' :: Char does not hold a name in the constructor name space. Yes, but it is also far from self-expanatory. With a constructor name, in a suitable environment you could just click on the constructor name and the environment would immediately pop up the declaration and documentation for that constructor and the type that it belongs to. Such an environment need not be particularly sophisticated, e.g. the tags support in vim and Emacs is sufficient. But with `Char', it would be much much more difficult. Including `Char' in a function signature provides no information for the user about what the meaning of that argument is. It is IMHO bad style. > And `N' hardly would do. There may be many other constructors wanting > short names. > Suppose there are about 10 functions to provide with the mode. > It will looke like this > > quotRem :: ...=> Mode_quotRem -> a -> a -> (a,a) > sortBy :: Mode_sort -> Comparison a -> [a] -> [a] > ... > data ModeQuotRem = QuotRem_minRem | QuotRem_positive | QuotRem_other > deriving(Eq,Ord,Enum,Show,Read) > -- contrived > > data Mode_sort = Sort_quick | Sort_merge | Sort_insert | Sort_other >deriving(Eq,Ord,Enum,Show,Read) > ... > Again, `Positive' would not do, it should be something like > QuotRem_Positive, and so on. This is a problem with Haskell, IMHO. Mercury allows overloading of constructor names, so in Mercury you could use just `Positive' rather than `QuotRem_Positive'. The type checker will resolve the ambiguity whenever possible. Note that if such a constructor was used as the first argument of a function like the `quotRem' and `sortBy' functions you've declared above, there would be no ambiguity. > For example, my program contains many expressions like > > f x y b = myRem 'c' ((myRem '_' x b)*(myRem '_' y b)) b > > Now, it has to be, maybe, remP = rem QuotRem_positive > remO = rem QuotRem_other > 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
On 01-Jun-2000, Antti-Juhani Kaijanaho <[EMAIL PROTECTED]> wrote: > > Like there is no way in Haskell 98 to access OS services beyond a certain > subset, there is no way in C90 or C99 to access OS services beyond a > certain subset. Haskell's subset is actually larger than C's. > > Like Haskell, C has no provisions for accessing code written in other > languages. > > In both languages, if you want to access OS services beyond the > standardized subset, or if you want to access code written in other > languages, you need to go beyond the standard and use some things that > make your programs a little more unportable. That may be true in some theoretical sense, but in the real world there are a zillion C libraries like OpenGL, Xlib, etc., which have already been ported to all the systems of interest, and which can be trivially accessed from C. Furthermore, these libraries are portable between different C compilers. For Haskell, there is currently no way of accessing OpenGL, for example, that is portable between different Haskell compilers. > Understand this: I am not against improving the FFI of the Haskell > systems or making their FFIs compatible. My point is that making the > FFI part if the language is not necessarily necessary. In today's world it is often very difficult to write complete applications in a single language, especially if you want to use a nice high-level language like Haskell. The need to make use of existing libraries written in other languages is so common that a language which does not provide portable support for this is severely lacking. It's not enough to provide non-portable ways of doing this; that just locks programmers into using a single implementation. This need has been recognized by modern programming languages and modern programming language standards. The ISO Ada 95 standard, for example, specifies standardized interfaces from Ada to C, Fortran, and COBOL. The 1998 ISO C++ standard requires C++ implementations to support a C interface. The Fortran standardization committee have been working on a standardized interface between Fortran and C (I don't know the current status of that). For Java, the Java Native Interface (JNI) provides a standard interface to C. For Mercury, the Mercury language reference manual specifies a C interface 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 do have a standard FFI. -- 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: mode argument
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 Haskell, IMHO. > > > Mercury allows overloading of constructor names, so in Mercury you > > could use just `Positive' rather than `QuotRem_Positive'. The type > > checker will resolve the ambiguity whenever possible. > > How will the type inferencer figure out the type if it isn't declared > explicitly? Well, the type inferencer considers all possibilities and eliminates those that are not type-correct. Often only one possibility remains. If, for example, you write data Foo = Positive | Negative data Bar = Sure | Certain | Positive f Positive = 1 f Negative = -1 g = f Positive then the type inference can easily infer that `f' has type `Foo -> ...' rather than `Bar -> ...', since otherwise the second clause of `f' would not be type-correct. From the type that it infers for `f', it can then infer that the occurrence of `Positive' in the definition of `g' has type `Positive'. In the cases that we were considering, namely mode arguments for functions in the standard Prelude, the Prelude would contain type declarations for those functions anyway, so if you write h = Prelude.func Positive then the type inference can figure out the type of `Positive' in the definition of `h' from the type declaration for `Prelude.func'. -- 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: mode in functions
On 01-Jun-2000, Ketil Malde <[EMAIL PROTECTED]> wrote: > Jan Skibinski <[EMAIL PROTECTED]> writes: > > For tar_x, tar_xv, tar_v kind of things people > > invented objects, recognizing that "tar -x" > > approach is not a user friendly technology. > > Oh? You realize there are Unix weenies on this list, don't you? > Cryptic commands with equally cryptic options is very user friendly > for an interactive command line. The emphasis there should be on _interactive_. An interactive command line tool and a programming 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 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: mode in functions
On 02-Jun-2000, S.D.Mechveliani <[EMAIL PROTECTED]> wrote: > Ketil Malde <[EMAIL PROTECTED]> writes > > > I could accept "mode flags" if the algorithm is extremely similar, > > e.g. passing a comparator function to a sort is a kind of mode flag > > (think ordered/reversed) which I think is perfectly acceptable. > > Having flags indicating algorithm to use (sort Merge (s:ss)) is IMHO > > silly. > > > Not at all. Silly it to call differently the functions that compute > the same map. > Also silly is to have quotRem & divMod > instead of quotRem . In addition to the criticisms that have already been leveled against this approach, another drawback with it is that makes things less extensible. For example, with the current approach, if I want to define a new sorting function, I just go ahead and do so, and apart from the user of my new function having to import my module, my new sorting function is completely first class, just like any sorting functions that are provided by the Prelude or standard libraries. But if we use mode arguments with some enumeration type, then there's no easy way for me to add a new enumeration constant to the enum, or to change the standard `sort' function so that it can call my sort function. So my new sort function ends up being in some sense a second-class citizen in comparison to the various different sort functions encapsulated as different modes of the standard `sort' function. For example, someone writing an algorithm that makes use of a sorting function might well make the mistake of abstracting away which kind of sort function is used by passing in a SortMode argument, foo :: SortMode -> ... foo mode ... = (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 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: mode in functions
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 the former, brevity may well be more important than readability, > > but for the latter it is definitely the other way around. > > But verbosity is not the same as readability! "head" is a perfectly > good name for a function that returns the first element of a list, > even though firstElementOf might be more descriptive. ... > So, commonly used names should be short I agree. But single character names, as originally suggested in this thread, are too short; at that point, readability has definitely been compromised. Only the most pervasive operations would warrant names so short, and modes for operations like sorting certainly don't fall into that category. -- 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: "Boxed imperatives" to implement pure functions (Was: Inverse Indices)
On 06-Jun-2000, Bjarke Dahl Ebert <[EMAIL PROTECTED]> wrote: > Has anyone made a generalization of accumArray, which allows users to > implement a pure function using imperative features? Yes. See the documentation for the `ST' module in the Hugs/ghc extension libraries. I enclose a brief extract. | 3.16. ST | |This library provides support for strict state threads, as described |in the PLDI '94 paper by John Launchbury and Simon Peyton Jones |[LazyStateThreads]. In addition to the monad ST, it also provides |mutable variables STRef and mutable arrays STArray. ... | data ST s a-- abstract type | runST :: forall a. (forall s. ST s a) -> a ... | data STArray s ix elt -- mutable arrays in state thread s | -- indexed by values of type ix | -- containing values of type a. | newSTArray :: Ix ix => (ix,ix) -> elt -> ST s (STArray s ix elt) | boundsSTArray :: Ix ix => STArray s ix elt -> (ix, ix) | readSTArray :: Ix ix => STArray s ix elt -> ix -> ST s elt | writeSTArray:: Ix ix => STArray s ix elt -> 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 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: Library conventions
On 24-Jun-2000, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote: > When an Either result encodes a good result or an error, the error > should be Left and the good result should be Right. Rationale: > partially applied type is a good Functor and Monad. Seems to be > consistently used (MonadEither, Parsec). Actually I dislike this practice of using `Either' for something which is either a good result or an error. In this case, there is an assymetry in the meaning we attach to the two cases. Using `Left' and `Right' for such cases is fundamentally 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 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
On 18-Jul-2000, Keith Wansbrough <[EMAIL PROTECTED]> wrote: > > IMHO GHC's documentation should clearly warn that programmers should > > not depend on even basic stability and exactness of floating point > > computations, and only stability is provided by -fstrictfp. > > GHC is no different from any other compiler for any other language in > this respect. There's a huge difference between languages like C, which have unspecified and/or undefined behaviour lurking in every nook and cranny, and pure functional languages like Haskell. Haskell functions are supposed to be referentially transparent mathematical functions: for any given function in any given program, for any given inputs to that function, you should get the same output from that function every time. > Floating-point values are *not* the mathematical `real > numbers', and should not be treated as such. Yes, but for any given Haskell program execution, the sum of any two floating-point values should be the same every time you compute it. In general it need not be the same as the sum of the equivalent real numbers, because floating point numbers are subject to 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 time in that program execution. -- 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
On 18-Jul-2000, Sven Panne <[EMAIL PROTECTED]> wrote: > > Nevertheless, there seems to be some consensus that optimization should > not change the outcome of a computation. Note that GCC's -O flag *does* > change it, at least if -ffloat-store is not given in addition. The newly > introduced GHC option -fstrictfp is intended to give back that guarantee, > but after this discussion I feel that it should be the default behaviour. I agree. And the inverse option (`-fno-strict-fp') should be documented as not conforming to the Haskell report. > A short description of GHC's internal handling of floating point values > and the accompanying problems: > >* GHC uses IEEE arithmetic for Float and Double. Is that true for every platform that GHC targets? >* Floating point values are internally represented as Rationals, which > is completely OK for literals given by the programmer. It is flexible > enough to make cross-compilation possible (which GHC currently can't > do for other reasons), a possibility which would be lost if Float/Double > were used for this, so this approach would 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 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
On 23-Jul-2000, Julian Assange <[EMAIL PROTECTED]> wrote: > Jon Fairbairn <[EMAIL PROTECTED]> writes: > > [George Russell wrote:] > > > Surely this is obvious to Haskell programmers? > > to me, anyway. If two runs (with different flags) of the > > compiler produce programmes that give different results, > > then one of them isn't adhering to the standard, (and so > > should be noted as such). That statement is not completely true. The Haskell report does not completely define the semantics of all Haskell programs. For example, the range of `Int' and the result of computations which overflow are left undefined. Such implementation-dependent qualities could certainly be subject to change depending on which compiler flags the user specifies. Furthermore, not all Haskell programs have deterministic behaviour. Programs that make non-trivial use of the IO monad can have nondeterministic behaviour. In fact, for some programs that make use of the `Random' module, such as the following, import Random main = do r <- randomRIO (1, 100) print (r :: Int) the whole idea is that you _won't_ get the same result each time. If the program produces the same results each time then this is arguably evidence that the implementation does NOT conform to the Haskell report! So, the best that you can really say for Haskell is that within a single run, for code which does not use the IO monad, you should get the same result each time within that run. > Microsoft VCC once (still?) suffers from this problem. Whether > it is because it accesses random, unassigned memory locations > or because the optimiser has time thesholds, is unknown. 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 undefined, unspecified, or implementation-defined behaviour. If a C or C++ program gives different behaviour on different runs or with different compilation flags, this is almost 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: The type of zip
On 24-Jul-2000, Chris Angus <[EMAIL PROTECTED]> wrote: > Has anyone ever thought of trying to use reflection in these cases. Yes, I've thought of it. That is how we implement the generic `read' and `print' in Mercury. Using reflection like this seems to be a quite powerful 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 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
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 > > undefined, unspecified, or implementation-defined behaviour. If a > > C or C++ program gives different behaviour on different runs or with > > different compilation flags, this is almost always due to the program > > depending on one of those areas, rather than due to the compiler not > > conforming to the standard. > > Standard, shmandard. If a compiler can't produce reproducable code, > then its of little value for scientific computing. *If* you write C code which strict conforms to the standard, then any conforming compiler will give you reproducible results. The only times that you will not get reproducible results is if you either accidentally or deliberately write code which is not strictly conforming, if you invoke the compiler in a non-standard-conforming mode, or if there is a compiler bug. Writing strictly conforming C code is difficult. Very difficult. If you want reproducible results, and you don't know how to write strictly conforming C code, then don't use C! There are plenty of languages which make it much easier to get reproducible results. -- 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: Classes
a missing > instance. And even if we could express our intention, f's type would > still not be instantiated to match the only instance of C [Hugs says > "cannot justify constraints" when trying to load f, and "unresolved > overloading" when I try to use g after commenting out f; what do > batch-compilers say, and do they change messages when we rename > the module to Main and include some definition of main?]. I translated this example to Mercury: :- module example. :- interface. :- typeclass c(T) where []. :- instance c(float) where []. :- func f = A <= c(A). :- func g = int <= c(int). :- implementation. f = 1. g = 2. The current Mercury compiler (like Haskell 98) does not support constraints of the form `c(int)'; it reports a "sorry, not implemented" error for the type declaration for `g'. If you comment out the declaration and clause for `g', then the Mercury compiler reports example.m:013: In clause for function `example:f/0': example.m:013: in function result term of clause head: example.m:013: type error in unification of variable `HeadVar__1' example.m:013: and constant `1'. example.m:013: variable `HeadVar__1' has type `A', example.m:013: constant `1' has type `int'. Note that even if you remove the type class constraint, `f' still has a type error. That's why the error message doesn't mention type class constraints. This error message could be improved, by explaining why it is that the type variable `A' can't be bound. The reason is that `A' is universally quantified. If you use an existential quantifier, :- some [A] func f = A => c(A). then you get a different error message, more like the one that I think you were expecting: example2.m:013: In clause for function `example2:f/0': example2.m:013: unsatisfiable typeclass constraint(s): example2.m:013: `example2:c(int)'. > > What I can't tell the compiler is "there will not be any other instances > > FA [foo] [bar], so if you need one, you may assume that foo == bar". > > Both seem reasonable from a logic-programming perspective, as well > as a few other modifications, but with the current lack of control over > the scope 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: Haskell and the NGWS Runtime
Erik Meijer <[EMAIL PROTECTED]> wrote: ^^ > [someone wrote:] > > Does anyone know where there is some information on Haskell integration > > with the Microsoft NGWS runtime, which provides > > cross language integration and a common system for memory managment, > > library functions etc. > > > > I am curious to see if the haskell integration is a good fit or a graunch > > (square peg into a round hole). > > > > I know some work is being done on haskell in this regard, but exactly what > > I do not know. > > The plan is to have the release out the door by September 1st. Will that release support Haskell, or just Mondrian? > The translation is quite elegant IMHO, I'm afraid I have to disagree on that point. Basically you translate quite a few things by implementing your own virtual machine on top of the .NET runtime. For example, argument passing is done with explicit pushes and pops on your own virtual machine stack, rather than by using the .NET runtime's argument passing. This approach makes the compiler is fairly simple, but the generated code is not what _I_ would call elegant. > it only encodes those features that > Haskell has, but the .NET runtime lacks, that is lazy evaluation and > currying (what else can you expect). Don't you currently encode tail calls too? And what about type classes and polymorphism? Also, as I understand it, Haskell/Mondrian programs that don't make use of currying -- e.g. those in which all functions have only one argument -- still get encoded, rather than being mapped directly. So the encoding is not done in way that you only pay for it when you use those features. This makes interoperability with other languages more difficult. > As we demo-ed at the PDC, we have full bidirectional interop between Haskell > and other .NET languages. Hmm, the "full" adjective here sounds like it might be a bit of an overstatement. Does that mean that I can call Mercury code from Haskell, have it all statically type checked, and not have to write any additional interface definitions or glue code? Including procedures which are polymorphic and/or use type classes? If so, I would be very surprised! I think the current level of interop supported is still a LONG way from what I would describe as "full" interoperability. So, could you elaborate on what sense you mean when you say we have "full" bidirectional interop? For example, which of the various CLS (Common Language Specification) categories does the Haskell and/or Mondrian implementation comply with? > The fact that there is a common runtime is a really great thing. In the old > days for example, you had to implement your own so called ActiveX scripting > engine to host Haskell programs in HTML pages, ASP pages, or WSH. Now you > only have to target to IL and get those goodies already paid for, ie you can > write ASP+ pages in Haskell, COBOL, Mercury, Perl, Phyton, APL, Smalltalk, > Scheme, Component Pascal, Eiffel, Oberon, ... (The corresponding thing for > Java would be that if I compile Haskell to Java, I get Haskelletes already > paid for). Actually that's not really true; compiling to IL is not enough. To support ASP+ for 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. 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 received substantial funding from MS, so my opinion on these issues may not be entirely objective. -- 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
l, these fast entry points definitely sound like an improvement. They're not mentioned on the Mondrian web page whose URL was posted earlier in this thread. Are these something you're planning to include in the Sept 1 release? > > Hmm, the "full" adjective here sounds like it might be a bit of an > > overstatement. Does that mean that I can call Mercury code from > > Haskell, have it all statically type checked, and not have to write > > any additional interface definitions or glue code? Including > > procedures which are polymorphic and/or use type classes? > > If so, I would be very surprised! I think the current level of interop > > supported is still a LONG way from what I would describe as "full" > > interoperability. > > Come on Fergus! You will never achieve interoperability on that level > except when your semantic domains match exactly or when you have an > extremely complicated intermediate language. For example, most > languages don't make the distinction between values and computations > as Haskell does, and I don't expect or want for example VB programmers > to do that either. But it does mean that whenever I call a VB function, > I must write a little glue code to compensate for the difference in > semantics. The same is true for calling nondeterministic or multi-moded > Mercury predicate. No, it's not true. You can call multi-moded or nondeterministic Mercury predicates directly from other .NET languages without any glue code. For multi-moded procedures, the mode number is part of the IL function name, so you just pick which function name you want to call, and call it. For nondeterminstic procedures, the caller needs to pass a success continuation callback function, which will get called once for each solution. But that's not glue code for the purpose of handling language inter-op; that's just the way in which the interface is exposed. If I were writing code in C that needed to use backtracking, I'd do it the same way, even if there was no Mercury code involved at all. (Note that currently you _do_ need to write glue code when calling other languages from Mercury. But you don't need to write glue code when calling Mercury from other languages. We also plan to automate the generation of glue code when calling other languages from Mercury, so that you won't need to write any of it manually.) > > For example, which of the various CLS (Common Language Specification) > > categories does the Haskell and/or Mondrian implementation comply with? > > Aha, finally you hit a real issue. To be a CLS extender would require > a lot of language extensions to a lot of languages, even to OO languages > like Java! But for Haskell the situation is even more severe. Indeed. But will your implementation even meet the specification for a CLS consumer? > > Actually that's not really true; compiling to IL is not enough. > > > > To support ASP+ for 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. 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. > > That is right. The thing here is to use the "code behind" style ASP pages. Could you elaborate? Or could you give a pointer to where we could find out more about "code behind" style ASP pages? -- 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
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 spit out either C# or Java. > > Is there any publically available technical information on what you > guys are talking about? I've been doing web searches, and searches on > the Microsoft web site, and I can't find anything on GOO, IL, or > "Common Language Specification". Technical information about this stuff (IL, the CLS, etc.) was included on the CDs that MS gave to the 6000-odd participants of their recent PDC (Professional Developers Conference) in Florida last month. So if you can find one of those, you might be in luck. But I don't think Microsoft have put anything about it up on the web. GOO is not a Microsoft invention, and nor is it part of Microsoft's .NET stuff. GOO is an intermediate language that was, AFAIK, invented by the Mondrian group. It might be described in the following paper: Erik Meijer and Koen Claessen. The Design and Implementation of Mondrian. In Proc. Haskell Workshop, 1997. -- 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
On 03-Aug-2000, Nigel Perry <[EMAIL PROTECTED]> wrote: > >I understand that point, but if doing that means that you need to > >implement the basic things like argument passing and procedure > >calling yourself, using your own virtual machine, rather than > >by using the underlying runtime's argument passing and procedure calling > >mechanisms, then I'd say that it is looking more like putting a round > >peg in a square hole than a good fit. > > Passing arguments on a separate stack is pretty lightweight. Well, I'm not sure that's true. Consider what you pay: - If you only have one stack, then the stack needs to be a stack of Object, and so for every argument that you put on the stack you need to - box it before putting it on the stack (if it is not already boxed) - downcast it to the right type after taking it off the stack - unbox it (if the type is an unboxed type) (If you use more than one stack, this can reduce such costs; but doing that increases the complexity of the approach significantly, and there are some significant costs in terms of performance from using multiple stacks that need to be weighed against the potential benefits.) - To get efficient access to your stack, you need to use at least one extra register to hold your stack pointer, or (quite likely) two extra registers, one for the array base and one for the offset. Note that on x86 there are only six general purpose registers, so you very quickly run out... Alternatively, if these are not in registers, then the cost of accessing the stack will be higher. - By not using the system stack, you reduce locality. This shows up in the greater register pressure (see above), and can also lead to more cache misses or cache collisions. - If the stack is an array, then (at least for verified code) every push and pop needs a bounds check. - Because of aliasing issues, the .NET runtime is very unlikely to optimize away the pushes and pops to your stack when it inlines methods. And indeed it will treat these pushes and pops as more expensive than ordinary argument passing (since they are!), and so it will be less inclined to inline such methods in the first place. Of course, doing a good job of inlining in the Haskell compiler will help reduce the damage here, but the Haskell compiler can't do cross-language inlining, and can't do JIT-time inlining across different assemblies or of dynamically loaded code, so you will still lose out in some scenarios. However, I guess it depends on what you mean by "light-weight". 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: monadic source of randomness
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: <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
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: <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
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: <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
On 11-Aug-2000, Manuel M. T. Chakravarty <[EMAIL PROTECTED]> wrote: > 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! This analysis actually misses the main point. Performance is not the main reason for wanting value types. The main reason for wanting value types is that there are many types which are better modelled as values rather than as objects. Of all people, functional programmers should surely be well aware of this! Note that Eiffel, which certainly tends towards purism in its OOP zeal, originally did without value types, but the Eiffel community found that this did cause problems and so since Eiffel 3.0, Eiffel has had value types (though they call them "Expanded Objects" -- I guess so that they can still call the language "purely" object oriented ;-). For similar reasons, Sather also distinguishes between value types and object types. Likewise I believe that a request for value types is high up on the Java extensions list. Complex numbers, for instance, are an example of a type which is much better modelled as a value type than as an object type. >From a modelling perspective, the most important difference between a value type and an object type is not that an object type is allocated on the heap, but that an object type has an identity. However, that said, there are cases where value types can give significant performance improvements over object types. > > > 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? Using a better garbage collector is certainly a good idea. However, there is a limit to how good you can make the garbage collector. Often it is much more cost effective to put work into reducing the program's allocation rate rather than trying to make the garbage collector faster. >From what I have heard, it sounds like MS have put quite a bit of work into their garbage collector. They use a generational mark-compact collector, with I think three generations, the first of which is sized to fit in the L0 (or was it L1?) cache, and they have several different versions for different situations, including a concurrent one for interactive use. They claim that in situations where you are frequently allocating small objects, the overhead of allocation is about 6 cycles per object (this of course does not include the collection cost), and they claim that in such situations the amortized overall cost of allocation plus collection is less than 50 cycles per object. These claims have not (to my knowledge) been independently verified, and personally I am somewhat sceptical, particular about the extent to which these figures, which are no doubt the best case figures, will extrapolate to real programs. However, 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 benchmarking things at this point would give us very little in the way of of useful comparisons. -- 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
On 02-Aug-2000, Doug Ransom <[EMAIL PROTECTED]> wrote: > The PDC slides and white papers should be available if you dig > through this site: > http://commnet.pdc.mscorpevents.com/default.asp In particular <http://commnet.pdc.mscorpevents.com/sessions.asp>. However, as seems to be usual (%*&^#*&^#@!) for MS, this page is NOT written in portable HTML. Certainly it didn't work with Netscape Communicator 4.61 on Linux when I tried it. When it comes to open standards, Microsoft are good at "talking the talk", but if the way they write web pages is 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
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.com/sessions.asp>. > > However, as seems to be usual (%*&^#*&^#@!) for MS, this page is NOT > > written in portable HTML. Certainly it didn't work with Netscape > > Communicator 4.61 on Linux when I tried it. > > And is Netscape Communicator 4.61 on Linux (bugs and all) a definitive > test of portable HTML? :-) The page doesn't display properly with Lynx (2.8.3dev.9) on Linux or with Opera (4.02) on Windows either. -- 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
On 11-Aug-2000, Sylvan Ravinet <[EMAIL PROTECTED]> wrote: > On Fri, 11 Aug 2000, R.S. Nikhil wrote: > > And is Netscape Communicator 4.61 on Linux (bugs and all) a definitive > > test of portable HTML? :-) > > Actually it seems to be quite readable by lynx... Yes -- 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's source code. -- 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
On 14-Aug-2000, Benjamin Leon Russell <[EMAIL PROTECTED]> wrote: > Tyson Dowd <[EMAIL PROTECTED]> wrote: > > I don't believe you can teach programmers anything by > > trying to take > > tools away from them. > > > > I believe you can only teach programmers by showing them > > a better tool. > > Aha, but *which* programmers? The C/C++ programmers who will bother > learning how to write safe code, or those who won't? Well, no sane C# course or book will teach the unsafe features of the language before the safe ones. So I think the vast majority of C/C++ programmers who learn C# will already know how to write safe C# code before they learn how to write unsafe C# code. > The problem is that many programmers will not focus on the safe features > if the unsafe ones remain. ... > For example, if the C/C++ programmers are used to explicit memory > management using malloc() and free(), then they are likely to keep writing > all their methods using this old style, even when the running time is > not crucial. This could potentially introduce more memory-related bugs > than necessary. I'm not an expert on C#, so I could be wrong about this, but as I understand it, C# does not have malloc() and free(), not even in the unsafe subset. Unsafe C# is not the same as C or C++. Furthermore, "unsafe" code will have a stigma attached to it, just like "goto" does today (or perhaps more so). So I think you overestimate the danger of C/C++ programmers continuing to write much of their code using unsafe features if they switch to C#. > Suppose the manager starts the project by requiring that all the > programmers write all non-time-critical portions of their code in pure C#. Why wouldn't the manager require that they write all non-time-critical portions of their code in safe C# (i.e. C# without the "unsafe" keyword)? > > On 14-Aug-2000, Benjamin Leon Russell <[EMAIL PROTECTED]> wrote: > > > Your not-quite-spoken assumption that it should be possible to write > > > everything in one language is just something I fundamentally disagree > > > with. The requirements of low-level kernel code are quite > > > different from those of most user-level applications, and > > > any single language that tries to address > > > both sets of requirements will do so poorly. > > > > Ah, a testable hypothesis! > > If you are right, then you should be able to criticize some other > > features of the language that have suffered as a result of unsafe > > 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 working with the language! Well, how about Modula II and Ada? -- 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 compilers targetting Wintel platforms, or microsoft's ".NET"...
On 29-Aug-2000, larisys <[EMAIL PROTECTED]> wrote: > There is at the moment a great fuss around the new Microsoft's ".NET" > platform. Articles about the related virtual machine and run-time > environment often cite Haskell as a language targetting the ".NET". 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 "NGWS". -- 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: inference question
On 31-Aug-2000, William Lee Irwin III <[EMAIL PROTECTED]> wrote: > {hugs} Example> :type cmethod . fromNat $ 1 > {hugs} cmethod . fromNat $ 1 :: (C a, Q a) => a > > This is the expected typing, which I expect to be valid. > > But the inferencer chokes on an actual binding like the following: > x = cmethod . fromNat $ 1 > > Example> let x = cmethod . fromNat $ 1 in 0 > ERROR: Unresolved overloading > *** Type : (Q a, P a) => Integer > *** Expression : let {...} in 0 You have run into the infamous monomorphism restriction. Haskell 98 does not allow variables like `x' above to be polymorphic. See section 4.5.5 in the Haskell report. For more information, try searching the archives of this mailing list for "monomorphism restriction". The error message that you get from Hugs could certainly be a lot clearer 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 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: Inferring types
On 08-Sep-2000, Jan Carlson <[EMAIL PROTECTED]> wrote: > I'm intrigued by the following Haskell behaviour: > > The type of (+) is > > (+) :: (Num a) => a -> a -> a > > Now, if I define > > p = (+) > > the type of p is inferred to be > > p :: Integer -> Integer -> Integer > > How come? > > I guess the answer can be found somewhere in the Haskell report, but I'd > really appreciate just a rough description of the issue. The infamous monomorphism restriction strikes again! Because of the syntax used to define `p', it falls foul of the monomorphism rule (4.5.5 in the Haskell report). This requires that its type be monomorphic. Then the defaulting rules (4.3.4) come in to play, and these mean that the type variable `a' gets the value `Integer', since that is the first type in default 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 type inferred for `p' will be the correct polymorphic type `Num a => a -> a -> a'. -- 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: help, classes!
On 13-Sep-2000, kirstin reese <[EMAIL PROTECTED]> wrote: > > Surely this is obvious, but I cannot figure out how to properly deal with > class constraints and monads. For instance, when trying > > instance Monad Set.Set where > xs >>= f = Set.unionSet (Set.map f xs) > return x = Set.single x > fail s = Set.empty > > hugs complains that it "Cannot justify constraints in instance member > binding" for >>=. unionSet type is Eq a => Set (Set a) -> Set a Basically there is no way to do this in Haskell. 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 routines that work on Monads. -- 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]
On 11-Sep-2000, Andrew Kennedy <[EMAIL PROTECTED]> wrote: > Perhaps some of the non-MS > .net compiler implementers would like to comment further? One serious usability problem with the Microsoft .net specs that I have seen is that Microsoft only provided them in a proprietry documentation 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" PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.
Re: How does one find lazyness bottlenecks?
On 12-Oct-2000, Sengan <[EMAIL PROTECTED]> wrote: > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. What makes you think that the GC time is due to insufficient laziness? My first thought is that high GC times may well be due to the opposite, too much laziness. Being lazy means that you create closures to represent unevaluated expressions, and those closures will eventually need 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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Overloaded function and implicit parameter passing
On 23-Oct-2000, José Romildo Malaquias <[EMAIL PROTECTED]> wrote: > - cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > - cut here ... > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 ... > Would anybody comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson <[EMAIL PROTECTED]> | "I have always known that the pursuit | of excellence is a lethal habit" WWW: <http://www.cs.mu.oz.au/~fjh> | -- the last words of T. S. Garp. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: First class modules
On 07-Nov-2000, Tom Pledger <[EMAIL PROTECTED]> wrote: > Supposing that (some version of) Haskell had first class modules, and > type variables could be universally quantified at the module level, > would rule 2 of the monomorphism restriction go away? No. |Rule 2. Any monomorphic type variables that remain when type |inference for an entire module is complete, are considered |ambiguous, and are resolved to particular types using the |defaulting rules (Section 4.3.4). Although this rule refers to the "entire module", its typical for the ambiguity 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 <[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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Passing an environment around
On 27-Oct-2000, José Romildo Malaquias <[EMAIL PROTECTED]> wrote: > On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote: > > Yes, as implemented using the dictionary > > translation, implicit parameterization can lead to loss of sharing, exactly in > > the same way that overloading (and HOF in general) can lead to loss of sharing. > > > > However, I can imagine that a compiler might chose to implement implicit > > parameters more like dynamic variables in lisp. Each implicit param essentially > > becomes a global variable, implemented as a stack of values - the top of the > > stack is the value currently in scope. This would avoid the sharing problem > > nicely. > > I suppose your implementation of implicit parameterization in GHC and Hugs > uses the dictionary translation, right? I believe so. > Would an alternative implementation > based on a stack of values be viable Yes. > and even done? Unlikely ;-) > Does it have serious drawbacks when compared with the > dictionary translation technique? In the form described by Jeff Lewis above, yes, it does: it's not thread-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 implemented). -- 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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Hugs and Linux
On 10-Nov-2000, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > > I can't get hugs98 to work under my linuxplatform. I have the Red > Hat distirbution 7.0. > The problem is that hugs requires a file called "readline.so.3" and > I have "readline.so.4" on my system. Does anyone know how to get > around this problem?? One *possible* work-around is to just try linking readline.so.4 to readline.so.3. In general that won't work, because the interface to readline.so.4 will be different from the interface to readline.so.3 (that's why they 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, Fergus. -- 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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Union Types for Haskell!?
On 24-Nov-2000, Bernd Holzmüller <[EMAIL PROTECTED]> wrote: > There is one thing I was really missing in all these projects: the > existence of union types (i.e. the union of value sets of two existing > data types) Mercury has a similar type system to Haskell. This question came up a lot during the early days of Mercury, since many Prolog programmers were used to a programming style that made significant use of undiscriminated union types. What operations would you allow on union types? There's a number of possible choices. Here's some of them: (1) The only operation allowed on a union type is calling a type class method of a type class for which all the types in the union are instances. (2) Allow pattern matching on values of particular types, using `case'. (3) Allow both (1) and (2) If we allow (2), then some programming mistakes that previously were type errors would instead become just inexhaustive pattern matches for which you get a run-time error. For example: foo :: Maybe a -> b -> Maybe b foo x y = case list of [] -> Nothing (x:xs) -> Just x where list = case x of Nothing -> 0-- oops, meant [] instead of 0 Just foo -> [y] If union types were allowed, with (2) above, this example would be legal, with `list' having the union type { [a], Integer }. But `foo Nothing 42' would evaluate to bottom, since the `case list' expression has no case with a pattern of type Integer. So allowing union types in this way would reduce static type safety, at least unless we also forbid inexhaustive pattern matches. If instead you only allow (1), then probably union types would not be suitable for expressing the kinds of things that you want to express with them. > Is there any reason for this restriction > in the Haskell type system? Does this lead to losing the principal type > property? If you allow (2) above, there may be serious problems for principal types. For example, consider f x = case x of Nothing -> False Just _ -> True What's the most general type for `f'? The type `f :: Maybe a -> Bool' is less general than e.g. `f :: Union { Maybe a, ... } -> Bool', but you certainly don't want to infer the latter type. So (2) is definitely out. I guess we could use a separate `typecase' rather than `case', and require that `typecase' always be exhaustive. That might solve some of the problems. But even then, there may be some tricky problems remaining. Union types introduce subtyping, and type inference with subtypes and polymorphism is tricky -- in fact undecidable, if I recall correctly. However, there have been some pragmatic attempts to solve this problem in practice, even though the general case may be undecidable. I think there was a paper at the Industrial Applications of Prolog conference in 1996 on a system called PAN (for "Prolog Analyzer") that had a type checker that supported undiscriminated unions and/or subtypes. There were some cases that it didn't handle, but the authors claimed that this wasn't a problem since those cases didn't arise in practice. > I find the existence of union types very attractive. Apart from enhanced > flexibility in modelling, type error messages would possibly be more > traceable, because different branches in if- or case-expressions would > have the *same* relevance, rather than the first branch being > type-checked becoming normative for all other branches. A type checker could easily generate better error messages in that sense simply by checking each case seperately first, and then merging the results, complaining if the types inferred in any two branches were not unifiable. But if you allow union types, the type checker couldn't report an error at the point where the two branches have types that are not unifiable; instead, it would have 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 where the error occurred. So I think allowing union types would most likely lead to *worse* error messages. -- 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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
On 21-Dec-2000, George Russell <[EMAIL PROTECTED]> wrote: > (3) Finally it would be nice to extend the module syntax to allow named > instances to be selectively exported and imported, just like variables. Mercury's module system allows instance declarations (which, as in Haskell 98, are unnamed) to be selectively exported. :- module foo. :- interface. :- import_module enum. :- type t. :- instance enum(t). :- implementation. :- instance enum(t) where [ ... ]. Mercury doesn't directly support selective import -- you can only import a whole module, not part of it. But if you really want that you can achieve it by putting each instance declaration in its own nested module. :- module foo. :- interface. :- import_module enum. :- type t. :- 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 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. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell