Re: ANNOUNCE: GHC 7.10.1 Release Candidate 3

2015-03-17 Thread Björn Peemöller
Am 16.03.2015 um 21:30 schrieb Austin Seipp:
> We are pleased to announce the third release candidate for GHC 7.10.1:
> 
> https://downloads.haskell.org/~ghc/7.10.1-rc3
> https://downloads.haskell.org/~ghc/7.10.1-rc3/docs/html/

The current version of cabal-install located at Hackage can not be
installed for the RC because of the following dependency error:

Setup: At least the following dependencies are missing:
filepath >=1.0 && <1.4

The problem is that cabal-install require filepath < 1.4, while the RC
ships with filepath-1.4. This issue [1] has already been solved in
cabal-install, so a new release available at Hackage would be desirable.

Regards,
Björn

[1]: https://github.com/haskell/cabal/issues/2461
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


GHC 7.10 regression when using foldr

2015-01-20 Thread Björn Peemöller
I just discovered that the following program compiled fine using GHC
7.8.4 but was rejected by GHC 7.10.1-rc1:

~~~
data List a = Nil | Cons a (List a)

instance Read a => Read (List a) where
  readsPrec d s = map convert (readsPrec d s)
where
convert (xs, s2) = (foldr Cons Nil xs, s2)
~~~

GHC 7.10 now complains:

~~~
Read.hs:5:23:
Could not deduce (Foldable t0) arising from a use of ‘convert’
from the context (Read a)
  bound by the instance declaration at Read.hs:4:10-32
The type variable ‘t0’ is ambiguous
Note: there are several potential instances:
  instance Foldable (Either a) -- Defined in ‘Data.Foldable’
  instance Foldable Data.Proxy.Proxy -- Defined in ‘Data.Foldable’
  instance GHC.Arr.Ix i => Foldable (GHC.Arr.Array i)
-- Defined in ‘Data.Foldable’
  ...plus three others
In the first argument of ‘map’, namely ‘convert’
In the expression: map convert (readsPrec d s)
In an equation for ‘readsPrec’:
readsPrec d s
  = map convert (readsPrec d s)
  where
  convert (xs, s2) = (foldr Cons Nil xs, s2)

Read.hs:5:32:
Could not deduce (Read (t0 a)) arising from a use of ‘readsPrec’
from the context (Read a)
  bound by the instance declaration at Read.hs:4:10-32
The type variable ‘t0’ is ambiguous
Relevant bindings include
  readsPrec :: Int -> ReadS (List a) (bound at Read.hs:5:3)
Note: there are several potential instances:
  instance (Read a, Read b) => Read (Either a b)
-- Defined in ‘Data.Either’
  instance forall (k :: BOX) (s :: k). Read (Data.Proxy.Proxy s)
-- Defined in ‘Data.Proxy’
  instance (GHC.Arr.Ix a, Read a, Read b) => Read (GHC.Arr.Array a b)
-- Defined in ‘GHC.Read’
  ...plus 18 others
In the second argument of ‘map’, namely ‘(readsPrec d s)’
In the expression: map convert (readsPrec d s)
In an equation for ‘readsPrec’:
readsPrec d s
  = map convert (readsPrec d s)
  where
  convert (xs, s2) = (foldr Cons Nil xs, s2)
~~~

The reason is the usage of foldr, which changed its type from

  foldr :: (a -> b -> b) -> b -> [a] -> b -- GHC 7.8.4

to

  foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- GHC 7.10.1

Thus, the use of foldr is now ambiguous. I can fix this by providing a
type signature

  convert :: ([a], String) -> (List a, String)

However, is this breaking change intended?

Regards,
Björn




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


Re: Strange performance effects with unsafePerformIO

2011-04-07 Thread Björn Peemöller
Simon Marlow schrieb:

> Incidentally this will be faster with GHC 7.2, because we implemented
> chunked stacks, so unsafePerformIO never has to traverse more than 32k
> of stack (you can tweak the chunk size with an RTS option).  This is
> still quite a lot of overhead, but at least it is bounded.
> 
> The example above runs in 1.45s for me with current HEAD, and I gave up
> waiting with 7.0.

Thank you all for your explanations,

the blackholing indeed seems to be the cause for the slowdown. Is there
any documentation available about the blackholing process?

Maybe we can find a hint on how to change our code to avoid the problem.

Regards,
Bjoern

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


Strange performance effects with unsafePerformIO

2011-03-24 Thread Björn Peemöller
Hello,

we have a strange performance behaviour when we use unsafePerformIO, at
least with GHC 6.12.3 and 7.0.1.

Please consider the example program following at the end of this post.
Running the original code the execution time is about 26 seconds, while
uncommenting one (or both) of the comments shrinks it to about 0.01
seconds on our machine.

Is there an explanation for this effect?

Regards,
Bjoern

-- ---

module Main where

import System.IO.Unsafe

traverse [] = return ()
-- traverse (_:xs) = traverse xs
traverse (_:xs) = traverse xs >> return ()

makeList 0 = []
-- makeList n = () : (makeList (n - 1))
makeList n = () : (unsafePerformIO . return) (makeList (n - 1))

main = traverse $ makeList (10^5)


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