Re: Haskell Wish list: library documentation

1999-09-09 Thread Lennart Augustsson
Josef Sveningsson wrote: > The report doesn't even say that Haskell should be lazy, only that it's > non-strict. Now, it happens that most (all?) implementations have very > similar operational semantics, but I don't think that a Haskell library > should assume anything more about the semantics o

Re: My Humble Haskell Wish: concatSep

1999-09-08 Thread Lennart Augustsson
"Frank A. Christoph" wrote: > I have a humble wish for the Wish List. > > I wish this function was in the Prelude or standard library: > > concatSep :: [a] -> [[a]] -> [a] > > with semantics > > concatSep _ [] = [] > concatSep _ [xs] = [xs] > concatSep sep (xs:xss) = xs ++ sep ++ concatSe

Re: Units of measure

1999-08-26 Thread Lennart Augustsson
Christian Sievers wrote: > Anatoli Tubman wrote: > > > I once wrote a C++ template library that did exactly that. Arbitrary units, > > rational exponents -- you can have (m^(3/2)/kg^(5/16)) dimensioned value. > > All at compile time, without runtime checking whatsoever. > > Is there any sense ph

Re: Monads in plain engllish (Was: Re: Licenses and Libraries)

1999-08-23 Thread Lennart Augustsson
felix wrote: > Everything just looks > so darn complicated - even if you are basically just doing the same thing: > CONS, APPLY, > and LAMBDA. Why CONS? APPLY and LAMBDA is all you need. :-) -- -- Lennart

Re: The dreaded layout rule

1999-07-30 Thread Lennart Augustsson
Malcolm Wallace wrote: > Because parsing > of infix operators is difficult, all implementations (to my knowledge) > leave resolution of fixity and associativity until later. Indeed, the > Haskell 98 standard recognises this (in an oblique way) by permitting > infix decls to appear *after* the fi

Re: The dreaded layout rule

1999-07-29 Thread Lennart Augustsson
"Carl R. Witty" wrote: > Does anybody disagree with my interpretation of the standard? Are > there any implementations that actually follow the standard here? > (Maybe the standard should be changed to follow the implementations in > this area.) I think you're absolutely right. And I can't ima

Re: Again: Referential Equality

1999-07-28 Thread Lennart Augustsson
Fergus Henderson wrote: > I'm not sure off-hand what the best fix would be. One possible solution > would be to force evaluation of the arguments if they are equal: > > equal x y = unsafePerformIO $ do > ptrEq <- ptrEqual x y > return (if ptrEq then x `

Re: Again: Referential Equality

1999-07-28 Thread Lennart Augustsson
Fergus Henderson wrote: > equal x y = unsafePerformIO $ do > ptrEq <- ptrEqual x y > return (ptrEq || deep_equals x y) > > Note that unlike `req', `equal' here _is_ referentially transparent. No, it's not. If x and y are both bottom you can get unexpected

Re: Again: Referential Equality

1999-07-27 Thread Lennart Augustsson
"D. Tweed" wrote: > On Tue, 27 Jul 1999, Simon Marlow wrote: > > > req a b = unsafePerformIO $ do > > >a' <- makeStableName a > > >b' <- makeStableName b > > >return (a' == b') > > > > That's exactly what to use in a situation like this. Pointer equality loses > > referential transpa

Re: primShiftInt broken or strange in C

