win32 test installer

2002-02-08 Thread Sigbjorn Finne

A test Windows Installer for the 5.03 snapshot release is now
available via

   http://galois.com/~sof/ghc-5.03-20020208.msi (25.2M)

Unless I hear of any fatal flaws encountered using it or I
discover glitches while sleeping, it will go up on
haskell.org/ghc/ tomorrow morning (PST).

--sigbjorn


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



ghc-5.02.1 Comments/Pragmas

2002-02-08 Thread Kevin Hammond

The parser fails (non-exhaustive pattern, parser/Parser.hs line 4700)
if provided with a comment such as:

{-##-}

or

{--}

The comment {-#-} is however accepted!  Presumably this is to do with
pragma parsing!

Kevin


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



RE: inscrutable warning

2002-02-08 Thread Julian Seward (Intl Vendor)


The warning says that the interpreter has ignored a 
polymorphic case, since it's hard to implement.  Your program
should still behave the same, although possibly less strictly
than you intended.

What really mystifies us is why there is such a thing in the
program in the first place.  Using -ddump-sat we can see that
there is indeed a 
   case ... of { DEFAULT - ... }
but how it came to be, I do not know.

We may investigate further.

J

| Can someone explain the following warning?
| 
| ---
| module Warning where
| 
| type A = IO ()
| 
| class CA t
|where a :: t - A
| instance CA ()
|where a = return
| instance (CA t) = CA (IO t)
|where a = (= a)
| 
| data B = B A
| 
| class CB t
|where b :: t - B
| instance (CA t) = CB (IO t)
|where b = B . a
| ---
| 
| % ghci Warning.hs
|___ ___ _
|   / _ \ /\  /\/ __(_)
|  / /_\// /_/ / /  | |  GHC Interactive, version 5.02.2, 
| for Haskell
| 98.
| / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
| \/\/ /_/\/|_|  Type :? for help.
| 
| Loading package std ... linking ... done.
| Compiling Warning  ( Warning.hs, interpreted )
| WARNING: ignoring polymorphic case in interpreted mode.
|Possibly due to strict polymorphic/functional constructor args.
|Your program may leak space unexpectedly.
| 
| Ok, modules loaded: Warning.
| Warning
| 
| ___
| Glasgow-haskell-users mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
| 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ANNOUNCE: GHC 5.03.20020204 snapshot release

2002-02-08 Thread Sigbjorn Finne

A Windows Installer for this snapshot is now available via
the GHC downloads page,

http://haskell.org/ghc/download_ghc_snapshot.html

enjoy
--sof

- Original Message - 
From: Julian Seward (Intl Vendor) [EMAIL PROTECTED]
To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
Sent: Tuesday, February 05, 2002 06:36
Subject: ANNOUNCE: GHC 5.03.20020204 snapshot release


 
 There have been a number of significant improvements made to GHC 
 since the 5.02 sources were branched off the main GHC development 
 tree, but we're not quite ready to make a full 5.04 release yet.  
 However, we're keen to get feedback on the new features from people
 that don't have easy access to CVS or don't have the time  patience
 to build GHC from scratch, so we're making a snapshot release of the
 current GHC, in source and binary form.
 
 There are NO GUARANTEES as to the stability of this release, although
 we do know it has passed our basic three-stage bootstrap test and run
 the regression tests successfully.  In some cases the documentation
 hasn't been fully updated to reflect the new features yet.
 
 Briefly, the changes relative to 5.02.2 are:
 
- The type system now supports arbitrary rank polymorphism,
  given appropriate type annotations.
 
- Heap profiling has had a major overhaul and now supports
  retainer profiling and biographical profiling ala nhc98.
 
- Major improvements to the native code generators. You can now 
  compile any and all code through them, including the Prelude. 
 
- The FFI syntax has been updated to match the latest version
  of the FFI Haskell 98 Addendum.
 
- newtypes support deriving *any* class for which the
  underlying type is also an instance.
 
- Linear implicit parameters: a highly experimental feature.
 
- GHCi has several new commands: 
 - ':show bindings' to list the bindings made on the command
   line,
 - ':show modules' to show which modules are loaded,
 - ':module' has been enhanced as per the discussion on the
  mailing list (syntax is still experimental - feedback
welcome).
 - ':browse'  similar to Hugs' :browse command.
 
 And many other minor changes  bugfixes.
 
 At the moment there is just the sources and a binary build for 
 x86-linux available.  We may add builds for other if they become 
 available.
 
 You can get it from
 http://haskell.cs.yale.edu/ghc/download_ghc_snapshot.html
 
 Enjoy!
 
 The GHC Development Team.


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



efficiency question

2002-02-08 Thread Hal Daume III

define

test1 l = 
let s1 = foldr (+) 1 l
s2 = foldr (-) 1 l
in  (s1, s2)

test2 l =
let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
in  s

why is test1 so much faster than test2 for long lists l (eg
[1..100])?  replacing foldr with foldl makes it faster (of course),
but test2 is still much slower.

i *expected* test2 to be much faster because you're only traversing the
list once.  presumably the two elements a and b in test2 could be put
in registers and i'd imagine test2 should be faster (it certainly would be
if written in c).

 - hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: efficiency question

2002-02-08 Thread Jorge Adriano

On Friday 08 February 2002 22:14, Hal Daume III wrote:
 define

 test1 l =
 let s1 = foldr (+) 1 l
 s2 = foldr (-) 1 l
 in  (s1, s2)

 test2 l =
 let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
 in  s

 why is test1 so much faster than test2 for long lists l (eg
 [1..100])?  replacing foldr with foldl makes it faster (of course),
 but test2 is still much slower.

 i *expected* test2 to be much faster because you're only traversing the
 list once.  presumably the two elements a and b in test2 could be put
 in registers and i'd imagine test2 should be faster (it certainly would be
 if written in c).

  - hal


