Re: Are new sequences really O(1)?

2005-05-27 Thread Marcin 'Qrczak' Kowalczyk
[moved from libraries to glasgow-haskell-users]

Ross Paterson <[EMAIL PROTECTED]> writes:

> GCs that happen during this process will be more expensive, as they
> have to scan the stack. I suspect that GC costs are swamping
> everything else for large n.

I just tweaked the implementation GC in my compiler of my language,
so that minor collection doesn't scan the whole stack, but only the
part up to the deepest point where the stack pointer has been since
the previous collection. Deeper regions contain only old pointers
so they don't need to be scanned (I have only two generations).

A program which builds a list of length 270,000 non-tail-recursively,
which in a strict language leads to proportional usage of the stack,
and performs on average 4kB of temporary allocations for each element,
so there are 9,000 GCs in total with the young heap of 128 kB, runs 10
times faster after the change. GC takes 5% of the time instead of 88%.

The implementation relies on the fact that only the topmost stack
frame can be mutated, so it's enough to look only one frame deeper
than the stack pointer reached. Each frame contained a pointer which
is used only for GC and for stack trace printing, and thus it can be
marked in the lowest bit without impacting normal operations.

I prefer to make non-tail recursion efficient than to have to rewrite
algorithms to use a large heap instead of the stack.

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Why hIsEOF wait for completely full buffer while hGetChar doesn't ?

2005-05-27 Thread Simon Marlow
On 27 May 2005 03:33, Nobuo Yamashita wrote:

> I am curious about reason why in GHC hIsEOF blocks in BlockBuffering
> mode while hGetChar doesn't.
> 
> I wrote following three programs for an experiment.
> 
>   -- echo0.hs
>   module Main where
>   import System.IO
>   main = hSetBuffering stdin (BlockBuffering (Just 5)) >> echo
>   echo = getChar >>= putChar >> hFlush stdout >> echo
> 
>   -- echo1.hs
>   module Main where
>   import System.IO
>   main = hSetBuffering stdin (BlockBuffering (Just 5)) >> echo
>   echo = do eof <- isEOF
> if eof then return ()
> else getChar >>= putChar >> hFlush stdout >> echo
> 
>   -- as.hs
>   module Main where
>   import System.IO
>   import Control.Concurrent
>   main = putChar 'a' >> hFlush stdour >> threadDelay 100 >> main
> 
> And run next two commandlines
> 
> % runghc as.hs | runghc echo0.hs
> % runghc as.hs | runghc echo1.hs
> 
> I had expected that the both behaviors were same; a character
> was output a second. But the former output a character a second, and
> the latter output 5 characters a time every 5 seconds.

Quite right, that's a bug, or at least an inconsistency.  hGetChar used
to wait for a completely full buffer before returning a character, but
we changed it to return as soon as any data at all was available.
However, we didn't change hIsEOF to match: it still waits for a
completely full buffer.  I've now fixed this.

As it turns out, BlockBuffering doesn't really do full block buffering
on an input Handle.  The BlockBuffering size does specify the maximum
amount of buffering performed, but all read operations return as soon as
the required amount of data is available, without waiting for the buffer
to completely fill up.  This seems a lot more useful than strict block
buffering.

Thanks for a well-researched bug report!

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: explicit signatures and default for integer literals

2005-05-27 Thread Dinko Tenev
*Main> :type fromList
fromList :: (Ord k) => [(k, a)] -> Map k a
*Main> :type new
new :: (New a b) => a -> b

The type of new probably accounts for the difference (even though it
still makes me wonder what the big deal is :)

Using functional dependencies seems to fix it, i.e.:

class New a b | a -> b where new :: a -> b

   or, perhaps more appropriately:

class New a b | b -> a where new :: a -> b


Cheers,

D. Tenev


