Re: Random comments

1998-12-03 Thread Ralf Hinze
| First: I had forgotten that what the Random module actually | gives you is [Integer], not [Int], but the same reasoning | applies. What's the range for the Integers? I guess Int is better suited. | Well, you naturally need functions that convert a list of | [Integer] to what you need. I'm

Re: Why I hate n+k

1998-11-30 Thread Ralf Hinze
Simon writes ... | Just to amuse you all, here's a quick Haskell 98 quiz: | | What do the following definitions do: | | 1 x + 1 = f x | | 2 (x + 1) = f 2 | | 3 (x + 1) * 2 = f x | | 4 (x + 1) 2 = g x | | | That's right! | | (1) partially defines (+). One could add

Re: Reduction count as efficiency measure?

1998-11-25 Thread Ralf Hinze
| 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? | | It would actually surprise me if there were; I'm having a hard time | imagining a realistic optimization that would do this.

Some more bugs

1998-11-19 Thread Ralf Hinze
Hi again, I tried the binary release of GHC 4.00 on my library of sorting routines. The compiler fails on ghc -c -O -W -fglasgow-exts -recomp -H32M QuickSortInPlace.lhs The error message is not that enlightening ;-). unimplemented check On ghc -c -O -W -fglasgow-exts

Re: MonadZero (concluded)

1998-11-06 Thread Ralf Hinze
| class Monad m = MonadPlus m where | mzero :: m a | mplus :: m a - m a - m a | | Why is this here? It doesn't need to be in the prelude. Just | leave it for the user to define (and then the user may pick | better names, like Ringad, zero, and +). -- P Yes, nuke

RE: MonadZero (concluded)

1998-11-06 Thread Ralf Hinze
| Does this mean that code which relies on ++ and do notation with Maybe | will stop working? ++ is specialized to lists, I'm afraid. Ralf

Haskell 98 libraries

1998-11-05 Thread Ralf Hinze
Haskell 98 libraries * Make each module export all the relevant types and functions that the Prelude defines, so that a programmer who does not import the Prelude can get access to all the (say) list types and functions by saying import List. This involves extra exports from

Re: mfail - fail

1998-11-05 Thread Ralf Hinze
| Here's an even better idea: replace mfail with fail. | It is, after all, the fail of the IO monad! | | Option 4'': Monad ((=), return, fail) Unfortunately not, fail of IO fame has type IOError - IO a and not String - m a as Monad's new member. Here's my suggestion: o Monad

Re: Default Default

1998-11-05 Thread Ralf Hinze
| John Peterson writes | | Int is really not a nice | datatype and we shouldn't be allowing it to crop up unexpectedly. | | Yes, but if we believed that, we should use Integer, not Int, for | length. | | You are right, beginners may stub their toe on factorial. On the other | hand, with

Re: MonadZero

1998-11-03 Thread Ralf Hinze
| 1.Fix up the current version. | use MonadZero for do expressions with *irrefutable* patterns | (instead of *unfailable* patterns as now) | 2.Nuke MonadZero altogether. | add mfail :: m a to Monad instead I opt for 2. It's certainly true that the second choice breaks existing

Re: MonadZero

1998-11-03 Thread Ralf Hinze
| I want to make a different plea: keep the language design consistent! | Yes, the difference between f, g, h is a wart, but let's have one wart | repeated, rather than two different warts. I am not convinced. This argument could be reverted to support alternative 2. Haskell uses patterns in

RE: topdelcs / decls

1998-10-23 Thread Ralf Hinze
| Your thought would destroy equational reasoning! For example you | would be able to define different equalties on the same data | structure. So Red==Black could be False in one place and True | in another place. Does that make any sense? Of course, it does. You neglect the fact that

Re: topdelcs / decls

1998-10-23 Thread Ralf Hinze
| just a thought .. why is it that some declarations | (data, type, newtype, class, instance) are only allowed | at the (module) top level? in some cases i'd like to have | more locality, and less namespace pollution. Let me add: local declaration might also increase the expressibility of

Re: relocate_TSO