1999-07-24 Thread Lennart Augustsson
Ralf Muschall wrote: > Today I saw a strange behavior of primShiftInt in hugs98 > (and all other functions which are implemented using the > operators ">> or "<<"). > The effect is that an expression like "x >> y" in C behaves > as if it were x >> (y & 0x001F). > > E.g. 64 >> 68 gives 4 instead o

Re: Punning

1999-07-22 Thread Lennart Augustsson
George Russell wrote:Standard ML, I'm glad to > say, has punning, and I don't remember it causing me any difficulties at > all as a programmer or a compiler writer. (I wrote the parser in the > latest version of MLj.) Please reverse this stupid ban in the next version > of the Haskell standard!

Re: Differences between some constructs

1999-07-11 Thread Lennart Augustsson
Marcin 'Qrczak' Kowalczyk wrote: > 1. Is there any difference between > \a b -> (a, b) > and > let f a b = (a, b) in f > ? No > > > 2. Is there any difference between > case x of (a, b) -> (b, a) > and > let (a, b) = x in (b, a) > ? Yes, if x is bottom. -- Lennart

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-02 Thread Lennart Augustsson
Peter Hancock wrote: > Maybe Lennart's recurse should be called listrec. I considered that name when I wrote my reply (having been subjected to type theory far many years :-), but I decided to drop list from the name since foldr & co do not have it. -- Lennart

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-02 Thread Lennart Augustsson
Kevin Atkinson wrote: > > I think the type should (almost) explain what it does :), let me exemplfy for lists > > recurse c n [] = n > > recurse c n (x:xs) = c x xs (recurse c n xs) > > > > So it's like foldr, except that the cons function gets the tail of the list, > > not just the head. With i

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > Lennart Augustsson wrote: > > > No, it will not be as efficient. foldr is not the right primitive for making > > functions on lists. You want the more general > > recurse :: (a -> c a -> b -> b) -> b -> c a -> b > > Coul

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > > Assuming that > > you allow pairs and lambda expressions you can do it like this: > > > > caseList xs n c = > > fst (foldr (\ x (_, xs) -> (\ n c -> c x xs, x `cons` xs)) > >(\ n c -> n, empty) xs) n c > > > > zip = > > foldr (\ a g ys -> caseList

Re: Zipping two sequences together with only cons, empty, foldr

1999-07-01 Thread Lennart Augustsson
Kevin Atkinson wrote: > Ok you haskell experts. I have an interesting challenge (or maybe just > a question if you have seen it before). > > Is it possible to zip two sequences together with just: > > cons :: a -> c a -> c a > empty :: c > foldr :: (a -> b -> b) -> b -> c a -> b > > And if s

Re: Field names

1999-07-01 Thread Lennart Augustsson
Koen Claessen wrote: > Hello all, > > I believe the following program is valid Haskell'98: > > >>> > module Main where > > data Hash = Hash{ (#) :: Int } > deriving (Show, Read) > > main = > do print s > print (read s :: Hash) > where > s = show (Hash 3) > <<< > > The problem is the us

Re: Making system call from Haskell?

1999-06-28 Thread Lennart Augustsson
Hans Aberg wrote: > At 13:15 +0800 1999/06/26, Nguyen Phan Dung wrote: > >Do anyone know another way to make system call from Haskell (such as finding > >files in a directory, change file attribute...) besides calling to another > >language to do the job? Both of these things are supported by t

Re: Language Feature Request: String Evaluation

1999-06-08 Thread Lennart Augustsson
"S. Alexander Jacobson" wrote: > HacWrite certainly seems like an improvement over Haskell. > However, it is just not as good as the scripting languages. > HacWrite still requires the author to differentiate between strings and > other types, still requires explicit use of show and still requires

Re:

1999-06-08 Thread Lennart Augustsson
Anatoli Tubman wrote: > How can I *efficiently* print (i.e. find the decimal, or in > general N-ary, representation of) large Integers, like factorial of 1? Use hbc? It uses the gmp routine to convert an Integer to a String. Converting 1! to a String takes much less time than computing

Re: how to write a simple cat

1999-06-04 Thread Lennart Augustsson
Friedrich Dominicus wrote: > That might be good advice but I/O is one of the most essential things > and I have to know how to use it proper for writing small skripts. Actually, you can do a lot without learning about I/O. The function `interact' converts a `String->String' function into an IO

Re: how to write a simple cat

1999-06-01 Thread Lennart Augustsson
Keith Wansbrough wrote: > Sven Panne wrote: > > > > Don't fear! Mr. One-Liner comes to the rescue:;-) > > > > > >longerThan fn lenlim = readFile fn >>= lines .| filter (length .| (>lenlim)) >.| zip [1..] .| map (\(n,l) -> shows n ") " ++ l) .| unlines .| putStr > > Friedrich wrote: > > >

Re: Kind Question

1999-05-26 Thread Lennart Augustsson
Kevin Atkinson wrote: > Kevin Atkinson wrote: > > > > Lennart Augustsson wrote: > > > Your grammar does not seem to cover > > > ((*->*) -> *) -> * > > > which you could get (as the kind of D) e.g. from > > > data D c = C (c []) > >

Re: Kind Question

1999-05-26 Thread Lennart Augustsson
> Now how would I use a type considering its constructor has a signature > of: > > C :: a [] -> D a data L1 f = C1 (f Int) x :: D L1 x = C (C1 []) -- Lennart

Re: Kind Question

1999-05-26 Thread Lennart Augustsson
Kevin Atkinson wrote: > I have a question for the Haskell experts on the list. (Especially > Haskell compiler writers). > > Is it possible to have a kind more complicated than: > > kind = kind' | kind' -> kind > kind' = * | ( kind'' ) > kind'' = * | * -> kind'' Yes, kinds are generated by th

Re: View on true ad-hoc overloading.

1999-05-19 Thread Lennart Augustsson
Kevin Atkinson wrote: > I was wondering what the generally felling to allowing true ad-hoc > overloading like it is done in C++ in Java but more powerful because > functions can also be overloaded by the return value. > > As I see it it will solve a hole series of problems: > > 1) Allow construct