I'd say that's because in the second case you also got to apply the (,), 
besides the (+)/(-) constructor during the transversing...
Am I right?

(if you had no mentioned it though, I'd probably also expect the 2nd one to 
be faster...)
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



socket question

2002-02-08 Thread Hal Daume III

suppose i want to write a stupid ftp client, i want to connect to the ftp
server, wait for it to give it's intro stuff (welcome to blah,
username: ) and then it wants input.  how do i do something like this?

so far, i have (don't laugh, this is the first socket haskell program i've
written.  ever.)

 connect cfg = withSocketsDo $ 
 do h - connectTo (remoteAddr cfg) (Service (remoteType cfg))
hWaitForInput h 1000
s - readWhileAvailable h
return s

 readWhileAvailable h =
 do b - hReady h
if b
then do c - hGetChar h
s - readWhileAvailable h
return (c : s)
else do return []

but this doesn't seem to ever halt :)

if i get rid of the hWaitForInput, it returns immediately with nothing.

if i replace hWaitForInput...readWhileAvailable with s - getContents h
; return (take 10 s) i get the beginning of the intro message (so it is
connecting properly).

please someone help me :)


--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: efficiency question

2002-02-08 Thread Jorge Adriano


 I'd say that's because in the second case you also got to apply the (,),
 besides the (+)/(-) constructor during the transversing...
 Am I right?

opss... I meant to write: the (,) constructor besides the (+)/(-)...
J.A.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: String manipulation.

2002-02-08 Thread Ketil Z. Malde

DK [EMAIL PROTECTED] writes:

 What I would like to ask, is how can I take a string from a list, and
 manipulate it, in order to convert it to an integer.

That's very simple, and I'm of course happy to help out with homework
questions.  (That's what mailinglists are for, after all.)  So, how
about: 

 convert :: String - Integer
 convert _ = 0

(This converts all strings to the integer zero.)

HTH, HAND. :-)

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Jan Skibinski's lhs modules ?

2002-02-08 Thread Wilhelm B. Kloke

As the site www.numeric-quest.com does not respond to my queries, I would
like to ask the community, where I can find a collection of the modules
QuantumVector.lhs etc.
?
-- 
Dipl.-Math. Wilhelm Bernhard Kloke
Institut fuer Arbeitsphysiologie an der Universitaet Dortmund
Ardeystrasse 67, D-44139 Dortmund, Tel. 0231-1084-257
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Specifying Kinds of Types

2002-02-08 Thread Ashley Yakeley

I'd like to be able to declare the kinds of new types and synonyms, 
because sometimes Haskell can't infer them. For instance:

data CMap0 p q = MkCMap0;

Without evidence, Haskell assumes that p and q have kind '*' (as per sec. 
4.6), and therefore CMap0 has kind '* - * - *'. Actually, I wanted p 
and q to both have kind '* - *', giving CMap0 kind '(* - *) - (* - *) 
- *'.

Here's another example:

type Composer c = forall x y z. (c y z) - (c x y) - (c x z);

Haskell gives x, y and z all the kind '*'. But I wanted them to have kind 
'* - *', giving c the kind '(* - *) - (* - *) - *' and Composer the 
kind '(* - *) - (* - *) - * - *'.

It's not currently possible to specify kinds, is it? Actually I think 
polymorphic kinds would be nice, but I can't say I desperately need them. 
I'd just like to be able to specify kinds somehow. For instance:

data CMap0 (p ::: * - *) (q ::: * - *) = MkCMap0;

...or perhaps

data ({* - *} p,{* - *} q) = CMap0 p q = MkCMap0;

...or whatever.


-- 
Ashley Yakeley, Seattle WA

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Specifying Kinds of Types

