From co19@cornell.edu Sun Mar 2 08:16:12 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Sun, 2 Mar 2003 10:16:12 +0200
Subject: modeling out of memory
Message-ID: <001201c2e094$00dc1480$25411bc2@mitajara>
This is a multi-part message in MIME format.
------=_NextPart_000_000A_01C2E0A4.C010F3B0
Content-Type: text/plain;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Greetings,
1) How does one model "out of memory" condition in Haskell, perhaps =
using a Maybe type?
2) Could you give an intutive description of data construction, and how =
it relates to lamda calculus?
Thanks
------=_NextPart_000_000A_01C2E0A4.C010F3B0
Content-Type: text/html;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Greetings,
1) How does one model "out of memory" =
condition in=20
Haskell, perhaps using a Maybe type?
2) Could you give an intutive =
description of data=20
construction, and how it relates to lamda calculus?
Thanks
------=_NextPart_000_000A_01C2E0A4.C010F3B0--
From co19@cornell.edu Sun Mar 2 08:18:13 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Sun, 2 Mar 2003 10:18:13 +0200
Subject: is identity the only polymorphic function without typeclasses?
Message-ID: <001601c2e094$48136f10$25411bc2@mitajara>
This is a multi-part message in MIME format.
------=_NextPart_000_0013_01C2E0A5.089EB680
Content-Type: text/plain;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Greetings,
Is identity function the only meaningful function one can write without =
constraining the type variable using a typeclass? If not, could you =
please give a counter-example?
Thanks
------=_NextPart_000_0013_01C2E0A5.089EB680
Content-Type: text/html;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Greetings,
Is identity function the only =
meaningful function=20
one can write without constraining the type variable using a typeclass? =
If not,=20
could you please give a counter-example?
Thanks
------=_NextPart_000_0013_01C2E0A5.089EB680--
From nick.name@inwind.it Sun Mar 2 12:52:25 2003
From: nick.name@inwind.it (Nick Name)
Date: Sun, 2 Mar 2003 13:52:25 +0100
Subject: modeling out of memory
In-Reply-To: <001201c2e094$00dc1480$25411bc2@mitajara>
References: <001201c2e094$00dc1480$25411bc2@mitajara>
Message-ID: <20030302135225.3f3d448c.nick.name@inwind.it>
On Sun, 2 Mar 2003 10:16:12 +0200
"Cagdas Ozgenc" wrote:
> Could you give an intutive description of data construction
In some form of typed lambda-calculus, you have the sum and product
types. An example is PCF; see for example:
http://citeseer.nj.nec.com/howard90operational.html
Vincenzo
From ajb@spamcop.net Sun Mar 2 23:33:47 2003
From: ajb@spamcop.net (Andrew J Bromage)
Date: Mon, 3 Mar 2003 10:33:47 +1100
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: <001601c2e094$48136f10$25411bc2@mitajara>
References: <001601c2e094$48136f10$25411bc2@mitajara>
Message-ID: <20030302233347.GA15697@smtp.alicorna.com>
G'day all.
On Sun, Mar 02, 2003 at 10:18:13AM +0200, Cagdas Ozgenc wrote:
> Is identity function the only meaningful function one can write
> without constraining the type variable using a typeclass? If not,
> could you please give a counter-example?
This might help:
@incollection{ wadler89theorems,
author = "Philip Wadler",
title = "Theorems for Free!",
booktitle = "Proceedings 4th Int.\ Conf.\ on Funct.\ Prog.\ Languages and Computer Arch., {FPCA}'89, London, {UK}, 11--13 Sept 1989",
publisher = "ACM Press",
address = "New York",
pages = "347--359",
year = "1989"
}
Cheers,
Andrew Bromage
From duncan@coutts.uklinux.net Sun Mar 2 23:54:24 2003
From: duncan@coutts.uklinux.net (Duncan Coutts)
Date: Sun, 2 Mar 2003 23:54:24 +0000
Subject: modeling out of memory
In-Reply-To: <001201c2e094$00dc1480$25411bc2@mitajara>
References: <001201c2e094$00dc1480$25411bc2@mitajara>
Message-ID: <20030302235424.2e41c39e.duncan@coutts.uklinux.net>
On Sun, 2 Mar 2003 10:16:12 +0200
"Cagdas Ozgenc" wrote:
> Greetings,
>
> 1) How does one model "out of memory" condition in Haskell, perhaps using a Maybe type?
Unfortuntely not since it would not be referentially transparent. It's
part of a more general issue of exceptions in pure code.
You can't have
calculateSomething :: X -> Maybe Y
Such that it returns Nothing if it ran out of memory.
You can do it in the IO monad, which is the standard technique:
doCalculateSomething :: X -> IO (Maybe Y)
doCalculateSomething x =
catchJust asyncExceptions
(evaluate $ Just $ calculateSomething x)
handleOOM
where
handleOOM StackOverflow = return Nothing --return nothing if out of memory
handleOOM HeapOverflow = return Nothing
handleOOM otherException = ioError otherException
Probably the thing to do is just catch the exceptions rather than have
your functions return Maybe types. That way you don't have to deal with
Maybes all over the place.
See the paper on asynchronous exceptions which mentions treating out of
memory conditions as an asynchronous exception:
http://research.microsoft.com/Users/simonpj/Papers/asynch-exns.htm
BTW HeapOverflow doesn't actually work yet according to the ghc
documentation.
Duncan
From jcast@ou.edu Mon Mar 3 03:37:50 2003
From: jcast@ou.edu (Jon Cast)
Date: Sun, 02 Mar 2003 21:37:50 -0600
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: Message from Cagdas Ozgenc of
"Sun, 02 Mar 2003 10:18:13 +0200."
<001601c2e094$48136f10$25411bc2@mitajara>
References: <001601c2e094$48136f10$25411bc2@mitajara>
Message-ID: <20030303033750.C18FF4A5ED@jcomain>
Cagdas Ozgenc wrote:
> Greetings,
> Is identity function the only meaningful function one can write
> without constraining the type variable using a typeclass? If not,
> could you please give a counter-example?
Certainly you can write lots of ``meaningful function''s without type
classes: not, (&&), (||), as well as many more complicated functions at
more complicated types.
You can also write useful polymorphic functions without type classes, as
long as you specify at least one type. For example, you can write
polymorphic functions over/yielding lists, such as repeat, cycle, map
and its many relatives, foldr and its many relatives, take and its
relatives, takeWhile and its relatives, etc. Similar functions often
exist for other types.
I'm somewhat curious, though: why do you ask this question? How do you
expand your question that makes the answer seem to be ``no''?
> Thanks
Jon Cast
From co19@cornell.edu Mon Mar 3 09:00:36 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Mon, 3 Mar 2003 11:00:36 +0200
Subject: is identity the only polymorphic function without typeclasses?
References: <001601c2e094$48136f10$25411bc2@mitajara>
<20030303033750.C18FF4A5ED@jcomain>
Message-ID: <009a01c2e163$669f6810$63968cc1@ozgenc>
> Cagdas Ozgenc wrote:
>
> > Greetings,
>
> > Is identity function the only meaningful function one can write
> > without constraining the type variable using a typeclass? If not,
> > could you please give a counter-example?
>
> Certainly you can write lots of ``meaningful function''s without type
> classes: not, (&&), (||), as well as many more complicated functions at
> more complicated types.
>
> You can also write useful polymorphic functions without type classes, as
> long as you specify at least one type. For example, you can write
> polymorphic functions over/yielding lists, such as repeat, cycle, map
> and its many relatives, foldr and its many relatives, take and its
> relatives, takeWhile and its relatives, etc. Similar functions often
> exist for other types.
>
> I'm somewhat curious, though: why do you ask this question? How do you
> expand your question that makes the answer seem to be ``no''?
I did not mean to include functions that take type constructors as
parameters (so lists are out of my discussion scope). I am only considering
functions that uses type variables that are not restricted by typeclasses.
In this setting could you give a few useful function signatures, and their
explanation? How does "not" work polymorphically for example?
From co19@cornell.edu Mon Mar 3 09:12:21 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Mon, 3 Mar 2003 11:12:21 +0200
Subject: modeling out of memory
References: <001201c2e094$00dc1480$25411bc2@mitajara>
<20030302235424.2e41c39e.duncan@coutts.uklinux.net>
Message-ID: <011601c2e165$0fa1be80$63968cc1@ozgenc>
> > Greetings,
> >
> > 1) How does one model "out of memory" condition in Haskell, perhaps
using a Maybe type?
>
> Unfortuntely not since it would not be referentially transparent. It's
> part of a more general issue of exceptions in pure code.
>
> You can't have
>
> calculateSomething :: X -> Maybe Y
>
> Such that it returns Nothing if it ran out of memory.
>
> Probably the thing to do is just catch the exceptions rather than have
> your functions return Maybe types. That way you don't have to deal with
> Maybes all over the place.
Does this make the use of Monads doubtful? I mean it doesn't seem easy to
have a completely pure language, and the time one starts introducing few
impurities one also starts thinking why not include many others?
Just a thought...
From bjpop@cs.mu.OZ.AU Mon Mar 3 09:31:33 2003
From: bjpop@cs.mu.OZ.AU (Bernard James POPE)
Date: Mon, 3 Mar 2003 20:31:33 +1100 (EST)
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: <009a01c2e163$669f6810$63968cc1@ozgenc> from Cagdas Ozgenc at
"Mar 3, 2003 11:00:36 am"
Message-ID: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
> I did not mean to include functions that take type constructors as
> parameters (so lists are out of my discussion scope). I am only considering
> functions that uses type variables that are not restricted by typeclasses.
There is const:
const :: a -> b -> a
const x _ = x
And of course a family of const like functions:
const' :: a -> b -> c -> a
const' x _ _ = x
and so on...
Of course const is related to id.
There is also undefined:
undefined :: a
undefined = undefined
You can extend this with arguments:
f :: a -> b
f x = undefined
or even:
f x = f x
and so on ...
Is this what you are looking for?
> In this setting could you give a few useful function signatures, and their
> explanation? How does "not" work polymorphically for example?
not isn't polymorphic in Haskell 98.
Cheers,
Bernie.
From bjpop@cs.mu.OZ.AU Mon Mar 3 09:41:15 2003
From: bjpop@cs.mu.OZ.AU (Bernard James POPE)
Date: Mon, 3 Mar 2003 20:41:15 +1100 (EST)
Subject: modeling out of memory
In-Reply-To: <011601c2e165$0fa1be80$63968cc1@ozgenc> from Cagdas Ozgenc at
"Mar 3, 2003 11:12:21 am"
Message-ID: <200303030941.UAA03285@mulga.cs.mu.OZ.AU>
> Does this make the use of Monads doubtful? I mean it doesn't seem easy to
> have a completely pure language, and the time one starts introducing few
> impurities one also starts thinking why not include many others?
I suggest that you read this paper:
A semantics for imprecise exceptions, Peyton-Jones et al.
You can find a copy on the documentation page for GHC:
http://haskell.cs.yale.edu/ghc/
See also:
Tackling the Awkward Squad: monadic input/output, concurrency, exceptions,
and foreign-language calls in Haskell, Peyton-Jones.
You can find it here:
http://citeseer.nj.nec.com/peytonjones00tackling.html
Cheers,
Bernie.
From co19@cornell.edu Mon Mar 3 09:49:29 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Mon, 3 Mar 2003 11:49:29 +0200
Subject: is identity the only polymorphic function without typeclasses?
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
Message-ID: <01c701c2e16a$39cd6420$63968cc1@ozgenc>
> > I did not mean to include functions that take type constructors as
> > parameters (so lists are out of my discussion scope). I am only
considering
> > functions that uses type variables that are not restricted by
typeclasses.
>
> There is const:
>
> const :: a -> b -> a
> const x _ = x
>
> And of course a family of const like functions:
>
> const' :: a -> b -> c -> a
> const' x _ _ = x
>
> and so on...
>
> Of course const is related to id.
>
> There is also undefined:
>
> undefined :: a
> undefined = undefined
>
> You can extend this with arguments:
>
> f :: a -> b
> f x = undefined
>
> or even:
>
> f x = f x
>
> and so on ...
>
> Is this what you are looking for?
Yes, I thought about these too. Do you find these functions practically
useful? Can you give an example where I can utilize these functions?
Thanks for the response
From karczma@info.unicaen.fr Mon Mar 3 10:09:17 2003
From: karczma@info.unicaen.fr (Jerzy Karczmarczuk)
Date: Mon, 03 Mar 2003 11:09:17 +0100
Subject: is identity the only polymorphic function without typeclasses?
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
Message-ID: <3E6329CD.10309@info.unicaen.fr>
Cagdas Ozgenc quotes himself (and somebody else):
>>>Is identity function the only meaningful function one can write
>>>without constraining the type variable using a typeclass? If not,
>>>could you please give a counter-example?
>>Certainly you can write lots of ``meaningful function''s without type
>>classes: not, (&&), (||), as well as many more complicated functions at
>>more complicated types.
>>
>>You can also write useful polymorphic functions without type classes, as
>>long as you specify at least one type.
...
>>I'm somewhat curious, though: why do you ask this question? How do you
>>expand your question that makes the answer seem to be ``no''?
>
>
> I did not mean to include functions that take type constructors as
> parameters (so lists are out of my discussion scope). I am only considering
> functions that uses type variables that are not restricted by typeclasses.
> In this setting could you give a few useful function signatures, and their
> explanation? How does "not" work polymorphically for example?
Bernard James POPE proposes:
> There is const:
> const :: a -> b -> a
> const x _ = x
> And of course a family of const like functions:
> const' :: a -> b -> c -> a
> const' x _ _ = x
> and so on...
> There is also undefined:
> undefined :: a
> undefined = undefined
...
>
> Is this what you are looking for?
====
My three eurocents.
I believe that the Author of the original query won't care more about
undefined stuff than most of us. He wants truly polymorphic functions,
of the type, say, a->b->a etc., without constraints.
The answer exists, although it is not always trivial to find interesting
examples.
Imagine a (postulated) polymorphic type, say, (a->b)->(b->a) . Consider
the symbol (->) to be an implication in logic. Ask yourself; "is it
a tautology, valid for *any* objects of types "a" or "b"? If yes, then
this is a type, and you can in principle find a model for it.
Example: composition
type: (a->b)->(c->a) -> (c->b)
function: (.)
(.) f g x = f (g x)
On the other hand the "type" (a->b) is *NOT* a valid theorem. This is not
a type. You won't find any model of it. No, no, get out with your
f x = undefined.
The "subst" combinator: subst f g x = f x (g x) has the type
(a->b->c) -> (a->b) -> a -> c (unless I've produced some mistake)
You can sing the rest of this solemn song yourself, you know the basic tune.
Read Luca Cardelli papers, Wadler's "Theorems for free", etc.
Jerzy Karczmarczuk
From wolfgang@jeltsch.net Mon Mar 3 10:20:42 2003
From: wolfgang@jeltsch.net (Wolfgang Jeltsch)
Date: Mon, 3 Mar 2003 11:20:42 +0100
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: <009a01c2e163$669f6810$63968cc1@ozgenc>
References: <001601c2e094$48136f10$25411bc2@mitajara>
<20030303033750.C18FF4A5ED@jcomain>
<009a01c2e163$669f6810$63968cc1@ozgenc>
Message-ID: <200303031120.09199.wolfgang@jeltsch.net>
On Monday, 2003-03-03, 10:00, CET, Cagdas Ozgenc wrote:
> [...]
> I did not mean to include functions that take type constructors as
> parameters (so lists are out of my discussion scope). I am only conside=
ring
> functions that uses type variables that are not restricted by typeclass=
es.
> In this setting could you give a few useful function signatures, and th=
eir
> explanation?
In the prelude:
error :: String -> a
> [...]
Wolfgang
From co19@cornell.edu Mon Mar 3 11:01:31 2003
From: co19@cornell.edu (Cagdas Ozgenc)
Date: Mon, 3 Mar 2003 13:01:31 +0200
Subject: is identity the only polymorphic function without typeclasses?
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
<3E6329CD.10309@info.unicaen.fr>
Message-ID: <01fb01c2e174$4b3a8ee0$63968cc1@ozgenc>
> My three eurocents.
> I believe that the Author of the original query won't care more about
> undefined stuff than most of us. He wants truly polymorphic functions,
> of the type, say, a->b->a etc., without constraints.
>
> The answer exists, although it is not always trivial to find interesting
> examples.
>
> Imagine a (postulated) polymorphic type, say, (a->b)->(b->a) . Consider
> the symbol (->) to be an implication in logic. Ask yourself; "is it
> a tautology, valid for *any* objects of types "a" or "b"? If yes, then
> this is a type, and you can in principle find a model for it.
>
> Example: composition
>
> type: (a->b)->(c->a) -> (c->b)
> function: (.)
> (.) f g x = f (g x)
>
> On the other hand the "type" (a->b) is *NOT* a valid theorem. This is not
> a type. You won't find any model of it. No, no, get out with your
> f x = undefined.
>
> The "subst" combinator: subst f g x = f x (g x) has the type
>
> (a->b->c) -> (a->b) -> a -> c (unless I've produced some mistake)
The time you grouped (a->b->c), you utilized the arrow type constructor to
build a function type, it is no different that using a polymorphic list. I
think I am not happy with the dual semantics of this arrow thingie. I have
to ponder on this some more, I guess.
Thanks for the response. Greatly appreciated.
From droundy@abridgegame.org Mon Mar 3 13:10:57 2003
From: droundy@abridgegame.org (David Roundy)
Date: Mon, 3 Mar 2003 08:10:57 -0500
Subject: Network module problem
Message-ID: <20030303131057.GB22524@jdj5.mit.edu>
Hello. I'm running into a problem with the Network module, which I suspect
is pretty easy to fix, but am not sure how to best do so.
The problem is that "accept" fails when the reverse DNS fails, with the
following error:
Fail: does not exist
Action: getHostByAddr
Reason: no such host entry
I'm not sure how to get around this. I don't actually need the hostname of
the client, and would be happy to just substitute its IP address in that
field, but I'm not sure how to do that.
If I understand correctly (which I may not), if I were to catch this
connection with code like:
(myh,_,_) <- accept s `catch` ...
there would be no way to actually get the handle itself from the
connection, which seems to imply that I'll have to go into the
Network.Socket module and use the lower level code (which looks like it
would be straightforward). However, it seems that this is a simple enough
(and presumably common enough) problem that there should be a more elegant
solution which would allow me to use the high level interface.
Is there any way to `catch` the exception within getHostByAddr, and
substitute the IP address for the output of that function? (I'll admit,
I've never thoroughly understood exceptions in any language, in the sense
of understanding how really to use them right.)
Also, what if I just didn't care about the hostname? That seems like a
common enough case that you wouldn't always want to do a reverse DNS lookup
on every accept. Does that just mean you would have to use the low level
interface?
--
David Roundy
http://civet.berkeley.edu/droundy/
From ajb@spamcop.net Mon Mar 3 23:22:38 2003
From: ajb@spamcop.net (Andrew J Bromage)
Date: Tue, 4 Mar 2003 10:22:38 +1100
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: <01c701c2e16a$39cd6420$63968cc1@ozgenc>
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
<01c701c2e16a$39cd6420$63968cc1@ozgenc>
Message-ID: <20030303232238.GA29357@smtp.alicorna.com>
G'day.
On Mon, Mar 03, 2003 at 11:49:29AM +0200, Cagdas Ozgenc wrote:
> Yes, I thought about these too. Do you find these functions practically
> useful? Can you give an example where I can utilize these functions?
Functions like this are useful for plugging into higher-order functions
to tailor them for your specific needs.
Here's an artificial example:
length = sum . map (const 1)
Cheers,
Andrew Bromage
From dasulliv@cs.indiana.edu Tue Mar 4 00:26:55 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 19:26:55 -0500
Subject: speedup help
Message-ID: <20030304002655.GA24692@cownose.cs.indiana.edu>
So, I'm having to calculate 'n choose k' an awful lot. At the moment I've got
this:
comb :: Integer -> Integer -> Integer
comb m 0 = 1
comb m n = (numerator(toRational (fact m) / toRational (fact n * fact (m-n))))
where fact is a memoized factorial function. It's not perfectly memoized,
though; I use lists, since that's easier by default. They should be arrays,
and possibly just changing that would speed comb up a lot. (Comb is currently
40% of runtime, fact is 23%.) But I think it should be possible to speed up
comb itself, too.
comb is only called from here:
sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i <- [0 .. n-1] ]
Here was one try:
fcomb :: Integer -> Integer -> Integer
fcomb m 0 = 1
fcomb m n = res
where
res = last * (m-n+1) `div` n
last = res
except, obviously, this doesn't work. I hope it's clear what I'm trying to
do, or what I would be in a more imperative language -- in C I'd probably have
some static variable in fcomb. I figure monads are needed, but I've been
unable to figure them out enough to apply them here. Will the monadism
propagate all the way up and require changing lots of function types? Bleah.
I'm using ghc, can I sneak some mutable in here instead?
Any advice? Also on using arrays, where my parameters come off the command
line. I imagine in C++ I'd just precompute a bunch of tables and then just
use those values in the actual algorithm.
Thanks!
-xx- Damien X-)
(if you're curious, this is for a class, but not a class on using Haskell. I
chose to use Haskell for this assignment after ghc -O, to my surprise,
outperformed ocaml. I suspect GMP deserves the real credit, but hey.)
From hdaume@ISI.EDU Tue Mar 4 00:59:21 2003
From: hdaume@ISI.EDU (Hal Daume III)
Date: Mon, 3 Mar 2003 16:59:21 -0800 (PST)
Subject: speedup help
In-Reply-To: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID:
I think you would get a big speed-up if you got rid of all the rational
stuff and just used:
comb m n = fact m `div` (fact n * fact (m-n))
If that doesn't speed it up enouch, you can of course cache fact m in your
computation and do something like:
sumbn n = sum [ bournoulli i * fm `div` (fn * fact (m-n)) | i <- [0..n-1]]
where fm = fact m
fn = fact n
it is possible that the compiler is inlining the call the comb, in which
case this has already been done for you. hard to say for sure. putting
'{-# INLINE comb #-}' might help a lot.
>From there, you should probably look at arrays if you can bound n.
--
Hal Daume III | hdaume@isi.edu
"Arrest this man, he talks in maths." | www.isi.edu/~hdaume
On Mon, 3 Mar 2003, Damien R. Sullivan wrote:
> So, I'm having to calculate 'n choose k' an awful lot. At the moment I've got
> this:
>
> comb :: Integer -> Integer -> Integer
> comb m 0 = 1
> comb m n = (numerator(toRational (fact m) / toRational (fact n * fact (m-n))))
>
> where fact is a memoized factorial function. It's not perfectly memoized,
> though; I use lists, since that's easier by default. They should be arrays,
> and possibly just changing that would speed comb up a lot. (Comb is currently
> 40% of runtime, fact is 23%.) But I think it should be possible to speed up
> comb itself, too.
>
> comb is only called from here:
> sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i <- [0 .. n-1] ]
>
>
> Here was one try:
>
> fcomb :: Integer -> Integer -> Integer
> fcomb m 0 = 1
> fcomb m n = res
> where
> res = last * (m-n+1) `div` n
> last = res
>
> except, obviously, this doesn't work. I hope it's clear what I'm trying to
> do, or what I would be in a more imperative language -- in C I'd probably have
> some static variable in fcomb. I figure monads are needed, but I've been
> unable to figure them out enough to apply them here. Will the monadism
> propagate all the way up and require changing lots of function types? Bleah.
> I'm using ghc, can I sneak some mutable in here instead?
>
> Any advice? Also on using arrays, where my parameters come off the command
> line. I imagine in C++ I'd just precompute a bunch of tables and then just
> use those values in the actual algorithm.
>
> Thanks!
>
> -xx- Damien X-)
>
> (if you're curious, this is for a class, but not a class on using Haskell. I
> chose to use Haskell for this assignment after ghc -O, to my surprise,
> outperformed ocaml. I suspect GMP deserves the real credit, but hey.)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From A.Rock@cit.gu.edu.au Tue Mar 4 01:20:02 2003
From: A.Rock@cit.gu.edu.au (Andrew Rock)
Date: Tue, 4 Mar 2003 11:20:02 +1000
Subject: speedup help
In-Reply-To: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID: <6C78799E-4DDF-11D7-B440-00039369159A@cit.gu.edu.au>
On Tuesday, March 4, 2003, at 10:26 AM, Damien R. Sullivan wrote:
> So, I'm having to calculate 'n choose k' an awful lot. At the moment
> I've got
> this:
>
> comb :: Integer -> Integer -> Integer
> comb m 0 = 1
> comb m n = (numerator(toRational (fact m) / toRational (fact n * fact
> (m-n))))
>
> where fact is a memoized factorial function. It's not perfectly
> memoized,
> though; I use lists, since that's easier by default. They should be
> arrays,
> and possibly just changing that would speed comb up a lot. (Comb is
> currently
> 40% of runtime, fact is 23%.) But I think it should be possible to
> speed up
> comb itself, too.
>
> comb is only called from here:
> sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i <- [0 ..
> n-1] ]
>
>
> Here was one try:
>
> fcomb :: Integer -> Integer -> Integer
> fcomb m 0 = 1
> fcomb m n = res
> where
> res = last * (m-n+1) `div` n
> last = res
>
Try this:
comb :: Integral a => a -> a -> a
comb n r = c n 1 1
where
c n' r' p | r' > r = p
| otherwise = c (n' - 1) (r' + 1) (p * n' `div` r')
Cheers,
Rock.
--
Andrew Rock -- A.Rock@cit.gu.edu.au -- http://www.cit.gu.edu.au/~arock/
School of Computing and Information Technology
Griffith University -- Nathan, Brisbane, Queensland 4111, Australia
From ajb@spamcop.net Tue Mar 4 01:25:01 2003
From: ajb@spamcop.net (Andrew J Bromage)
Date: Tue, 4 Mar 2003 12:25:01 +1100
Subject: speedup help
In-Reply-To:
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID: <20030304012501.GA31100@smtp.alicorna.com>
G'day all.
On Mon, Mar 03, 2003 at 04:59:21PM -0800, Hal Daume III wrote:
> I think you would get a big speed-up if you got rid of all the rational
> stuff and just used:
>
> comb m n = fact m `div` (fact n * fact (m-n))
Or, even better, if you didn't multiply stuff that you're just going
to divide out in the first place.
choose :: (Integral a) => a -> a -> Integer
choose m n
| m < 0 = 0
| n < 0 || n > m = 0
| n > m `div` 2 = choose' n (m-n)
| otherwise = choose' (m-n) n
where
choose' i' j'
= let i = toInteger i'
j = toInteger j'
in productRange (i+1) j `div` factorial j
factorial :: (Integral a) => a -> Integer
factorial n = productRange 1 n
productRange :: (Integral a) => Integer -> a -> Integer
productRange b n
| n < 5
= case n of
0 -> 1
1 -> b
2 -> b*(b+1)
3 -> (b*(b+1))*(b+2)
4 -> (b*(b+3))*((b+1)*(b+2))
_ -> 0
| otherwise
= let n2 = n `div` 2
in productRange b n2 * productRange (b+toInteger n2) (n-n2)
Note that productRange uses a divide-and-conquer algorithm. The
reason for this is that it's more efficient to multiply similarly-sized
Integers than dissimilarly-sized Integers using GMP.
Cheers,
Andrew Bromage
From mlc67@columbia.edu Tue Mar 4 01:29:06 2003
From: mlc67@columbia.edu (mike castleman)
Date: Mon, 3 Mar 2003 20:29:06 -0500
Subject: speedup help
In-Reply-To: <20030304002655.GA24692@cownose.cs.indiana.edu>
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID: <20030304012906.GB29241@pinetree.mlcastle.net>
I have no idea if the following is faster or not (I suspect not), but
it is certainly easier to read:
n `choose` k = (n `permute` k) `div` (fact k)
n `permute` k = product [(n-k+1) .. n]
fact n = product [1 .. n]
mike
--
mike castleman / mlc67@columbia.edu / http://mlcastle.net
aolim: mlcastle / icq: 3520821 / yahoo: mlc000
"we have invented the technology to eliminate scarcity, but we are
deliberately throwing it away to be benefit those who profit from
scarcity....I think we should embrace the era of plenty, and work out
how to mutually live in it." -- john gilmore
From dasulliv@cs.indiana.edu Tue Mar 4 01:30:32 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 20:30:32 -0500
Subject: speedup help
In-Reply-To: <20030304012501.GA31100@smtp.alicorna.com>
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
<20030304012501.GA31100@smtp.alicorna.com>
Message-ID: <20030304013032.GA24901@cownose.cs.indiana.edu>
On Tue, Mar 04, 2003 at 12:25:01PM +1100, Andrew J Bromage wrote:
> Or, even better, if you didn't multiply stuff that you're just going
> to divide out in the first place.
I had thought of that before, and used a simple
comb m n = product [m, m-1 .. m-n+1] / fact (m-n)
but the unmemoized product proved to be slower than the original.
This looks rather different, though. :)
-xx- Damien X-)
From dasulliv@cs.indiana.edu Tue Mar 4 02:53:24 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 21:53:24 -0500
Subject: speedup help update
In-Reply-To:
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID: <20030304025324.GA25170@cownose.cs.indiana.edu>
On Mon, Mar 03, 2003 at 04:59:21PM -0800, Hal Daume III wrote:
> comb m n = fact m `div` (fact n * fact (m-n))
This was the biggest help, 33 seconds instead of my original 43. fact is the
big consumer now, and I think cries out for being arrayed, especially as it
gets used a lot elsewhere too.
> If that doesn't speed it up enouch, you can of course cache fact m in your
> computation and do something like:
>
> sumbn n = sum [ bournoulli i * fm `div` (fn * fact (m-n)) | i <- [0..n-1]]
> where fm = fact m
> fn = fact n
I'm not sure what this is doing. i has to be in the comb part.
> From there, you should probably look at arrays if you can bound n.
Bound at compile time or at some early point in run time? The program's
behavior is determined by command line arguments, and filling an array with n
factorials would be perfectly appropriate.
I'm sorry to report that the other suggestions didn't help much. Andrew
Rock's took 80 seconds. Andrew Bromage's did gain a slight improvement --
41 seconds instead of 43. If I replace the factorial in
in productRange (i+1) j `div` factorial j
with my own fact then it goes to 37 seconds. But that's still more time than
Hal's simple use of Integers.
Top 3 functions of the version with Hal's code are:
fact Main 28.5 0.0
comb Main 21.8 9.7
sumbn Main 10.7 16.4
Time to look at arrays, finally.
-xx- Damien X-)
From dasulliv@cs.indiana.edu Tue Mar 4 03:03:17 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 22:03:17 -0500
Subject: speedup help update
In-Reply-To: <20030304025324.GA25170@cownose.cs.indiana.edu>
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
<20030304025324.GA25170@cownose.cs.indiana.edu>
Message-ID: <20030304030317.GA25244@cownose.cs.indiana.edu>
I would like to say that programming this project (calculate the
Euler-Mascheroni constant to as many digits as possible in a minute) in
Haskell has been fairly pleasant overall. The startup time was a bit oogy
-- ocaml was faster to get a working program -- and ghc's compilation time
continues to aggravate me (10x slower than ocaml, or even slower with -O --
but then the code's faster), and I fear getting my code really efficient will
be a pain. But the code itself is nice and elegant and it was neat being able
to do sums on list comprehensions. My code tends to map pretty
straightforwardly to the math on paper, which is really nice for being assured
of correctness.
-xx- Damien X-)
From dasulliv@cs.indiana.edu Tue Mar 4 03:33:44 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 22:33:44 -0500
Subject: do let in
Message-ID: <20030304033344.GA25362@cownose.cs.indiana.edu>
main =
do
args <- System.getArgs
let (m, b) = (read (args!!0), read (args!!1))
let lim :: Int
lim = read (args!!2)
printstate = args!!3
time1 <- getClockTime
let n = 2^b
let afact = array (0,n) ((0,1):[(i,i*afact!(i-1)) | i<-[1..n]]) in
let (glo, ghi) = gamma_tup lim m b
time2 <- getClockTime
gives the Hugs error
ERROR "gamma3_7.hs":141 - Syntax error in expression (unexpected `;', possibly
due to bad layout)
I tried indenting the last two lines, or just the penulatimate line, but no
joy. I've modified my functions to use afact instead of fact, but I'm hoping
to have it exist as a global for them, rather than modifying all the function
signatures to pass afact down the chain.
Help, please?
-xx- Damien X-)
From ajb@spamcop.net Tue Mar 4 04:01:13 2003
From: ajb@spamcop.net (Andrew J Bromage)
Date: Tue, 4 Mar 2003 15:01:13 +1100
Subject: speedup help update
In-Reply-To: <20030304025324.GA25170@cownose.cs.indiana.edu>
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
<20030304025324.GA25170@cownose.cs.indiana.edu>
Message-ID: <20030304040113.GA32151@smtp.alicorna.com>
G'day all.
On Mon, Mar 03, 2003 at 09:53:24PM -0500, Damien R. Sullivan wrote:
> Time to look at arrays, finally.
This might help:
http://haskell.org/wiki/wiki?MemoisingCafs
Cheers,
Andrew Bromage
From hdaume@ISI.EDU Tue Mar 4 04:03:44 2003
From: hdaume@ISI.EDU (Hal Daume III)
Date: Mon, 3 Mar 2003 20:03:44 -0800 (PST)
Subject: do let in
In-Reply-To: <20030304033344.GA25362@cownose.cs.indiana.edu>
Message-ID:
in 'do' notation, 'let' doesn't take an in. so you want to get rid of the
'in' on the third to last line.
> main =
> do
> args <- System.getArgs
> let (m, b) = (read (args!!0), read (args!!1))
> let lim :: Int
> lim = read (args!!2)
> printstate = args!!3
> time1 <- getClockTime
> let n = 2^b
> let afact = array (0,n) ((0,1):[(i,i*afact!(i-1)) | i<-[1..n]]) in
> let (glo, ghi) = gamma_tup lim m b
> time2 <- getClockTime
>
> gives the Hugs error
> ERROR "gamma3_7.hs":141 - Syntax error in expression (unexpected `;', possibly
> due to bad layout)
>
> I tried indenting the last two lines, or just the penulatimate line, but no
> joy. I've modified my functions to use afact instead of fact, but I'm hoping
> to have it exist as a global for them, rather than modifying all the function
> signatures to pass afact down the chain.
>
> Help, please?
>
> -xx- Damien X-)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From dasulliv@cs.indiana.edu Tue Mar 4 04:05:41 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 23:05:41 -0500
Subject: do let in
In-Reply-To:
References: <20030304033344.GA25362@cownose.cs.indiana.edu>
Message-ID: <20030304040541.GB25505@cownose.cs.indiana.edu>
On Mon, Mar 03, 2003 at 08:03:44PM -0800, Hal Daume III wrote:
> in 'do' notation, 'let' doesn't take an in. so you want to get rid of the
> 'in' on the third to last line.
But then I get "undefined variable afact" when my functions try to refer to
it.
-xx- Damien X-)
From bjpop@cs.mu.OZ.AU Tue Mar 4 04:06:13 2003
From: bjpop@cs.mu.OZ.AU (Bernard James POPE)
Date: Tue, 4 Mar 2003 15:06:13 +1100 (EST)
Subject: do let in
In-Reply-To: <20030304033344.GA25362@cownose.cs.indiana.edu> from
"Damien R. Sullivan"
at
"Mar 3, 2003 10:33:44 pm"
Message-ID: <200303040406.PAA28390@mulga.cs.mu.OZ.AU>
Damien writes:
> main =
> do
> args <- System.getArgs
> let (m, b) = (read (args!!0), read (args!!1))
> let lim :: Int
> lim = read (args!!2)
> printstate = args!!3
> time1 <- getClockTime
> let n = 2^b
> let afact = array (0,n) ((0,1):[(i,i*afact!(i-1)) | i<-[1..n]]) in
> let (glo, ghi) = gamma_tup lim m b
> time2 <- getClockTime
>
> gives the Hugs error
> ERROR "gamma3_7.hs":141 - Syntax error in expression (unexpected `;', possibly
> due to bad layout)
>
> I tried indenting the last two lines, or just the penulatimate line, but no
> joy. I've modified my functions to use afact instead of fact, but I'm hoping
> to have it exist as a global for them, rather than modifying all the function
> signatures to pass afact down the chain.
>
> Help, please?
Did you supply all of the code for main, or did you chop it off at some point?
I'm not exactly sure what you want to do, but I'm guessing that you
want the variable afact to be in scope on the right-hand-side of
some other functions in your program (gamma_tup, for example).
For whatever reason you do not want to pass it explicitly as an argument?
Have a read your question properly? If not I'm sorry.
So perhaps you want to simulate a global variable.
John Hughes has written a nice paper for the Journal of FP that discusses
some design considerations for global variables in Haskell (+ extensions).
Perhaps you could have a quick read of it. You might find a suitable solution
in there.
The paper is called: Global Variables in Haskell. You can get a draft from
his web-site, http://www.math.chalmers.se/~rjmh/
Also while you are at it, you might want to read the rules for do-notation
syntax, this might help with your syntax problems.
Section 3.14 of the (revised) Haskell 98 Report:
http://research.microsoft.com/Users/simonpj/haskell98-revised/haskell98-report-html/index98.html
Cheers,
Bernie.
From dasulliv@cs.indiana.edu Tue Mar 4 04:14:26 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Mon, 3 Mar 2003 23:14:26 -0500
Subject: do let in
In-Reply-To: <200303040406.PAA28390@mulga.cs.mu.OZ.AU>
References: <20030304033344.GA25362@cownose.cs.indiana.edu>
<200303040406.PAA28390@mulga.cs.mu.OZ.AU>
Message-ID: <20030304041426.GA25575@cownose.cs.indiana.edu>
On Tue, Mar 04, 2003 at 03:06:13PM +1100, Bernard James POPE wrote:
> Damien writes:
> > main =
> > do
> > args <- System.getArgs
> > let (m, b) = (read (args!!0), read (args!!1))
> > let lim :: Int
> > lim = read (args!!2)
> > printstate = args!!3
> > time1 <- getClockTime
> > * let n = 2^b
> > * let afact = array (0,n) ((0,1):[(i,i*afact!(i-1)) | i<-[1..n]]) in
> > let (glo, ghi) = gamma_tup lim m b
> > time2 <- getClockTime
> >
> Did you supply all of the code for main, or did you chop it off at some point?
I did chop it off, but the only new lines were the ones I've marked with a *
in this e-mail, and the rest works.
> I'm not exactly sure what you want to do, but I'm guessing that you
> want the variable afact to be in scope on the right-hand-side of
> some other functions in your program (gamma_tup, for example).
Exactly.
> For whatever reason you do not want to pass it explicitly as an argument?
For the reason that I'm lazy and don't want to have to modify all my functions
which use afact, or call functions which use afact, and don't see why I should
have to -- they were able to call the 'fact' function as a global, and can
refer to a global 'afact' if I define it outside of main with a fixed value.
I don't see why having a global dependent on outside input should be so much
harder.
> So perhaps you want to simulate a global variable.
Yeah. And I've tried various permutations
let afact = ... in
let (glo, ...
let afact = ... in
(glo, ...
let afact = ... in
(glo, ...
let afact = ...
let (glo...
etc.
-xx- Damien X-)
From bjpop@cs.mu.OZ.AU Tue Mar 4 04:29:48 2003
From: bjpop@cs.mu.OZ.AU (Bernard James POPE)
Date: Tue, 4 Mar 2003 15:29:48 +1100 (EST)
Subject: do let in
In-Reply-To: <20030304041426.GA25575@cownose.cs.indiana.edu> from
"Damien R. Sullivan"
at
"Mar 3, 2003 11:14:26 pm"
Message-ID: <200303040429.PAA00579@mulga.cs.mu.OZ.AU>
Hi,
> For the reason that I'm lazy and don't want to have to modify all my functions
> which use afact, or call functions which use afact, and don't see why I should
> have to -- they were able to call the 'fact' function as a global, and can
> refer to a global 'afact' if I define it outside of main with a fixed value.
> I don't see why having a global dependent on outside input should be so much
> harder.
Of course afact depends on the value of n, which is only known in main.
So you need a way of passing n to afact, and you get the same problem as
before.
> > So perhaps you want to simulate a global variable.
>
> Yeah. And I've tried various permutations
>
> let afact = ... in
> let (glo, ...
>
> let afact = ... in
> (glo, ...
>
> let afact = ... in
> (glo, ...
>
> let afact = ...
> let (glo...
None of these will work because of the scoping rules in Haskell (which are
static, perhaps you are used to languages with dynamic scope?).
If you follow the desugaring rules for do notation, it might be clearer how
the scoping rules work. I posted a reference in my previous mail.
So if you want a global variable - read the paper by Hughes that I mentioned
previously. It is short, easy to understand, and covers the typical
ways Haskell programmers might try to do it (dirty and clean). It might even
clarify the scoping issues involved.
If you can't be bothered to read the paper, then I'm afraid you'll have to
thread the value of afact through your code.
Cheers,
Bernie.
From jcast@ou.edu Tue Mar 4 04:45:38 2003
From: jcast@ou.edu (Jon Cast)
Date: Mon, 03 Mar 2003 22:45:38 -0600
Subject: do let in
In-Reply-To: Message from
"Damien R. Sullivan"
of
"Mon, 03 Mar 2003 23:14:26 EST."
<20030304041426.GA25575@cownose.cs.indiana.edu>
References: <20030304033344.GA25362@cownose.cs.indiana.edu>
<200303040406.PAA28390@mulga.cs.mu.OZ.AU>
<20030304041426.GA25575@cownose.cs.indiana.edu>
Message-ID: <20030304044538.594EC4A5ED@jcomain>
"Damien R. Sullivan" wrote:
> For the reason that I'm lazy and don't want to have to modify all my
> functions which use afact, or call functions which use afact, and
> don't see why I should have to -- they were able to call the 'fact'
> function as a global, and can refer to a global 'afact' if I define it
> outside of main with a fixed value. I don't see why having a global
> dependent on outside input should be so much harder.
Never programmed in C++ much, eh?
In general, getting the ordering of initialization right in the general
case is a harder problem than you might think.
Jon Cast
From mpj@cse.ogi.edu Tue Mar 4 04:46:22 2003
From: mpj@cse.ogi.edu (Mark P Jones)
Date: Mon, 3 Mar 2003 20:46:22 -0800
Subject: speedup help
In-Reply-To: <20030304002655.GA24692@cownose.cs.indiana.edu>
Message-ID: <000001c2e209$04c04e10$3d01a8c0@blue>
Hi Damien,
| So, I'm having to calculate 'n choose k' an awful lot. At
| the moment I've got this:
|
| comb :: Integer -> Integer -> Integer
| comb m 0 = 1
| comb m n = (numerator(toRational (fact m) / toRational (fact
| n * fact (m-n))))
|
| where fact is a memoized factorial function. It's not
| perfectly memoized, though; I use lists, since that's easier
| by default. They should be arrays, and possibly just
| changing that would speed comb up a lot. (Comb is currently
| 40% of runtime, fact is 23%.) But I think it should be
| possible to speed up comb itself, too.
If you're looking to calculate memoized n choose k, then I'd suggest
looking at the following. First, where do the n choose k numbers come
from? Forget factorial! Think Pascal's triangle!
pascal :: [[Integer]]
pascal = iterate (\row -> zipWith (+) ([0] ++ row) (row ++ [0])) [1]
Now we can define a variant of your comb function like this:
comb :: Int -> Int -> Integer
comb n m = pascal !! n !! m
(Add an extra line if you want comb to work for values outside the
range: 0 <= m <= n. You could also replace the rows of the triangle
with arrays, if you want. No factorials, multiplies, or divides here,
and natural memoization ...)
| comb is only called from here:
| sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i
| <- [0 .. n-1] ]
In that case, you can take further advantage of using Pascal's triangle
by recognizing that numbers of the form (comb (n+1) i) are just the
entries in the (n+1)th row. (All but the last two, for reasons I
don't understand ... did you possibly want [0..n+1]?) So we get the
following definition:
sumbn n = sum [ bernoulli i * fromIntegral c
| (i,c) <- zip [0..n-1] (pascal!!(n+1)) ]
Actually, I prefer the following version that introduces an explicit
dot product operator:
sumbn n = take n (map bernoulli [0..]) `dot` (pascal!!(n+1))
dot xs ys = sum (zipWith (*) xs ys)
I don't have your setup to test the performance of these definitions,
but I'd be curious to know how they fare. Even if they turn out to be
slower, I thought these definitions were interesting and different
enough to justify sharing ...
All the best,
Mark
From jcast@ou.edu Tue Mar 4 04:57:01 2003
From: jcast@ou.edu (Jon Cast)
Date: Mon, 03 Mar 2003 22:57:01 -0600
Subject: is identity the only polymorphic function without typeclasses?
In-Reply-To: Message from Andrew J Bromage of
"Tue, 04 Mar 2003 10:22:38 +1100."
<20030303232238.GA29357@smtp.alicorna.com>
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
<01c701c2e16a$39cd6420$63968cc1@ozgenc>
<20030303232238.GA29357@smtp.alicorna.com>
Message-ID: <20030304045701.DCD6F4A5ED@jcomain>
Andrew J Bromage wrote:
> G'day.
> On Mon, Mar 03, 2003 at 11:49:29AM +0200, Cagdas Ozgenc wrote:
> > Yes, I thought about these too. Do you find these functions
> > practically useful? Can you give an example where I can utilize
> > these functions?
> Functions like this are useful for plugging into higher-order
> functions to tailor them for your specific needs.
> Here's an artificial example:
> length = sum . map (const 1)
Incidentally, here's another artificial example:
> indices = zipWith const [0..]
This can be used to define scanl, incidentally:
> scanl f z xn = [foldl f z (take i xn) | i <- indices (undefined:xn)]
(where the undefined: just reflects the fact that we want one more
element than xn has).
Jon Cast
From dasulliv@cs.indiana.edu Tue Mar 4 05:08:57 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Tue, 4 Mar 2003 00:08:57 -0500
Subject: do let in
In-Reply-To: <20030304044538.594EC4A5ED@jcomain>
References: <20030304033344.GA25362@cownose.cs.indiana.edu>
<200303040406.PAA28390@mulga.cs.mu.OZ.AU>
<20030304041426.GA25575@cownose.cs.indiana.edu>
<20030304044538.594EC4A5ED@jcomain>
Message-ID: <20030304050857.GA25771@cownose.cs.indiana.edu>
On Mon, Mar 03, 2003 at 10:45:38PM -0600, Jon Cast wrote:
> Never programmed in C++ much, eh?
Only for a few years, professionally.
> In general, getting the ordering of initialization right in the general
> case is a harder problem than you might think.
It's not something I'd be having trouble with here. Get args, call
precompute(), call functions, print output.
-xx- Damien X-)
From dasulliv@cs.indiana.edu Tue Mar 4 05:11:54 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Tue, 4 Mar 2003 00:11:54 -0500
Subject: do let in
In-Reply-To: <200303040429.PAA00579@mulga.cs.mu.OZ.AU>
References: <20030304041426.GA25575@cownose.cs.indiana.edu>
<200303040429.PAA00579@mulga.cs.mu.OZ.AU>
Message-ID: <20030304051154.GB25771@cownose.cs.indiana.edu>
On Tue, Mar 04, 2003 at 03:29:48PM +1100, Bernard James POPE wrote:
> So if you want a global variable - read the paper by Hughes that I mentioned
> previously. It is short, easy to understand, and covers the typical
> ways Haskell programmers might try to do it (dirty and clean). It might even
I've read it and looked at the implicit parameters paper ghc points to.
Implicit parameters seem like what I'd want, but I can't get that to compile
either. But it's getting late and I should probably go back tomorrow.
(Turned all uses of afact into ?fact, and tried let ... gamma_tup ... with
afact = array ... And compiled with -fglasgow-exts)
-xx- Damien X-)
From jadrian@mat.uc.pt Tue Mar 4 10:57:35 2003
From: jadrian@mat.uc.pt (Jorge Adriano)
Date: Tue, 4 Mar 2003 10:57:35 +0000
Subject: do let in
In-Reply-To: <20030304051154.GB25771@cownose.cs.indiana.edu>
References: <20030304041426.GA25575@cownose.cs.indiana.edu>
<200303040429.PAA00579@mulga.cs.mu.OZ.AU>
<20030304051154.GB25771@cownose.cs.indiana.edu>
Message-ID: <200303041057.35125.jadrian@mat.uc.pt>
> On Tue, Mar 04, 2003 at 03:29:48PM +1100, Bernard James POPE wrote:
> > So if you want a global variable - read the paper by Hughes that I
> > mentioned previously. It is short, easy to understand, and covers the
> > typical ways Haskell programmers might try to do it (dirty and clean). It
> > might even
>
> I've read it and looked at the implicit parameters paper ghc points to.
> Implicit parameters seem like what I'd want, but I can't get that to
> compile either. But it's getting late and I should probably go back
> tomorrow. (Turned all uses of afact into ?fact, and tried let ... gamma_tup
> ... with afact = array ... And compiled with -fglasgow-exts)
I think the use of the "with" keyword is deprecated. Instead of,
foo with ?u=bar
you should now use,
let ?u=bar in foo
That might be it.
J.A.
From simonmar@microsoft.com Tue Mar 4 16:37:08 2003
From: simonmar@microsoft.com (Simon Marlow)
Date: Tue, 4 Mar 2003 16:37:08 -0000
Subject: Network module problem
Message-ID: <9584A4A864BD8548932F2F88EB30D1C60C018562@tvp-msg-01.europe.corp.microsoft.com>
> Hello. I'm running into a problem with the Network module,=20
> which I suspect
> is pretty easy to fix, but am not sure how to best do so.
>=20
> The problem is that "accept" fails when the reverse DNS=20
> fails, with the
> following error:
>=20
> Fail: does not exist
> Action: getHostByAddr
> Reason: no such host entry
>=20
> I'm not sure how to get around this. I don't actually need=20
> the hostname of
> the client, and would be happy to just substitute its IP=20
> address in that field, but I'm not sure how to do that.
We've made this change in the library, the next release of GHC will
include the fix. Unfortunately there's no immediate workaround, other
than using the Network.Socket interface to accept (which isn't hard, the
Network.accept wrapper is fairly simple).
Cheers,
Simon
From dasulliv@cs.indiana.edu Tue Mar 4 20:45:51 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Tue, 4 Mar 2003 15:45:51 -0500
Subject: speedup help
In-Reply-To: <000001c2e209$04c04e10$3d01a8c0@blue>
References: <20030304002655.GA24692@cownose.cs.indiana.edu>
<000001c2e209$04c04e10$3d01a8c0@blue>
Message-ID: <20030304204551.GA28630@cownose.cs.indiana.edu>
On Mon, Mar 03, 2003 at 08:46:22PM -0800, Mark P Jones wrote:
> pascal :: [[Integer]]
> pascal = iterate (\row -> zipWith (+) ([0] ++ row) (row ++ [0])) [1]
>
> comb :: Int -> Int -> Integer
> comb n m = pascal !! n !! m
> In that case, you can take further advantage of using Pascal's triangle
> by recognizing that numbers of the form (comb (n+1) i) are just the
> entries in the (n+1)th row. (All but the last two, for reasons I
> don't understand ... did you possibly want [0..n+1]?) So we get the
No, the sum for a Bernoulli number is a combination times another Bernoulli
number from 0 to n-1. Hard to have B_n depend on B_n. At least in a nice
recurrence...
> sumbn n = sum [ bernoulli i * fromIntegral c
> | (i,c) <- zip [0..n-1] (pascal!!(n+1)) ]
This code as is takes about 23 seconds, comparable to the 22 seconds of
factorial with array (hardcoded, since I can't get it dynamically in a pretty
fashion.) If I turned pascal into arrays it might be even faster. I'd have
to change something though, right, zipWith wouldn't work with arrays?
> Actually, I prefer the following version that introduces an explicit
> dot product operator:
>
> sumbn n = take n (map bernoulli [0..]) `dot` (pascal!!(n+1))
> dot xs ys = sum (zipWith (*) xs ys)
This needed some modification, since bernoulli returns Rationals, so I had
zipWith use a special mult function. It just took 25 seconds.
> slower, I thought these definitions were interesting and different
> enough to justify sharing ...
Hey, you're even faster too! At least for messing with comb.
Aaron Denney, to his credit, had a pretty similar idea a week ago, but I
didn't get what he was talking about then. Newbies like code they can paste
in. :)
Thanks!
-xx- Damien X-)
From sqrtofone@yahoo.com Tue Mar 4 22:14:06 2003
From: sqrtofone@yahoo.com (Jay Cox)
Date: Tue, 4 Mar 2003 16:14:06 -0600
Subject: is identity the only polymorphic function without typeclasses?
References: <200303030931.UAA02634@mulga.cs.mu.OZ.AU>
<3E6329CD.10309@info.unicaen.fr> <01fb01c2e174$4b3a8ee0$63968cc1@ozgenc>
Message-ID: <00c601c2e29b$635c5940$0201a8c0@yahoo.com>
> The time you grouped (a->b->c), you utilized the arrow type constructor to
> build a function type, it is no different that using a polymorphic list. I
> think I am not happy with the dual semantics of this arrow thingie. I have
> to ponder on this some more, I guess.
>
> Thanks for the response. Greatly appreciated.
I'm not a student of type theory, but what follows is my own attempt to
rigorously (per my definitions) formalize an answer.
Lets forget about the undefined, bottom, error, or whatever cases and look
at the following.
Lets think about this inductively.
First off, lets start off with something of type a. (here we don't mean that
something
of type forall a . a, which is a whole different type, we just mean we have
something with a specific type, we just don't care what it is.)
Now, with the arrow constructor we can build two new types of functions.
a - > a (of which the only useful function I can see is id or a constant
function
which constrains the type of the 1st argument.)
b -> a (which is basically a constant function.)
we can continue to build new functions by either adding an existing type
variable
from the list of expressions we have created, or introducing the new type
variable c.
so now we have
U: a -> a -> a
V: a -> b -> a
W: b -> a -> a
X: b -> b -> a
Y: c -> a -> a
Z: c -> b -> a
Analyzing the functions (U..Z) we find:
U: could be any any thing similar to asTypeOf (selecting either the first
or second arguments, constraining them to a single type,) or a constant
valued function.
V: choose first argument or constant
W: choose second argument or constant.
X: constant f (But could this be a very odd but perhaps minorly useful
method to constrain types of certain values in some type system?) Lets call
this a constant asTypeOf function
Y: whoops! this is isomprophic to W
Z: constant f
Now, if we go on creating 3,4,...,N parameter, etc. functions, could we find
anything other than functions which could not described described as some
combination of the following? (Assume i is integer and z_i is just a
specific argumetn number).
1: selecting asTypeOf function
(with type constraint a on arguments (y_1,y_2, ...),
type constraint b on arguments (z_1,z_2, ....),
type constraint c ....)
I am considering id as one of these, since it selects its first (and
only) argument.
2: constant asTypeOf function
with type constraints similar to that of case 1.
3: constant function without type constraints.
This is where induction can get confusing, because we need to deal with 6
cases.
existing type var on cases 1,2, and 3, and new type var on cases 1,2,and 3.
I will denote the cases et1,et2,et3 and nt1,nt2,nt3 respectively.
et1: just (possibly*) adds a new type constraint to new function
et2: just (possibly*) adds a new type constraint to new function
et3: now we have a constraint on the type, so the new function is a case 2
function.
nt1: no new type constraint
nt2: no new type constraint
nt3: no new type constraint (Th new function is a constant function without
type constraints).
* I say possibly here because in the case where you selected a type var
amongst the set of type vars which are already declared in your list of
created functions, and add
it to a function which does not have that type var, it would be the same as
adding a new type var. If this is confusing, just consider cases W and Y a
from few paragraphs above (where meantion, "whoops, this is isomorphic...")
and maybe you'll understand what I'm trying to say.
So it looks like you only get those three cases if you go by my partitioning
of the kinds of functions.
Jay Cox
From info@deals2go.co.uk Thu Mar 6 00:37:13 2003
From: info@deals2go.co.uk (Ami)
Date: Wed, 5 Mar 2003 16:37:13 -0800
Subject: You missed my Birthday again!
Message-ID:
Hi ya,
Can't believe you missed my Birthday again, give me a call when you get this e-mail.
You have to check out this great present Mel sent me, everyone at work is going mad over it!
www.deals2go.co.uk/script
Ami
From paul@theV.net Thu Mar 6 04:57:23 2003
From: paul@theV.net (paul@theV.net)
Date: Thu, 6 Mar 2003 12:57:23 +0800
Subject: ForeignPtr question (was Re: debug with GHC FFI?)
In-Reply-To: <20030225134900.GA8529@gime.com>
References: <20030225134900.GA8529@gime.com>
Message-ID: <20030306045723.GA4410@gime.com>
I am using Green Card 2.05, but it seems to me that its support
for Ptr/Addr types are not up-to-date. I then use ForeignPtr
to marshall a C structure, but have some problem with pointers
which is garbage collected too early.
Here is a code sample:
------------------------ snip ------------------------
%fun destroyByteBuffer :: Addr -> IO ()
%code if (arg1) { free(arg1); }
%result ()
data ByteBufferType = ByteBufferType
type ByteBuffer = ForeignPtr ByteBufferType
marshall_byteBuffer :: ByteBuffer -> IO Addr
marshall_byteBuffer ptr = withForeignPtr ptr (\x -> return (ptrToAddr x))
unmarshall_byteBuffer :: Addr -> IO ByteBuffer
unmarshall_byteBuffer addr = newForeignPtr (addrToPtr addr) (destroyByteBuffer addr)
%fun readInt :: ByteBuffer -> IO Int
%call (byteBuffer (addr bf))
%code INT32 r, v = 0;
% r = bb_get_int((Byte_Buffer *) bf, &v);
%fail {r != _NO_ERR} {"readInt failed"}
%result (int v)
------------------------ snip ------------------------
The code would sometimes segfault in bb_get_int(..), and since
it was coded in a separate C file, I was able to trace down
the error in GDB, which hinted that, part of the C structure in
"bf" was already freed prior to the bb_get_int(..) function call.
So my guess is that "destroyByteBuffer" was invoked even when
I use "withForeignPtr" to marshall the ByteBuffer type.
What did I do wrong here? Is it a bug with Greencard or something
I am still missing when constructing a garbage collectible
ForeignPtr in FFI?
Regards,
.paul.
On Tue, Feb 25, 2003 at 09:49:00PM +0800, paul@theV.net wrote:
> I am using Green Card to make some FFI modules with GHC, but
> sometimes it segfaults in the middle of nowhere, leaving
> no sensible stack trace in gdb.
>
> I wonder what is the proper way to debug FFI modules written
> in C? Trying to add a "-g" flag doesn't seem help at all...
>
> Regards,
> .paul.
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
From oleg@pobox.com Fri Mar 7 00:32:44 2003
From: oleg@pobox.com (oleg@pobox.com)
Date: Thu, 6 Mar 2003 16:32:44 -0800 (PST)
Subject: speedup help
Message-ID: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
| comb is only called from here:
| sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i
| <- [0 .. n-1] ]
Probably I misunderstand what "bernoulli i" stands for. If it is meant
Bernoulli number B_i,
http://mathworld.wolfram.com/BernoulliNumber.html
then the above expression is quite inefficient. Bernoulli numbers with
odd indices are all zero, except B_1, which is -1/2. Therefore, the above
expression ought to be written as
sumbn n = 1 - (fromIntegral (n+1)%(fromIntegral 2)) +
sum [ (b' i) * fromIntegral(comb (n+1) i) | i <- [2,4 .. n-1] ]
It appears that you compute the sumbn to obtain B_n from the equality
sum [bernoulli i * (comb (n+1) i) | i<-[0..n]] == 0
Have you tried
bernoulli n = sum [ (sumib k n) % (k+1) | k<-[1..n]]
where
sumib k n = sum [ (comb k r) * r^n | r<-[2..k]]
- sum [ (comb k r) * r^n | r<-[1,3..k]]
the advantage of the latter series is that sumib is an Integer, rather
than a rational. The powers of r can be memoized.
Here's the code
-- powers = [[r^n | r<-[1..]] | n<-[1..]]
powers = [1..] : map (zipWith (*) (head powers)) powers
-- neg_powers = [[(-1)^r * r^n | r<-[1..]] | n<-[1..]]
neg_powers =
map (zipWith (\n x -> if n then x else -x) (iterate not False)) powers
pascal:: [[Integer]]
pascal = [1,1] : map (\line -> zipWith (+) (line++[0]) (0:line)) pascal
bernoulli n = sum [ fromIntegral (sumib k n) % fromIntegral (k+1) | k<-[1..n]]
sumib:: Int -> Int -> Integer
sumib k n = sum $ zipWith (*) (neg_powers!!(n-1)) (tail $ pascal!!(k-1))
This code seems to compute 'bernoulli 82' in less then a second, in
Hugs (on a 2GHz Pentium IV).
From nick.name@inwind.it Fri Mar 7 02:22:38 2003
From: nick.name@inwind.it (Nick Name)
Date: Fri, 7 Mar 2003 03:22:38 +0100
Subject: instance declaration troubles
Message-ID: <20030307032238.6c0ccbf1.nick.name@inwind.it>
I want to declare the following:
class Get a where
ls :: a b -> IO [b]
mk :: IO [b] -> a b
instance (Get a) => Functor a where
fmap f x = mk (ls x >>= return . map f)
But to have ghc type everything, I have to turn on "-fglasgow-exts
-fallow-undecidable-instances -fallow-overlapping-instances".
Is there a clean way to state that all types in my type class are also
in the "Functor" type class?
If not, what is the problem?
Vincenzo
From wtwjek@winternet.com Fri Mar 7 03:23:44 2003
From: wtwjek@winternet.com (Bill Wood)
Date: Thu, 06 Mar 2003 21:23:44 -0600
Subject: speedup help
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
Message-ID: <3E6810C0.D2E2E83E@winternet.com>
Oleg has a very interesting approach; in particular, he avoids
explicit recursion and (most) computing with rationals, while
also replacing the factorials in binary coefficients by using
successive rows of Pascal's triangle. He also skips over the
B_{2k+1}, k > 0, which are all 0.
I slogged through the "standard" expansions, deriving a tail
recursive function that rolls along successive Bernoulli numbers,
generating successive rows of Pascal's triangle along the way,
and returning the list of B_n .. B_0. You can think of the list
of Bernoulli numbers as "memoizing" just-in-time.
Running it in Hugs on a 650Mhz Athlon with 128M RAM, bernoulli 82
took ca. 1 sec. Compiling with ghc -O, bernoulli 1000 took approx.
15 sec. wall time; bernoulli 10000 blew the heap.
I couldn't get getCPUTime (from module CPUTime) to work for me; if
anyone can enlighten me on how to get timing of function execution
I'd appreciate it.
BTW profiling didn't work; when I tried to compile with profiling
flags I received error msgs saying that interface files for standard
libraries couldn't be found. Compiling without the flags seems to
work just fine.
Oleg's program brings up another interesting point for all you
mathematicians out there: I found two basically different expansion
formulas for Bernoulli numbers. One is based on the formal
expansion of the equation
(B + 1)^n = B^n
which results in binomial-theorem expansions all of whose terms are
positive. The other is based on formal expansion of the equation
(B - 1)^n = B^n
which results in binomial-theorem expansions whose terms alternate
in sign. The amazing thing is, they two sets of numbers only differ
at one term: the first formula results in B_1 = -1/2 while the
second results in B_1 = +1/2 !
I found the second formula in Conway & Guy, _The Book of Numbers_,
p.108.
The second formula, with tiny variations, can be found in Knuth,
_Fundamental Algorithms_, p. 109, Abramowitz & Stegun, _Handbook
of Mathematical Functions_, p. 804 and Song Y. Yan, _Number Theory for
Computing_, p. 75
This has gotten a little long, sorry. If you want I can post my Haskell
code or send privately.
-- Bill Wood
wtwjek@winternet.com
From hdaume@ISI.EDU Fri Mar 7 03:15:48 2003
From: hdaume@ISI.EDU (Hal Daume III)
Date: Thu, 6 Mar 2003 19:15:48 -0800 (PST)
Subject: instance declaration troubles
In-Reply-To: <20030307032238.6c0ccbf1.nick.name@inwind.it>
Message-ID:
>From the GHC docs:
In the signature of a class operation, every constraint must mention at
least one type variable that is not a class type variable. Thus:
class Collection c a where
mapC :: Collection c b => (a->b) -> c a -> c b
is OK because the constraint (Collection a b) mentions b, even though it
also mentions the class variable a. On the other hand:
class C a where
op :: Eq a => (a,b) -> (a,b)
is not OK because the constraint (Eq a) mentions on the class type
variable a, but not b. However, any such example is easily fixed by moving
the offending context up to the superclass context:
class Eq a => C a where
op ::(a,b) -> (a,b)
A yet more relaxed rule would allow the context of a class-op signature to
mention only class type variables. However, that conflicts with Rule
1(b) for types above.
--
Hal Daume III | hdaume@isi.edu
"Arrest this man, he talks in maths." | www.isi.edu/~hdaume
On Fri, 7 Mar 2003, Nick Name wrote:
>
> I want to declare the following:
>
> class Get a where
> ls :: a b -> IO [b]
> mk :: IO [b] -> a b
>
> instance (Get a) => Functor a where
> fmap f x = mk (ls x >>= return . map f)
>
>
> But to have ghc type everything, I have to turn on "-fglasgow-exts
> -fallow-undecidable-instances -fallow-overlapping-instances".
>
> Is there a clean way to state that all types in my type class are also
> in the "Functor" type class?
>
> If not, what is the problem?
>
> Vincenzo
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From dasulliv@cs.indiana.edu Fri Mar 7 03:45:47 2003
From: dasulliv@cs.indiana.edu (Damien R. Sullivan)
Date: Thu, 6 Mar 2003 22:45:47 -0500
Subject: speedup help
In-Reply-To: <3E6810C0.D2E2E83E@winternet.com>
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
<3E6810C0.D2E2E83E@winternet.com>
Message-ID: <20030307034547.GA9686@cownose.cs.indiana.edu>
On Thu, Mar 06, 2003 at 09:23:44PM -0600, Bill Wood wrote:
> I couldn't get getCPUTime (from module CPUTime) to work for me; if
Yeah, I had the same problem -- it would just return ten million or some other
number, consistently. Use of getClockTime and diffClockTimes didn't help
either.
> anyone can enlighten me on how to get timing of function execution
For my purposes I run my program prefixed with the Unix command 'time', and
with minimal output because printing 25k of rational digits seems to take a
while. Having found parameters which finish in just under a minute I then
rerun with output. Then I try to convince my TA this is valid. :)
> BTW profiling didn't work; when I tried to compile with profiling
I was having problems with ghc 5.04; I got told to try 5.04.2 and haven't had
problems since. Blessed be my sysadmins who responded quickly.
To Oleg: I know about odd Bernoullis being zero and use that in the Bernoulli
function itself; I hadn't thought about trying to simplify sumbn itself.
Interesting...
-xx- Damien X-)
From wtwjek@winternet.com Fri Mar 7 07:45:32 2003
From: wtwjek@winternet.com (Bill Wood)
Date: Fri, 07 Mar 2003 01:45:32 -0600
Subject: speedup help
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
Message-ID: <3E684E1C.CCBCCC41@winternet.com>
. . .
> This code seems to compute 'bernoulli 82' in less then a second, in
> Hugs (on a 2GHz Pentium IV).
Just a note: I compiled and ran Oleg's and mine for comparison. The
two seem to be of the same complexity, with Oleg's a little faster
(modulo my using wall time; see previous msg.)
Oleg's blew the heap at 847; mine valiantly struggled on 'til it blew
the heap at 1910. I must be doing something right, since I'm carrying
around the list of all numbers from B_0 through B_n, while Oleg cleverly
avoids that. I was also surprised to see Oleg's blow the heap at an
*odd* value -- I thought he skipped those.
-- Bill Wood
wtwjek@winternet.com
From simonpj@microsoft.com Fri Mar 7 13:24:50 2003
From: simonpj@microsoft.com (Simon Peyton-Jones)
Date: Fri, 7 Mar 2003 13:24:50 -0000
Subject: instance declaration troubles
Message-ID:
Argh. The documentation is out of date, or rather, inconsistent.
In Section 7.3.4 you'll see that GHC -fglasgow-exts lifts the
restriction that class methods must not constrain only the class type
variable.
I'll fix 7.3.5.2, which you are quoting.
Simon
| -----Original Message-----
| From: Hal Daume III [mailto:hdaume@ISI.EDU]
| Sent: 07 March 2003 03:16
| To: Nick Name
| Cc: haskell-cafe@haskell.org
| Subject: Re: instance declaration troubles
|=20
| From the GHC docs:
|=20
| In the signature of a class operation, every constraint must mention
at
| least one type variable that is not a class type variable. Thus:
|=20
| class Collection c a where
| mapC :: Collection c b =3D> (a->b) -> c a -> c b
|=20
| is OK because the constraint (Collection a b) mentions b, even though
it
| also mentions the class variable a. On the other hand:
|=20
| class C a where
| op :: Eq a =3D> (a,b) -> (a,b)
|=20
| is not OK because the constraint (Eq a) mentions on the class type
| variable a, but not b. However, any such example is easily fixed by
moving
| the offending context up to the superclass context:
|=20
| class Eq a =3D> C a where
| op ::(a,b) -> (a,b)
|=20
| A yet more relaxed rule would allow the context of a class-op
signature to
| mention only class type variables. However, that conflicts with Rule
| 1(b) for types above.
|=20
| --
| Hal Daume III | hdaume@isi.edu
| "Arrest this man, he talks in maths." | www.isi.edu/~hdaume
|=20
| On Fri, 7 Mar 2003, Nick Name wrote:
|=20
| >
| > I want to declare the following:
| >
| > class Get a where
| > ls :: a b -> IO [b]
| > mk :: IO [b] -> a b
| >
| > instance (Get a) =3D> Functor a where
| > fmap f x =3D mk (ls x >>=3D return . map f)
| >
| >
| > But to have ghc type everything, I have to turn on "-fglasgow-exts
| > -fallow-undecidable-instances -fallow-overlapping-instances".
| >
| > Is there a clean way to state that all types in my type class are
also
| > in the "Functor" type class?
| >
| > If not, what is the problem?
| >
| > Vincenzo
| > _______________________________________________
| > Haskell-Cafe mailing list
| > Haskell-Cafe@haskell.org
| > http://www.haskell.org/mailman/listinfo/haskell-cafe
| >
|=20
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
From hdaume@ISI.EDU Fri Mar 7 15:08:06 2003
From: hdaume@ISI.EDU (Hal Daume III)
Date: Fri, 7 Mar 2003 07:08:06 -0800 (PST)
Subject: instance declaration troubles
In-Reply-To:
Message-ID:
Double Argh! I just noticed that this isn't what I meant to quote and now
I can't find it. But the basic idea of what I wanted to quote was that:
YOu have to have at least one non-type variable in instance declarations
otherwise we don't necessarily know that reduction will terminate. I.e.:
instance A a => B a where
instance B a => A a where
will not terminate if you ever try to reduce A to B. I recall from the
docs that Simon is "looking for a rule which lifts this rule but still
maintains decidability." or something along those lines.
Sorry about that!
- Hal
--
Hal Daume III | hdaume@isi.edu
"Arrest this man, he talks in maths." | www.isi.edu/~hdaume
On Fri, 7 Mar 2003, Simon Peyton-Jones wrote:
> Argh. The documentation is out of date, or rather, inconsistent.
>
> In Section 7.3.4 you'll see that GHC -fglasgow-exts lifts the
> restriction that class methods must not constrain only the class type
> variable.
>
> I'll fix 7.3.5.2, which you are quoting.
>
> Simon
>
> | -----Original Message-----
> | From: Hal Daume III [mailto:hdaume@ISI.EDU]
> | Sent: 07 March 2003 03:16
> | To: Nick Name
> | Cc: haskell-cafe@haskell.org
> | Subject: Re: instance declaration troubles
> |
> | From the GHC docs:
> |
> | In the signature of a class operation, every constraint must mention
> at
> | least one type variable that is not a class type variable. Thus:
> |
> | class Collection c a where
> | mapC :: Collection c b => (a->b) -> c a -> c b
> |
> | is OK because the constraint (Collection a b) mentions b, even though
> it
> | also mentions the class variable a. On the other hand:
> |
> | class C a where
> | op :: Eq a => (a,b) -> (a,b)
> |
> | is not OK because the constraint (Eq a) mentions on the class type
> | variable a, but not b. However, any such example is easily fixed by
> moving
> | the offending context up to the superclass context:
> |
> | class Eq a => C a where
> | op ::(a,b) -> (a,b)
> |
> | A yet more relaxed rule would allow the context of a class-op
> signature to
> | mention only class type variables. However, that conflicts with Rule
> | 1(b) for types above.
> |
> | --
> | Hal Daume III | hdaume@isi.edu
> | "Arrest this man, he talks in maths." | www.isi.edu/~hdaume
> |
> | On Fri, 7 Mar 2003, Nick Name wrote:
> |
> | >
> | > I want to declare the following:
> | >
> | > class Get a where
> | > ls :: a b -> IO [b]
> | > mk :: IO [b] -> a b
> | >
> | > instance (Get a) => Functor a where
> | > fmap f x = mk (ls x >>= return . map f)
> | >
> | >
> | > But to have ghc type everything, I have to turn on "-fglasgow-exts
> | > -fallow-undecidable-instances -fallow-overlapping-instances".
> | >
> | > Is there a clean way to state that all types in my type class are
> also
> | > in the "Functor" type class?
> | >
> | > If not, what is the problem?
> | >
> | > Vincenzo
> | > _______________________________________________
> | > Haskell-Cafe mailing list
> | > Haskell-Cafe@haskell.org
> | > http://www.haskell.org/mailman/listinfo/haskell-cafe
> | >
> |
> | _______________________________________________
> | Haskell-Cafe mailing list
> | Haskell-Cafe@haskell.org
> | http://www.haskell.org/mailman/listinfo/haskell-cafe
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From nick.name@inwind.it Fri Mar 7 15:33:39 2003
From: nick.name@inwind.it (Nick Name)
Date: Fri, 7 Mar 2003 16:33:39 +0100
Subject: instance declaration troubles
In-Reply-To:
References: <20030307032238.6c0ccbf1.nick.name@inwind.it>
Message-ID: <20030307163339.7be30331.nick.name@inwind.it>
Yes, I usually RTFM before posting, but you have misunderstood my
question (however, thanks for always reading and answering newbie
questions like mine); what I want to do is the
instance (Get a) => Functor a where
fmap f x = mk (ls x >>= return . map f)
Now, what I mean is: "any type in Get class is also in Functor class,
and I tell you how". But I need undecidable instances! Why? Is there a
simple way to state this property, that the Get class is a subset of the
Functor class?
Vincenzo
From hdaume@ISI.EDU Fri Mar 7 15:47:09 2003
From: hdaume@ISI.EDU (Hal Daume III)
Date: Fri, 7 Mar 2003 07:47:09 -0800 (PST)
Subject: instance declaration troubles
In-Reply-To: <20030307163339.7be30331.nick.name@inwind.it>
Message-ID:
See my "Double Argh" message, but other than that, the only way is if you
redefine your Functor class to be a subclass of Get, which means you need
to define your own and cannot use the library one (unless something like
superclass is adopted...there's a recommendation out there for this
somewhere). You need undecidable instances because in general something
like this is not decidable. The way that undecidable instances deals with
the problem is that it sets a depth for instance reduction and if this
depth is hit, it just dies.
That said, "undecidable instances" sound very scary, but they're really
not. You can google around for a conversation I had with SPJ about this a
while back, but something being an und instance is a compile time
property. That is, if compilation succeeds, you don't have anything to
worry about and the worst that can happen at compilation time is that
you'll hit the bottom of this stack.
--
Hal Daume III | hdaume@isi.edu
"Arrest this man, he talks in maths." | www.isi.edu/~hdaume
On Fri, 7 Mar 2003, Nick Name wrote:
> Yes, I usually RTFM before posting, but you have misunderstood my
> question (however, thanks for always reading and answering newbie
> questions like mine); what I want to do is the
>
> instance (Get a) => Functor a where
> fmap f x = mk (ls x >>= return . map f)
>
> Now, what I mean is: "any type in Get class is also in Functor class,
> and I tell you how". But I need undecidable instances! Why? Is there a
> simple way to state this property, that the Get class is a subset of the
> Functor class?
>
> Vincenzo
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
From nick.name@inwind.it Fri Mar 7 16:02:16 2003
From: nick.name@inwind.it (Nick Name)
Date: Fri, 7 Mar 2003 17:02:16 +0100
Subject: instance declaration troubles
In-Reply-To:
References: <20030307163339.7be30331.nick.name@inwind.it>
Message-ID: <20030307170216.4b6c5101.nick.name@inwind.it>
On Fri, 7 Mar 2003 07:47:09 -0800 (PST)
Hal Daume III wrote:
>
> That said, "undecidable instances" sound very scary, but they're
> really not. You can google around for a conversation I had with SPJ
> about this a while back, but something being an und instance is a
> compile time property. That is, if compilation succeeds, you don't
> have anything to worry about and the worst that can happen at
> compilation time is that you'll hit the bottom of this stack.
Thanks, you've been clear, even I miss that in haskell98 one can't
define subset properties between type classes... maybe because that
would mean "subtyping"?
Vincenzo
From simonpj@microsoft.com Fri Mar 7 16:13:14 2003
From: simonpj@microsoft.com (Simon Peyton-Jones)
Date: Fri, 7 Mar 2003 16:13:14 -0000
Subject: instance declaration troubles
Message-ID:
It's in 7.3.5.3. I'm going to make it more prominent
S
| -----Original Message-----
| From: Hal Daume III [mailto:hdaume@ISI.EDU]
| Sent: 07 March 2003 15:08
| To: Nick Name
| Cc: Haskell Cafe
| Subject: RE: instance declaration troubles
|=20
| Double Argh! I just noticed that this isn't what I meant to quote and
now
| I can't find it. But the basic idea of what I wanted to quote was
that:
|=20
| YOu have to have at least one non-type variable in instance
declarations
| otherwise we don't necessarily know that reduction will terminate.
I.e.:
|=20
| instance A a =3D> B a where
| instance B a =3D> A a where
|=20
| will not terminate if you ever try to reduce A to B. I recall from
the
| docs that Simon is "looking for a rule which lifts this rule but still
| maintains decidability." or something along those lines.
|=20
| Sorry about that!
|=20
| - Hal
|=20
| --
| Hal Daume III | hdaume@isi.edu
| "Arrest this man, he talks in maths." | www.isi.edu/~hdaume
|=20
| On Fri, 7 Mar 2003, Simon Peyton-Jones wrote:
|=20
| > Argh. The documentation is out of date, or rather, inconsistent.
| >
| > In Section 7.3.4 you'll see that GHC -fglasgow-exts lifts the
| > restriction that class methods must not constrain only the class
type
| > variable.
| >
| > I'll fix 7.3.5.2, which you are quoting.
| >
| > Simon
| >
| > | -----Original Message-----
| > | From: Hal Daume III [mailto:hdaume@ISI.EDU]
| > | Sent: 07 March 2003 03:16
| > | To: Nick Name
| > | Cc: haskell-cafe@haskell.org
| > | Subject: Re: instance declaration troubles
| > |
| > | From the GHC docs:
| > |
| > | In the signature of a class operation, every constraint must
mention
| > at
| > | least one type variable that is not a class type variable. Thus:
| > |
| > | class Collection c a where
| > | mapC :: Collection c b =3D> (a->b) -> c a -> c b
| > |
| > | is OK because the constraint (Collection a b) mentions b, even
though
| > it
| > | also mentions the class variable a. On the other hand:
| > |
| > | class C a where
| > | op :: Eq a =3D> (a,b) -> (a,b)
| > |
| > | is not OK because the constraint (Eq a) mentions on the class type
| > | variable a, but not b. However, any such example is easily fixed
by
| > moving
| > | the offending context up to the superclass context:
| > |
| > | class Eq a =3D> C a where
| > | op ::(a,b) -> (a,b)
| > |
| > | A yet more relaxed rule would allow the context of a class-op
| > signature to
| > | mention only class type variables. However, that conflicts with
Rule
| > | 1(b) for types above.
| > |
| > | --
| > | Hal Daume III | hdaume@isi.edu
| > | "Arrest this man, he talks in maths." |
www.isi.edu/~hdaume
| > |
| > | On Fri, 7 Mar 2003, Nick Name wrote:
| > |
| > | >
| > | > I want to declare the following:
| > | >
| > | > class Get a where
| > | > ls :: a b -> IO [b]
| > | > mk :: IO [b] -> a b
| > | >
| > | > instance (Get a) =3D> Functor a where
| > | > fmap f x =3D mk (ls x >>=3D return . map f)
| > | >
| > | >
| > | > But to have ghc type everything, I have to turn on
"-fglasgow-exts
| > | > -fallow-undecidable-instances -fallow-overlapping-instances".
| > | >
| > | > Is there a clean way to state that all types in my type class
are
| > also
| > | > in the "Functor" type class?
| > | >
| > | > If not, what is the problem?
| > | >
| > | > Vincenzo
| > | > _______________________________________________
| > | > Haskell-Cafe mailing list
| > | > Haskell-Cafe@haskell.org
| > | > http://www.haskell.org/mailman/listinfo/haskell-cafe
| > | >
| > |
| > | _______________________________________________
| > | Haskell-Cafe mailing list
| > | Haskell-Cafe@haskell.org
| > | http://www.haskell.org/mailman/listinfo/haskell-cafe
| > _______________________________________________
| > Haskell-Cafe mailing list
| > Haskell-Cafe@haskell.org
| > http://www.haskell.org/mailman/listinfo/haskell-cafe
| >
|=20
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
From oleg@pobox.com Sat Mar 8 01:58:58 2003
From: oleg@pobox.com (oleg@pobox.com)
Date: Fri, 7 Mar 2003 17:58:58 -0800 (PST)
Subject: speedup help
In-Reply-To: <3E684E1C.CCBCCC41@winternet.com>
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
<3E684E1C.CCBCCC41@winternet.com>
Message-ID: <200303080158.h281wwm5060438@adric.fnmoc.navy.mil>
> Oleg's blew the heap at 847; mine valiantly struggled on 'til it blew
> the heap at 1910.
Hmm, I managed to compute bernoulli 2000 and even bernoulli 3000. The
code is included. It took 7 minutes (2GHZ Pentium IV, 1GB memory) to
compute bernoulli 2000 and 33 minutes for bernoulli 3000. I monitored
the memory usage of the compiled application using top and found that
the resident set stayed at 30MB, which is a little bit less than the
resident set for Emacs. My emacs has a dozen of open windows, and has
been running for a month. Just for the record, here's the result of
bernoulli 3000:
(-2891939 ...6744 other digits... 81) % 12072109463901626300591430
Incidentally, we can show that the denominator is correct, by
von Staudt-Clausen theorem:
> primes = 2:map head (iterate sieve [3,5..])
> sieve (p:xs) = [ x | x<-xs, x `rem` p /= 0 ]
> b_denom twok
> = product [ p | p <- takeWhile (<= twok1) primes,
> twok `rem` (p-1) == 0]
> where twok1 = twok + 1
Here's the code (which was compiled with "ghc -O2")
import Ratio
import System.Environment
-- powers = [[r^n | r<-[2..]] | n<-1..]
powers = [2..] : map (zipWith (*) (head powers)) powers
-- powers = [[(-1)^r * r^n | r<-[2..]] | n<-1..]
neg_powers =
map (zipWith (\n x -> if n then x else -x) (iterate not True)) powers
pascal:: [[Integer]]
pascal = [1,2,1] : map (\line -> zipWith (+) (line++[0]) (0:line)) pascal
bernoulli 0 = 1
bernoulli 1 = -(1%2)
bernoulli n | odd n = 0
bernoulli n =
(-1)%2
+ sum [ fromIntegral ((sum $ zipWith (*) powers (tail $ tail combs)) -
fromIntegral k) %
fromIntegral (k+1)
| (k,combs)<- zip [2..n] pascal]
where powers = (neg_powers!!(n-1))
main = do
[arg] <- getArgs
let n = (read arg)::Int
print $ "Bernoulli of " ++ (show n) ++ " is "
print (bernoulli n)
From wtwjek@winternet.com Sat Mar 8 08:26:13 2003
From: wtwjek@winternet.com (Bill Wood)
Date: Sat, 08 Mar 2003 02:26:13 -0600
Subject: speedup help
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
<3E684E1C.CCBCCC41@winternet.com>
<200303080158.h281wwm5060438@adric.fnmoc.navy.mil>
Message-ID: <3E69A925.FFFC5072@winternet.com>
. . .
>
> > Oleg's blew the heap at 847; mine valiantly struggled on 'til it blew
> > the heap at 1910.
>
> Hmm, I managed to compute bernoulli 2000 and even bernoulli 3000. The
> code is included. It took 7 minutes (2GHZ Pentium IV, 1GB memory) to
> compute bernoulli 2000 and 33 minutes for bernoulli 3000. I monitored
> the memory usage of the compiled application using top and found that
> the resident set stayed at 30MB, which is a little bit less than the
> resident set for Emacs. My emacs has a dozen of open windows, and has
> been running for a month. Just for the record, here's the result of
> bernoulli 3000:
>
> (-2891939 ...6744 other digits... 81) % 12072109463901626300591430
Well, kudos to Oleg! I just ran his code from the msg this one replies
to and got similar results: On a 650 Mhz Athlon with 128MB RAM I
compiled with "ghc -O" (GHC 5.00.1). Using the "time" command,
bernoulli 2000 took 490 sec. user time while bernoulli 3000 took 2170
sec.
user time. Notice there were no heap overflows this time. I hope
someone can explain the differences in space behavior between the
version
in Oleg's mail of March 6 and this version. I'm surprised we are as
close
as we are in time given that my processor is less than half as fast. I
would also expect that my having 1/8-th the memory he has would slow me
down more due to page faulting.
The current version also fixes a minor glitch: the earlier version gave
B_0 = 0 instead of 1.
I think I got the right results for B_3000: My print-out had the same
denominator along with a 6762-digit numerator with the same initial
seven and final two digits. I don't get 6744 digits in the middle,
however.
I'm impressed by the good performance characteristics of high-level
Haskell code.
Nice work Oleg,
-- Bill Wood
wtwjek@winternet.com
From tom@moertel.com Sat Mar 8 16:08:09 2003
From: tom@moertel.com (Tom Moertel)
Date: Sat, 08 Mar 2003 11:08:09 -0500
Subject: speedup help
References: <200303070032.h270Witl058549@adric.fnmoc.navy.mil>
<3E684E1C.CCBCCC41@winternet.com>
<200303080158.h281wwm5060438@adric.fnmoc.navy.mil>
<3E69A925.FFFC5072@winternet.com>
Message-ID: <3E6A1569.15D83AEC@moertel.com>
Bill Wood wrote:
>
> I think I got the right results for B_3000: [...]
Mathematica 4.1 computes B_3000 as follows:
In[1]:= BernoulliB[3000]
Out[1]=
-28919392162925009628147618267854828678617917853903846822112332719169192942048\
518130533026045150594816676476469224548430690874860242714680177615276168526041\
[ 83 lines omitted ]
535500476970565917875995082926214969042647564930033701717898024811160065586065\
5536080415376091806331620179538459843417141322454179981 /
12072109463901626300591430
Cheers,
Tom
From almutaim@hotmail.com Sun Mar 9 11:48:31 2003
From: almutaim@hotmail.com (Mansour Al-Mutairi)
Date: Sun, 9 Mar 2003 03:48:31 -0800
Subject: GHC Error Message.
Message-ID:
This is a multi-part message in MIME format.
------=_NextPart_000_001D_01C2E5EE.C0996250
Content-Type: text/plain;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Hi,
Could someone please explain to me why the following error message =
happen:
When I load the following code into GHC I get an error message:
code:
-------------------------------------------------------------------------=
--------------------------
data AParser String =3D AP {apapply::([String]->[(String,[String])])}
instance Monad AParser where
return v =3D AP (\inp -> [(v,inp)])
(AP p) >>=3D f =3D AP (\inp -> concat [ apapply (f v) inp1 | =
(v,inp1) <- p inp])
-------------------------------------------------------------------------=
--------------------------
error:
-------------------------------------------------------------------------=
--------------------------
Inferred type is less polymorphic than expected
Quantified type variable `b' is unified with another quantified =
type variable `a'
When trying to generalise the type inferred for `>>=3D'
Signature type: forall a1 b1.
AParser a1 -> (a1 -> AParser b1) -> AParser =
b1
Type to generalise: forall a1 b1.
AParser a1 -> (a1 -> AParser b1) -> AParser =
b1
In the instance declaration for `Monad AParser'
Failed, modules loaded: none.
-------------------------------------------------------------------------=
--------------------------
But when I create the type synonym
type Stack =3D [String]
data AParser String =3D AP {apapply::(Stack -> [(String,Stack)])}
and use Stack instead of [String], GHC does not complain???
Thanks.
Mansour.
------=_NextPart_000_001D_01C2E5EE.C0996250
Content-Type: text/html;
charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable
Hi,
Could someone please explain to me why =
the=20
following error message happen:
When I load the following code into GHC =
I get an=20
error message:
code:
----------------------------------------------------------------=
-----------------------------------
data AParser String =3D AP=20
{apapply::([String]->[(String,[String])])}
instance Monad AParser where
=
return=20
v =3D AP (\inp ->=20
[(v,inp)])
(AP p) >>=3D f =3D AP (\inp =
->=20
concat [ apapply (f v) inp1 | (v,inp1) <- p inp])
----------------------------------------------------------------=
-----------------------------------
error:
----------------------------------------------------------------=
-----------------------------------
Inferred type is less polymorphic than=20
expected
Quantified type =
variable=20
`b' is unified with another quantified type variable =
`a'
=20
When trying to generalise the type inferred for=20
`>>=3D'
Signature=20
type: forall a1=20
b1.
=
&=
nbsp; =20
AParser a1 -> (a1 -> AParser b1) -> AParser=20
b1
Type to generalise: =
forall a1=20
b1.
=
&=
nbsp; =20
AParser a1 -> (a1 -> AParser b1) -> AParser =
b1
In=20
the instance declaration for `Monad AParser'
Failed, modules loaded:=20
none.
----------------------------------------------------------------=
-----------------------------------
But when I create the type synonym
type Stack =3D [String]
data AParser String =3D AP {apapply::(Stack -> =
[(String,Stack)])}
and use Stack instead of [String], GHC does not complain???
Thanks.
Mansour.
------=_NextPart_000_001D_01C2E5EE.C0996250--
From nick.name@inwind.it Sun Mar 9 23:59:00 2003
From: nick.name@inwind.it (Nick Name)
Date: Mon, 10 Mar 2003 00:59:00 +0100
Subject: Alternatives to finalization
Message-ID: <20030310005900.342e6750.nick.name@inwind.it>
As the result of a conversation on haskell-gui, I have tried to
implement the disallocation of resources when a stream is garbage
collected.
To explain myself:
I have a function
f :: IO [a]
which returns a lazy stream after allocating some resource to feed it
(say installing a callback).
I wish that the resource could be disallocated when it's no longer used.
I did the obvious implementation with Weak.addFinalizer; results are
encouraging but not completely satisfying; the scheme I used is:
f = do
allocateResource
l <- makeTheStream
addFinalizer l (disallocateResource)
return l
The problem is that if no memory is allocated, no garbage collection
happens; of course finalization is not guaranteed, as the manual states.
Another alternative is to make f return an esplicit "close stream"
action:
f :: IO ([a],IO ())
Is anyone willing to explain me other alternatives if there are, or to
tell me that there aren't?
Thanks for attention
Vincenzo
From simonpj@microsoft.com Mon Mar 10 09:09:12 2003
From: simonpj@microsoft.com (Simon Peyton-Jones)
Date: Mon, 10 Mar 2003 09:09:12 -0000
Subject: GHC Error Message.
Message-ID:
This is a multi-part message in MIME format.
--------------InterScan_NT_MIME_Boundary
Content-Type: multipart/alternative;
boundary="----_=_NextPart_001_01C2E6E4.B7834A51"
------_=_NextPart_001_01C2E6E4.B7834A51
Content-Type: text/plain;
charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
------------------------------------------------------------------------
---------------------------
data AParser String =3D AP {apapply::([String]->[(String,[String])])}
=20
Whoa! You can't declare a data type like that! You must have a type
variable after the data type name, thus:
=20
data AParser a =3D AP ....
=20
It's an egregious bug that GHC does not reject your data type
declaration.
=20
After that, all bets are off. Some deeply-wired-in invariant is not
being obeyed, and all manner of bad things may happen.
=20
=20
Thank you for showing up the bug -- I'll fix it.
=20
Simon
=20
------_=_NextPart_001_01C2E6E4.B7834A51
Content-Type: text/html;
charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
------------------------------------------------------=
---------------------------------------------
data AParser String =3D AP
{apapply::([String]->[(String,[String])])}
Whoa! You can’t declare =
a data type
like that! You must have a type variable after the data type name, =
thus:
=
data AParser a =3D AP =
....
It’s an egregious bug that =
GHC does
not reject your data type declaration.
After that, all bets are off. =
Some
deeply-wired-in invariant is not being obeyed, and all manner of bad =
things may
happen.
Thank you for showing up the bug -- =
I’ll
fix it.
Simon
------_=_NextPart_001_01C2E6E4.B7834A51--
--------------InterScan_NT_MIME_Boundary--
From alastair@reid-consulting-uk.ltd.uk Mon Mar 10 11:30:01 2003
From: alastair@reid-consulting-uk.ltd.uk (Alastair Reid)
Date: Mon, 10 Mar 2003 11:30:01 +0000
Subject: Alternatives to finalization
In-Reply-To: <20030310005900.342e6750.nick.name@inwind.it> (Nick Name's
message of
"Mon, 10 Mar 2003 00:59:00 +0100")
References: <20030310005900.342e6750.nick.name@inwind.it>
Message-ID:
Nick Name contemplates two ways of finalizing
external resources:
> [lots of context deleted]
> f :: IO [a]
> f = do
> allocateResource
> l <- makeTheStream
> addFinalizer l (disallocateResource)
> return l
> [snip]
>
> Another alternative is to make f return an esplicit "close stream"
> action:
>
> f :: IO ([a],IO ())
>
> Is anyone willing to explain me other alternatives if there are, or
> to tell me that there aren't?
The second form (explicit release of resources) is better when:
1) It is important to release resources promptly (because they are
scarce or expensive).
2) It is easy to identify the last use of the resource and to call
the finalizer explicitly.
This usually requires that your code be strict and that you are in
the IO monad.
3) If there is any chance that you could release the resource too early,
you have a good way of detecting the problem and propagating an
appropriate error value or exception.
Detection is usually easy to arrange using a Haskell proxy which
records whether the finalizer has been called.
Reporting the problem can usually be done using the Maybe type,
Haskell 98 style IOErrors or Asynchronous Exceptions.
The first form is better when any of these do not hold. The best
example where automatic finalization is appropriate is the
hGetContents function (which your function 'f' seems to resemble).
Laziness makes it hard to predict the lifetime of the stream. The
code consuming the stream tends to be pure so there's no obvious place
to call the finalizer from. And, finally, the code consuming the
stream is unlikely to respond well to an exception being raised
because, more than likely, it was written for use in a context where
exceptions meant complete failure not failure of an IO operation.
Nick name says that a problem with the first is:
> The problem is that if no memory is allocated, no garbage collection
> happens; of course finalization is not guaranteed, as the manual
> states.
Haskell code tends to consume memory at a fairly constant rate so, as
long as your program is not blocked waiting for input, you should be
consuming memory. You then need to tweak the configuration of the
garbage collector (+RTS -h... ...-RTS in GHC) to make the GC trigger
at the desired frequency.
You should also use the garbageCollect function (part of the FFI
specification) to let you explicitly invoke the garbage collector.
You might call this immediately before any blocking IO operations.
Calling the GC too often can be expensive. In an image processing
system at Yale, we built a tiny 'model' of the resource usage to try
to call the GC only when it might plausibly release resources (or when
we were very short of resources). The idea was to track how many
resources were allocated and to try to estimate (based on past
behaviour) how many of those are likely to be released if we were to
call GC now. We'd then only call the GC if the overhead (ratio of
collectable resources to required resources) exceeded some threshold.
Hope this is of some help
--
Alastair Reid alastair@reid-consulting-uk.ltd.uk
Reid Consulting (UK) Limited http://www.reid-consulting-uk.ltd.uk/alastair/
From chak@cse.unsw.edu.au Mon Mar 10 22:30:50 2003
From: chak@cse.unsw.edu.au (Manuel M T Chakravarty)
Date: Tue, 11 Mar 2003 09:30:50 +1100 (EST)
Subject: Alternatives to finalization
In-Reply-To: <20030310005900.342e6750.nick.name@inwind.it>
References: <20030310005900.342e6750.nick.name@inwind.it>
Message-ID: <20030311.093050.1036149216.chak@cse.unsw.edu.au>
Nick Name wrote,
> As the result of a conversation on haskell-gui, I have tried to
> implement the disallocation of resources when a stream is garbage
> collected.
>
> To explain myself:
>
> I have a function
>
> f :: IO [a]
>
> which returns a lazy stream after allocating some resource to feed it
> (say installing a callback).
>
> I wish that the resource could be disallocated when it's no longer used.
> I did the obvious implementation with Weak.addFinalizer; results are
> encouraging but not completely satisfying; the scheme I used is:
>
> f = do
> allocateResource
> l <- makeTheStream
> addFinalizer l (disallocateResource)
> return l
>
> The problem is that if no memory is allocated, no garbage collection
> happens; of course finalization is not guaranteed, as the manual states.
You may want to have a look at how ports are closed by
finalizers in the Haskell Ports Library:
http://www.cse.unsw.edu.au/~chak/haskell/ports/
It seems that the set up there is similar to yours.
Cheers,
Manuel
From john@repetae.net Tue Mar 11 00:38:24 2003
From: john@repetae.net (John Meacham)
Date: Mon, 10 Mar 2003 16:38:24 -0800
Subject: Alternatives to finalization
In-Reply-To: <20030310005900.342e6750.nick.name@inwind.it>
References: <20030310005900.342e6750.nick.name@inwind.it>
Message-ID: <20030311003824.GA5258@momenergy.repetae.net>
another possibility is a withStream type function which explicitly
finalizes.
withStream :: Stream a -> ([a] -> IO b) -> IO b
the idea being the stream is freed when the IO b finishes.
this can easily be built on your explicit 'close stream' version below,
but may not be flexable enough for what people want to do with streams.
John
On Mon, Mar 10, 2003 at 12:59:00AM +0100, Nick Name wrote:
> As the result of a conversation on haskell-gui, I have tried to
> implement the disallocation of resources when a stream is garbage
> collected.
>
> To explain myself:
>
> I have a function
>
> f :: IO [a]
>
> which returns a lazy stream after allocating some resource to feed it
> (say installing a callback).
>
> I wish that the resource could be disallocated when it's no longer used.
> I did the obvious implementation with Weak.addFinalizer; results are
> encouraging but not completely satisfying; the scheme I used is:
>
> f = do
> allocateResource
> l <- makeTheStream
> addFinalizer l (disallocateResource)
> return l
>
> The problem is that if no memory is allocated, no garbage collection
> happens; of course finalization is not guaranteed, as the manual states.
>
> Another alternative is to make f return an esplicit "close stream"
> action:
>
> f :: IO ([a],IO ())
>
> Is anyone willing to explain me other alternatives if there are, or to
> tell me that there aren't?
>
> Thanks for attention
>
> Vincenzo
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
--
---------------------------------------------------------------------------
John Meacham - California Institute of Technology, Alum. - john@foo.net
---------------------------------------------------------------------------
From afie@cs.uu.nl Tue Mar 11 10:30:47 2003
From: afie@cs.uu.nl (Arjan van IJzendoorn)
Date: Tue, 11 Mar 2003 11:30:47 +0100
Subject: ANNOUNCE: Helium, for Learning Haskell, version 1.1
Message-ID: <00a701c2e7b9$481c1080$ec50d383@sushi>
Dear all,
We are proud to announce version 1.1 of Helium. It can
be found at the Helium website:
http://www.cs.uu.nl/~afie/helium/
Version 1.1 has the following improvements:
- An installer for Windows systems for an improved out-of-
the-box experience.
- A cool Java-based graphical interpreter called Hint
written by a student at our institute. It has a nice GUI
with colours, toolbar buttons and menu's. The best feature
is that it integrates with your favourite editor and you
can jump to the exact locations of messages by clicking on
them!
- New warnings and hints for common mistakes: "sin .3",
"X = 5" (see below for examples of messages)
- Completely new presentation of type errors with more
information
- Much improved syntax error messages thanks to a new lexer.
And thanks to Parsec we can tell not only what was
unexpected, but also what would be legal at that position.
- The command-line interpreter is now called 'texthint' to
avoid conflicts with hmake's 'hi' (sorry!). TextHint is
improved in many ways. For one, it now accepts file
paths after :l. Other improvements can be found if you
type :?
- User manuals for the different tools (helium, hint,
texthint) and other helpful information on the Helium
website
- We've compiled Helium with Oxygen (ghc -O2) and this makes
the compiler twice as fast. Great work, GHC people!
- One well-placed 'seq' makes Helium another 25% faster.
- Very many minor bug fixes
- The webpage is simpler, wider and easier to navigate thanks
to a road map
Have fun!
the Helium team
--
Examples of Helium messages
These messages where generated by typing expressions on the
texthint prompt. If you compile a file with these errors you
will get exact error locations.
Prelude> [(1, 3]
Unexpected close bracket ']'
Hint: Expecting a close bracket for '('
Prelude> sinn .2
Warning: Function composition (.) immediately followed by number
Hint: If a Float was meant, write "0.2"
Otherwise, insert a space for readability
Undefined variable "sinn"
Hint: Did you mean "sin" ?
Prelude> map [1..10] even
Type error in application
expression : map [1 .. 10] even
term : map
type : (a -> b) -> [a] -> [b]
does not match : [Int] -> (Int -> Bool) -> c
probable fix : re-order arguments
Prelude> let X = 5 in X
Left hand side pattern defines no variables
Undefined constructor "X"
Hint: Use identifiers starting with a lower case letter
to define a function or a variable
Undefined constructor "X"
Prelude> 1+chr '0'
Type error in variable
expression : chr
type : Int -> Char
expected type : Char -> Int
probable fix : use ord instead
From nick.name@inwind.it Tue Mar 11 12:41:33 2003
From: nick.name@inwind.it (Nick Name)
Date: Tue, 11 Mar 2003 13:41:33 +0100
Subject: Alternatives to finalization - the fourth child?
In-Reply-To:
References: <20030310005900.342e6750.nick.name@inwind.it>
Message-ID: <20030311134133.15c1d8ba.nick.name@inwind.it>
On Mon, 10 Mar 2003 11:30:01 +0000
Alastair Reid wrote:
> Nick name says that a problem with the first is:
> > The problem is that if no memory is allocated, no garbage collection
> > happens; of course finalization is not guaranteed, as the manual
> > states.
>
> Haskell code tends to consume memory at a fairly constant rate so, as
> long as your program is not blocked waiting for input, you should be
> consuming memory. You then need to tweak the configuration of the
> garbage collector (+RTS -h... ...-RTS in GHC) to make the GC trigger
> at the desired frequency.
Ok, today the combination of compilers/libraries I use have *decided* I
won't do tests any longer :(
=== Talking about the "f :: IO [a]" approach
On my first test, if I had the program waiting there for events, I
didn't see the finalizer at work, even if calling "performGC" ***inside
the event handler*** (handling a mouse motion event). I saw the mouse
motion handler print and print debug information, but never the
finalizer printing that "callback uninstalled".
However, calling a "print fib 100" somewhere in my main function shows
that finalizers really work sometimes. I see you (the FFI team) have had
a very long discussion on finalizers, but I have not the skills to
understand it fully.
I guess the main problem here is that I am giving up the control of
disallocating a resource (the callback) to an entity (the garbage
collector) wich cares about a *different* resource, with *different*
cost (the memory); however, when the programs is at work, garbage IS
collected and so I guess the solution is pretty satisfying in general.
=== The fourth child ???
Now, I think, if one had a resource wich he really cares about more than
memory and threads or timers, and if he was still wishing to give a
stream produced with this resource around to threads and pure functions,
he could...
... produce a stream with some "unsafeInterleaveIO" operations; each of
these operations:
1. checks for the existence of the resource
2. if necessary allocates it
3. anyway, retrigger a timer wich, at timeout, deallocates the resource
Step 2 can be replaced with
2'. if the resource doesn't exist, then it's time to return the infamous
empty list
What do you think of this approach? Have you ever tried it? (of course,
with this formulation, in general I guess timeouts are standard practice
with scarce resources).
And, the timeout can be replaced with "another one wants my resource".
And, is it time to reopen that operating systems book? :)
Vincenzo
From pavel@joker.botik.ru Wed Mar 12 12:55:27 2003
From: pavel@joker.botik.ru (Pavel G. Zhbanov)
Date: Wed, 12 Mar 2003 15:55:27 +0300
Subject: Explicit function call
Message-ID: <20030312125527.GA28305@joker.botik.ru>
Hello,
How can I make an explicit function call in a "do" sequence?
Ex:
... do let a = myFunc ...
b = myFunc ...
c = "Something else"
return c
...
As I understand myFunc will not be executed, but I need it...
Please, help.
--
Pavel Zhbanov
From afie@cs.uu.nl Wed Mar 12 13:02:41 2003
From: afie@cs.uu.nl (Arjan van IJzendoorn)
Date: Wed, 12 Mar 2003 14:02:41 +0100
Subject: Explicit function call
References: <20030312125527.GA28305@joker.botik.ru>
Message-ID: <008401c2e897$aac295e0$ec50d383@sushi>
> How can I make an explicit function call in a "do" sequence?
>
> Ex:
> ... do let a = myFunc ...
> b = myFunc ...
> c = "Something else"
> return c
> ...
>
> As I understand myFunc will not be executed,
Correct.
> but I need it...
If it has a side effect, it will have type "IO something" (or whatever monad
your using) and you can write:
do a <- myFunc ...
If it doesn't have a side effect, why do it anyway? The result 'c' does not
depend on a.
Arjan
From pavel@joker.botik.ru Wed Mar 12 13:06:56 2003
From: pavel@joker.botik.ru (Pavel G. Zhbanov)
Date: Wed, 12 Mar 2003 16:06:56 +0300
Subject: Explicit function call
In-Reply-To: <008401c2e897$aac295e0$ec50d383@sushi>
References: <20030312125527.GA28305@joker.botik.ru>
<008401c2e897$aac295e0$ec50d383@sushi>
Message-ID: <20030312130656.GB28305@joker.botik.ru>
>
> If it doesn't have a side effect, why do it anyway? The result 'c' does not
> depend on a.
>
myFunc uses IORef and it's (IORef's) result I use afterwards in some
other functions.
--
Pavel Zhbanov
From jcast@ou.edu Wed Mar 12 13:52:52 2003
From: jcast@ou.edu (Jon Cast)
Date: Wed, 12 Mar 2003 07:52:52 -0600
Subject: Explicit function call
In-Reply-To: Message from pavel@joker.botik.ru (Pavel G. Zhbanov) of
"Wed, 12 Mar 2003 16:06:56 +0300."
<20030312130656.GB28305@joker.botik.ru>
References: <20030312125527.GA28305@joker.botik.ru>
<008401c2e897$aac295e0$ec50d383@sushi>
<20030312130656.GB28305@joker.botik.ru>
Message-ID: <20030312135256.CF95A4A6B0@jcomain>
pavel@joker.botik.ru (Pavel G. Zhbanov) wrote:
> > If it doesn't have a side effect, why do it anyway? The result 'c'
> > does not depend on a.
> myFunc uses IORef and it's (IORef's) result I use afterwards in some
> other functions.
OK: what is myFunc's type? If it ends in IO alpha, for some alpha, you
can say: do a <- myFunc ... etc. If it doesn't, then you should
probably re-think its definition.
Jon Cast
From pavel@joker.botik.ru Wed Mar 12 14:26:54 2003
From: pavel@joker.botik.ru (Pavel G. Zhbanov)
Date: Wed, 12 Mar 2003 17:26:54 +0300
Subject: Explicit function call
In-Reply-To: <20030312135256.CF95A4A6B0@jcomain>
References: <20030312125527.GA28305@joker.botik.ru>
<008401c2e897$aac295e0$ec50d383@sushi>
<20030312130656.GB28305@joker.botik.ru>
<20030312135256.CF95A4A6B0@jcomain>
Message-ID: <20030312142654.GA29385@joker.botik.ru>
On Wed, Mar 12, 2003 at 07:52:52AM -0600, Jon Cast wrote:
> pavel@joker.botik.ru (Pavel G. Zhbanov) wrote:
> > > If it doesn't have a side effect, why do it anyway? The result 'c'
> > > does not depend on a.
>
> > myFunc uses IORef and it's (IORef's) result I use afterwards in some
> > other functions.
>
> OK: what is myFunc's type? If it ends in IO alpha, for some alpha, you
> can say: do a <- myFunc ... etc. If it doesn't, then you should
> probably re-think its definition.
>
> Jon Cast
myFunc :: a -> [b]
(a and b are my own types)
Actually, inside myFunc I used unsafePerformIO (didn't want to change
the whole programm just because of one function). The purpose of myFunc
is to append some value to "some list" lying somewhere (somewhere is
"defined" by IORef), store the resulting list and return a copy.
I want to do something like this (in a sequence):
append two values to "some list" , then call a function (myFunc2) that
uses "some list" and return the value returned by myFunc2.
--
Pavel Zhbanov
From glynn.clements@virgin.net Wed Mar 12 14:27:14 2003
From: glynn.clements@virgin.net (Glynn Clements)
Date: Wed, 12 Mar 2003 14:27:14 +0000
Subject: Explicit function call
In-Reply-To: <20030312142654.GA29385@joker.botik.ru>
References: <20030312125527.GA28305@joker.botik.ru>
<008401c2e897$aac295e0$ec50d383@sushi>
<20030312130656.GB28305@joker.botik.ru>
<20030312135256.CF95A4A6B0@jcomain>
<20030312142654.GA29385@joker.botik.ru>
Message-ID: <15983.17346.372212.31479@cerise.nosuchdomain.co.uk>
Pavel G. Zhbanov wrote:
> > > > If it doesn't have a side effect, why do it anyway? The result 'c'
> > > > does not depend on a.
> >
> > > myFunc uses IORef and it's (IORef's) result I use afterwards in some
> > > other functions.
> >
> > OK: what is myFunc's type? If it ends in IO alpha, for some alpha, you
> > can say: do a <- myFunc ... etc. If it doesn't, then you should
> > probably re-think its definition.
>
> myFunc :: a -> [b]
> (a and b are my own types)
>
> Actually, inside myFunc I used unsafePerformIO (didn't want to change
> the whole programm just because of one function). The purpose of myFunc
> is to append some value to "some list" lying somewhere (somewhere is
> "defined" by IORef), store the resulting list and return a copy.
There's a reason why the name unsafePerformIO begins with "unsafe". It
is *not* a magic wand that can simply get rid of the "IO" whenever it
turns out to be inconvenient.
You need to change myFunc's type to:
myFunc :: a -> IO [b]
then use:
do a <- myFunc ...
--
Glynn Clements
From afie@cs.uu.nl Thu Mar 13 12:01:20 2003
From: afie@cs.uu.nl (Arjan van IJzendoorn)
Date: Thu, 13 Mar 2003 13:01:20 +0100
Subject: Learning Haskell, update
Message-ID: <00eb01c2e958$42a245c0$ec50d383@sushi>
Hi all,
I've removed the frequently asked questions box at the bottom. It was
unused.
Fritz Ruehr made a nice Learning Haskell logo. Thank you, Fritz!
NHC is compilable under Windows now, so the remark "no windows version" has
been removed.
Is there someone who wants to make a more decent language comparison table?
If not, I'm thinking of removing it. Many things are said about it already
in the comp.lang.functional FAQ.
Greetings, Arjan
From Tom.Pledger@peace.com Thu Mar 13 20:59:53 2003
From: Tom.Pledger@peace.com (Tom Pledger)
Date: Fri, 14 Mar 2003 09:59:53 +1300
Subject: How to search for a string sequence in a file a rewrite it???
In-Reply-To: <003401c2e99c$f896fd50$0800a8c0@thenorio>
References:
<003401c2e99c$f896fd50$0800a8c0@thenorio>
Message-ID: <15984.61769.688226.77805@tux-17.corp.peace.com>
(moving to haskell-cafe)
Alexandre Weffort Thenorio writes:
| Ooops a small error before but here is the right one.
|
| Great. I got almost everything. My problem now is:
|
| I got a function called findstr where
|
| findstr "aaaa" "zzzzz" ["xxxxaaaa","xxxaaaaxxx"] =
| ["xxxxzzzzz","xxxzzzzzxxx"]
with the inferred type
findstr :: String -> String -> [String] -> [String]
| and then I try something like
|
| fillIn lines = do
| bkfilled <- (findstr str str2 lines)
with the inferred type
(findstr str str2 lines) :: [String]
Note that [] (the list data constructor) is a monad. So, this 'do'
expression is in the [] monad, where perhaps you intended the IO
monad. Computations in the [] monad have the effect of iterating over
the elements of lists. So, the bound variable gets the inferred type
bkfilled :: String
which you've noticed in the error message.
| write bkfilled
|
| where write takes a [String] and concatenates it writing it to a file then.
| But I get this error saying:
|
| Expected Type: [String]
| Inferred Type: String
| In the first argument of 'write' namelly 'bkfilled'
| In a do expection pattern binding: write bkfilled
|
| Any idea?? I mean bkfilled is supposed to be [String] but it says it is a
| String, any idea why???
The smallest code change to fix this is to add a 'return', which will
wrap another monad (in this case, IO) around findstr's [String] result...
> fillIn lines = do
> bkfilled <- return (findstr str str2 lines)
> write bkfilled
... but you should be able to simplify that code, using one of the
monad laws in http://haskell.org/onlinereport/basic.html#sect6.3.6
Regards,
Tom
From oleg_inconnu@myrealbox.com Fri Mar 14 11:23:41 2003
From: oleg_inconnu@myrealbox.com (Oleg)
Date: Fri, 14 Mar 2003 06:23:41 -0500
Subject: Redefining methods in a subCLASS
Message-ID: <200303140623.41686.oleg_inconnu@myrealbox.com>
Hi
Is it possible to redefine methods in a subclass (not an instance)? E.g. I get
errors in
class (Show a) => Employee a where
speak :: a -> [Char]
speak x = "Employee: " ++ (show x)
class (Employee a) => Manager a where
speak x = "Manager: " ++ (show x)
Thanks
Oleg
From Markus.Schnell@infineon.com Fri Mar 14 11:26:29 2003
From: Markus.Schnell@infineon.com (Markus.Schnell@infineon.com)
Date: Fri, 14 Mar 2003 12:26:29 +0100
Subject: AW: How to read an initialization file.
Message-ID:
I would recommend reading the variables in the main
and pack the rest of your program into a monad.
But only if you really need to access the variables
from everywhere and don't want to pass them around
explicitely.
Markus
> I need to be able to access these values effieiently and from
> virtually anywhere in the program. It would be nice to "at some
> point" open the file and read all these variables, all at once.
From nick.name@inwind.it Sat Mar 15 19:01:32 2003
From: nick.name@inwind.it (Nick Name)
Date: Sat, 15 Mar 2003 20:01:32 +0100
Subject: Problem with hugs, concurrency and unsafeInterleaveIO (maybe a bug?)
Message-ID: <20030315200132.1d560866.nick.name@inwind.it>
I am trying to lazily wait an MVar in hugs, in conjunction with
concurrent haskell:
-----
import Concurrent
import IOExts
f = do
v <- newEmptyMVar
c <- getContents
forkIO (putMVar v (head c))
r <- unsafeInterleaveIO (takeMVar v)
return v
f2 = f >>= unsafeInterleaveIO . takeMVar
main1 = f >>= takeMVar >>= print
main2 = f2 >>= print
main3 = f2 >>= (\ x -> yield >> print x)
-----
main1 and main3 work flawlessly, but main2 aborts with "no more threads
to run".
I think that main2 should work, because in evaluating the result of f2,
the main thread should suspend and yield.
Is there somebody who wants to enlighten me?
Vincenzo
From alastair@reid-consulting-uk.ltd.uk Sun Mar 16 21:04:43 2003
From: alastair@reid-consulting-uk.ltd.uk (Alastair Reid)
Date: Sun, 16 Mar 2003 21:04:43 +0000
Subject: Problem with hugs, concurrency and unsafeInterleaveIO (maybe
a bug?)
In-Reply-To: <20030315200132.1d560866.nick.name@inwind.it> (Nick Name's
message of
"Sat, 15 Mar 2003 20:01:32 +0100")
References: <20030315200132.1d560866.nick.name@inwind.it>
Message-ID:
> I am trying to lazily wait an MVar in hugs, in conjunction with
> concurrent haskell:
>
> [code snipped]
>
> I think that main2 should work, because in evaluating the result of
> f2, the main thread should suspend and yield.
Hugs creates a fresh scheduler instance for each invocation of
unsafePerformIO and unsafeInterleaveIO. I think your code requires
threads to be able to 'migrate' from one scheduler instance to
another.
Hugs can, perhaps, be made a little more flexible by maintaining a
single pool of runnable threads. There are limits to how far we can
go though because (very roughly speaking) we have to be able to 'find'
the right instance of unsafePerformIO to 'awaken' when the relevant
thread completes. The difficulty is that those instances are stored
on the C stack and must be awakened in the right order.
--
Alastair Reid alastair@reid-consulting-uk.ltd.uk
Reid Consulting (UK) Limited http://www.reid-consulting-uk.ltd.uk/alastair/
From cmoline@shaw.ca Tue Mar 18 02:19:19 2003
From: cmoline@shaw.ca (Chris Moline)
Date: 17 Mar 2003 19:19:19 -0700
Subject: [OT[ proving programs for novices
Message-ID: <1047953959.57970.73.camel@localhost>
hi. this isnt a haskell question but i am hoping you will forgive it.
i was wondering where i could find books/websites/tutorials on how to
construct proofs and how to prove programs. preferably books that are
aimed at novices with some programming experience but little math/logic
experience.
i have paul hudaks hsoe book which has some material on proving
properties of programs.
sincerely
chris moline
From hrichrds@swbell.net Tue Mar 18 03:23:42 2003
From: hrichrds@swbell.net (Hamilton Richards)
Date: Mon, 17 Mar 2003 21:23:42 -0600
Subject: [OT[ proving programs for novices
In-Reply-To: <1047953959.57970.73.camel@localhost>
References: <1047953959.57970.73.camel@localhost>
Message-ID:
At 7:19 PM -0700 3/17/03, Chris Moline wrote:
>hi. this isnt a haskell question but i am hoping you will forgive it.
>
>i was wondering where i could find books/websites/tutorials on how to
>construct proofs and how to prove programs. preferably books that are
>aimed at novices with some programming experience but little math/logic
>experience.
For imperative programming:
D. Gries, The Science of Programming. Springer Verlag, New York, 1981.
E.W. Dijkstra, A Discipline of Programming. Prentice-Hall, 1975.
For functional programming:
R. Bird, Introduction to Functional Programming using Haskell,
2nd edition. Prentice-Hall, 1998.
--
------------------------------------------------------------------
Hamilton Richards Department of Computer Sciences
Senior Lecturer The University of Texas at Austin
512-471-9525 1 University Station C0500
Taylor Hall 5.138 Austin, Texas 78712-1188
ham@cs.utexas.edu hrichrds@swbell.net
------------------------------------------------------------------
From wtwjek@winternet.com Wed Mar 19 01:05:47 2003
From: wtwjek@winternet.com (Bill Wood)
Date: Tue, 18 Mar 2003 19:05:47 -0600
Subject: [OT[ proving programs for novices
References: <1047953959.57970.73.camel@localhost>
Message-ID: <3E77C26B.D4F97051@winternet.com>
. . .
> For imperative programming:
>
> D. Gries, The Science of Programming. Springer Verlag, New York, 1981.
>
> E.W. Dijkstra, A Discipline of Programming. Prentice-Hall, 1975.
These are two excellant sources; I've learned from each and taught from
each.
However, they are both a bit stiff for the student with little
background in
logic or mathematics. Several texts did come out in the late 80's that
taught
the same approach from a more elementary starting point. Three such are
E.W.Dijkstra and W.H.J. Feijen, A Method of Programming,
Addison-Wesley, 1988,
ISBN 0-201-17536-3
Geoff Dromey, Program Derivation/The Development of Programs from
Specifications, Addison-Wesley, 1989, ISBN 0-201-41624-7
Edward Cohen, Programming in the 1990s, Springer-Verlag, 1990,
ISBN 0-387-97382-6
> For functional programming:
>
> R. Bird, Introduction to Functional Programming using Haskell,
> 2nd edition. Prentice-Hall, 1998.
I'd like to hear abut more sources here as well. I've started in on
Richard Bird and Oege de Moor, Algebra of Programming, Prentice
Hall,1997,
ISBN 0-13-507245-X
but it is hardly elementary!
Another very interesting text is
John Cooke, Constructing Correct Software/the basics,
Springer-Verlag,
1988, ISBN 3-540-76156-X
which almost combines imperative and functional programming (and
logical)
by presenting a method of transforming (logical) specifications through
functions into imperative programs.
-- Bill Wood
wtwjek@winternet.com
From tuyencn@yahoo.co.uk Tue Mar 25 07:49:14 2003
From: tuyencn@yahoo.co.uk (=?iso-8859-1?q?tuyen=20pham?=)
Date: Tue, 25 Mar 2003 07:49:14 +0000 (GMT)
Subject: shortest path with Haskell
Message-ID: <20030325074914.86597.qmail@web41303.mail.yahoo.com>
Hi every one !
I have a big problem with implementation the
Dijkstra's shortest path with Haskell .the condition
is it must be implemented with priority queue using
list (or tree).Any of yo have the code for this ? I
really
really needs for help !!!
thankssssssss a lot!!!!!!
pham
__________________________________________________
Do You Yahoo!?
Everything you'll ever need on one web page
from News and Sport to Email and Music Charts
http://uk.my.yahoo.com
From Keith.Wansbrough@cl.cam.ac.uk Tue Mar 25 10:19:56 2003
From: Keith.Wansbrough@cl.cam.ac.uk (Keith Wansbrough)
Date: Tue, 25 Mar 2003 10:19:56 +0000
Subject: shortest path with Haskell
In-Reply-To: Your message of
"Tue, 25 Mar 2003 07:49:14 GMT."
<20030325074914.86597.qmail@web41303.mail.yahoo.com>
Message-ID:
> Hi every one !
> I have a big problem with implementation the
> Dijkstra's shortest path with Haskell .the condition
> is it must be implemented with priority queue using
> list (or tree).Any of yo have the code for this ? I
> really
> really needs for help !!!
> thankssssssss a lot!!!!!!
> pham
I suggest you ask your instructor/lecturer, or consult your textbook.
--KW 8-)
--
Keith Wansbrough
http://www.cl.cam.ac.uk/users/kw217/
University of Cambridge Computer Laboratory.
From mobm6@netscape.net Mon Mar 24 21:39:32 2003
From: mobm6@netscape.net (Mrs.Sese-seko)
Date: Mon, 24 Mar 2003 13:39:32 -0800
Subject: (no subject)
Message-ID: <20030325124541.0B7E3422078@www.haskell.org>
Dear friend=2C
I am Mrs=2E Sese-Seko widow of late president Mobutu Sese-Seko of zaire=3F now known as democratic republic of congo =28drc=29=2E I am moved to write you this letter=2C this was in confidence considering my present circumstance and situation=2E I escaped along with my husband and two of our sons Theophilus and Basher out of Democratic Republic of Congo =28DRC=29 to Abidjan=2C
cote d'ivoire where my family and I settled=2C while
we later moved to settled in morroco where my husband later died of cancer disease=2E
However due to this situation we decided to changed most of my husband's billions of dollars deposited in swiss bank and other countries into other forms of
money coded for safe purpose because the new head of
state of =28dr=29 Mr=2C laurent kabila has made arrangement with the swiss government and other european countries to freeze all my late husband's treasures deposited in
some european countries=2E hence my children and I decided laying low in Africa to study the situation till when things gets better=2E
Now that President kabila is dead and the son taking over =28Joseph kabila=29=2E one of my late husband's chateaux in southern france was confiscated by the french government=2C and as such I had to change my identity so that my investment will not be traced and confiscated=2E
I have deposited the sum Thirty Million United State Dollars=28US$30=2C000=2C000=2C00=2E=29 with a security company =2C for safekeeping=2E The funds are security coded to prevent them from knowing the content=2E
What I want you to do is to indicate your interest that you will assist us by receiving the money on our
behalf=2E
Acknowledge this message=2C so that I can introduce you to my son =28Theophilus=29 who has the out modalities
for the claim of the said funds=2E I want you to
assist in investing this money=2C but I will not want my identity revealed=2E
I will also want to buy properties and stock in multi-national companies and to engage in other safe
and non-speculative investments=2E May I at this point
emphasise the high level of confidentiality=2C which this business demands=2C and hope you will not
betray the trust and confidence=2C which I repose in you=2E in conclusion=2C if you want to assist us =2C my son shall put you in the true picture of the business=2C
tell you where the funds are currently being
maintained and also discuss other modalities including remuneration for your services=2E
For this reason kindly furnish us your contact information=2C that is your personal telephone
and fax number for confidential purpose=2E
Best regards=2C
Mrs=2Csese-seko
From karczma@info.unicaen.fr Tue Mar 25 13:10:56 2003
From: karczma@info.unicaen.fr (Jerzy Karczmarczuk)
Date: Tue, 25 Mar 2003 14:10:56 +0100
Subject: African money
References: <20030325124541.0B7E3422078@www.haskell.org>
Message-ID: <3E805560.1030407@info.unicaen.fr>
Dear friends,
Some of you know me personally. I am the son of hm., my father, who left
me hm., some money, which I have multiplied through an extremely fruitful
work on functional programming.
Anyway, I am willing to spend a part of this money on your behalf.
If somebody has any idea how to empoison, strangle, shoot, electrocute
or burn alive this annoying bastard who proposes regularly to everybody
on Internet all that financial transactions with Nigeria, Congo, etc.,
please contact me. You don't even need to do the dirty job. Just show
me this fellow, I'll dispatch him with my bare hands. (I realized that
shooting might be more difficult. As a part of my military training in
Poland I learned very well how to disassemble a Kalashnikov, even
blind-eyed. But being a pacifist, I refused to learn how to assemble
it back correctly.)
Aren't there any institutions who could stop that, otherwise? Together
with others who propose to change $25 into billions, or to enlarge some
interesting parts of a male hardware?
Or tell me how to *effectively* filter all that away. Or, I'll go mad
and I strangle some of my students. Anyway they deserve it.
Yours friendly
Jerzy Karczmarczuk
From afie@cs.uu.nl Tue Mar 25 13:23:41 2003
From: afie@cs.uu.nl (Arjan van IJzendoorn)
Date: Tue, 25 Mar 2003 14:23:41 +0100
Subject: African money
References: <20030325124541.0B7E3422078@www.haskell.org>
<3E805560.1030407@info.unicaen.fr>
Message-ID: <01c201c2f2d1$c079ce50$ec50d383@sushi>
Hi Jerzy,
> If somebody has any idea how to empoison, strangle, shoot, electrocute
[...]
Violence is never the answer.
Maybe SpamAssassin is: http://spamassassin.org/
Ask your system administrator to install it. You will then have to write a
script in an ad-hoc, untyped, side-effecting language and gone is (most of)
the spam.
Greetings, Arjan
From peterson-john@cs.yale.edu Tue Mar 25 13:28:16 2003
From: peterson-john@cs.yale.edu (John Peterson)
Date: Tue, 25 Mar 2003 08:28:16 -0500
Subject: African money
In-Reply-To: <01c201c2f2d1$c079ce50$ec50d383@sushi> (afie@cs.uu.nl)
References: <20030325124541.0B7E3422078@www.haskell.org>
<3E805560.1030407@info.unicaen.fr> <01c201c2f2d1$c079ce50$ec50d383@sushi>
Message-ID: <200303251328.h2PDSGx24065@ragged.cs.yale.edu>
If the spam storm gets too heavy on haskell-cafe we can switch to
moderator approval as on the main Haskell list. We have the spam
assassin available at haskell.org but I've been reluctant to turn it
loose on the lists. Maybe the time has come ...
John
From pro@missioncriticalit.com Tue Mar 25 13:59:20 2003
From: pro@missioncriticalit.com (Peter Ross)
Date: Tue, 25 Mar 2003 14:59:20 +0100
Subject: African money
In-Reply-To: <3E805560.1030407@info.unicaen.fr>
References: <20030325124541.0B7E3422078@www.haskell.org>
<3E805560.1030407@info.unicaen.fr>
Message-ID: <20030325135920.GA25385@miscrit.be>
On Tue, Mar 25, 2003 at 02:10:56PM +0100, Jerzy Karczmarczuk wrote:
> Or tell me how to *effectively* filter all that away. Or, I'll go mad
> and I strangle some of my students. Anyway they deserve it.
>
I use bogofilter (bogofilter.sf.net). I am currently getting 98%
accuracy in filtering my email after about two months training and as
far as I know only a few false positives early in the training.
If you are on a windows box, then I would suggest looking at Popfilter
(popfilter.sf.net).
Hope this helps,
Pete
From mobm6@netscape.net Tue Mar 25 00:03:20 2003
From: mobm6@netscape.net (Mrs.Sese-seko)
Date: Mon, 24 Mar 2003 16:03:20 -0800
Subject: (no subject)
Message-ID: <20030325151200.1FB49422078@www.haskell.org>
Dear friend=2C
I am Mrs=2E Sese-Seko widow of late president Mobutu Sese-Seko of zaire=3F now known as democratic republic of congo =28drc=29=2E I am moved to write you this letter=2C this was in confidence considering my present circumstance and situation=2E I escaped along with my husband and two of our sons Theophilus and Basher out of Democratic Republic of Congo =28DRC=29 to Abidjan=2C
cote d'ivoire where my family and I settled=2C while
we later moved to settled in morroco where my husband later died of cancer disease=2E
However due to this situation we decided to changed most of my husband's billions of dollars deposited in swiss bank and other countries into other forms of
money coded for safe purpose because the new head of
state of =28dr=29 Mr=2C laurent kabila has made arrangement with the swiss government and other european countries to freeze all my late husband's treasures deposited in
some european countries=2E hence my children and I decided laying low in Africa to study the situation till when things gets better=2E
Now that President kabila is dead and the son taking over =28Joseph kabila=29=2E one of my late husband's chateaux in southern france was confiscated by the french government=2C and as such I had to change my identity so that my investment will not be traced and confiscated=2E
I have deposited the sum Thirty Million United State Dollars=28US$30=2C000=2C000=2C00=2E=29 with a security company =2C for safekeeping=2E The funds are security coded to prevent them from knowing the content=2E
What I want you to do is to indicate your interest that you will assist us by receiving the money on our
behalf=2E
Acknowledge this message=2C so that I can introduce you to my son =28Theophilus=29 who has the out modalities
for the claim of the said funds=2E I want you to
assist in investing this money=2C but I will not want my identity revealed=2E
I will also want to buy properties and stock in multi-national companies and to engage in other safe
and non-speculative investments=2E May I at this point
emphasise the high level of confidentiality=2C which this business demands=2C and hope you will not
betray the trust and confidence=2C which I repose in you=2E in conclusion=2C if you want to assist us =2C my son shall put you in the true picture of the business=2C
tell you where the funds are currently being
maintained and also discuss other modalities including remuneration for your services=2E
For this reason kindly furnish us your contact information=2C that is your personal telephone
and fax number for confidential purpose=2E
Best regards=2C
Mrs=2Csese-seko
From mark@chaos.x-philes.com Tue Mar 25 15:57:25 2003
From: mark@chaos.x-philes.com (Mark Carroll)
Date: Tue, 25 Mar 2003 10:57:25 -0500 (EST)
Subject: African money
In-Reply-To: <3E805560.1030407@info.unicaen.fr>
Message-ID:
On Tue, 25 Mar 2003, Jerzy Karczmarczuk wrote:
(snip)
> Anyway, I am willing to spend a part of this money on your behalf.
> If somebody has any idea how to empoison, strangle, shoot, electrocute
> or burn alive this annoying bastard who proposes regularly to everybody
> on Internet all that financial transactions with Nigeria, Congo, etc.,
> please contact me. You don't even need to do the dirty job. Just show
(snip)
Rich Kulawiec, on Dave Farber's Interesting People list, recently said
interesting things at http://tinyurl.com/84dm
Personally, I like SAUCE at http://tinyurl.com/84dp but it's not for
everyone, or even most people. (Needs to be attached to exim.)
ObHaskell: I have bought my own domain and have got to the point where
soon there will not be a public permanent e-mail address for me. I plan to
write software to help keep public addresses rolling over, keeping track
of which "private" addresses have been given to whom, what is whitelisted
and blacklisted, etc. I worry a bit about character IO being slow, but
maybe Haskell might be a good implementation language for this system.
Perhaps I'll have to look out for a library for parsing e-mail messages.
-- Mark
From d98macke@dtek.chalmers.se Tue Mar 25 20:44:08 2003
From: d98macke@dtek.chalmers.se (Marcus Lindblom)
Date: Tue, 25 Mar 2003 21:44:08 +0100
Subject: African money
Message-ID: <005a01c2f30f$48d4cd80$91f70bc1@fizzgig>
From: John Peterson
>
> If the spam storm gets too heavy on haskell-cafe we can switch to
> moderator approval as on the main Haskell list. We have the spam
> assassin available at haskell.org but I've been reluctant to turn it
> loose on the lists. Maybe the time has come ...
Many lists use moderator approval on non-list members. Maybe spam
assassin could be turned loose on just those non-member mails, and have
those passing through be moderator reviewed?
/Marcus
From simons@cryp.to Tue Mar 25 21:40:20 2003
From: simons@cryp.to (Peter Simons)
Date: 25 Mar 2003 22:40:20 +0100
Subject: parsing e-mail messages (Re: African money)
References: <3E805560.1030407@info.unicaen.fr>
Message-ID: <87he9runuj.fsf_-_@peti.cryp.to>
Mark Carroll writes:
> Perhaps I'll have to look out for a library for parsing e-mail
> messages.
I have written a set of parser functions for RFC 2822 messages, which
should do exactly that. It's not finished yet, but if you're
interested in using the code (and in providing feedback), I'll gladly
give you -- and anybody else, for that matter -- a copy.
Peter
From peterson-john@cs.yale.edu Wed Mar 26 00:19:32 2003
From: peterson-john@cs.yale.edu (John Peterson)
Date: Tue, 25 Mar 2003 19:19:32 -0500
Subject: African money
In-Reply-To: <005a01c2f30f$48d4cd80$91f70bc1@fizzgig>
(d98macke@dtek.chalmers.se)
References: <005a01c2f30f$48d4cd80$91f70bc1@fizzgig>
Message-ID: <200303260019.h2Q0JWc24664@ragged.cs.yale.edu>
I checked and we do have spam assassin running on all haskel.org
mail. The latest Nigerian spamlet somehow made it past -
unfortunately nobody has been keeping the spam rules up to date, The
mail haskell list is member only posting but not haskell-cafe. The
member only posting is slightly painful to keep in operation so we'd
prefer not to change the status of haskell-cafe unless things get
worse. Quite a few people subscribe to the haskell list and then find
that they aren't recognized as members because of slight differences
in the From: address so we have to manually approve post fairly often.
John
From ketil@ii.uib.no Wed Mar 26 06:49:10 2003
From: ketil@ii.uib.no (Ketil Z. Malde)
Date: 26 Mar 2003 07:49:10 +0100
Subject: parsing e-mail messages (Re: African money)
In-Reply-To: <87he9runuj.fsf_-_@peti.cryp.to>
References: <3E805560.1030407@info.unicaen.fr>
<87he9runuj.fsf_-_@peti.cryp.to>
Message-ID:
Peter Simons writes:
> Mark Carroll writes:
>> Perhaps I'll have to look out for a library for parsing e-mail
>> messages.
> I have written a set of parser functions for RFC 2822 messages, which
> should do exactly that. It's not finished yet, but if you're
> interested in using the code (and in providing feedback), I'll gladly
> give you -- and anybody else, for that matter -- a copy.
..and if anybody cares, I've cooked up functions that build word
frequency tables, and compare them using a Bayesian approach (more or
less like Paul Graham's "A Plan for Spam"). Haskell, of course.
Need a bit of tweaking, but works reasonably well, last time I
looked.
-kzm
--
If I haven't seen further, it is by standing in the footprints of giants
From kkyu@hotmail.com Tue Mar 25 15:28:21 2003
From: kkyu@hotmail.com (休闲一类)
Date: Tue, 25 Mar 2003 15:28:21
Subject: hi
Message-ID: <20030326072611.B4E12422078@www.haskell.org>
东方布包艺术网是一个配套服饰体系,主要产品为女性时尚休闲背包,
制作材料以棉麻布料为主,产品前卫出众又不失浪漫纯朴。充分体现
出现代都市女性所追求的简洁、大方、时尚休闲风格。装袋休闲的心情
,回归自然的舒坦中。一种仿佛时间逝去的感觉。色彩被湮没在都市的
环境中。所有的颜色看上去都像受过污染,有种烟雾蒙蒙的感觉。在寻
找自然色彩过程中发现,展示纯洁美的白色也成为闪亮点。
详细可以查看:http://www.fadcn.com http://www.sbxm.com
提供精品图书1.5-3折,人文类5-6折,经济类4-5折。
详细可查看:http://www.sky999.net
提供主机域名
QQ在线支持:124438130
使用极星邮件群发,无须通过邮件服务器,直达对方邮箱,速度绝对一流!
下载网址:http://www.lovexin.com,更多免费的超酷软件等你来下……
----------------------------------------------------
INFORMATION
This message has been sent using a trial-run version
of the TSmtpRelayServer Delphi Component.
----------------------------------------------------
From olczyk@interaccess.com Wed Mar 26 07:49:07 2003
From: olczyk@interaccess.com (Thaddeus L. Olczyk)
Date: Wed, 26 Mar 2003 01:49:07 -0600
Subject: African money
In-Reply-To: <20030325135920.GA25385@miscrit.be>
References: <20030325124541.0B7E3422078@www.haskell.org>
<3E805560.1030407@info.unicaen.fr> <20030325135920.GA25385@miscrit.be>
Message-ID:
On Tue, 25 Mar 2003 14:59:20 +0100, Peter Ross
wrote:
>On Tue, Mar 25, 2003 at 02:10:56PM +0100, Jerzy Karczmarczuk wrote:
>> Or tell me how to *effectively* filter all that away. Or, I'll go mad
>> and I strangle some of my students. Anyway they deserve it.
>>
>I use bogofilter (bogofilter.sf.net). I am currently getting 98%
>accuracy in filtering my email after about two months training and as
>far as I know only a few false positives early in the training.
>
>If you are on a windows box, then I would suggest looking at Popfilter
>(popfilter.sf.net).
^^^^^^^^^^^
This url is just a blank directory.
From pro@missioncriticalit.com Wed Mar 26 09:11:52 2003
From: pro@missioncriticalit.com (Peter Ross)
Date: Wed, 26 Mar 2003 10:11:52 +0100
Subject: African money
In-Reply-To:
References: <20030325124541.0B7E3422078@www.haskell.org>
<3E805560.1030407@info.unicaen.fr> <20030325135920.GA25385@miscrit.be>
Message-ID: <20030326091152.GA29655@miscrit.be>
On Wed, Mar 26, 2003 at 01:49:07AM -0600, Thaddeus L. Olczyk wrote:
> On Tue, 25 Mar 2003 14:59:20 +0100, Peter Ross
> wrote:
>
> >On Tue, Mar 25, 2003 at 02:10:56PM +0100, Jerzy Karczmarczuk wrote:
> >> Or tell me how to *effectively* filter all that away. Or, I'll go mad
> >> and I strangle some of my students. Anyway they deserve it.
> >>
> >I use bogofilter (bogofilter.sf.net). I am currently getting 98%
> >accuracy in filtering my email after about two months training and as
> >far as I know only a few false positives early in the training.
> >
> >If you are on a windows box, then I would suggest looking at Popfilter
> >(popfilter.sf.net).
> ^^^^^^^^^^^
> This url is just a blank directory.
I am sorry I got the name confused. It is actually called *popfile*.
The URL is popfile.sf.net
From nick.name@inwind.it Wed Mar 26 12:21:16 2003
From: nick.name@inwind.it (Nick Name)
Date: Wed, 26 Mar 2003 13:21:16 +0100
Subject: Asynchronous exceptions and "resume"
Message-ID: <20030326132116.4d358e0e.nick.name@inwind.it>
Hi all, is there a way, or is it planned to, or has anyone published
articles on... resuming from asynchronous exceptions?
I mean: it would be useful there was a
suspend :: ThreadID -> IO ()
where the result is the remaining computation of the other thread, wich
one could forkIO again, or simply run in the current thread.
If this is not possible, it would still be useful that the IO action
returned by "suspend" would only "resume" the other thread, as an
alternative to a brutal "kill" wich destroys any work done by the other
thread.
The first form seems interesting when one wants to fork off a long
computation, but wants the ability to wait for it again if necessary;
pointers to articles are always appreciated.
Vincenzo
From nick.name@inwind.it Wed Mar 26 12:23:37 2003
From: nick.name@inwind.it (Nick Name)
Date: Wed, 26 Mar 2003 13:23:37 +0100
Subject: Asynchronous exceptions and "resume"
In-Reply-To: <20030326132116.4d358e0e.nick.name@inwind.it>
References: <20030326132116.4d358e0e.nick.name@inwind.it>
Message-ID: <20030326132337.1753289f.nick.name@inwind.it>
On Wed, 26 Mar 2003 13:21:16 +0100
Nick Name wrote:
> suspend :: ThreadID -> IO ()
^^^^^
Oh, yes, I meant
suspend :: ThreadID -> IO (IO ())
V.
From simonmar@microsoft.com Wed Mar 26 14:35:33 2003
From: simonmar@microsoft.com (Simon Marlow)
Date: Wed, 26 Mar 2003 14:35:33 -0000
Subject: Asynchronous exceptions and "resume"
Message-ID: <9584A4A864BD8548932F2F88EB30D1C60C5F0A90@tvp-msg-01.europe.corp.microsoft.com>
> Hi all, is there a way, or is it planned to, or has anyone published
> articles on... resuming from asynchronous exceptions?
>=20
> I mean: it would be useful there was a=20
>=20
> suspend :: ThreadID -> IO ()
>=20
> where the result is the remaining computation of the other=20
> thread, wich
> one could forkIO again, or simply run in the current thread.=20
This is fairly easy to implement in GHC. Simple call
Schedule.c:raiseAsync() with NULL for the exception, and make it return
the final closure after it has stripped the thread's stack. Entering
that closure should restart the thread's computation exactly where it
left off. If the thread was blocked on something (eg. takeMVar), then
it should restart the blocking operation.
The types aren't quite right: the closure you get back will behave like
an application of unsafePerformIO, so you will need to wrap it using eg.
Control.Exception.evaluate to get an IO action.
I'm sure there are plenty of cool uses for this...
Cheers,
Simon
From droundy@abridgegame.org Wed Mar 26 15:23:51 2003
From: droundy@abridgegame.org (David Roundy)
Date: Wed, 26 Mar 2003 10:23:51 -0500
Subject: how to track down infinite loop?
Message-ID: <20030326152350.GA4863@jdj5.mit.edu>
Hello. I've got an infinite loop (I think) which I recently introduced to
my code (the visible symptom is stack space overflow), and am wondering if
there is an easier way to figure out where it might be. The problem being
that I've made a rather large number of changes (all of which are mutually
dependent).
In the past, I've used ghc's heap profiling to track this sort of thing
down, as I can pretty easily trace from that what functions were called in
the infinite loop. The problem I'm now having is that the string
describing the call stack is truncated too much, so I can't see who the
real culprit is.
I know the best thing would be to go over all my changes with a
fine-toothed comb, but it would be nice to have an idea where to look.
Actually, it's not all that much new code, but I usually find it hard to
see a bug that I've written myself...
Any ideas for tricks to see where a program is looping indefinitely? I'm
sure I can track down this bug pretty easily, but is seems like this is
something one really ought to be able to do...
--
David Roundy
http://civet.berkeley.edu/droundy/
From olaf@cs.york.ac.uk Wed Mar 26 18:24:04 2003
From: olaf@cs.york.ac.uk (Olaf Chitil)
Date: Wed, 26 Mar 2003 18:24:04 +0000
Subject: how to track down infinite loop?
References: <20030326152350.GA4863@jdj5.mit.edu>
Message-ID: <3E81F044.184E64B0@cs.york.ac.uk>
David Roundy wrote:
> Any ideas for tricks to see where a program is looping indefinitely? I'm
> sure I can track down this bug pretty easily, but is seems like this is
> something one really ought to be able to do...
May I answer your question by advertising the Haskell tracer Hat?
http://www.cs.york.ac.uk/fp/hat/
The various trace viewing tools of Hat show you your computation in
various ways and thus help you in particular to locate a fault. In your
case hat-trail is the right tool. Just start hat-trail with the trace of
your looping computation (you may interrupt the computation early to
save time and trace space; but note that a traced computation is
considerably slower). Then repeatedly press "enter" to see the whole
virtual stack. Each stack entry shows a function with its arguments in
most evaluated form.
I should point out that Hat works for Haskell 98; it supports only few
libraries and no ghc language extensions. Real soon we will release a
new version supporting more libraries, a few language extensions
(multiparameter classes, functional dependencies) and some other
improvements.
Ciao,
Olaf
--
OLAF CHITIL,
Dept. of Computer Science, The University of York, York YO10 5DD, UK.
URL: http://www.cs.york.ac.uk/~olaf/
Tel: +44 1904 434756; Fax: +44 1904 432767
From droundy@abridgegame.org Wed Mar 26 19:24:30 2003
From: droundy@abridgegame.org (David Roundy)
Date: Wed, 26 Mar 2003 14:24:30 -0500
Subject: how to track down infinite loop?
In-Reply-To: <200303260740.30146.moran@galois.com>
References: <20030326152350.GA4863@jdj5.mit.edu>
<200303260740.30146.moran@galois.com>
Message-ID: <20030326192429.GA14538@jdj5.mit.edu>
On Wed, Mar 26, 2003 at 07:40:30AM -0800, Andy Moran wrote:
> On Wednesday 26 March 2003 07:23 am, David Roundy wrote:
>
> I would try using Debug.Trace.trace. It takes a string and an expression,
> and returns the expressions while outputting the string to stderr (I
> think). You can choose your own mnemonics to prevent the truncation
> problem.
Thanks for the hint! I like trace, strongly reminiscent of the good old
technique of sprinkling printfs around. :)
It turned out the problem was running sequence on an infinite list of type
[Maybe a]. In retrospect obvious, but sort of hard to notice (especially
since the infinite list is created in a different module from the sequence
call. Fortunately, in this case it is safe to just truncate the list to
some large size (since the function in question is only used in the
quickChecking code, and not in the actual code).
--
David Roundy
http://civet.berkeley.edu/droundy/
From droundy@abridgegame.org Thu Mar 27 23:08:05 2003
From: droundy@abridgegame.org (David Roundy)
Date: Thu, 27 Mar 2003 18:08:05 -0500
Subject: how to use POSIX function utime?
Message-ID: <20030327230805.GC1803@jdj5.mit.edu>
I'm trying to figure out how to use the POSIX function utime. I'm pretty
much stumped at the moment, largely because I can't figure out how to do
anything useful with ClockTime variables.
I can't see any way to make use of GHC.Posix.utime, as it gives a binding
to the utime function, but the argument is of type Ptr (), and I can't see
how to make this to a pointer to the contents of a pair of ClockTimes.
I had thought that I could just write my own utime wrapper in C, but I'm
still stumped on getting anything out of a ClockTime! The problem is that I
would like my code to be portable, so I can't assume a ClockTime is a
UInt32 (or that a time_t is a 32 bit int). Any ideas how I can get around
this?
The only idea I have at the moment is to define a MyClockTime which is
always a UInt64 and then do in my C wrapper I could cast back and forth
from time_t to an int64 type. Ugh.
--
David Roundy
http://www.abridgegame.org
From glynn.clements@virgin.net Fri Mar 28 01:39:13 2003
From: glynn.clements@virgin.net (Glynn Clements)
Date: Fri, 28 Mar 2003 01:39:13 +0000
Subject: how to use POSIX function utime?
In-Reply-To: <20030327230805.GC1803@jdj5.mit.edu>
References: <20030327230805.GC1803@jdj5.mit.edu>
Message-ID: <16003.42945.457914.134095@cerise.nosuchdomain.co.uk>
David Roundy wrote:
> I'm trying to figure out how to use the POSIX function utime. I'm pretty
> much stumped at the moment, largely because I can't figure out how to do
> anything useful with ClockTime variables.
>
> I can't see any way to make use of GHC.Posix.utime, as it gives a binding
> to the utime function, but the argument is of type Ptr (), and I can't see
> how to make this to a pointer to the contents of a pair of ClockTimes.
>
> I had thought that I could just write my own utime wrapper in C, but I'm
> still stumped on getting anything out of a ClockTime! The problem is that I
> would like my code to be portable, so I can't assume a ClockTime is a
> UInt32 (or that a time_t is a 32 bit int). Any ideas how I can get around
> this?
AFAICT, the correct interface is Posix.setFileTimes:
setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
setFileTimes name atime mtime = do
...
EpochTime is the Haskell equivalent of C's time_t (integral number of
seconds since the epoch).
--
Glynn Clements
From droundy@abridgegame.org Fri Mar 28 14:30:56 2003
From: droundy@abridgegame.org (David Roundy)
Date: Fri, 28 Mar 2003 09:30:56 -0500
Subject: how to use POSIX function utime?
In-Reply-To: <16003.42945.457914.134095@cerise.nosuchdomain.co.uk>
References: <20030327230805.GC1803@jdj5.mit.edu>
<16003.42945.457914.134095@cerise.nosuchdomain.co.uk>
Message-ID: <20030328110054.GA1576@jdj5.mit.edu>
On Fri, Mar 28, 2003 at 01:39:13AM +0000, Glynn Clements wrote:
>
> AFAICT, the correct interface is Posix.setFileTimes:
>
> setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO ()
> setFileTimes name atime mtime = do
> ...
>
> EpochTime is the Haskell equivalent of C's time_t (integral number of
> seconds since the epoch).
Thanks for the pointer! It seems I had totally missed the documentation on
hslibs, and was thus looking in entirely the wrong place. (Feeling
somewhat foolish...)
--
David Roundy
http://civet.berkeley.edu/droundy/