Re: {-# rules

1999-05-08 Thread Lennart Augustsson
Wolfram Kahl wrote: > In the end, my dreams even include a proof format > that can be checked by the compiler :-) Dependent types! That's all you need. -- -- Lennart

Re: Dynamic binding and heterogeneous lists

1999-04-19 Thread Lennart Augustsson
Kevin Atkinson wrote: > I am sorry for the naive question but how do you fell about adding > dynamic binding to Haskell to make it possible to have heterogeneous > lists with out having to use a nasty union type which has a number of > problems. > What you want(?) is existential types. Most imp

Re: Plea for Change #2: Tools

1999-03-29 Thread Lennart Augustsson
> ghc -c Add.hs > ghc -c Main.hs > ghc -o Main Main.o Add.o Or just ghc Add.hs Main.gs But I agree. I always use hbcmake and it does what I want. -- Lennart

Re: Plea for Change #1: Why, O why, `Main'?

1999-03-29 Thread Lennart Augustsson
> Add to this that the `Main' module must reside in a `Main' file and > you have an unfortunate consequence that you can only have one `Main' > function in each directory. That's not so. Haskell doesn't say anything about what files modules have to reside in. Some implementation may have the re

Re: question to GHC 4.02

1999-03-29 Thread Lennart Augustsson
> I have written this small simple program > > module Add where > add :: Int -> Int -> Int > addx1 x2 x1 + x2 > > I have create an object file with the command % ghc -c additon.hs > Now I will create an executable file. > What I have to do? Well, where is your Main module? Haskell

Re: constructor class & data constructor context

1999-03-02 Thread Lennart Augustsson
> data (Num a) => Rsi a = Rsi a a > data (Integral a) => Rse a = Rse a a Contexts on data declarations in Haskell essentially pointless. Just remove them and figure out how to make your code work without them, since they don't do anything. -- Lennart

Re: Haskell 2 -- Dependent types?

1999-02-27 Thread Lennart Augustsson
> So what does Cayenne do if you don't declare the type for `push'? > Does it report an error? The basic principle in Cayenne is that you need type signatures everywhere. This is sometimes rather verbose and is relaxed in some cases, but not here. If you omit the type signature the compiler wi

Re: Haskell 2 -- Dependent types?

1999-02-26 Thread Lennart Augustsson
> (I believe that there are type > theories with dependent types, such as the one in Thompson's _Type > Theory and Functional Programming_, where each term has at most one > type; so it can't just be dependent types that disallow principal > types.) The more I think about this, the less I belie

Re: Haskell 2 -- Dependent types?

1999-02-26 Thread Lennart Augustsson
> This occurs because in the absense of type declarations, > Haskell assumes that any recursion will be monomorphic, > which is in general not necessarily the case. As I'm sure you know, type inference is in general impossible for polymorphic recursion, and since Haskell insists on decidable type

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Lennart Augustsson
> I've lost track of what we're talking about here. In what system can > we not hope for principal types? (I believe that there are type > theories with dependent types, such as the one in Thompson's _Type > Theory and Functional Programming_, where each term has at most one > type; so it can't

Re: Haskell 2 -- Dependent types?

1999-02-25 Thread Lennart Augustsson
> 2) Yes, I agree that the possibility that user-supplied type > declarations can change the meaning of the program is a strike against > the idea. I don't find that so strange. If there are no principal types (which we can't hope for), then user added signatures can have the effect of changing