2002-02-08 Thread Koen Claessen

Ashley Yakeley wondered:

 | I'd like to be able to declare the kinds of new types
 | and synonyms, because sometimes Haskell can't infer
 | them. For instance:
 |
 | data CMap0 p q = MkCMap0;
 |
 | Actually, I wanted p and q to both have kind '* - *'.

The following workaround might be useful in this case:

  data CMap0 p q = MkCMap0
 | DummyConstructor (p Int) (q Int)

But that doesn't help with the following example:

 | type Composer c = forall x y z. (c y z) - (c x y) - (c x z);
 |
 | [..x..y..z..] But I wanted them to have kind '* - *'.

Here, you might do the following trick:

  type HasKind_Help x dummy = x
  type HasKind_Star_To_Star x   = HasKind_Help x (x Int)

  type C c x y = c (HasKind_Star_To_Star x)
   (HasKind_Star_To_Star y)

  type Composer c =
forall x y z . C c y z - C c x y - C c x z

(not tested!) There might be an easier workaround, too, but
you get the idea.

/Koen.

--
Koen Claessen
http://www.cs.chalmers.se/~koen
Chalmers University, Gothenburg, Sweden.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Specifying Kinds of Types

2002-02-08 Thread Lennart Augustsson

 data CMap0 (p ::: * - *) (q ::: * - *) = MkCMap0;
Or
data (CMap0 :: (* - *) - (* - *) - *) = MkCMap0

-- Lennart
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Specifying Kinds of Types

2002-02-08 Thread Rijk J . C . van Haaften

Ashley Yakeley wrote:
I'd like to be able to declare the kinds of new types and synonyms,
because sometimes Haskell can't infer them. For instance:

 data CMap0 p q = MkCMap0;

Without evidence, Haskell assumes that p and q have kind '*' (as per sec.
4.6), and therefore CMap0 has kind '* - * - *'. Actually, I wanted p
and q to both have kind '* - *', giving CMap0 kind '(* - *) - (* - *)
- *'.
...
It's not currently possible to specify kinds, is it?

It is possible using a trick due to John Hughes. In
 Proceedings of the 1999 Haskell Workshop,
he wrote in his article
 Restricted Data Types in Haskell
this note:

  3 There is one unpleasant hack in the figure: The constructor Unused 
in the
 data type definition for Set. It is there purely in order to force the 
compiler
 to assign the parameter cxt the correct kind: without it, cxt does not 
appear
 at all in the right hand side of the definition, and is therefore 
assigned the
 (incorrect) kind *. The application cxt a forces the correct kind * - 
* to be
 assigned, and embedding it in the type cxt a - () prevents the type 
of the
 context from interfering with the derivation of a Show instance.

The figure mentioned contains

 data Set cxt a = Set [a] | Unused (cxt a - ()) deriving Show

You can follow the example of John, writing

data CMap0 p q = MkCMap0 | Unused (p a - ()) (q a - ());