1998-10-16 Thread Ralf Hinze
| Ralf Hinze [EMAIL PROTECTED] writes: | | jod 78 a.out | a.out: fatal error: relocate_TSO | jod 79 | | Gotta be a native code generator bug. Try compiling with -fvia-C. | | Cheers, | Simon Does not work, I'm afraid ... jod 157 ghc -fvia-C EDigits.lhs ghc: module version changed

Re: Haskell 98

1998-10-16 Thread Ralf Hinze
| Comments to me directly ([EMAIL PROTECTED]), or the Haskell mailing | list. Here we are ... (comments are marked with `]') Typing of do expressions [...] 2. Nuke MonadZero altogether. Instead, augment the Monad

Eval and seq

1998-10-13 Thread Ralf Hinze
High, it seems that the class `Eval' has vanished and `seq' is now truely polymorphic. Right? Perhaps worth mentioning in the Release notes as the change may affect some programs ((Eval a) = is no longer a valid context). Cheers, Ralf

relocate_TSO

1998-10-13 Thread Ralf Hinze
-- X-Sun-Data-Type: text X-Sun-Data-Description: text X-Sun-Data-Name: text X-Sun-Charset: us-ascii X-Sun-Content-Lines: 108 High again, the build was successful ;-). Unfortunately, the first test program which aims at stressing the new RTS dies with a fatal error. Here is a transcript

YAB (yet another bug)

1998-10-13 Thread Ralf Hinze
-- X-Sun-Data-Type: text X-Sun-Data-Description: text X-Sun-Data-Name: text X-Sun-Encoding-Info: uuencode X-Sun-Content-Lines: 69 begin 600 text M25R92!IR!T:4@;F5X="!O;F4Z(=H8R=S(]N;'D@8V]M;65N="!IR!@ M=6YI;7!L96UE;G1E9"!C:5C:RN(%1H90ID971A:6QS(%R92!G:79E;B!B

Another 4.00 bug

1998-10-12 Thread Ralf Hinze
High again, make boot succeeded, make all stops with [..] IdUtils.lhs:16: Module `PrimOp' does not export `primOpInfo' IdUtils.lhs:16: Module `PrimOp' does not export `PrimOpInfo(..)' Compilation had errors make[2]: *** [basicTypes/IdUtils.o] Error 1 make[1]: *** [all] Error 1 make: ***

input file doesn't exist: parser/U_tree.hs

1998-10-12 Thread Ralf Hinze
High, could not resist to install brand new 4.00. However, `make boot' on my Solaris box was not successful: [...] parser/entidt.c parser/list.c parser/literal.c parser/maybe.c parser/pbinding.c parser/qid.c parser/tree.c parser/ttype.c ghc -M -optdep-f -optdep.depend -optdep-o

Re: Yet another superfluous file ...

1998-10-12 Thread Ralf Hinze
| Ralf Hinze [EMAIL PROTECTED] writes: | | | TyVar.lhs:71: Value not in scope: `uniqueOf' | | TyVar.lhs:178: Value not in scope: `uniqueOf' | | | What do you think: Is it safe to react uniformly to these errors by | just deleting the offending file? | | The distribution on the ftp

Re: type inference references?

1998-10-09 Thread Ralf Hinze
| Sorry for the naive query but could somebody satisfy my curiosity by | emailing me with a reference to material explaining the following? [...] | -- pierrot{reidrm}665: cat test.hs | | g x = id x :: [a] | main = putStr "test\n" Sorry for the late reply but the next term is just about to start

Re: Instance contexts.

1998-07-28 Thread Ralf Hinze
| I'd like to support Alex here: it is absolutely necessary to relax | condition 10 of SPJ's list. | | http://www.dcs.gla.ac.uk/~simonpj/multi-param.html | | Idioms like the one above (`Ord (s a)' or | `Show (s a)') arise too often and are completely natural. | | One of the great

Re: avoiding repeated use of show

1998-07-22 Thread Ralf Hinze
I would like to avoid using show all the time for printing strings e.g. val = "the sum of 2 and 2 is "++(show $ 2 + 2)++" whenever." I would prefer to type something like: val = "the sum of 2 and 2 is "./(2+2)./" whenever." -- i can' find a better haskell compatible operator I

Re: avoiding repeated use of show

1998-07-22 Thread Ralf Hinze
| I would be more inclined to use . The reason is typing efficiency. | '' is awkward to be typing frequently immediately after '"'. I do not type that fast ;-). | You are acutally using (.) below. Is there a way to do that (via | Fran like lifting?)? I'm afraid no. | instance Stringable