Re: Haskell-2

1999-02-23 Thread Lennart Augustsson
> I think views are really neat, but am not quite sure how I feel about > pattern guards. Views are neat. Pattern guards are an absolute must. They are just The Right Thing when you need them, and working around not having them is clumsy. -- Lennart

Re: Haskell 2 -- Dependent types?

1999-02-22 Thread Lennart Augustsson
> ...I thought about this pretty hard. Particularly I thought about using > classes; this was fruitless. So I decided I'd invent a new language feature > and a nice little syntax to handle it. > > Sorted l r = Ordered r /\ Permutation l r > > sort :: (l :: [a]) -> (r :: [a]) <= Sorted l r You'v

Re: Haskell 2 -- Dependent types?

1999-02-22 Thread Lennart Augustsson
[EMAIL PROTECTED] wrote: > > enabling types to express all properties you want is, IMO, the right way. > > Why do I feel that there must be another approach to programming? > > How many people do you expect to program in Haskell once you are done adding all > it takes to "express all imaginable

Re: Haskell 2 -- Dependent types?

1999-02-22 Thread Lennart Augustsson
> I consider even the second one to be mixing the proofs > with the code, because there's no easy way that I can tell at > a glance that `sortReallySorts' is a proof rather than a program. But I consider that a feature and not a bug. :-) -- Lennart

Re: Haskell 2 -- Dependent types?

1999-02-22 Thread Lennart Augustsson
> > No, the proof (whereever it is) would no longer type check. > > As I understand it, this is not necessarily true: > if the proof contains loops, it might type check, > even though it is not really a valid proof. You're right. If the proof is looping it will still pass as a proof. -- L

Re: Haskell 2 -- Dependent types?

1999-02-22 Thread Lennart Augustsson
> I believe "//" here is a C++/Java/C9X-style comment. > Just read it as if "//" were "--". Everything from > the "//" until the end of line is a comment. Wow! That's it. Since (//) is an operator on arrays in Haskell I was trying to make sense out of it, and failed miserably. :-) --

Re: Haskell 2 -- Dependent types?

1999-02-21 Thread Lennart Augustsson
> Well if the ComplicatedTypeToSpecifySorting is correct (I don't know if > this is possible, but I suspect it isn't) it will of course not type check. Of course it is possible. The types in Cayenne have the same power as predicate logic, so you can specify most anything you like. Here's a poss

Re: Haskell 2 -- Dependent types?

1999-02-21 Thread Lennart Augustsson
> > > F a * = member (map (F a) [0..]) // member [a] a -> Bool > > I mave no clue what this means. What is `member'? > > Member is memq, in, etc. Checks for membership in a list. I'm still lost. What is // and how does it bind? This is how I parse it: (member (map (F a) [0..])) // ( (member

Re: Haskell 2 -- Dependent types?

1999-02-21 Thread Lennart Augustsson
> Well, yes, up to a point, but it may be clearer if the simple > regular types part is kept separate from the undecidable part, > as was done in NU-Prolog, or as is done in Eiffel. I'm not necesssarily advocating that the properties and proofs of these properties should be mixed with the regular

Re: Haskell 2 -- Dependent types?

1999-02-21 Thread Lennart Augustsson
> The basic problem that I have with this is that although dependent types > do allow you to specify a lot of things in the type system, I'm not sure > that using the type system is really the best way to specify these things. Well, I think types are just the place for these things. People alrea

Re: Haskell 2 -- Dependent types?

1999-02-20 Thread Lennart Augustsson
Nick Kallen <[EMAIL PROTECTED]> wrote: > > apply f (p:ps) = apply (f p) ps > > apply f [] = f > > I wanted to express the type as something like: > > > apply :: (a -> a -> ... -> a) [a] -> a No, that's not what you want. :-) You want apply :: (a -> a -> ... -> b) [a] -> b I think the distinc

Re: Haskell 2 -- Dependent types?