(I think I'm correctly applying the trick, but other
Proceedings-readers will correct me if I'm wrong.)

As John writes, this is a hack, but we have no
other choice.

Rijk-Jan van Haaften

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Specifying Kinds of Types

2002-02-08 Thread Ross Paterson

On Fri, Feb 08, 2002 at 12:39:30PM +0100, Rijk J.C.van Haaften wrote:
 Ashley Yakeley wrote:
 I'd like to be able to declare the kinds of new types and synonyms,
 because sometimes Haskell can't infer them.
 
 It is possible using a trick due to John Hughes. In
 Proceedings of the 1999 Haskell Workshop,
 he wrote in his article
 Restricted Data Types in Haskell
 [...]
 
 data Set cxt a = Set [a] | Unused (cxt a - ()) deriving Show

Another kludge, that works with newtypes too, is

type Hint a b = a
newtype Set cxt a = Set (Hint [a] (cxt a)) deriving Show
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Specifying Kinds of Types

2002-02-08 Thread John Hughes

Ashley Yakeley wrote:

I'd like to be able to declare the kinds of new types and synonyms, 
because sometimes Haskell can't infer them. For instance:

data CMap0 p q = MkCMap0;

Without evidence, Haskell assumes that p and q have kind '*' (as per sec. 
4.6), and therefore CMap0 has kind '* - * - *'. Actually, I wanted p 
and q to both have kind '* - *', giving CMap0 kind '(* - *) - (* - *) 
- *'.

I'll second that! I've had to use the likes of

 data CMap0 p q = MkCMap0 | forall a. Unused (p (q a))

in the past, but this is ugly and doesn't work for type or newtype. And of
course, next time you have to call the constructor Unused2 or UnusedCMap0 or
whatever to avoid a name clash...

It's not currently possible to specify kinds, is it? Actually I think 
polymorphic kinds would be nice, but I can't say I desperately need them. 

The nicest thing about polymorphic kinds would be that we wouldn't NEED to
specify them: kind inference would produce the principal kind, and you can't
do better than that. I assume it will be a while before we start wanting
rank-2 polykindism!

Compilers already do kind inference, and presumably explicitly set
uninstantiated kind variables to * at some stage. Maybe generalising them
instead would be a simple modification and language extension that would solve
this kind of problem.

John Hughes
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: Specifying Kinds of Types

2002-02-08 Thread Simon Peyton-Jones

Yes.  GHC already does this in interface files, and
it'd be rather easy to make it do so in source programs too.

It seems like the Right Thing to do. I'll do it.

(John suggests going to kind polymorphism, but that would
raise a bunch of new issues in GHC's impls so I won't do that.
Yet.)

Simon

| -Original Message-
| From: Ashley Yakeley [mailto:[EMAIL PROTECTED]] 
| Sent: 08 February 2002 11:26
| To: Haskell List
| Subject: Specifying Kinds of Types
| 
| 
| I'd like to be able to declare the kinds of new types and synonyms, 
| because sometimes Haskell can't infer them. For instance:
| 
| data CMap0 p q = MkCMap0;
| 
| Without evidence, Haskell assumes that p and q have kind '*' 
| (as per sec. 
| 4.6), and therefore CMap0 has kind '* - * - *'. Actually, I 
| wanted p 
| and q to both have kind '* - *', giving CMap0 kind '(* - *) 
| - (* - *) 
| - *'.
| 
| Here's another example:
| 
| type Composer c = forall x y z. (c y z) - (c x y) - (c x z);
| 
| Haskell gives x, y and z all the kind '*'. But I wanted them 
| to have kind 
| '* - *', giving c the kind '(* - *) - (* - *) - *' and 
| Composer the 
| kind '(* - *) - (* - *) - * - *'.
| 
| It's not currently possible to specify kinds, is it? Actually I think 
| polymorphic kinds would be nice, but I can't say I 
| desperately need them. 
| I'd just like to be able to specify kinds somehow. For instance:
| 
| data CMap0 (p ::: * - *) (q ::: * - *) = MkCMap0;
| 
| ...or perhaps
| 
| data ({* - *} p,{* - *} q) = CMap0 p q = MkCMap0;
| 
| ...or whatever.
| 
| 
| -- 
| Ashley Yakeley, Seattle WA
| 
| ___
| Haskell mailing list
| [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
| 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: ANNOUNCE: GHC 5.03.20020204 snapshot release

2002-02-08 Thread Sigbjorn Finne

A Windows Installer for this snapshot is now available via
the GHC downloads page,

http://haskell.org/ghc/download_ghc_snapshot.html

enjoy
--sof

- Original Message - 
From: Julian Seward (Intl Vendor) [EMAIL PROTECTED]
To: [EMAIL PROTECTED]; [EMAIL PROTECTED]
Sent: Tuesday, February 05, 2002 06:36
Subject: ANNOUNCE: GHC 5.03.20020204 snapshot release


 
 There have been a number of significant improvements made to GHC 
 since the 5.02 sources were branched off the main GHC development 
 tree, but we're not quite ready to make a full 5.04 release yet.  
 However, we're keen to get feedback on the new features from people
 that don't have easy access to CVS or don't have the time  patience
 to build GHC from scratch, so we're making a snapshot release of the
 current GHC, in source and binary form.
 
 There are NO GUARANTEES as to the stability of this release, although
 we do know it has passed our basic three-stage bootstrap test and run
 the regression tests successfully.  In some cases the documentation
 hasn't been fully updated to reflect the new features yet.
 
 Briefly, the changes relative to 5.02.2 are:
 
- The type system now supports arbitrary rank polymorphism,
  given appropriate type annotations.
 
- Heap profiling has had a major overhaul and now supports
  retainer profiling and biographical profiling ala nhc98.
 
- Major improvements to the native code generators. You can now 
  compile any and all code through them, including the Prelude. 
 
- The FFI syntax has been updated to match the latest version
  of the FFI Haskell 98 Addendum.
 
- newtypes support deriving *any* class for which the
  underlying type is also an instance.
 
- Linear implicit parameters: a highly experimental feature.
 
- GHCi has several new commands: 
 - ':show bindings' to list the bindings made on the command
   line,
 - ':show modules' to show which modules are loaded,
 - ':module' has been enhanced as per the discussion on the
  mailing list (syntax is still experimental - feedback
welcome).
 - ':browse'  similar to Hugs' :browse command.
 
 And many other minor changes  bugfixes.
 
 At the moment there is just the sources and a binary build for 
 x86-linux available.  We may add builds for other if they become 
 available.
 
 You can get it from
 http://haskell.cs.yale.edu/ghc/download_ghc_snapshot.html
 
 Enjoy!
 
 The GHC Development Team.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



[Newbie] Programming with MArray

2002-02-08 Thread José Romildo Malaquias

Hello.

To learn how to program with muttable arrays in Haskell, I have done
a very simple program to sum two arrays. I am submitting it to this
group so that it can be reviewd and commented. I have not find
examples on how to program with muttable arrays.

I would like for instance to see comments on the way the
iteration over the array indices was done: using a list
of indices. I looked for a way of incrementting an
index, starting from the lower bound towards the upper
bound, but failed in finding it. Is there other ways of
iterating over the muttable array other then using
its list of indices?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]


module Main where

import MArray
import ST

addArray :: (Ix ix, Num a) =
STArray s ix a - STArray s ix a - STArray s ix a - ST s ()

addArray v1 v2 v3
| b1 == b2  b1 == b3 = mapM_ update (indices v1)
| otherwise= error Bounds mismatch in addArray
where
b1 = bounds v1
b2 = bounds v2
b3 = bounds v3
update i = do x1 - readArray v1 i
  x2 - readArray v2 i
  writeArray v3 i (x1 + x2)

testAddArray = do v1 - newListArray (1,10) [0..10]
  v2 - newListArray (1,10) [1..10]
  v3 - newArray_ (1,10)
  addArray v1 v2 v3
  getElems v3

main = do xs - stToIO testAddArray
  print xs



efficiency question

2002-02-08 Thread Hal Daume III

define

test1 l = 
let s1 = foldr (+) 1 l
s2 = foldr (-) 1 l
in  (s1, s2)

test2 l =
let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
in  s

why is test1 so much faster than test2 for long lists l (eg
[1..100])?  replacing foldr with foldl makes it faster (of course),
but test2 is still much slower.

i *expected* test2 to be much faster because you're only traversing the
list once.  presumably the two elements a and b in test2 could be put
in registers and i'd imagine test2 should be faster (it certainly would be
if written in c).

 - hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: efficiency question