Re: Scoped typed variables.

1998-07-22 Thread Ralf Hinze
| Just as a sanity check, following an augmented proposal "A" where we can also | annotate the return type as well, consider these: | | f :: a - (a - a) - a | f x = \g - (g :: a - a) x | | f (x :: a) :: (a - a) - a = \g - (g :: a - a) x | | Which of these two is

Re: Monomorphism

1998-07-21 Thread Ralf Hinze
One of the original motivations for questioning the DMR steems from the fact that function definitions expressed as simple pattern bindings are sometimes rejected. The definition sum as = foldr (+) 0 as is accepted but sum = foldr (+) 0 is not which is admittingly irritating.

Re: type synonyms

1998-07-09 Thread Ralf Hinze
data / type / newtype: i'd like to have these choices type T1 = record C1 .. | C2 .. type T2 = T1 type T3 = new T2 with T2 identical to T1, and T3 being an identical copy of T2 (but different from T2) inheriting all its constructors and operations. That's basically newtype with

Re: multi param type classes

1998-07-08 Thread Ralf Hinze
you want to lift this restriction: The type of each class operation must mention all of the class type variables. how would you resolve ambiguities? probably by requiring an explicit type signature at the point of usage. No longer ;-). I find SPJ's summary on

Re: Structure of monads in an abstract form?

1998-07-06 Thread Ralf Hinze
I think you can "encode", or "mimick" every monad by the following type, which is the monad of continuations: type M a = (a - Action) - Action [...] Unfortunately the Haskell type system is often too restrictive to encode the wanted features. I have for example no idea how to do

Pattern match(es) are non-exhaustive

1998-07-02 Thread Ralf Hinze
That's not really a bug. Ghc's output is sometimes not properly formatted, ie parenthesis are missing. Look at Pattern match(es) are non-exhaustive in the definition of function `lp' Patterns not recognized: G G _ _ _ _ (_ : _) The last line should read G (G _ _) _ _ (_

Re: type errors

1998-07-01 Thread Ralf Hinze
Ok, I did not reconize this solution, it seems to me the (nearly) proper one. But why not write: class = Dictionary dict where delete :: (Eq key, Ord key) = key - dict key dat - dict key dat ... So one could avoid multiparamter classes at all. The two types key and dat

Re: INTERNAL ERROR: importEntity

1998-06-29 Thread Ralf Hinze
... Then I made this change to storage.c diff -c -r1.42 storage.c *** storage.c 1998/01/26 04:13:30 1.42 --- storage.c 1998/06/28 01:58:53 *** *** 1771,1776 --- 1771,1778 jmp_buf regs; /* save registers on stack */

Re: Syntax dubion

1998-06-26 Thread Ralf Hinze
if I write (a b) x = a x b x hugs accepts it, but ghc rejects it. I think that ghc is correct in that the report only allows funlhs - var apat {apat } | pati+1 varop(a,i) pati+1 | lpati

Re: what is leaking?

1998-06-26 Thread Ralf Hinze
When I try to execute this: result = foldl (+) 0 [1..10] main = putStr $show (result `mod` 10) Hugs gives: ERROR: Garbage collection fails to reclaim sufficient space GHC gives: Stack space overflow: current size 262152 bytes. Why would this have an error? The list should be

Re: Teaching Haskell

1998-06-24 Thread Ralf Hinze
CUP just released my book on "Purely Functional Data Structures". I just got hold of a copy. My impression: it is *really* worth reading. Ralf

Re: laws for MonadPlus?

1998-06-23 Thread Ralf Hinze
what laws should hold for the (++) operation? Associativity and leftward distributivity are missing in the Report: (m ++ n) ++ o = m ++ (n ++ o) (m ++ n) = k = (m = k) | (n = k) On the other hand right distributivity does not hold in general. Conversely, the report also

Re: FW: Exceptions are too return values!

1998-06-10 Thread Ralf Hinze
I'd be interested to know what people think of this. Here's a reasonable design for exceptions in Haskell: ... The neat thing about this is that the exceptions can be *raised* in arbitrary purely functional code, without violating referential transparency. The question of which exception

Inference of instance declarations

1998-06-04 Thread Ralf Hinze
[This is a repost of an email I sent yesterday to `[EMAIL PROTECTED]'. For some reasons it did not come through. Either the moderator didn't like it or something is wrong with `haskell.org'. I tacitly assume the latter ;-). RH] [This email is mainly directed to the type and class system experts

Re: How to do Exceptions in Haskell (I think)

1998-06-04 Thread Ralf Hinze
would it be a solution if you defined data RetVal b a = Result a | Exception b in this case you could say instance Monad (RetVal b) where return = Result Result x = f = f x Exception x = f = Exception x Incidentally, the predefined data type `Either' may be used for this