1999-02-20 Thread Lennart Augustsson
> Fair enough (although I'd say "cautious", rather than "pessimistic" > :-). I just think we should have a lot more experience with dependent > types in Haskell (by adding it as an experimental feature to one of > the existing Haskell systems, and having people play with it for a > while) before

Re: Haskell 2 -- Dependent types?

1999-02-19 Thread Lennart Augustsson
> Actually, I think Lennart means PEPM '99. Indeed! Just because it was colocated with POPL99 doesn't make it the same conference. :-) -- Lennart

Re: Haskell 2 -- Dependent types?

1999-02-19 Thread Lennart Augustsson
> OK, I'm curious. Two people replied that C++ has undecidable type > checking. I was not aware of this (although I can't say I'm too > surprised); do you have a reference? It's actually the template processing that can loop, but it is sort of part of the type checking. You can find an article

Re: A plea for a little Haskell help.

1999-02-17 Thread Lennart Augustsson
> What's wrong with > > class Foo a b where > write :: a -> b -> IO () > > ? Well, it's not Haskell. :-) -- Lennart

Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Lennart Augustsson
> 2.in the face of the above, we need to give the compiler more guidance. > Personally, I favour type declarations everywhere: all identifiers should be > introduced as being of a particular specified type. > > Of course, whether these principles are compatible with Haskell it another > ques

Re: Haskell 2 -- Dependent types?

1999-02-17 Thread Lennart Augustsson
> I'm not sure that anybody has "accepted" > undecidable type checking. People using Gofer or C++ seem to have. -- Lennart

Re: Thanks, and new question re existensials

1999-01-04 Thread Lennart Augustsson
Nigel Perry wrote: > At 10:11 pm + 5/11/99, Marcin 'Qrczak' Kowalczyk wrote: > >Fri, 5 Nov 1999 22:26:17 +1300, Nigel Perry <[EMAIL PROTECTED]> pisze: > > > > > I missed the start of this and am a bit confused - I keep seeing > > > "forall", which is universal, not "there exists", which is >

Re: Haskell 98 draft report

1998-12-21 Thread Lennart Augustsson
> It looks odd to me too. I think this is just taken from some other > standard, so I don't propose to alter it. Were you asleep during your numerical analysis classes? :-) If you always round x.5 up you will get numbers that are a little to big on the average since x.5 is exactly halfway inbe

Re: Interesting class and instance question

1998-12-11 Thread Lennart Augustsson
> So yes, you could use this technique to code up monad transformers > etc. in Hugs and GHC. Well, you can do it with a little work in hbc as well. It has been possible for a long while, and then you guys decided on a different syntax. :-) -- Lennart

Re: Stream of random comments continues

1998-12-04 Thread Lennart Augustsson
> There was a paper > published in the JFP about a better way of splitting streams which I think > appeared sometime between January 1996--October 1996. Are you perhaps referring to the paper by me, Mikael Rittri, and Dan Synek called "On generating unique names" (Jan 94). It has a low level tri

Re: Random comments

1998-12-03 Thread Lennart Augustsson
> I guess you would end up with nearly the same code (unless I overlook > an obvious alternative in which case I would love to see the simple and > straightforward solution ;-). Let's be concrete: say you need n > Integers within range (l, r), m Ints and p Doubles. Using a monad-based > approach

Re: Random comments

1998-12-03 Thread Lennart Augustsson
> The stream-based approach has its problems if one requires random > values of different types. If this is vital one automatically starts to > use functions of type Seed -> (value, Seed). I don't understand at all. Why would random values of different types require that signature? Why can you

Re: Reduction count as efficiency measure?

1998-11-25 Thread Lennart Augustsson
> Is this true in practice? That is, are there programs which have > different asymptotic running times when compiled under ghc or hbc than > when running under Hugs? Theoretically it might happen, but in practice it would be very rare (at least for hbc). There one exception, hbc implements a t

Re: Reduction count as efficiency measure?

1998-11-24 Thread Lennart Augustsson
> which of those data structures would give me the best > response time? There is no simple answer to that question. It depends on how you use it and what implementation you're going to use. Set up a typical usage scenario and test it on the platform you are going to use it on, that's

Re: Reduction count as efficiency measure?

