Non-exhaustive patterns in function coreAltsType

2001-10-19 Thread Josef Svenningsson
Hi! While bootstrapping a ghc checked out from cvs from yesterday I ran into a problem. While compiling PrelBase.lhs I got the following error message: ghc-5.03: panic! (the `impossible' happened, GHC version 5.03): coreSyn/CoreUtils.lhs:97: Non-exhaustive patterns in function

nativeGen/MachCode.lhs

2001-10-19 Thread Josef Svenningsson
Hi again! In order to compile the module nativeGen/MachCode.lhs I have to add isAsmTemp to the import list of module CLabel. Currently it says: import CLabel ( CLabel, labelDynamic ) but I change it to: import CLabel ( CLabel, labelDynamic, isAsmTemp ) isAsmTemp is only

forall for all places

2001-10-19 Thread Ralf Hinze
GHC 5.02 accepts forall types only at some sensible places: this works data CPS a = CPS { unCPS :: forall ans . (a - ans) - ans } this doesn't work newtype CPS a = CPS { unCPS :: forall ans . (a - ans) - ans } this works newtype CPS a = CPS (forall ans . (a - ans) -

Bug with -h and -c together

2001-10-19 Thread Ian Lynagh
Here's another one, using GHC 5.02 [ian@urchin current]$ cat W.lhs module Main where main :: IO() main = putStrLn $ show $ last [1..10] [ian@urchin current]$ ghc W.lhs -prof -auto-all -o W [ian@urchin current]$ ./W +RTS -h 10 [ian@urchin current]$ ./W +RTS -c 10

RE: Working character by character in Haskell

2001-10-19 Thread Simon Marlow
Humn... I agree with both of you, Albert and Tom. I started it from the beginning, using map and don't using reverse anymore. But the C program is still 7x faster than the Haskell one. Here is the code of the Haskell program: main :: IO () main = do bmFile - openFileEx in.txt

Re: Working character by character in Haskell

2001-10-19 Thread Ketil Malde
Simon Marlow [EMAIL PROTECTED] writes: Well, in Haskell each character of the string takes 20 bytes: 12 bytes for the list cell, and 8 bytes for the character itself Why does a list cell consume as much as 12 bytes? Two pointers (data and next) and a 32-bit tag field, perhaps? And a 64-bit

Strict functions

2001-10-19 Thread Ian Lynagh
Hi all I've been reading the GHC docs and they say that strict functions are good for space and time. Section 6.2 goes on to explain how to read the .hi files to determine the strictness of a function. However, it doesn't explain all the cases I am seeing. Example of the ones I've noticed are:

Multi-parameter OOP

2001-10-19 Thread George Russell
Recently I've been experimenting with a sort of OOP with GHC, using existential types and (overlapping, undecidable) multi-parameter type classes, but it doesn't seem to work as you might expect because of the way GHC resolves overloaded functions at compile-time. For example, given class A

Re: Strict functions

2001-10-19 Thread Andrew J Bromage
G'day all. On Fri, Oct 19, 2001 at 02:30:59PM +0100, Ian Lynagh wrote: Also, the prelude definition of zipWith has LVL whereas the following definition has LVV. Why is something like the following not used? zipWith :: (a-b-c) - [a] - [b] - [c] zipWith f (a:as) (b:bs) = f

RE: Working character by character in Haskell

2001-10-19 Thread Jan-Willem Maessen
Simon Marlow [EMAIL PROTECTED] writes: To really match the C program, you need to use IOExts.hGetBuf and IOExts.hPutBuf, and do the operations on raw characters in memory. Using a UArray of Word8 would be better, but there aren't any operations to do IO to/from a UArray yet (actually I've

Why is (monad) elegance so costly?

2001-10-19 Thread marku
I am about to rewrite my Z animation tool (JAZA) in a style that makes more intensive use of state monads. However, my experiments with a simplified lambda-calculus example shows that (with GHC 5.00) the state monad is dramatically less efficient than the simple identity monad: 4 TIMES

Re: Multi-parameter OOP

2001-10-19 Thread Marcin 'Qrczak' Kowalczyk
Fri, 19 Oct 2001 17:02:54 +0200, George Russell [EMAIL PROTECTED] pisze: So is there any other way of doing this sort of dynamic lookup at runtime, in a reasonably neat way? There is module Dynamic. I don't know if it helps or is reasonably neat. -- __( Marcin Kowalczyk * [EMAIL

Your Property Portfolio

2001-10-19 Thread Smith Hawkshaw Properties
£ 5 million worth of Bank Mortgage Reposessions Terraced houses ideal for renting. Tenants waiting. SMITH HAWKSHAW PROPERTIES Full Property Management Service available. Finance available from 5% fixed for 5 years Our family have been purveyors of properties for over 100 years. For

Re: Multi-parameter OOP

2001-10-19 Thread Ashley Yakeley
At 2001-10-19 08:02, George Russell wrote: a naive user (like me a month ago) might expect that this to work, so that toBool (WrappedA a) (WrappedB b) will return False unless a is an A1, and b a B1, in which case it returns True. I think existential types are arranged so that Haskell never

Re: Large lists, heaps, stacks...

2001-10-19 Thread Janis Voigtlaender
Till Doerges writes: select' :: [a] - [Integer] - ([a],[a]) select' xs poss = sAcc xs (sort poss) 0 ([],[]) where sAcc :: [a] - [Integer] - Integer - (([a],[a]) - ([a],[a])) ... Crash select' test [0..] (35922 reductions, 63905 cells) ERROR: Control stack overflow ... 2) Why

Re: Large lists, heaps, stacks...

2001-10-19 Thread Janis Voigtlaender
Till Doerges writes: I tried to implement a function that separates a list into two parts according to a list of indices given. (Does anything like that perhaps exist already in the Prelude?) ... 1) Could anybody please explain the behaviour of select and select' to me? To

final test: Research Job in Compositional Reasoning and Analysis @ Heriot-Watt Univ., Scotland, UK

2001-10-19 Thread Joe Wells
Title: Research Position Research Position Useful Logics, Types, Rewriting, and their Automation (ULTRA) GroupComputing and Electrical Engineering DepartmentHeriot-Watt UniversityEdinburgh, Scotland, UK Description of the Position A research position is available on an

Re: Large lists, heaps, stacks...

2001-10-19 Thread Steinitz, Dominic J
Have you looked in the list library? partition or groupBy may be what you want. Dominic. - To receive our special fares directly by email, register at http://www.britishairways.com/registration

list comprehension

2001-10-19 Thread Stephanie Randles
Hi, I have a script here interleave::[Integer] - [Strings] - [String]interleave(x:xs) (y:ys) = words [a | a - (unwords [(show x), (filter (/= 1) y), "+"])] and the error message i receive is (Instance of Num Char required for definition of interleave) and I don't understand what this

Re: list comprehension

2001-10-19 Thread Ch. A. Herrmann
Stephanie == Stephanie Randles [EMAIL PROTECTED] writes: Stephanie Hi, I have a script here Stephanie interleave :: [Integer] - [Strings] - [String] Stephanie interleave (x:xs) (y:ys) = words [a | a - (unwords Stephanie [(show x), (filter (/= 1) y), +])] Stephanie and the

Re: Working character by character in Haskell

2001-10-19 Thread Malcolm Wallace
Simon Marlow [EMAIL PROTECTED] writes: Well, in Haskell each character of the string takes 20 bytes: 12 bytes for the list cell, and 8 bytes for the character itself Ahem, _Haskell_ mandates no such thing. Perhaps you are talking about a specific implementation? ghc probably. Isn't it

Re: list comprehension

2001-10-19 Thread Rijk-Jan van Haaften
Hello, Hi, I have a script here interleave :: [Integer] - [Strings] - [String] interleave (x:xs) (y:ys) = words [a | a - (unwords [(show x), (filter (/= 1) y), +])] Firstly, Strings is not a standard type. I suspect you mean String so the type signature is interleave :: [Integer] - [String]

Re: More Unicode nit-picking

2001-10-19 Thread Marcin 'Qrczak' Kowalczyk
19 Oct 2001 06:09:09 +0100, Colin Paul Adams [EMAIL PROTECTED] pisze: But this seems to assume there is a one-to-one mapping of upper-case to lower-case equivalent, and vice-versa. Apparently this is not so. Indeed, but there exists a default locale-independent case mapping. Language-specific

Re: Large lists, heaps, stacks...

2001-10-19 Thread Till Doerges
Hi everybody, thanks for all the answers! On Fri, Oct 19, 2001 at 09:55:00AM +0200, Janis Voigtlaender wrote: [...] You might try the following version that does not build up huge data structures in accumulating parameters to output them only in the two base cases. Rather, it produces

Main module editor/Interpreter

2001-10-19 Thread Eric Allen Wohlstadter
Has anyone made a program for Hugs that allows you to add type definitions and top level functions to the Main module from the interpreter command line? I find it odd that I have load from a text file to experiment with data types, classes, etc. If this sort of thing is not available convince me

RE: Haskell 98 - Standard Prelude - Floating Class

2001-10-19 Thread Simon Peyton-Jones
An apparently-innocuous suggestion about adding default methods for sinh and cosh led to a flood of mail. Since no consensus emerged, I plan to leave things as they are in the Haskell 98 Report. Namely, the following default methods for the Floating class are there: x**y = exp (log x

Re: strong typing is not a panaceum, and, anyway...

2001-10-19 Thread Brian Boutel
Jerzy Karczmarczuk wrote: Brian Boutel to Sergey Mechveliani: There is no scientific reason why all computations with types and type resolution should preceed all computations with non-types. No scientific reason, but a strong engineering reason. The engineering idea is to

A small doubt

2001-10-19 Thread Saswat Anand
Hi, I am wondering why this function should not work with input [x,y] (list with two elements) too, since third element is not referenced. Why is it so eager to pattern match. fun = \list - let [a,b,c] = list in [a,b] Thanks, Saswat

Re: A small doubt

2001-10-19 Thread Marcin 'Qrczak' Kowalczyk
Sat, 20 Oct 2001 10:58:02 +0800 (GMT-8), Saswat Anand [EMAIL PROTECTED] pisze: I am wondering why this function should not work with input [x,y] (list with two elements) too, since third element is not referenced. What a pattern matches is independent from which of the variables it binds