Many thanks to both Georg and Lemmih. Actually, I had considered laziness,
but I didn't pursue it enough. I tried one version of runNReps in which I
passed (f x) as an additional arg; when that didn't work, a little thought
convinced me that laziness was doing me in. I also tried another approac
Hi Bill,
You know, Haskell is so smart that it realised that you want to measure it and
therefore it performs very good -- NO, I am just kidding!
Welcome to lazy programming!
The thing is, that you don't force the evaluation of the result of you function
f. Therefore you program doesn't bother to
On Mon, 17 Jan 2005 10:48:18 -0600, jekwtw <[EMAIL PROTECTED]> wrote:
>
> I'm putting together a script to gather run-time stats for some functions
> I'm working with, and I'm having a terrible time. My strategy is to
> evaluate a function a number of times and compute the difference between the
I'm putting together a script to gather run-time stats for some
functions I'm working with, and I'm having a terrible time. My strategy is
to evaluate a function a number of times and compute the difference between the
elapsed CPU time before and after the repeated calls.
> timeNReps :: (a -
This must be a bug then, because the following works!
y :: Num a => a
y = fromIntegral (y::Int)
A simpler example might be:
x :: Int
x = y
y :: Num a => a
y = fromIntegral x
I have not studied the report to see if this should be legal.
___
Oops, I initially hit r instead of L...
--
Carsten Schultz (2:38, 33:47), FB Mathematik, FU Berlin
http://carsten.codimi.de/
PGP/GPG key on the pgp.net key servers,
fingerprint on my home page.
--- Begin Message ---
Hi!
On Sun, Jan 16, 2005 at 06:17:24PM -0800, Ashley Yakeley wrote:
> I suspect
I suspect its becuse q needs to get the dictionary for 'm' from
somewhere... as it is recursive, p calls q calls p, so p must have
the dictionary for 'm' in its context... So this works:
module Main where
p :: Monad m => m ()
p = q >>= id
q :: Monad m => m (m ())
q = return p
Keea
On 13 January 2005 23:36, Nick Main wrote:
> I'm planning to implement a small OO language on top of GHC (think
> JavaScript) and need to decide on how to implement the mutable object
> graph that is required.
>
> The two approaches I'm considering are:
> - something on top of Data.Graph
> - us
On 14 January 2005 12:58, Dimitry Golubovsky wrote:
> Now I need more advice on which "flavor" of Unicode support to
> implement. In Haskell-cafe, there were 3 flavors summarized: I am
> reposting the table here (its latest version).
>
> |Sebastien's| Marcin's | Hugs
> ---+--
On Mon, Jan 17, 2005 at 09:52:18AM +, Keean Schupke wrote:
> You cannot sequence two operations from different monads...
Note that this compiles:
module Bug where
{
p :: IO ();
p = q >>= id;
q :: (Monad m) => m (IO ());
q = return (return ()); -- the only change is in this li
Got the wrong type sig there...
p :: IO ()
p = run q >>= id
Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
You cannot sequence two operations from different monads...
p has type: m (IO ())
id has type, IO () (in this case because this is what p returns)...
You can do:
p :: (Monad m) => m (IO ())
p = q >>= (\a -> return a)
Or
p :: (Monad m) => m (IO ())
p = run q >>= id -- provided an overloa
12 matches
Mail list logo