2002-02-08 Thread Jorge Adriano

On Friday 08 February 2002 22:14, you wrote:
 define

 test1 l =
 let s1 = foldr (+) 1 l
 s2 = foldr (-) 1 l
 in  (s1, s2)

 test2 l =
 let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
 in  s

 why is test1 so much faster than test2 for long lists l (eg
 [1..100])?  replacing foldr with foldl makes it faster (of course),
 but test2 is still much slower.

 i *expected* test2 to be much faster because you're only traversing the
 list once.  presumably the two elements a and b in test2 could be put
 in registers and i'd imagine test2 should be faster (it certainly would be
 if written in c).

I'd say that's because in the second case you also got to apply the (,), 
besides the (+)/(-) constructor during the transversing...
Am I right?

J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: efficiency question

2002-02-08 Thread Konst Sushenko

 
 On Friday 08 February 2002 22:14, you wrote:
  define
 
  test1 l =
  let s1 = foldr (+) 1 l
  s2 = foldr (-) 1 l
  in  (s1, s2)
 
  test2 l =
  let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
  in  s
 
  why is test1 so much faster than test2 for long lists l (eg
  [1..100])?  replacing foldr with foldl makes it faster 
 (of course),
  but test2 is still much slower.
 
  i *expected* test2 to be much faster because you're only 
 traversing the
  list once.  presumably the two elements a and b in 
 test2 could be put
  in registers and i'd imagine test2 should be faster (it 
 certainly would be
  if written in c).
 
 I'd say that's because in the second case you also got to 
 apply the (,), 
 besides the (+)/(-) constructor during the transversing...
 Am I right?
 
 J.A.

My guess is that it is due to the laziness of the addition/subtraction
in (,)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: efficiency question

2002-02-08 Thread Hal Daume III

I've tried using a strict fold:

foldl' f a [] = a
foldl' f a (x:xs) = (foldl' f $! f a x) xs

but that has no effect (or minimal effect).

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 8 Feb 2002, Konst Sushenko wrote:

  
  On Friday 08 February 2002 22:14, you wrote:
   define
  
   test1 l =
   let s1 = foldr (+) 1 l
   s2 = foldr (-) 1 l
   in  (s1, s2)
  
   test2 l =
   let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
   in  s
  
   why is test1 so much faster than test2 for long lists l (eg
   [1..100])?  replacing foldr with foldl makes it faster 
  (of course),
   but test2 is still much slower.
  
   i *expected* test2 to be much faster because you're only 
  traversing the
   list once.  presumably the two elements a and b in 
  test2 could be put
   in registers and i'd imagine test2 should be faster (it 
  certainly would be
   if written in c).
  
  I'd say that's because in the second case you also got to 
  apply the (,), 
  besides the (+)/(-) constructor during the transversing...
  Am I right?
  
  J.A.
 
 My guess is that it is due to the laziness of the addition/subtraction
 in (,)
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: efficiency question