Re: quicksort and compiler optimization

1998-05-07 Thread Ralf Hinze
The tutorial defines: quicksort []= [] quicksort (x:xs) = quicksort [y | y - xs, yx ] ++ [x] ++ quicksort [y | y - xs, y=x] This code strikes me as twice as slow as it could be because it seems to requires two loops through the list on each recursive call. I guess it is only

Re: Threading Monads

1998-05-05 Thread Ralf Hinze
Graeme Moss writes A question born out only of curiosity: Can anyone provide a definition of `thread' equivalent to this: thread :: Monad m = [a - m a] - a - m a thread [] a = return a thread (k:ks) a = k a = thread ks not using pattern matching (eg. using map or fold) that

Re: GHC 3.00 Bug or New Restriction ????

1998-02-06 Thread Ralf Hinze
Simon Marlow [EMAIL PROTECTED] writes Best way around it is to use a newtype: newtype ListBlah = ListBlah [Blah] instance Show ListBlah where Ok, it's a bit of a pain to put the extra constructors everywhere, but at least you don't lose any efficiency. Is that `True'? Does the

Re: Query on multi-param type classes

1998-01-30 Thread Ralf Hinze
Dear Jon, dear Simon, class (Monad m, Monad (t m)) = AMonadT t m where lift :: m a - t m a I'm frankly unsure of the consequences of lifting the restriction. Can you give a compact summary of why you want to? Our multi-parameter type-class paper gives none, and if you've got one

Still unhappy

1998-01-29 Thread Ralf Hinze
Guess what? It's the old 'for i in ;' problem again. Try 'make install SHELL=bash' (I think the upper case is important). Yes, the upper case is important. However, installing happy from the binaries still does not work. Here is a summary of my undertakings: gunzip

Re: haskell and exceptions

1998-01-29 Thread Ralf Hinze
Matthias Fischmann writes ... I am now trying to learn Haskell for half a week and I like it a lot. But I still did not find out too much about exception handling. Is it possible that there is no ml-like mechanism with `raise' and `handle' built in? Yes, I know about types like data

Installing 3.0, also unhappy