On 5/27/05, Mirko Rahn <[EMAIL PROTECTED]> wrote:
> 
> Hi all,
> 
> an explicit given signature causes ghc to choose the right types for
> integer literals as in
> 
> {-# OPTIONS -fglasgow-exts #-}
> 
> import Data.Map
> 
> f :: Ord a => [a] -> Map a Int
> f xs = fromList $ zip xs [0..]
> 
> Here the Literal 0 is threated as (0::Int).
> 
> But the setting
> 
> {-# OPTIONS -fglasgow-exts #-}
> 
> import Data.Map
> 
> class New a b where new :: a -> b
> 
> instance Ord a => New [(a,b)] (Map a b) where new = fromList
> 
> g :: Ord a => [a] -> Map a Int
> g xs = new $ zip xs [0..]
> 
> causes the error message
> 
> Could not deduce (New [(a, b)] (Map a Int)) from the context (Ord a)
>arising from use of `new' at Why.hs:10:7-9
> 
> ghc seems to be unable to threat the Literal 0 as (0::Int) this time but
> I do not understand why :-(
> 
> Can anyone explain it?
> 
> Thanks,
> 
> --
> -- Mirko Rahn -- Tel +49-721 608 7504 --
> --- http://liinwww.ira.uka.de/~rahn/ ---
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org 
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users 
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Contexts differ in length

2005-05-27 Thread Remi Turk
On Fri, May 27, 2005 at 12:11:26PM +0100, Simon Peyton-Jones wrote:
> It's in the same patch of the compiler as Ross's specialisation request,
> so I'll try to do both at once.
> 
> Simon

Thank you! It is a kind of show-stopper for my project so I'd be
very grateful. ;)

(my "I want Data.HashTable in IO/ST/etc" "project")

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


explicit signatures and default for integer literals

2005-05-27 Thread Mirko Rahn


Hi all,

an explicit given signature causes ghc to choose the right types for 
integer literals as in


{-# OPTIONS -fglasgow-exts #-}

import Data.Map

f :: Ord a => [a] -> Map a Int
f xs = fromList $ zip xs [0..]

Here the Literal 0 is threated as (0::Int).

But the setting

{-# OPTIONS -fglasgow-exts #-}

import Data.Map

class New a b where new :: a -> b

instance Ord a => New [(a,b)] (Map a b) where new = fromList

g :: Ord a => [a] -> Map a Int
g xs = new $ zip xs [0..]

causes the error message

   Could not deduce (New [(a, b)] (Map a Int)) from the context (Ord a)
  arising from use of `new' at Why.hs:10:7-9

ghc seems to be unable to threat the Literal 0 as (0::Int) this time but 
I do not understand why :-(


Can anyone explain it?

Thanks,

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Contexts differ in length

2005-05-27 Thread Robert van Herk

Simon Peyton-Jones wrote:


| A while ago I sent an email to the glasgow haskell users maillinglist
to
| explain how the "Contexts differ in length" feature (or bug :-))
| restricted me in writing a haskell application. I was hoping for a
| reply, however I didn't receive one (yet).

It's a sensible suggestion.  Until now no one has said it actually stops
them writing the program they want to write.  Thanks for bringing it up
again.  It's not too hard to implement, and I'll try to get to it soon.
 

Thank you! It is a kind of show-stopper for my project so I'd be very 
grateful.



It's in the same patch of the compiler as Ross's specialisation request,
so I'll try to do both at once.

Simon
 



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Contexts differ in length

2005-05-27 Thread Simon Peyton-Jones

| A while ago I sent an email to the glasgow haskell users maillinglist
to
| explain how the "Contexts differ in length" feature (or bug :-))
| restricted me in writing a haskell application. I was hoping for a
| reply, however I didn't receive one (yet).

It's a sensible suggestion.  Until now no one has said it actually stops
them writing the program they want to write.  Thanks for bringing it up
again.  It's not too hard to implement, and I'll try to get to it soon.
It's in the same patch of the compiler as Ross's specialisation request,
so I'll try to do both at once.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users