2002-02-08 Thread Hal Daume III

This doesn't seem to make a difference, eithr (I just tried it).

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 8 Feb 2002, Konst Sushenko wrote:

 Did you try strict +/-? In (,). I am just curious.
 
  -Original Message-
  From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
  Sent: Friday, February 08, 2002 3:53 PM
  To: Konst Sushenko
  Cc: Jorge Adriano; [EMAIL PROTECTED]
  Subject: RE: efficiency question
  
  
  I've tried using a strict fold:
  
  foldl' f a [] = a
  foldl' f a (x:xs) = (foldl' f $! f a x) xs
  
  but that has no effect (or minimal effect).
  
  --
  Hal Daume III
  
   Computer science is no more about computers| [EMAIL PROTECTED]
than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
  
  On Fri, 8 Feb 2002, Konst Sushenko wrote:
  

On Friday 08 February 2002 22:14, you wrote:
 define

 test1 l =
 let s1 = foldr (+) 1 l
 s2 = foldr (-) 1 l
 in  (s1, s2)

 test2 l =
 let s = foldr (\x (a,b) - (x+a,x-b)) (1,1) l
 in  s

 why is test1 so much faster than test2 for long lists l (eg
 [1..100])?  replacing foldr with foldl makes it faster 
(of course),
 but test2 is still much slower.

 i *expected* test2 to be much faster because you're only 
traversing the
 list once.  presumably the two elements a and b in 
test2 could be put
 in registers and i'd imagine test2 should be faster (it 
certainly would be
 if written in c).

I'd say that's because in the second case you also got to 
apply the (,), 
besides the (+)/(-) constructor during the transversing...
Am I right?

J.A.
   
   My guess is that it is due to the laziness of the 
  addition/subtraction
   in (,)
   ___
   Haskell mailing list
   [EMAIL PROTECTED]
   http://www.haskell.org/mailman/listinfo/haskell
   
  
  
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: efficiency question

2002-02-08 Thread Jorge Adriano

On Friday 08 February 2002 23:52, Hal Daume III wrote:
 I've tried using a strict fold:

 foldl' f a [] = a
 foldl' f a (x:xs) = (foldl' f $! f a x) xs

 but that has no effect (or minimal effect).

That wouldn't work even if if laziness is the problem because that would only 
cause the elements of the list to be evaluated to head normal form, the 
elements of the pair would not be evaluated so you'd have a 'suspension of  
(minus and plus) operations'.

instead of 
 (\x (a,b) - (x+a,x-b))
try 
 (\x (a,b) - (((,) $! x-a)$! x-b) )

I just noticed that you were the one who sent me the DeepSeq module.
This is the kind of place where I want to use it.
Instead of $!, try $!!.


And Konst Sushenko wrote:
My guess is that it is due to the laziness of the addition/subtraction
in (,)

Seems to me like lazyness is not the right guess because both functions Hall 
first posted were lazy. So I think it's just the overhead of applying (,) 
besides (+) and (-) in each step. Do I make sense or am I missing something?

J.A.

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: efficiency question

2002-02-08 Thread Hal Daume III

I agree that it's the overhead of (,), but I don't see why there would be
any overhead for doing this.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Sat, 9 Feb 2002, Jorge Adriano wrote:

 On Friday 08 February 2002 23:52, Hal Daume III wrote:
  I've tried using a strict fold:
 
  foldl' f a [] = a
  foldl' f a (x:xs) = (foldl' f $! f a x) xs
 
  but that has no effect (or minimal effect).
 
 That wouldn't work even if if laziness is the problem because that would only 
 cause the elements of the list to be evaluated to head normal form, the 
 elements of the pair would not be evaluated so you'd have a 'suspension of  
 (minus and plus) operations'.
 
 instead of 
  (\x (a,b) - (x+a,x-b))
 try 
  (\x (a,b) - (((,) $! x-a)$! x-b) )
 
 I just noticed that you were the one who sent me the DeepSeq module.
 This is the kind of place where I want to use it.
 Instead of $!, try $!!.
 
 
 And Konst Sushenko wrote:
 My guess is that it is due to the laziness of the addition/subtraction
 in (,)
 
 Seems to me like lazyness is not the right guess because both functions Hall 
 first posted were lazy. So I think it's just the overhead of applying (,) 
 besides (+) and (-) in each step. Do I make sense or am I missing something?
 
 J.A.
 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Kinds Workaround

2002-02-08 Thread Ashley Yakeley

At 2002-02-08 03:36, Koen Claessen wrote:

Here, you might do the following trick:

  type HasKind_Help x dummy = x
  type HasKind_Star_To_Star x   = HasKind_Help x (x Int)

  type C c x y = c (HasKind_Star_To_Star x)
   (HasKind_Star_To_Star y)

  type Composer c =