1998-01-28 Thread Ralf Hinze
Dear Simon and Simon, probably the worst design decision in the last five years was to detach Happy from the compiler distribution, at least for me :-(. When I tried to install ghc-3.00 I immediately fell on my face: Happy is required ... So I tried to install Happy from the binary

Re: insert sort with foldr

1998-01-12 Thread Ralf Hinze
Dear Jose, I am trying to define common functions with recursive combinators avoiding recursive definitions. I have found some problems with the "insert" function that inserts an element x in an ordered list xs This function is used when you define insertion sort as "foldr insert []" --

RE: insert sort with foldr

1998-01-12 Thread Ralf Hinze
Yes, you are right, but that is the same function that I wrote in my original message as 'newfoldr': newFoldr::(a-[a]-b-b)-b-[a]-b newFoldr f c [] = c newFoldr f c (x:xs) = f x xs (newFoldr f c xs) Well, I merely wanted to throw in the technical term. I asked if that function

Installation from source failed

1997-12-23 Thread Ralf Hinze
Dear Simon Simon, unfortunately I did not succeed in installing GHC from source. Probably I'm missing something. Here is a short summary of my trial: gunzip ghc-2.10-src.tar.gz | tar xf - gunzip happy-1.5-src.tar.gz | tar -xf - mkdir fptools.sparc cd fptools.sparc lndir ../fptools .

Compiling from source does not work

1997-11-28 Thread Ralf Hinze
Dear all, I grabbed the new source distribution but booting does still not work. It appears that happy is not found: ... ../../happy/src/happy +RTS -K2m -H10m -RTS -1.2-g rename/ParseIface.y make[2]: ../../happy/src/happy: Command not found make[2]: *** [rename/ParseIface.hs] Error 127

Re: Sorting and Type Classes

1997-10-17 Thread Ralf Hinze
[Benchmark suckers and implementors only] Chris writes ... While experimenting with the sorting algorithms that have been posted here recently I discovered that the benchmarks were being quite seriously distorted by the use of type classes to implement some of them. Even the use of `Ord a'

Re: ghc Diagnostics

1997-10-13 Thread Ralf Hinze
I take your point that this isn't very consistent: there should be a way to turn off all warnings easily. What do other people think? The options are: * have all warnings off by default, a standard set of warnings being available by adding the -W command line option. I

Universal quantification

1997-10-12 Thread Ralf Hinze
Dear type wizards, what's wrong with the following program? module Test where data Empty q = Empty (Ord a = q a) q :: (Ord a) = [a] q = [] e0, e1, e2:: Empty [] e0=

*** Pattern-matching error within GHC!

1997-10-12 Thread Ralf Hinze
-- X-Sun-Data-Type: text X-Sun-Data-Description: text X-Sun-Data-Name: text X-Sun-Charset: us-ascii X-Sun-Content-Lines: 44 Dear bug chasers, ghc-2.08 fails to compile the attached module uname -a SunOS jod 5.5 Generic_103093-14 sun4u sparc SUNW,Ultra-1 ghc-2.08 -O -c ListLib.lhs

UnHappy

1997-10-10 Thread Ralf Hinze
Dear Buggies, `make all' is not successful (booting with ghc-0.29) because there are some Happy generated files containing `newtype' declarations which ghc-0.29 does not swallow. Diagnostics: ghc-0.29 -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser

Re: heap sort or the wonder of abstraction

1997-10-09 Thread Ralf Hinze
Lennart wrote Well, I'm a sucker for a benchmark so I ran all of these with hbc. I also added the smooth merge sort that comes with hbc. ... As you can see there is no clear winner, but I see no real reason to change the sort that comes with hbc to something else at this moment. You are

Splay sort

1997-10-09 Thread Ralf Hinze
Ralf, could I ask you to run my code below through your experiments (I don't have easy access to anything but hugs at the moment)? Here we are ... 5 | |= | |= |== | 1 2* | 1..100* | 2 1* | 100..1* | 1 2 2 1* |random

Re: heap sort or the wonder of abstraction

1997-10-08 Thread Ralf Hinze
ot;, second edition, 1996, Cambridge University Press [3] Chris Okasaki. "Purely Functional Data Structures", PhD thesis, School of Computer Science, Carnegie Mellon University,1996, CMU-CS-96-177 [4] Ralf Hinze."Einf"uhrung in die funktionale Programmierung mit Miranda&qu

Type signature expressions

1997-08-26 Thread Ralf Hinze
Dear Fellow Bug Chasers, ghc-2.05 (with some patches applied ;-)) does not digest the following program: module Test ( module Test ) where import List class Sequence s where fromList :: [a] - s a toList:: s a - [a] instance Sequence [] where

A challenge

1997-08-01 Thread Ralf Hinze
-- X-Sun-Data-Type: text X-Sun-Data-Description: text X-Sun-Data-Name: text X-Sun-Charset: us-ascii X-Sun-Content-Lines: 64 [This is not a bug report, but a challenge for the GHC wizards.] Dear Simon, dear Sigbjorn, I remember vaguely that you asked for programs which run fast with

data dependencies broken by an optimisation pass

1997-06-17 Thread Ralf Hinze
Dear Glasgow-Wizards, my first experiment with second-order types failed. The following piece of code causes ghc to panic. === module SOL( module SOL ) where import GlaExts data SeqView t a

Discrepancy

1997-04-30 Thread Ralf Hinze
Dear all, I stumbled across a subtle discrepancy between Hugs and GHC. After some thought I decided that the Glasgow Haskell Compiler is `buggy'. However, since the Report is not explicit about this issue (at least I did not find a clue) the case is probably not settled. Assume we have the

<    1   2