1998-11-24 Thread Lennart Augustsson
> So are assembly language instructions. Yet, I could think about > some average instruction size for similarly written programs. Do you mean `time' rather than `size'? If you do, then you can get rather wrong results when considering assembly language since the concept of timing an individual in

Re: Haskell 98 progress...

1998-11-23 Thread Lennart Augustsson
> Actually, shouldn't "isn't" be parsed as a single varid? From the 1.4 > report: OK, OK, let me change my example: {- A comment, isn 't it? -} -- Lennart

Re: Haskell 98 progress...

1998-11-23 Thread Lennart Augustsson
> I'd better make sure that scanning *can't* give an error, though. There are several errors that can occur in the lex phase, e.g., '\q'bad character literal "\q"bad string literal \u0001 bad character in input I REALLY dislike the idea of having my comment

Re: Haskell 98 progress...

1998-11-23 Thread Lennart Augustsson
> Come to think of it, that's good: > > {- This is a string "-}" burble -} > > would now not be confused by the quoted -}; the lexeme is > a string not a '-}' thing. I don't understand this remark. Are you telling me that after a '{-' token the usual lexical process is used to find the m

Re: Reduction count as efficiency measure?

1998-11-23 Thread Lennart Augustsson
> May I at least assume the implication: > reduction_count1 > reduction_count2 ==> time1 > time2 ? I'm not sure how the reduction count is done in Hugs, but if it simply counts G-machine instructions then you can't assume even this. It's likely to be true, but G-machine instructions

Re: monomorphism etc.

1998-11-12 Thread Lennart Augustsson
> > > > [...] if you dislike tuples you can use nested pairs > > At the cost of losing a little type-safety. That's really a very minimal loss. (And it's not really a loss of type safety, just the possibilty of confusing a part of a "tuple" with another "tuple"). I'd be more worried about the

Re: monomorphism etc.

1998-11-12 Thread Lennart Augustsson
> I think it would be > really nice if it were possible to create a container capable of > containing any number of objects of any number of types It would That's not possible in Haskell. Since you want an any number of different types in this new type it would need to have a variable numbe

Re: derive conflicts with multiply-defined and module level import

1998-11-07 Thread Lennart Augustsson
> This is *exectly* the reasoning I am opposed to. It is not to the language > designer to decide for me what is readable of not! But what if someone else has to read your programs? Maybe a uniform style isn't so horrible. -- Lennart PS. Or maybe you're firmly in the Microsludge camp now w

Re: MonadZero (concluded)

1998-11-06 Thread Lennart Augustsson
> This is ok by me. Does anyone object? I don't understand why MonadZero/MonadPlus should go away. Isn't the idea that when in doubt Haskell 98 should do what Haskell 1.4 did? What's the compelling reason for removing these classes? I've used several of the functions that would go away. It wo

Re: MonadZero (concluded?)

1998-11-05 Thread Lennart Augustsson
> Option 1: Monad( .., mfail, mzero ), MonadPlus( mplus ) > Option 2: Monad( .., mfail), MonadPlus( mzero, mplus ) > Option 3: Monad( .., mfail), MonadPlus( mplus ), MonadZero( mzero ) I prefer 3 (with 2 as a close second) since it is most like status quo. -- Lennart

Re: Haskell 98 progress

1998-11-05 Thread Lennart Augustsson
> Integers are a well defined mathematical concept and the > Integer class should reflect this. Having a bottom value seems > wierd to me. Indeed, I'd be quite happy to exclude it if our type systems were powerful enough to handle it. Integers with bottom should have type 'Lif

Re: Haskell 98 progress

1998-11-05 Thread Lennart Augustsson
Simon wrote: > - The do-expression and MonadZero debate. You'll have seen a > lot about this, and I'll circulate a separate proposal. Sorry, I'm not happy with this proposal. Monads are a well defined mathematical concept and I think the Monad class should reflect this. Having a mzero (an

Re: declaring properties

1998-10-21 Thread Lennart Augustsson
> Thank you. I had a look a couple months back but I would be glad if you > could provide a small example (please do not use your obfuscating skills > :-) I think the example of having a proof that the (==) is an equivalence relation is exactly what you're talking about. It's given in the paper.

Re: declaring properties

1998-10-21 Thread Lennart Augustsson
> I am wondering if it would be feasible to declare laws that are guaranteed > to hold for some objects in a Haskell-like functional language. It's feasible. But you need a richer language than Haskell. A language with dependent types would work. Take a look at Cayenne. It can express these kin

Re: Int vs Integer

1998-10-06 Thread Lennart Augustsson
> I must say that I am now strongly inclined to adopt (2); that is, > to make Haskell 98 be the same as Haskell 1.4 on Int vs Integer matter. Thank you Simon for those sensible words. I'm for a very conservative design for Haskell 98; we can always play around with new ideas in Haskell 2.000 (or

Re: Haskell, CORBA and Java (Was: Re: Current state of GUI...)

1998-08-10 Thread Lennart Augustsson
> I am quite unhappy to see these developments (e.g., > H/Direct) being based on some proprietary standards, as it > means that they are rather useless to me. I agree! -- Lennart

Re: RE: Felleisen on Standard Haskell

1998-08-04 Thread Lennart Augustsson
> >That said, the more I think about it, I don't really believe that > >"Standard Haskell" will accomplish much. The fact is that everyone > >wants many of the features in Haskell 2, and so even today would prefer > >using an implementation that is probably not fully compliant with > >anything t

Re: Declared type too general?

1998-06-23 Thread Lennart Augustsson
> > > class Aggregate a where > > > toList::(Num b)=>a->[b] > > > fromList::(Num b)=>[b]->a > > > > > data MyAgg =Agg Int Int > > > instance Aggregate MyAgg where > > > toList (Agg x y) = [x,y] > > > fromList [x,y] = (Agg x y) > I understand what it is saying. I don't understand why it is

Re: Declared type too general?

1998-06-20 Thread Lennart Augustsson
> I have defined: > > > class Aggregate a where > > toList::(Num b)=>a->[b] > > fromList::(Num b)=>[b]->a > > > data MyAgg =Agg Int Int > > instance Aggregate MyAgg where > > toList (Agg x y) = [x,y] > > fromList [x,y] = (Agg x y) > > Hugs won't compile this because it says the declared ty

Re: FW: Exceptions are too return values!

1998-06-10 Thread Lennart Augustsson
> * raise :: String -> a > * handle :: (String -> IO a) -> IO a -> IO a > I'd be interested to know what people think of this. I like the trick of handle being in the IO monad to avoid problems with evaluation order. As usual though, it can be a high price to pay if all you wanted was a little

Re: haskell.org

1998-05-05 Thread Lennart Augustsson
> As to the topics of binary IO, Unicode, and the Haskell report: while > nobody has had the energy to really work the Unicode stuff into an > implementation, the purpose of putting it into the report is to > indicate our intention to do this in the future. What are you talking about? Hbc has su

Re: 2^(-1)

1998-04-09 Thread Lennart Augustsson
> Why is the class heirarchy set up such that 2^(-1) gives and error in > hugs and ghc? It has nothing to do with ghc or Hugs, it's the way Haskell is defined. If (^) was defined the way you suggest then it would be impossible to raise a number from the Integral class to an exponent since there

Re: Monads and their operational behavior

1997-11-27 Thread Lennart Augustsson
> Space leaks like this are lurking in a lot of places in the standard > prelude, so it's quite funny that Hugs/GHC don't address this problem, > although solutions are known. > > What's the behaviour of NHC/HBC in these cases? hbc has 876 bytes in use on the heap and the stack is 13 entries dee

Re: Haskell 1.4 and Unicode

1997-11-07 Thread Lennart Augustsson
Unicode was added at the last moment, so there is likely to be some descrepancies. > 1) I assume that layout processing occurs after Unicode preprocessing; > otherwise, you can't even find the lexemes. If so, are all Unicode > characters assumed to be the same width? I think that's what is inte

Re: heap sort or the wonder of abstraction

1997-10-09 Thread Lennart Augustsson
Oh, Chris, here's a line for your splay sort: splay 0.636 2.625 0.952 - 0.603 2.698 - 3.582 5.731 2.350 - BTW, I don't think the test program does the right thing. It prints the last element of the sorted list, but there is nothing that says that computing this

Re: heap sort or the wonder of abstraction