forall x y z . C c y z - C c x y - C c x z

Yuck... I discovered a much simpler workaround, a class which has a 
parameter of kind '*':

class T a where
{
undef :: a; -- force kind '*'
};

instance T a where -- true for all types
{
undef = undefined;
};

data (T (p Bool),T (q Bool)) = CMap0 p q = MkCMap0;

type Composer c = forall x y z. (T (x Bool)) = (c y z) - (c x y) - 
(c x z);

Neat, huh? Finally, a reason for allowing contexts in data type 
declarations!


-- 
Ashley Yakeley, Seattle WA

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Re: XSLT, Perl, Haskell, a word on language design

2002-02-08 Thread Eray Ozkural (exa)

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On Tuesday 05 February 2002 12:29, Dimitre Novatchev wrote:
  So, there are actually people who seriously take XSLT to be a
  programming language? Interesting, as I think it is just overdoing an
 
  already overdone
  concept (hint: it's a poor ascii tree).

 Yes, there are such people. Actually, all the examples from John
 Hughes' article Why functional programming matters can be implemented
 in XSLT 1.0, as shown in the recently published article:

 The Functional Programming Language XSLT at
 http://www.topxml.com/xsl/articles/fp


It's nice to know about the computational power and expressive capabilities 
of a formal system ;) On the other hand, the examples in the article did not 
strike me as programs written in a programming language. They seemed to me 
more like an inefficient way of describing some programs. It is of course a 
proof of concept type of argument in the paper I assume.

I think I can implement some functional concepts using templates in C++, but 
would that pass as a functional programming language?

Besides, I thought two of the primary design goals for a programming language 
were readability and writability. In my opinion, XSLT lacks at least those 
two due to its XML syntax.

Keep functional,

- -- 
Eray Ozkural (exa) [EMAIL PROTECTED]
Comp. Sci. Dept., Bilkent University, Ankara
www: http://www.cs.bilkent.edu.tr/~erayo
GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 7C07 AE16 874D 539C
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: For info see http://www.gnupg.org

iD8DBQE8ZJ7qfAeuFodNU5wRAktzAJ0ZNpZlYwGDzquUHbWM6o9DHyBiHwCcDkAu
aLAIs00zoLi3GELLC7iuixk=
=MMI0
-END PGP SIGNATURE-
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Simpler Fibonacci function

2002-02-08 Thread Eray Ozkural (exa)

