Re: vagiaries of computer arithmetic

1997-03-09 Thread Lennart Augustsson
> What, if anything, does Haskell specify with regard to > (a) integer overflow, I presume you mean Int overflow since Integer cannot overflow. The report used to say that the behaviour is unspecified, i.e. it might wrap around, or cause an error, or make your machine blow up :-) > (b

Re: Making argv a constant

1997-01-18 Thread Lennart Augustsson
> I would claim it has really nothing to do with first-class modules > or parameterized modules. They can be simulated by ordinary Haskell > data types with named fields. No they can not. Haskell records do not allow local polymorphism, so you have a significant loss of power. -- Lennar

Re: Making argv a constant

1997-01-18 Thread Lennart Augustsson
Just some more comments from me about argv. It's not that I hate a global argv, in fact hbc has come with a library with a global argv since day 1 (and global program name, environment, and file system as well. Why stop at argv?) I use the global argv now and then, but when I do also feel that

Re: Making argv a constant

1997-01-17 Thread Lennart Augustsson
Fergus Henderson wrote: > Sigbjorn Finne, you wrote: > > > > I don't honestly see what having these handles as constant *gain* you, > > so why then have them as such, if not having them constant gives you > > extra expressiveness? > > But, unless I'm missing something, making them non-constant

Re: Making argv a constant

1997-01-17 Thread Lennart Augustsson
Sverker Nilsson <[EMAIL PROTECTED]> wrote: > So if it turns out to be possible to make the environment a constant, > it should open up possibilities for other constants as well. I > would rather see a general mechanism. Something like: > > performOnceBeforeMain:: IO a -> a > > timeStarted = pe

Re: Making argv a constant

1997-01-16 Thread Lennart Augustsson
> There's a difference between the handle and its contents. > stdin etc. really are constant, it is just their contents (the > stuff you get if you read from that handle) that may vary. Exactly what I was going to write. -- Lennart

Re: Making argv a constant

1997-01-16 Thread Lennart Augustsson
> As for recursive "newtype": Really? That's news to me. "newtype" > definitions only have one constructor, so any recursive definition would be an > infinite datatype. Since a newtype constructor is unlifted, this would make > recursive newtypes pretty useless. How about this? newtype L

Re: Making argv a constant

1997-01-15 Thread Lennart Augustsson
> I know you could go wild with monads, c. classes etc. and try to > squirrel away these things, but argv is a constant (in a sane world), > so why not treat it as such (ditto for the environment)? Thoughts? Well, in 1983 Thomas Johnsson and I decided that this was the way to go and this is the w

Re: Haskell character set

1997-01-15 Thread Lennart Augustsson
> I have a dream that one day my daughter will be able to use her name > (which contains two grave accents) as a valid Haskell identifier! Well, if the accented letters are among "aeiouy" then she already can. If the implementation you use doesn't accept that then it's not a Haskell implementatio

Re: Haskell character set

1997-01-14 Thread Lennart Augustsson
> The character type Char is an enumeration and consists of 256 values, > conforming to the ISO 8859-1 standard . > > One thing is that according to the ISO 8859-1 standard not all 256 > one-byte characters are legal. Thus, the quoted sentence is imprecise. Aren't they? Which would not be l

Re: Question.

1996-12-21 Thread Lennart Augustsson
> > class Many m where > > components :: m a -> [a] > > > instance (Many m, Show a) => Show (m a) where > >showsPrec _ ma = shows (components ma) > > I know that an instance declaration requires a type constructor > (and m is a type constructor variable), but I don't understand why. > The

Re: first-class structures & existential types

1996-12-02 Thread Lennart Augustsson
> The name "first class structures" seems to imply that the local > quantification is restricted to structures, and from a first > look at Jones' paper it seems that structures are a new language > construct. Now Haskell already has records and algebraic types. > Are structures any different fr

Re: Type inference bug?

1996-10-29 Thread Lennart Augustsson
> Doesn't Haskell do the same if you say: > > class Cow a where > pig :: a -> Int > fly :: Int This is not legal Haskell. The class variable must occur in every method type. -- Lennart

Re: Coercions and type synonyms

1996-07-05 Thread Lennart Augustsson
> In the Haskell Report 1.3 it says > > "Type synonyms are a strictly syntactic mechanism to make type > signatures more readable. A synonym and its definition are > completely interchangable." > (BTW, these sentences are the first of section 4.2.3, but they > probably should be t

Re: Status of Haskell 1.3

1996-05-09 Thread Lennart Augustsson
> No implementations of 1.3 are available yet, but we expect all the > major Haskell systems to conform to the new report soon. While this strictly true, hbc 0..0 (announced in comp.lang.functional a few days ago) is almost Haskell 1.3, the only difference is some minor Prelude and Library di

Re: type&kind inference

1996-03-11 Thread Lennart Augustsson
> The restriction on the currying of type synonyms is therefore > a semantic restriction on types, not just a syntactic restriction on > type expressions. Exactly. But I don't think we need to complicate the kind system by having special kinds for type synonyms. In fact type synonyms can be sai

Re: type&kind inference

1996-03-10 Thread Lennart Augustsson
> Are partial applications of data-types allowed then? > If not, the higher kinds would not make sense. Yes, partial appication of data types is allowed. As you said, without it there wouldn't be much much point of it all. > The report has a pointer to a paper by Mark Jones, where this is > pre

Re: type&kind inference

1996-03-09 Thread Lennart Augustsson
> data App f a = A (f a) ... > Take for instance the declaration: > something = A () > what is the type of something ? > It could be App (\x->x) (), but it could also be > App (\x->()) a, for any type a, and a few others. But there are no types `(\x->x)' or `(\x->())' in Haskell.

Re: Haskell 1.3

1996-03-08 Thread Lennart Augustsson
> Suggestion: Include among the basic types of Haskell a type `Empty' > that contains no value except bottom. Absolutely! But I don't think it should be built in (unless absolutely necessary). It looks ugly, but we could say that a data declaration does not have to have any constructors:

Re: Haskell 1.3

1996-03-08 Thread Lennart Augustsson
> Suggestion: Include among the basic types of Haskell a type `Empty' > that contains no value except bottom. Absolutely! But I don't think it should be built in (unless absolutely necessary). It looks ugly, but we could say that a data declaration does not have to have any constructors:

Re: Preliminary Haskell 1.3 report now available

1996-03-07 Thread Lennart Augustsson
I always favoured `=' over `<-', but I don't care much. -- Lennart

Re: Preliminary Haskell 1.3 report now available

1996-03-07 Thread Lennart Augustsson
I always favoured `=' over `<-', but I don't care much. -- Lennart

Re: Haskell 1.3 (newtype)

1995-09-12 Thread Lennart Augustsson
Simon, I think you're mistaken. Simon writes: > > newtype Age = Age Int > > foo :: Age -> (Int, Age) > foo (Age n) = (n, Age (n+1)) > > Now, we intend that a value of type (Age Int) should be represented by > an Int. Thus, apart from the types involved, the following

Re: haskell

1995-03-10 Thread Lennart Augustsson
> Dear Kevin Hammond > >If you think this flame not too intemperate, please put it out on > the haskell mailing list. Don't blame Kevin! You're not the first one who complains about the Prelude being structured in the wrong way. Unfortunately the Haskell class system isn't powerful enough

Re: haskell

1994-03-17 Thread Lennart Augustsson
> > class Eq_Monad f where > > result :: a -> f a > > bind :: Eq b => f a -> (a -> f b) -> f b > > join :: Eq a => f (f a) -> f a > > ... > Is there any reason why qualified types should not appear as the > declared types of instance variables in class declarations? Polymorphic H

Re: Multiple Parameter Classes

1994-03-15 Thread Lennart Augustsson
> The main implementation problem is extending instance lookup to cover > multiple type constructors. The prototype Glasgow compiler was > designed to allow this, and I believe hbc also does this (as well as > Gofer, of course), so it's not a big issue! No, hbc don't do this (yet). But the ext

Suggestion to simplify the Haskell grammar

1994-03-12 Thread Lennart Augustsson
In order to simplify and make Haskell more consistent I suggest the following additions to the grammar () should be treated as a conid (or con) [] should be treated as a conid (or con) and less urgent (->)should be a con This simplifies the grammar, and al

Re: haskell

1994-02-18 Thread Lennart Augustsson
> Am I alone in finding the standard prelude for Haskell unsatisfactory > when it comes to dealing with different sorts of numbers and how they > are related? No, I do too!! > lower in the hierarchy. It is a great relief to be able to use pi/2 > rather than pi/2.0 every time. I Haskell you hav

Re: Polymorphic recursion

1993-12-16 Thread Lennart Augustsson
> One modest extension we could make to the Haskell type system is > > to permit polymorphic recursion if > a type signature is provided I'm absolutely for this suggestion (especially since hbc already has it :-). My reason for this is that it is already possible to do this in Ha

Layut question (again!)

1993-12-15 Thread Lennart Augustsson
Is the following legal Haskell? (I'm sure I've asked this before, but i don't think there was a consensus.) f x = g x where g y = case y of [] -> 0 The problem is that after where a '{' is inserted and another after of. The report now says that for each subsequent line if a line i

Question

1993-11-17 Thread Lennart Augustsson
Prompted by an IOHCC entry I have the following question: Is the following legal? -- module M(x) where x = 1 z = x==1 -- If the definition of z wasn't there it would clearly be illegal since it exports an overload non-function value. But the use of x in

Re: Modules and type classes

1993-11-16 Thread Lennart Augustsson
Phil writes: > GLOBAL INSTANCE PROPERTY: if an instance exists of a given > class at a given type, this instance is in scope everywhere > that the class and type are in scope. > > If this was not the case, then the point at which overloading was > resolved (definition point or

Obfuscated Haskell Code Contest

1993-11-05 Thread Lennart Augustsson
a semantics that is still debated. The goal: a program of at most 1024 characters that is as incomprehensible as possible. Deadline: 1 Jan 1994. Send to: [EMAIL PROTECTED] Full rules (stolen from the C contest) below. Have fun -- Lennart Augustsson 1st International

Re: Strictness

1993-11-02 Thread Lennart Augustsson
> To correctly evaluate seq (x, y) 5 it would be necessary to concurrently > evaluate x and y, since (x, y) is bottom if and only if both x and y are > bottom. (I enjoy finding a flaw in Miranda because there are so few to > be found!) Another flaw: There is a seq hidden in foldl. -

Re: Strictness

1993-10-29 Thread Lennart Augustsson
Phil writes: > In the absence of convincing answers, I'd rather have as many laws > as possible, hence my preference for unlifted tuples and products. Here's another law that I find useful: If we write f p = p where p is some pattern&expression then I expect f to be the identity func

Re: re. 1.3 cleanup: patterns in list comprehensions

1993-10-15 Thread Lennart Augustsson
> I don't like hacks. So, I either have to massage the grammar into > deterministic LR parsable form (difficult) or use a nondeterministic > LR parser (not readily available). What about Ratatosk. It's readily available and it's a backtracking LR(0) parser. That should be enough. -- L

Re: re. 1.3 cleanup: patterns in list comprehensions

1993-10-15 Thread Lennart Augustsson
Stefan Kahrs writes: > [About Miranda] This works, because patterns > are syntactically a subclass of expressions. But this is not true for Haskell (@ and _ are only in patterns), but the technique still works. You just have to work harder and join pat and exp and then always have a semantic c

Re: Binary mode I/O

1993-10-13 Thread Lennart Augustsson
> I find that this limits considerably its usage. Can't the Bin representations > of Char, Int, Float and Double (and maybe more) be standardized? I think Haskell Bin stuff is braindamaged and rather useless. I suggest we remove from Haskell until we figure out how to do what that tries to do i

Re: Haskell 1.3 (n+k patterns)

1993-10-12 Thread Lennart Augustsson
jl writes: > I feel the need to be inflamatory: > > I believe n+k should go. Again, I agree completely. Let's get rid of this horrible wart once and for all. It's a special case that makes the language more difficult to explain and implement. I've hardly seen any programs using it so I don

Re: Arrays and Assoc

1993-10-05 Thread Lennart Augustsson
> >But I think we can have the cake and eat it too, if we get rid of the > >restriction (which I never liked) that operators beginning with : must be a > >constructor: just define > >a := b = (a,b) > > Unfortunately that won't work if := had been used in patterns. I think > backward compatibil

Re: Arrays and Assoc

1993-10-05 Thread Lennart Augustsson
> >But I think we can have the cake and eat it too, if we get rid of the > >restriction (which I never liked) that operators beginning with : must be a > >constructor: just define > >a := b = (a,b) > > Unfortunately that won't work if := had been used in patterns. Nonsense. Of course construc

Re: ADTs and strictness

1993-10-05 Thread Lennart Augustsson
> I thought this inequality was one of the distinguishing characteristics of > lazy functional programming relative to the standard lambda-calculus. To > quote from Abramsky's contribution to "Research Topics in Functional > Programming", Addison-Wesley 1990: > >Let O == (\x.xx)(\x.xx) be t

Re: Arrays and Assoc

1993-10-05 Thread Lennart Augustsson
> 1. We should get rid of Assoc. I agree wholeheartedly! Do we have tp consider backwards compat? > 2. Arrays should be lazier. I agree again. But I think both kinds should be provided. > 3. AccumArray should mimic foldr, not foldl. Right! -- Lennart

Re: ADTs in Haskell

1993-10-04 Thread Lennart Augustsson
> What, precisely, is the definition of > a constructor strict in a specified field? In particular, how do > you define it, and implement it, if that field has a functional > type? Remember, in Haskell function types are unlifted, so we > should have (\_ -> bottom) = bottom. Well, if you go f

Re: ADTs in Haskell

1993-10-04 Thread Lennart Augustsson
Phil suggests that we add newtype T a_1 ... a_k = C t_1 ... t_n and use that to construct non-lifted ADTs. While this works well, I'd prefer to have strictness annotations on construtors instead. Haskell has very few means for making programs more efficient when you really need it,

Re: the hbc parsing library

1993-09-20 Thread Lennart Augustsson
> This is a rather belated summary of the replies to my earlier query > about the library of parsing combinators which comes with the hbc > compiler. OK, I'll try again. My last reply bounced. The parsing library you have got was just an experiment. It should never have been released. A much

Re: + and -: syntax wars!

1993-05-26 Thread Lennart Augustsson
> This whole issue regarding redefinition of + and - is getting confused > unnecessarily. Both of these are in PreludeCore and cannot be renamed > or hidden. Because of this their fixities cannot be changed. It is > possible to locally shadow + and - but this cannot change their > fixities an

- again

1993-05-23 Thread Lennart Augustsson
I'm still struggeling with syntactic issues. Is the following expression allowed in Haskell? 2 * -3 Hbc, ghc, and gofer all accept it, but as far as I can see from the grammar it should not be allowed. What is the intention? -- Lennart

Re: n+k patterns

1993-05-18 Thread Lennart Augustsson
> Both (>=) and (-) belong to classes defined in PreludeCore, > and hence cannot be rebound. This was a deliberate decision, > made in order to turn your point into a non-problem. It's true that things from PreludeCore cannot be rebound on the top level, but they can be rebound locally. So the

More questions

1993-05-17 Thread Lennart Augustsson
More questions along the same lines as for n+k: Does == in the pattern match translation refer to == in PreludeCore? Does negate in the translation of -e refer to negate in PreludeCore? -- Lennart

n+k patterns

1993-05-17 Thread Lennart Augustsson
Could those in charge of the formal semantics of Haskell (yes, that's you folks in Glasgow!) tell me what the meaning of n+k patterns are? In the report it says that case e0 of { x+k -> e; _ -> e' } translates to if e0 >= k then { let { x' = e0-k } in e[x'/x] else e' Which >=

Layout

1993-04-21 Thread Lennart Augustsson
Oh ye Haskell wizards. Is the following program syntactically legal or not? x = leta = let { b=1; c=2 } in 3 in 4 I.e. is the layout rule from an outer scope in effect even inside explicit brackets? Here's another x = let a = let in 3 in 4 OK, what ha

Re: hbc: Int/Integer

1993-03-30 Thread Lennart Augustsson
> Evaluating sum [1..10] (compiled with hbc) > results in a wrong value. > Haskell seems to assume Int to be the > correct type. But Integer is needed. Haskell assumes nothing at all. Haskell uses its default rules for ambiguous type resolution, and the normal setting of this is that Int is

Re: Stupid Haskell question

1993-02-26 Thread Lennart Augustsson
> > I also think its neat that you seem to have found a use for cyclic > > unification. This is definitely an impetus to extend the language to > > include cyclic types. (I don't expect we'll do this for a while > > though. You might consider modifying the Glasgow Haskell compiler to > > includ

Re: Stupid Haskell question

1993-02-26 Thread Lennart Augustsson
> a)). Mycroft first suggested a type system that would allow such > functions to be typed, but I think it is still an open question as to > whether an inference algorithm exists for the type system. (There was > a paper published that claimed an algorithm, but it was later withdrawn > as incorr

New version of the HBC Haskell compiler - 0.999.1

1993-01-14 Thread Lennart Augustsson
you want to know more. -- Lennart Augustsson - New Haskell B./LML release (0.999.1) There is now a new version of the Haskell B./LML compiler

Re: Another import question

1992-12-29 Thread Lennart Augustsson
> kh> In that case, perhaps you should always use data declarations (with a > kh> dummy constructor) rather than type synonyms. Some compilers will give > kh> you better error messages this way, and a good compiler might eliminate > kh> the extra constructor anyway (depending on how good a strict

Re: A question on Haskell B compiler

1992-11-18 Thread Lennart Augustsson
Make sure you have the latest version, 0.998.5. If you still get the error mail me again. -- Lennart

Re: End of file on ReadChannels

1992-09-06 Thread Lennart Augustsson
As far as I can tell there is no way to detect EOF with ReadChannels. Maybe you should ask the designer (Paul Hudak) of this language feature how to do it. The endless stream of -1 with hbc is definitely a kind of bug. I'll fix it. -- Lennart

Re: What am I doing wrong???

1992-09-05 Thread Lennart Augustsson
The constructor layout is quite complicated (to save some space for common cases), in this case it would be like this --- | TAG | cno | | ---/--- __/ / v | VEK | 5 | | | ptr | ptr | ptr |

Re: Is Haskell I/O system adequate?

1992-08-06 Thread Lennart Augustsson
> I don't agree with this. Certainly for the example given, it is possible > to code the required problem in Haskell, as Junxian J Liu indicated in > the original posting: Of course Haskell is adequate in some sense. Just like Turing machines are. I always take these questions as regarding how

Re: Is Haskell I/O system adequate?

1992-08-03 Thread Lennart Augustsson
> IS THE I/O SYSTEM IN HASKELL ADEQUATE? I think the answer is: NO! What you want to do cannot be done in Haskell. Some people may argue that it should be done in another way, but I think your Miranda solution is perfectly good. If you are more interested in getting a running pro

Re: New lmlc/hbc

1992-07-30 Thread Lennart Augustsson
What is your problem with -i? I don't know that I've changed anything. But maybe some change got lost somehow? -- Lennart

New lmlc/hbc

1992-07-30 Thread Lennart Augustsson
you want to know more. -- Lennart Augustsson - New Haskell B./LML release (0.998.1) There is now a new version of the Haskell B./LML compiler

Re: Help reading binary data

1992-05-26 Thread Lennart Augustsson
> Err, Lennart, doesn't your implementation > > a) write C doubles (even for Float) > b) attach extra information to the file Yes, quite right. After some email with David I've now realized that my initial understanding of his problem was correct, and that there is now (clea

Re: Help reading binary data

1992-05-20 Thread Lennart Augustsson
> While I'm finding the "Gentle Tutorial" and "The Report" to be fairly > easy to follow in general, I am having trouble figuring out how to read > binary files in and out of Haskell programs. I didn't see any relevant > examples in the progs/demo directory. Could someone please send me som

Re: Strictness in Haskell

1992-04-08 Thread Lennart Augustsson
> Yes, in general it's not possible. That is, I can't write a function > > evaluate :: a -> a > > which will force its argument to WHNF. I don't think you mean what you are actually saying, it's perfectly possible write evaluate :-) evaluate x = x This function will evaluate its a

Re: Existential types

1992-03-19 Thread Lennart Augustsson
Nigel writes: > [Note: Hope+C is not totally sound - but this is not due to the type > system itself but rather to the existance of the unsafe (and > untypeable) polymorphic equality function (alpha # alpha -> truval). > As in many (most?) functional languages this function is a bit-level > compa

unzip

1992-02-25 Thread Lennart Augustsson
The new unzip* functions in 1.2 are not suitable for unzipping an infinite list. (What Phil called "A splitting headache".) Is this deliberate or a mistake? I'd like them to be lazier. All you need is to change from unzip = foldr (\(a,b) (as,bs) -> (a:as,b:bs)) ([],[]) to

Prelude bug

1992-02-25 Thread Lennart Augustsson
After 3 hours of debugging I finally found it!! There is a bug in the definition of Complex cos, tan, cosh, and tanh in the Prelude (just sign flipping error). They should be as below. All this work using Standard Math really brings back memories... -- Lennart cos (x:+y) = co

Re: The Great Integer Division Controversy

1992-02-24 Thread Lennart Augustsson
> I am willing to change `div` > to `quo` and `dvf` to `div` if there is consensus. I like the new naming better, BUT this is a change that is not backwards compatible. Are we worrying about such things yet? Or is still possible to make them without the wrath of the masses? -- Lennart

Re: Modules again

1992-02-19 Thread Lennart Augustsson
> You just can't name a constructor in an export list. So if you say "T", > you can't mean the constructor T, you must mean the type or class T. OK, a perfectly good solution and explanation. I then suggest that you change the wording in the report. Currently it says (p. 44) "Data constructor

1.2 alpha mistake

1992-02-17 Thread Lennart Augustsson
In the table of Prelude operators (p. 53) the operator :% is listed, this operator is not (and should not be) exported from the Prelude, and should be removed from the table. -- Lennart

Haskell library

1992-02-17 Thread Lennart Augustsson
The Haskell library seems to be contain few entries (none to be exact), so I've decided to add something. On animal.cs.chalmers.se I've placed two very simple, but useful modules. One implements a random number generator (a very good one; I didn't design it), and the other a sorting function tha

Report bug

1992-02-17 Thread Lennart Augustsson
The 1.2 preface says that type synonyms are exported with "T..", shouldn't that be "T(..)"? -- Lennart

Re: Division, remainder, and rounding functions

1992-02-17 Thread Lennart Augustsson
I think the suggestion Joe has made about division is good, but I also think it is overkill! Let's not add even more things to the Prelude that are not going to be used. My opinions on this matter is: - have something which is efficiently implementable (i.e. close to what the

Modules again

1992-02-17 Thread Lennart Augustsson
Well, here's another problem I've encountered. Consider this module: module M(T) where data T = T Is this legal? Clearly I am just trying to export the type T, but it happens that the type has a constructor with the same name. Naming a constructor in the export list is explic

<    1   2   3   4