1997-10-09 Thread Lennart Augustsson
Ralf wrote: 10 | < |<= | > |>= |== | 1 2* | 1..100* | 2 1* | 100..1* | 1 2 2 1* |random merge | 3.15 | 9.16 | 2.83 | 8.96 | 3.18 | 6.65 | 9.60 | 6.64 | 9.46 | 6.58 |

Re: length that yields Integer - Int is a WART

1997-08-25 Thread Lennart Augustsson
> > I need the length of a list and it should be of type Integer, while the > > prelude function yields type Int. > > This looks like a bug in the prelude to me. It's not inconceivable > that in some implementation it might be possible to have a list with > length greater than the capacity of I

Re: RE: how about main :: IO Int

1997-08-22 Thread Lennart Augustsson
> Nope, returning from main is defined by the C standard to be equivalent > to calling exit(), as if main() where invoked as `exit(main(argc, argv))'. Well, it might be standardized, but I've been bitten by implementations that generate a random exit code if you just return 0 from main. This was

Re: RE: how about main :: IO Int

1997-08-22 Thread Lennart Augustsson
> Isn't this a Unix-specific convention, to treat the value returned by > main() > as the exit value of the process? Yes, and it only works in some flavours of Unix. The proper way to exit a C program is to call exit(). The proper way to exit a Haskell program is to call exitWith. -- L

Re: local definitions of `>>=' etc.

1997-05-27 Thread Lennart Augustsson
> Should `test' evaluate to `[1,2,3,4,5,6]' or `[4,5,6,4,5,6,4,5,6]'? > That is, should the `do' syntactic sugar expand to code that uses > plain `>>' or `Prelude.>>'? > > The Haskell 1.4 report is not clear on this point, IMHO. Here is a quote from the report (3 Expressions): Free variable

Re: Monads, Functors and typeclasses

1997-05-14 Thread Lennart Augustsson
Koen Claessen wrote: > In this case we could allow the programmer giving a default declaration > for the superclass methods during the class definition of the subclass. An > example would be: Allowing defaults to be given in subclasses has been discussed. If it was problem free I think it would

Re: A new view of guards

1997-04-28 Thread Lennart Augustsson
> Is this a storm in a teacup? Much huff and puff for a seldom-occurring > situation? No! It happens to me ALL THE TIME. The Glasgow Haskell Compiler > is absolutely littered with definitions like clunky. I agree! I considered a similar extension some years ago now, but I never wrote it dow

HBC 0.9999.4

1997-04-24 Thread Lennart Augustsson
*** Haskell B. release 0..4 *** Hbc 0..4 is a compiler for full Haskell 1.4, both the language and the libraries. It is available for a large number of platforms (see below). * How to get it Use ftp to ftp://ftp.cs.chalmers.se/pub/haskell/chalmers/ and get the parts that yo

Re: reading numbers

1997-03-21 Thread Lennart Augustsson
> > I thought Haskell 1.3 allowed "2" as a valid Float for read. > > What implementation are you using? > > Our hbc compiler will indeed provide a `read' function that parses strings like > "2" as Floats but our Hugs (1.3) and ghc (2.01) won't. In any case, input like > "foo" will still cause t

Re: reading numbers

1997-03-20 Thread Lennart Augustsson
> > atof:: String -> Float > > atof s = read s > > works fine except that it fails for some reasonable inputs like "2" and there > is no way of detecting and handling failures. I am just about to code an > `atof' for them but was wondering if there is a better way. I thought Haskell 1.3 allowed

Re: Assuming universal quantification

1997-03-14 Thread Lennart Augustsson
[EMAIL PROTECTED] writes: > > > data F = MkF t -> t -- did I get the syntax right? > > Almost > > data F = MkF (t -> t) > > > > > > foo :: (Int, String, F) -> (Int, String) > > > foo (i, s, MkF f) = (f i, f s) > > > > In fact, this extension has been implemented in Hugs > > and

Re: polymorphic higher-order terms

1997-03-13 Thread Lennart Augustsson
> data F = MkF t -> t -- did I get the syntax right? Almost data F = MkF (t -> t) > > foo :: (Int, String, F) -> (Int, String) > foo (i, s, MkF f) = (f i, f s) In fact, this extension has been implemented in Hugs and ghc as well as I understand it, but neither of t

<    1   2   3   4   >