-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On Tuesday 05 February 2002 21:08, Paul Hudak wrote:

 Well, I cannot speak for the other references, since I did not write
 them :-).  On the other hand, stream processing *is* a stylistic way to
 write certain kinds of functional programs, with the idea of replacing
 an iteration with a stream.  But I agree that this particular example
 should not be the equivalent of hello world.  (Of course, for that,
 one would just write:


A stream is still an iteration. I think fibonacci (series) function is best 
represented as a recursive function, and if you want to show that functional 
languages look a bit like mathematics then that is how it should have been 
demonstrated. All that juggling in the original version Brian complained 
about may have arisen from efficiency considerations (was it the case?), 
however such considerations do not have any pedagogic use. [*]
 
And as I had pointed out before, that tutorial is not at all the brightest 
piece of introductory documentation when you compare it to certain printed 
texts for Haskell programming language. (In any case, the ocaml tutorial 
seems to me better designed than haskell's 'gentle' introduction.) Brian 
would probably be much more comfortable with a decent book

Thanks,

[*] If I had to teach someone the horrible C language, I would not start with 
goto statement that might make a performance difference in certain codes. 
(And goto is used in C codes when it will be efficient)

- -- 
Eray Ozkural (exa) [EMAIL PROTECTED]
Comp. Sci. Dept., Bilkent University, Ankara
www: http://www.cs.bilkent.edu.tr/~erayo
GPG public key fingerprint: 360C 852F 88B0 A745 F31B  EA0F 7C07 AE16 874D 539C
-BEGIN PGP SIGNATURE-
Version: GnuPG v1.0.6 (GNU/Linux)
Comment: For info see http://www.gnupg.org

iD8DBQE8ZJ71fAeuFodNU5wRAm14AKCABDvMa3CQNSIo3pHEWNzTR7MLqgCbBrqk
UPlVeY4HBspBPXW3PJ1LqMc=
=Y7DF
-END PGP SIGNATURE-
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: character syntax

2002-02-08 Thread Simon Marlow


 itz All this taken together, I mean, _really_, is the lexical
 itz structure of Haskell a botch, or what?
 
 Jon No. Innovative. All the problems described in this thread reflect
 Jon unwarranted assumptions inherited in emacs. It's plainly possible
 Jon to parse Haskell, and not hard either.
 
 First, parsing of a complete program (eg. by a compiler) is quite
 different from parsing a buffer that is being edited by a human.  The
 latter is hard, even for fairly well-specified languages.
 Irregularities only make it harder.

For syntax highlighting you only need to lexically analyse the buffer, not parse it.  
Haskell's lexical syntax is parseable by regular expressions, which means it shouldn't 
be hard to plug a syntax highlighter for Haskell into just about any editor.

I don't understand why you say that parsing a buffer being edited by a human is hard - 
perhaps doing incremental lexing is slightly harder than whole-file lexing, but not 
that much harder.  The state of a Haskell lexer can be represented with a little 
trickery by an integer, so it isn't hard to cache the lexer's state at the beginning 
of each line.  I did this once as an experiment when I added Haskell syntax 
highlighting to one of the KDE editors (I forget which).

The problem is not Haskell, it's emacs.  Emacs's syntax highlighting has fairly 
deeply-wired-in assumptions about C-like languages (eg. last I looked you still 
couldn't support nested comments properly in font-lock).

Cheers,
Simon
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: character syntax

2002-02-08 Thread Jorge Adriano

On Friday 08 February 2002 14:35, Ketil Z. Malde wrote:
 Jorge Adriano [EMAIL PROTECTED] writes:
  Haskell looks nice... Isabell looks beautiful :-)

 I'm not familiar with Isabell, but aren't we comparing apples and
 oranges here?  E.g. you can prettify .lhs pretty nicely with one of
 the LaTeX packages available.

Well yes :-)
You said Personally, I think the Haskell syntax is beautiful, and in my 
answer I talked about the way it looked on Xemacs, not the syntax. 
But not sure if we are talking about the same thing here, how do you prettify 
the .lhs files? Are you talking about the dvi you get in the end or the way 
it looks while editing the code? 

  And no, I don't have the time to do something
  better myself now, so I'll just stick to it :-)

 If somebody would come up with a mode that used lambdas and arrows to
 render things nicely in my editor, I wouldn't mind.  But I don't think
 the benefit for me would be great enough to justify the effort (I'm
 not much of a lisp hacker).

I wouldn't mind either. Everything looks really nice, making your code really 
easy to read, it's not just the greek leters, the 'forall's, the arrows '=', 
the 'and's and the 'or's.
But the Isabell/Isar/Proof General (which I haven't used in a long time) mode 
had more to it than just that. The menus were pretty good, buttons (with 
icons) for some commands... it turns Xemacs into a very nice GUI for isabelle.

J.A.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: efficiency question

2002-02-08 Thread Jorge Adriano

 I'd say that's because in the second case you also got to apply the (,),
 besides the (+)/(-) constructor during the transversing...
 Am I right?

opss... I meant to write: the (,) constructor besides the (+)/(-)...
J.A.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



RE: efficiency question

2002-02-08 Thread Konst Sushenko

(moved to haskell-café)

I ran Hal's code on my computer, and with test2 I get a stack overflow (so I had to 
use +RTS option for it to finish). test1 does not overflow stack (of standard size, I 
mean without +RTS). Which implies that test2 uses more stack space than test1. why 
would it use more stack if not because of laziness?

konst

 -Original Message-
 From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
 Sent: Friday, February 08, 2002 4:35 PM
 To: Jorge Adriano
 Cc: Konst Sushenko; [EMAIL PROTECTED]
 Subject: Re: efficiency question
 
 
 I agree that it's the overhead of (,), but I don't see why 
 there would be
 any overhead for doing this.
 
 --
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 
 On Sat, 9 Feb 2002, Jorge Adriano wrote:
 
  On Friday 08 February 2002 23:52, Hal Daume III wrote:
   I've tried using a strict fold:
  
   foldl' f a [] = a
   foldl' f a (x:xs) = (foldl' f $! f a x) xs
  
   but that has no effect (or minimal effect).
  
  That wouldn't work even if if laziness is the problem 
 because that would only 
  cause the elements of the list to be evaluated to head 
 normal form, the 
  elements of the pair would not be evaluated so you'd have a 
 'suspension of  
  (minus and plus) operations'.
  
  instead of 
   (\x (a,b) - (x+a,x-b))
  try 
   (\x (a,b) - (((,) $! x-a)$! x-b) )
  
  I just noticed that you were the one who sent me the DeepSeq module.
  This is the kind of place where I want to use it.
  Instead of $!, try $!!.
  
  
  And Konst Sushenko wrote:
  My guess is that it is due to the laziness of the 
 addition/subtraction
  in (,)
  
  Seems to me like lazyness is not the right guess because 
 both functions Hall 
  first posted were lazy. So I think it's just the overhead 
 of applying (,) 
  besides (+) and (-) in each step. Do I make sense or am I 
 missing something?
  
  J.A.
  
 
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe