Re: Haskell Platform Update?

2014-05-31 Thread Daniel Fischer
On Friday 30 May 2014, 23:42:57, Caitlin wrote:
 Hi all.
 
 I was just wondering if an updated release for the Haskell Platform was
 planned in the neat future? The current schedule lists November of last
 year as being the time for release candidates..
 
 Thanks,
 
 ~Caitlin

Yes, the preparations are in progress. I can't tell if it's going to be 
released really soon (next week) or within the next month, or whether 
something again throws a spanner into the works and it takes longer.

The delay is in no small part due to the release of GHC 7.8 having been 
delayed for a nontrivial amount of time.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: installing random-1.0.1.1

2014-04-22 Thread Daniel Fischer
On Tuesday 22 April 2014, 22:53:36, Sergei Meshveliani wrote:
 People,
 
 can you, please, explain me how to make the `random' package visible for
 GHC ?

It is visible to GHC, but `cabal install random` installed the package into 
the user database:

 and now  ghc-pkg list
 shows
 
 -
 /home/mechvel/ghc/7.8.2/inst0/lib/ghc-7.8.2/package.conf.d
...
 
 /home/mechvel/.ghc/x86_64-linux-7.8.2/package.conf.d
random-1.0.1.1
 --

whereas

 
make configure
 
 reports
 
   runghc Setup.hs configure --ghc

by default only looks into the global package database.

If you don't want to use the cabal tool to install your DoCon and stick with 
the `runghc Setup.hs ...` way, you have the choice to either

- pass the --user flag to `runghc Setup.hs configure` so that it uses also the 
user package database where your random package sits (then DoCon is also 
installed for the user and not globally), or

- install random in the global package database, `cabal install --global 
random` so that `runghc Setup.hs ...` finds the package in the global DB.

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


Re: 7.8.1 cabal install of vector package (dependent on primitive package) fails

2014-04-10 Thread Daniel Fischer
On Wednesday 09 April 2014, 23:42:26, Carter Schonwald wrote:
 i bet you have cabal --version reply with  1.16
 
 1) cabal update
 2) cabal install cabal-install
 3) rm ~/.cabal/config # old pre 1.18 config should go!
 4) cabal update # also probably add ~/.cabal/bin to path

There should be a step to edit the config file here, one may want to change a 
number of default settings, such as

documentation
library-profiling
shared
library-for-ghci
split-objs

 5)  cabal install vector
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-17 Thread Daniel Fischer
On Montag, 17. Dezember 2012, 07:07:21, Johan Tibell wrote:
 This compiles badly in 7.4.2:
 
 f :: Int - Word
 f = fromIntegral
 
 I need a workaround.

Mine produces (with optimisations, of course)

Convert.f :: GHC.Types.Int - GHC.Word.Word
[GblId,
 Arity=1,
 Caf=NoCafRefs,
 Str=DmdType U(L)m,
 Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
 Tmpl= \ (ds_asy [Occ=Once!] :: GHC.Types.Int) -
 case ds_asy of _ { GHC.Types.I# x#_asB [Occ=Once] -
 GHC.Word.W# (GHC.Prim.int2Word# x#_asB)
 }}]
Convert.f =
  \ (ds_asy :: GHC.Types.Int) -
case ds_asy of _ { GHC.Types.I# x#_asB -
GHC.Word.W# (GHC.Prim.int2Word# x#_asB)
}

which is what one would expect. And all of 6.12.3, 7.0.2, 7.0.4, 7.2.1, 7.2.2, 
7.4.1, 7.4.2, 7.6.1 agree on that.

I think there is some context needed to nail the problem.

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


Re: ghci 7.4.1 no longer loading .o files?

2012-02-27 Thread Daniel Fischer
On Monday 27 February 2012, 18:56:47, Yitzchak Gale wrote:
 It's nice if there is a way for experts to load .o files
 in GHCi, e.g., for the rare case where the performance
 difference for some specific module is so great that you
 can't work effectively interactively in some other module
 that imports it.

Is that so rare? For me it's pretty standard that the core modules _have_ 
to be loaded as object files, interpreting them would make things orders of 
magnitude slower (100× - 1000×), they'd be unusably slow.

So in my opinion it's absolutely essential that modules can be loaded as 
object files.

 There could be something to set in .ghci
 for people who do like that behavior all the time,
 perhaps.

And that too, if it's no longer the default.

 But it should not be the default.

But with it not being the default, I could live well.

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


Re: ANNOUNCE: GHC 7.4.1 Release Candidate 2

2012-02-04 Thread Daniel Fischer
On Wednesday 01 February 2012, 19:08:16, Evan Laforge wrote:
 On Wed, Feb 1, 2012 at 8:16 AM, Simon Hengel s...@typeful.net wrote:
  Are you referring to the classical pattern, that allows you to add a
  shebang?
  
 #!/usr/bin/env runhaskell
  
  import Distribution.Simple
  main = defaultMain
 
 Ohh, so it's a trick to allow #! in there... I guess that would
 explain it!  I just type runghc on everything and it seems like a lot
 of those don't have the executable bit set, so I hadn't thought of
 that reason.

That may have been the idea, but doesn't make a difference. GHC allows a 
shebang line as the first line of a file also in .hs files.

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


Re: GHC HEAD build error

2011-12-07 Thread Daniel Fischer
On Wednesday 07 December 2011, 16:45:31, Bas van Dijk wrote:
 Hello,
 
 I'm trying to build GHC HEAD but get the following error:
 
 inplace/bin/ghc-stage1   -H64m -O0 -fasm -Iincludes -Irts
 -Irts/dist/build -DCOMPILING_RTS -package-name rts  -dcmm-lint  -i
 -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build
 -Irts/dist/build/autogen-optc-O2   -c
 rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o
 
 rts/HeapStackCheck.cmm:159:305: parse error on input `('
 
 The bug is in the GC_GENERIC macro on line 99:
 
 Capability_interrupt(MyCapability())  != 0 :: CInt
 
 However, I can't spot the problem.

I had the same recently, it's probably because GHCConstants.h and 
DerivedConstants.h have been moved but you still have them in include/ from 
a previous build.
Deleting them should fix it.

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


Re: heads up: GHC gets a new constraint solver (again)

2011-11-16 Thread Daniel Fischer
On Wednesday 16 November 2011, 19:22:53, Dimitrios Vytiniotis wrote:
 Friends,
 
 After a very busy period of hard work with Simon, we've re-engineered
 GHCs constraint solver and I just pushed a big patch on master along
 with modifications in the testsuite.
 
 The new constraint solver is based on the existing in its core ideas but
 is shorter, much cuter, and for many programs much faster (for others
 performance is roughly the same)
 
 If you had a program that was taking very long to compile in the past,
 we'd be very interested to see how this reengineered constraint solver
 performs on it. Same if you spot problems or notable regressions.

Seems to be a clear win for T5030:

bytes allocated 943772224 is less than minimum allowed 12
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again
*** unexpected failure for T5030(normal)

:D

But due to its greater efficiency, it's dangerous in cases like 
SkolemOccursLoop.
It seems the new solver gets as far with a context-stack of N as the old 
got with a context-stack of 2N+1 there.
When, like in SkolemOccursLoop, the context grows exponentially in size, 
you're running out of memory even with a relatively small context-stack.

Cheers,
Daniel

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


Should GHC default to -O1 ?

2011-11-08 Thread Daniel Fischer
On the haskell-cafe as well as the beginners mailing lists, there 
frequently (for some value of frequent) are posts where the author inquires 
about a badly performing programme, in the form of stack overflows, space 
leaks or slowness.

Often this is because they compiled their programme without optimisations, 
simply recompiling with -O or -O2 yields a decently performing programme.

So I wonder, should ghc compile with -O1 by default?
What would be the downsides?

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


Re: Should GHC default to -O1 ?

2011-11-08 Thread Daniel Fischer
On Tuesday 08 November 2011, 17:16:27, Simon Marlow wrote:
 most people know about 1, but I think 2 is probably less well-known.
 When in the edit-compile-debug cycle it really helps to have -O off,
 because your compiles will be so much quicker due to both factors 1  2.

Of course. So defaulting to -O1 would mean one has to specify -O0 in the 
.cabal or Makefile resp. on the command line during development, which 
certainly is an inconvenience.

 
 So the default -O setting is a careful compromise, trying to hit a good
 compile-time/runtime tradeoff.  Perhaps we're more sensitive in Haskell
 because -O can easily give you an order of magnitude or more speedup,

It can even make the difference between a smoothly running programme and a 
dying one, if one is naively using the right (wrong) constructs.

So the nub of the question is, which downside is worse?

My experience is limited, so I haven't sufficient data to form a reasoned 
opinion on that, hence I ask.

 whereas in C you're likely to get a pretty consistent 30% or so.  The
 difference between -O and -O2 is another careful tradeoff.
 

 
 I suppose we should really run an up to date set of benchmarks on some
 real Haskell programs (i.e. not nofib) and reconsider how we set these
 defaults.  I really doubt that we'll want to turn on -O by default,
 though.

I suppose there are no cheap but effective optimisations one could move to 
the default behaviour, or that would've been done :(


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


Re: GHC infinite loop when building vector program

2011-10-11 Thread Daniel Fischer
On Tuesday 11 October 2011, 21:11:30, Bas van Dijk wrote:
 Hello,
 
 When benchmarking my new vector-bytestring[1] package I discovered
 that building the following program causes GHC to go into, what seems
 to be, an infinite loop:
 

 
 I use vector-0.9 and ghc-7.2.1.

Replicated with vector-0.7.1 and ghc-7.2.1 (^C'ed after six minutes).
Compilation finishes (unsurprisingly) with -fno-spec-constr or with
{-# NOINLINE f #-}.

It compiles fine with vector-0.7.0.1 and ghc-7.0.4.

 
 Regards,
 
 Bas

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
On Sunday 09 October 2011, 15:30:20, Jean-Marie Gaillourdet wrote:
 Hi Daniel,
 
 On 09.10.2011, at 14:45, Daniel Fischer wrote:
  On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:
  This seems to be a Heisenbug as it is extremely fragile, when adding
  a | grep 1 to the while loop it seems to disappears. At least on
  my computers.
  
  Still produces 1s here with a grep.
 
 Well, it may have been bad luck on my site.

Or maybe Macs behave differently.

 
 Thanks, for reproducing it. I failed to see it on Linux so far. So I
 guess a bug report is in order?

I'd think so.  Although due to the changes in 7.2 there's nothing to fix 
here anymore, it might point to something still to be fixed.

 Or are bug reports to old versions not welcome?

Within reason. Reporting bugs against 5.* would be rather pointless now, 
but = 6.10 should be okay.
If the behaviour has been fixed as a by-product of some other change, at 
least a test could be made to prevent regression.
If, like here, the directly concerned code has been changed, probably 
nothing is to be done, but the bug may have been caused by something else 
which still needs to be fixed, so better report one bug too many.

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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
Jean-Marie Gaillourdet:
 the Eq instance of TypeRep shows the same non-deterministic behavior:

Of course, equality on TypeReps is implemented by comparison of the Keys.

On Sunday 09 October 2011, 16:40:13, Jean-Marie Gaillourdet wrote:
 Hi Daniel,

 I've been chasing the source of the non-deterministic of my library for
 quite some time now. And at several points in time I had the impression
 that modifyMVar would not always be atomic.

It isn't:

MVars offer more flexibility than IORefs, but less flexibility than STM. 
They are appropriate for building synchronization primitives and performing 
simple interthread communication; however they are very simple and 
susceptible to race conditions, deadlocks or uncaught exceptions. Do not 
use them if you need perform larger atomic operations such as reading from 
multiple variables: use STM instead.

In particular, the bigger functions in this module (readMVar, swapMVar, 
withMVar, modifyMVar_ and modifyMVar) are simply the composition of a 
takeMVar followed by a putMVar with exception safety. These only have 
atomicity guarantees if all other threads perform a takeMVar before a 
putMVar as well; otherwise, they may block.

But I don't think that's the problem here.

 (Of course under the
 assumption that no other code touches the MVar). But in that case as
 well as in the case here it is only reproducible by looping the
 execution of the binary. Moving the loop into the Haskell program will
 show the bug in the first iteration or never.

That's what I expect.
I think what happens is:

-- from Data.Typeable

cache = unsafePerformIO $ ...


mkTyConKey :: String - Key
mkTyConKey str 
  = unsafePerformIO $ do
let Cache {next_key = kloc, tc_tbl = tbl} = cache
mb_k - HT.lookup tbl str
case mb_k of
  Just k  - return k
  Nothing - do { k - newKey kloc ;
  HT.insert tbl str k ;
  return k }

occasionally, the second thread gets to perform the lookup before the first 
has updated the cache, so both threads create a new entry and update the 
cache.

If you loop in the Haskell programme, after the first round each thread 
definitely finds an entry for (), so the cache isn't updated anymore.

 
 I will report a bug.
 
 Jean


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


Re: Is this a concurrency bug in base?

2011-10-09 Thread Daniel Fischer
On Sunday 09 October 2011, 17:51:06, Jean-Marie Gaillourdet wrote:
  That sounds plausible. Do you see any workaround? Perhaps repeatedly
  evaluating typeOf?
 
 typeOf' seems to be a working workaround: 
 
 typeOf' val
 | t1 == t2 = t1
 | otherwise = typeOf' val
   where
 t1 = typeOf'' val
 t2 = typeOf''' val
 {-# NOINLINE typeOf' #-}
 
 
 typeOf'' x = typeOf x
 {-# NOINLINE typeOf'' #-}
 typeOf''' x = typeOf x
 {-# NOINLINE typeOf''' #-}

That'll make it very improbable to get bad results, but not impossible.

Thread1: typeOf' (); typeOf'' (), lookup, not there
Thread2: typeOf' (); typeOf'' (), lookup, not there
Thread1: create and insert; typeOf''' (), entry present, use ~ Key 0
Thread2: create and insert, overwites entry with Key 0,
 new entry has Key 1; typeOf''' (), entry present, use ~ Key 1

It will probably take a long time until it bites, but when it does, it will 
hurt.
A proper fix would need a lock to ensure only one thread at a time can 
access the cache.

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


Re: Evaluating type expressions in GHCi

2011-09-20 Thread Daniel Fischer
On Wednesday 21 September 2011, 01:02:52, wagne...@seas.upenn.edu wrote:
 Would it be possible to have no command at all? Types are  
 distinguished by upper-case letters, so it should be possible to tell  
 whether a given expression is a value-level or a type-level expression.

Unless I'm misunderstanding, no:

{-# LANGUAGE TypeFamilies #-}
module TFEx where

type family F a
type instance F Int = Bool
type instance F Bool = Int
type instance F (a, b) = (F a, F b)

data Foo a = F a deriving Show
data Moo = Int | Bool deriving Show

*TFEx F (Int,Bool)
F (Int,Bool)
*TFEx :t F (Int,Bool)
F (Int,Bool) :: Foo (Moo, Moo)
*TFEx :t undefined :: F (Int,Bool)
undefined :: F (Int,Bool) :: (Bool, Int)
*TFEx

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


Windows build problems

2011-09-15 Thread Daniel Fischer
I'm trying to set up a build/test environment on Windows.

Building ghc (sh validate) fails after a while due to flex and bison 
crashing. Those two come with git and even
$ flex --version
(or bison) crashes, so they seem truly hosed.

Do I need flex/bison at all to build ghc?
It seems they're not used on linux for building ghc.
So, if not, how do I configure things that the build doesn't try to use 
bison/flex?
If yes, would installing flex and bison from gnuwin32 work?

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


Re: Windows build problems

2011-09-15 Thread Daniel Fischer
On Thursday 15 September 2011, 21:41:10, Bill Tutt wrote:
 From Daniel Fischer:
  I'm trying to set up a build/test environment on Windows.
  
  Building ghc (sh validate) fails after a while due to flex and bison
  crashing. Those two come with git and even
  $ flex --version
  (or bison) crashes, so they seem truly hosed.
  
  Do I need flex/bison at all to build ghc?
  It seems they're not used on linux for building ghc.
  So, if not, how do I configure things that the build doesn't try to
  use bison/flex?
  If yes, would installing flex and bison from gnuwin32 work?
 
 I ran into this issue last night as well. See
 http://hackage.haskell.org/trac/ghc/ticket/5489

Ugh. I'd like to avoid uninstalling msys and installing something new if 
possible.

 
 flex appears to be required from integer-gmp's ./configure for one of
 GMP's demo programs. (a calculator demo I think)

I can't find anything indicating that on linux, so it'd be probably be due 
to using the in-tree gmp on Windows? But the only mention of flex that 
seems possibly relevant is

# These flags make flex 8-bit
SRC_FLEX_OPTS   += -8

in mk/config.mk.in, and bison is only mentioned in two word lists in 
libraries/bytestring/tests at all (as the animal of course).
So I'm still mystified.

 
 I'm trying to see if a slightly newer msys installation process as
 listed in the Trac bug will take care of it.

If you get it to work, I'd appreciate detailed (Windows is so far utterly 
incomprehensible to me, so they'd better be very explicit) instructions.

 
 However, last night I got a stage 1 ghc seg fault while compiling some
 Haskell code further along in the build.

Perhaps compiling GHC.Debug.hs? That's where I get a stage1 segfault on 
linux when bootstrapping with 7.2.1, cf 
http://hackage.haskell.org/trac/ghc/ticket/5484

However, I'm bootstrapping with 7.0.4 (switched on Windows due to the ar 
location problem mentioned in #5488, that gets me to the bison/flex 
problem, builds fine on linux).

 
 I currently have a devel1 build in progress to see what I come up with
 next.
 
 I also ran into: http://hackage.haskell.org/trac/ghc/ticket/5488 about
 bootstrapping using the Windows 7.2.1 standalone bits to bootstrap
 ghc-HEAD.
 If the devel1 build doesn't give any useful symptoms to pass along
 I'll probably retry the build using the Haskell Platform compiler.

If your stage1 segfault is the same as mine, switching to 7.0.x should get 
you around it.

 
 Fyi,
 Bill

Thx,
Daniel

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


Re: With every new GHC release, also released any new versions of libraries

2011-08-25 Thread Daniel Fischer
On Thursday 25 August 2011, 10:39:29, Johan Tibell wrote:
 P.S. Could someone please remind me why containers ships with GHC?

Some other packages shipped with GHC depend on containers, e.g. hoopl, 
template-haskell, haskeline, binary.
And via haskeline, ghci depends on containers too.

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


Re: Can't find interface-file declaration for type constructor or class integer-gmp:GHC.Integer.Type.Integer

2011-08-18 Thread Daniel Fischer
On Thursday 18 August 2011, 19:13:45, Johan Tibell wrote:
 On Thu, Aug 18, 2011 at 7:07 PM, Simon Peyton-Jones
 
 simo...@microsoft.com wrote:
  | I shouldn't have to modify PrelNames since I kept GHC.Integer.Type,
  | no? Or does PrelNames have to contain the name of the module that
  | originally defined the type?
  
  Yes, exactly!
 
 This causes some trouble though, as the module named in PrelNames must
 exist in both in integer-gmp and integer-simple i.e. it must be some
 generic name like GHC.Integer.Type 

GHC.Integer.Impl.Type ?

 rather than a name containing e.g.
 GMP. I could keep the data type definition where it is
 (GHC.Integer.Type) but then I would have a hard time exporting it from
 e.g. GHC.Integer.GMP.Internals without undoing Ian's patch which
 removed the slightly odd GHC.Integer - GHC.Integer.GMP.Internals -
 GHC.Integer.Type module dependency in integer-gmp.


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


Re: integer-simple

2011-07-29 Thread Daniel Fischer
On Friday 29 July 2011, 18:51:23, Chris Dornan wrote:
 Hi All,
 
 
 
 I am still having difficulty getting a plain GHC build with
 INTEGER_LIBRARY = integer-simple. (I outlined my problem here yesterday
 http://www.haskell.org/pipermail/glasgow-haskell-users/2011-July/020631
 .htm l .)

 RHEL 5 and 6 are very different development environments yet all my
 attempts to build with a variety of source trees from 6.12.1 to 7.0.4
 with INTEGER_LIBRARY = integer-simple has ended here. There is clearly
 something I am doing wrong! (Though it is difficult to see what.)
 
 Does anybody have any idea what could be causing this?
 

Not I, sorry.

 
 
 Is anybody else doing integer-simple builds?
 
 It would be nice to get some info on the configurations that are
 working.

After your post yesterday, I built HEAD with integer-simple (build flavour 
perf, though, not quickest; openSuSE-11.4, x86_64; built with 7.0.4) and it 
worked [ghci and a few test programmes].

Maybe you should try building with GHC-7 (and different build flavours?).

Cheers,
Daniel


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


Re: Profile: zero total time

2011-07-07 Thread Daniel Fischer
On Thursday 07 July 2011, 20:44:57, Matthew Farkas-Dyck wrote:
 I am trying to take a profile of a program, but when I run it, the
 total time (as given in the profiling report file) is zero!

If you're on a Mac, it could be

http://hackage.haskell.org/trac/ghc/ticket/5282

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


Re: GHC HEAD broken on OS X

2011-06-26 Thread Daniel Fischer
On Monday 27 June 2011, 05:52:42, austin seipp wrote:
 After doing a 'git pull origin master  ./sync-all pull origin
 master', I get the following build failure when stage1 attempts to
 compile the RTS code:
 
 http://paste.debian.net/121097/
 
 A quick glance at the errors seem to indicate this work is related to
 the new events stuff for GHC. Duncan was working on this last I think
 - is anybody else experiencing this failure?

Works on linux x86_64 (the build fails elsewhere, cf. 
http://hackage.haskell.org/trac/ghc/ticket/5276, unless I specify 
THREADS=1).

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


Testsuite failures and some easy fixes

2011-06-21 Thread Daniel Fischer
Today's HEAD produced 49 unexpected failures, most of which are caused by 
trivia.

- tcrun006 and tcrun029 use datatype contexts which were removed from HEAD 
(7 ways each), can be fixed by adding a language pragma
(cf. also http://hackage.haskell.org/trac/ghc/ticket/5229)

- ghcpk01.stdout hasn't yet been updated to include the new trusted field

- ffi005 fails to compile (7 ways) due to an ambiguous occurrence of 
unsafePerformIO (Foreign and System.IO.Unsafe)

- cg005 and T4059 have unexpected stderr due to a warning about 
unsafePerformIO going to be removed from Foreign

- T4437 fails to compile due to a type change:
T4437.hs:9:39:
Couldn't match expected type `(String,
   CmdLineParser.FlagSafety,
   ExtensionFlag,
   DynFlags.TurnOnFlag - DynFlags.DynP 
())'
with actual type `(t0, t1, t2)'
In the pattern: (ext, _, _)
In a stmt of a list comprehension: (ext, _, _) - xFlags
In the expression: [ext | (ext, _, _) - xFlags]

Those are easily fixed by the attached patches (but some may need a more 
principled fix).

Further, 17 unexpected failures are due to hpc output being formatted 
differently from the expectation (5x hpc_fork, 6x hpc001, 6x tough).

Two unexpected failures (T4809, cgrun068) are due to mtl not being built 
the dyn way.

The remaining 5 are
- T4801 (allocating too little because there are fewer Generic instances 
for tuples)
- dph-diophantine-opt (3 ways)
- dph-words-opt

On my 32-bit box, also T3294 unexpectedly fails since about a week ago due 
to too little allocation (a bit below 690M, minimum allowed 800M).
If that's reproducible and not known to be temporary, the bounds should be 
adjusted.

Cheers,
Daniel
From 92dbf9a5b4516d27fc0d389f842e21b4d3df5e5e Mon Sep 17 00:00:00 2001
From: Daniel Fischer daniel.is.fisc...@googlemail.com
Date: Tue, 21 Jun 2011 14:32:13 +0200
Subject: [PATCH 1/7] DatatypeContexts for tcrun006

---
 tests/ghc-regress/typecheck/should_run/tcrun006.hs |5 +++--
 1 files changed, 3 insertions(+), 2 deletions(-)

diff --git a/tests/ghc-regress/typecheck/should_run/tcrun006.hs b/tests/ghc-regress/typecheck/should_run/tcrun006.hs
index c55ef88..4c84331 100644
--- a/tests/ghc-regress/typecheck/should_run/tcrun006.hs
+++ b/tests/ghc-regress/typecheck/should_run/tcrun006.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE DatatypeContexts #-}
 -- !!! Selectors for data and newtypes with contexts
 
 -- This program, reported in Aug'00 by Jose Emilio Labra Gayo
@@ -8,8 +9,8 @@
 
 module Main where
 
-newtype (Eq f) = NewT  f = NewIn  { newout  :: f } 
-data(Eq f) = DataT f = DataIn { dataout :: f } 
+newtype (Eq f) = NewT  f = NewIn  { newout  :: f }
+data(Eq f) = DataT f = DataIn { dataout :: f }
 
 main = print (newout (NewIn ok new) ++ dataout (DataIn  ok data))
 
-- 
1.7.3.4

From 890b8504052a7debcca0a221db0d4543a328004f Mon Sep 17 00:00:00 2001
From: Daniel Fischer daniel.is.fisc...@googlemail.com
Date: Tue, 21 Jun 2011 14:33:15 +0200
Subject: [PATCH 2/7] DatatypeContexts for tcrun029

---
 tests/ghc-regress/typecheck/should_run/tcrun029.hs |5 +++--
 1 files changed, 3 insertions(+), 2 deletions(-)

diff --git a/tests/ghc-regress/typecheck/should_run/tcrun029.hs b/tests/ghc-regress/typecheck/should_run/tcrun029.hs
index 53c67e5..f25a401 100644
--- a/tests/ghc-regress/typecheck/should_run/tcrun029.hs
+++ b/tests/ghc-regress/typecheck/should_run/tcrun029.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE DatatypeContexts #-}
 -- Killed GHC 5.02.3
 
 -- Confusion about whether the wrapper for a data constructor
@@ -6,11 +7,11 @@
 
 module Main where
 
-data Color = Red 
+data Color = Red
 	   | Black
 	 deriving Show
 
-data Ord k = Tree k d = None 
+data Ord k = Tree k d = None
 		   | Node{color::Color,
 			  key::k,
 			  item::d,
-- 
1.7.3.4

From a5ed55598fa0044e1f548dbe09cd8811f7ba796e Mon Sep 17 00:00:00 2001
From: Daniel Fischer daniel.is.fisc...@googlemail.com
Date: Tue, 21 Jun 2011 14:34:56 +0200
Subject: [PATCH 3/7] Use System.IO.unsafePerformIO in ffi005

---
 tests/ghc-regress/ffi/should_run/ffi005.hs |6 +++---
 1 files changed, 3 insertions(+), 3 deletions(-)

diff --git a/tests/ghc-regress/ffi/should_run/ffi005.hs b/tests/ghc-regress/ffi/should_run/ffi005.hs
index 1496922..12b71ba 100644
--- a/tests/ghc-regress/ffi/should_run/ffi005.hs
+++ b/tests/ghc-regress/ffi/should_run/ffi005.hs
@@ -4,7 +4,7 @@
 import Foreign
 import Foreign.C
 import Control.Exception
-import System.IO.Unsafe
+import System.IO.Unsafe as U
 import Prelude hiding (read)
 import System.IO (hFlush, stdout)
 
@@ -40,7 +40,7 @@ main = do
 
   putStrLn \nTesting sin==IO wrapped_sin (should return lots of Trues)
   sin_addr2 - wrapIO (return . sin)
-  print (testSin sin (unsafePerformIO . (dyn_sinIO sin_addr2)))
+  print (testSin sin (U.unsafePerformIO . (dyn_sinIO sin_addr2)))
   freeHaskellFunPtr sin_addr2
 
   putStrLn \nTesting sin==Id wrapped_sin (should

Re: GHC and Haskell 98

2011-06-17 Thread Daniel Fischer
On Friday 17 June 2011, 17:11:39, Jacques Carette wrote:
 I favour Plan A.

+1

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


Re: URL for GHC 7.0.3

2011-06-15 Thread Daniel Fischer
On Wednesday 15 June 2011, 16:53:37, Antoine Latter wrote:
 Does this page help?
 
 http://www.haskell.org/ghc/download_ghc_7_0_3
 
 Take care,
 Antoine

I would, however, recommend going for the new

http://www.haskell.org/ghc/download_ghc_7_0_4

which fixes a couple of bugs in 7.0.3

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


Re: testsuite, failures galore

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 12:31:36, Simon Marlow wrote:
  The ticket has low priority, but if anybody has an idea how to check
  whether libbfd depends on libz in the configure script, I'd appreciate
  it.
 
 Could you install a shared version of libbfd?

I have one,

$ locate libbfd
/home/dafis/.deps/libbfd.Plo
/usr/lib/libbfd-2.20.0.20100122-6.so
/usr/lib/libbfd.a
/usr/lib/libbfd.la

The problem is, as far as I can tell, that a) libbfd.a is picked up instead 
of the .so in the first place, and b) that both depend on libz:

$ ldd /usr/lib/libbfd-2.20.0.20100122-6.so 
linux-gate.so.1 =  (0xe000)
libz.so.1 = /lib/libz.so.1 (0xb743e000)
libc.so.6 = /lib/libc.so.6 (0xb72d3000)
/lib/ld-linux.so.2 (0xb76fd000)

There's

# Libraries that this one depends upon.
dependency_libs=' -lz'

in libbfd.la, and the inflate* symbols are undefined in libbfd*.

 Failing that, the
 easiest  thing to do would be to make a test that compiles a program
 depending on libbfd and if it fails to link, just disable HAVE_LIBBFD
 (it's no great loss).

I'm far from an expert, but as far as I can see, there is already such a 
test, in configure.ac:

AC_CHECK_LIB(bfd,bfd_init)

with a test using bfd_init in configure. Unfortunately, that doesn't detect 
if libz is needed without using some functions depending on it.
If I had the slightest idea how to make it detect the dependency on libz, I 
happily would, but I've not yet found any introduction to shell scripting 
or using autotools accessible to a complete beginner.

 
 Cheers,
 Simon

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


Re: testsuite, failures galore

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 14:44:58, Simon Marlow wrote:
 
 What you need is libbfd.so, which is a symbolic link to the versioned
 library (libbfd-2.20.0.20100122-6.so).  This is normally installed by
 the development version of the library (e.g. libbfd-dev on
 Debian-derived distros).

Couldn't find anything like that for openSuSE (11.3), the versioned .so 
comes with binutils, libbfd.a (and .la) come from binutils-devel.

I'll take a look at the AC stuff and if I don't see how it might work, I'll 
try with a manually created symlink.

 
 The shared version has the dependency built-in, so the GHC build system
 wouldn't have to do anything (that's how it works here).
 
  I'm far from an expert, but as far as I can see, there is already such
  a test, in configure.ac:
  
  AC_CHECK_LIB(bfd,bfd_init)
 
 I think that only tests for the presence of the symbol in the library,
 it doesn't test that compiling an executable against that library
 actually works.
 

Well, compiling and running a simple test programme that calls bfd_init() 
works here without linking in libz, so I guess that test wouldn't detect 
the dependency even if it actually runs the executable.

  with a test using bfd_init in configure. Unfortunately, that doesn't
  detect if libz is needed without using some functions depending on
  it. If I had the slightest idea how to make it detect the dependency
  on libz, I happily would, but I've not yet found any introduction to
  shell scripting or using autotools accessible to a complete beginner.
 
 Yes, I'm afraid the learning curve is a bit steep.  It's so hard to get
 right that I wouldn't even attempt to try to fix it without a machine to
 test on!  A good place to start would be tests that do similar things -
 a quick look at the code suggests AC_COMPILE_IFFELSE and AC_LINK_IFFELSE
 might be useful, also FP_CHECK_FUNC looks like it might do what you
 want.

I'll look.

Cheers,
Daniel

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


Re: testsuite, failures galore

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 16:04:28, Simon Marlow wrote:
 On 31/05/2011 14:53, Daniel Fischer wrote:
  Well, compiling and running a simple test programme that calls
  bfd_init() works here without linking in libz, so I guess that test
  wouldn't detect the dependency even if it actually runs the
  executable.
 
 That's very mysterious.  Perhaps bfd_init doesn't pull in anything that
 has the libz dependency,

That's what I think.

 and you have to call some other function in the
 bfd library instead.  Here's a fragment of code in the RTS that calls
 bfd functions:
 
  bfd_init();
  abfd = bfd_openr(name, default);
  if (abfd == NULL) {
   barf(can't open executable %s to get symbol table, name);
  }
  if (!bfd_check_format_matches (abfd, bfd_object, matching)) {
   barf(mismatch);
  }

calling bfd_openr alone produces tons of undefined references, I've no idea 
what libraries I'd have to link with also :(

 
 
 Cheers,
   Simon

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


Re: testsuite, failures galore

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 16:39:19, Donn Cave wrote:
 Quoth Daniel Fischer daniel.is.fisc...@googlemail.com,
 ...
 
  calling bfd_openr alone produces tons of undefined references, I've no
  idea what libraries I'd have to link with also :(
 
 Try -lbfd -liberty -lz ?
 
   Donn

Thanks. That worked. Without a symlinked libbfd.so in /usr/lib, linking 
failed without -lz, programme successfully ran when linked with -lz;
With a symlink, -lz wasn't even needed (and no undefined reference.. 
failures in the testsuite either). It seems the linker looks for libbfd.so 
first, if that isn't found, it falls back on libbfd.a which needs -lz.

So basically, it's an openSuSE bug, I'd say.
Nevertheless, having a test would be good.
Unfortunately, looking at configure.ac and configure didn't give me any 
idea how to do it yet.

Cheers,
Daniel

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


Re: testsuite, failures galore

2011-05-31 Thread Daniel Fischer
On Tuesday 31 May 2011 16:04:28, Simon Marlow wrote:
 That's very mysterious.  Perhaps bfd_init doesn't pull in anything that 
 has the libz dependency, and you have to call some other function in
 the  bfd library instead.

Not having a better idea, I replaced bfd_init in the AC_CHECK_LIB with 
bfd_uncompress_section_contents, because that one definitely pulls in the 
libz dependency.
And it worked for me™.

Without libbfd-version.so symlinked to libbfd.so, the test failed to link, 
hence there was no
#define HAVE_LIBBFD 1
written to confdefs.h, no link failures due to the libz dependency in the 
testsuite.

With the symlink, the test linked,
#define HAVE_LIBBFD 1
was written to confdefs.h, no link failures due to the libz dependency in 
the testsuite.

Unless there's a reason that change would break things elsewhere, it'd be a 
simple fix.

Cheers,
Daniel
From b7170be4f9d62e695316a70435919cc2769334d1 Mon Sep 17 00:00:00 2001
From: Daniel Fischer daniel.is.fisc...@googlemail.com
Date: Wed, 1 Jun 2011 03:42:11 +0200
Subject: [PATCH] new test for libbfd

---
 configure.ac |2 +-
 1 files changed, 1 insertions(+), 1 deletions(-)

diff --git a/configure.ac b/configure.ac
index 2de4d8a..662285a 100644
--- a/configure.ac
+++ b/configure.ac
@@ -782,7 +782,7 @@ fi
 dnl ** check whether this machine has BFD and liberty installed (used for debugging)
 dnlthe order of these tests matters: bfd needs liberty
 AC_CHECK_LIB(iberty, xmalloc)
-AC_CHECK_LIB(bfd,bfd_init)
+AC_CHECK_LIB(bfd, bfd_uncompress_section_contents)
 
 dnl 
 dnl Check for libraries
-- 
1.7.1

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


testsuite, failures galore

2011-05-29 Thread Daniel Fischer
So my last testsuite run (validate --slow) with a new HEAD produced 651 
unexpected failures :(

Okay, the thing is that I forgot to add EXTRA_HC_OPTS=-optl-lz, see
http://hackage.haskell.org/trac/ghc/ticket/3756

So, unless I miscounted, 611 of those were in way threaded1 due to:

 Linking arrowrun001 ...
 /usr/lib/gcc/i586-suse-linux/4.5/../../../libbfd.a(compress.o): In
 function `bfd_uncompress_section_contents':
 
 /usr/src/packages/BUILD/binutils-2.20.0/build-
dir3/bfd/../../bfd/compress.c:96:0:
  undefined reference to `inflateInit_'
 
 /usr/src/packages/BUILD/binutils-2.20.0/build-
dir3/bfd/../../bfd/compress.c:106:0:
  undefined reference to `inflateReset'
 
 /usr/src/packages/BUILD/binutils-2.20.0/build-
dir3/bfd/../../bfd/compress.c:103:0:
  undefined reference to `inflate'
 
 /usr/src/packages/BUILD/binutils-2.20.0/build-
dir3/bfd/../../bfd/compress.c:108:0:
  undefined reference to `inflateEnd'
 
 collect2: ld gab 1 als Ende-Status zurück
 
 *** unexpected failure for arrowrun001(threaded1)

The ticket has low priority, but if anybody has an idea how to check 
whether libbfd depends on libz in the configure script, I'd appreciate it.

Of the remaining 40 unexpected failures, 14 were due to the removal of 
datatype contexts (tcrun006 and tcrun029), 7 (tcrun007) were due to a parse 
error because -XGenerics does nothing anymore (so ghc couldn't parse {|), 
3 due to a missing Show instance in dph.
The remaining may or may not be serious, looking at them now.

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


Re: testsuite results

2011-05-16 Thread Daniel Fischer
Continuing with today's HEAD's results:
7506 expected passes
 235 expected failures
   0 unexpected passes
   9 unexpected failures

More failures than Friday, with fewer tests run (no profiling).

But what's the actual difference?
We have our old acquaintances
   T3064(normal)
   T5084(normal)
   dph-diophantine-opt(normal,threaded1,threaded2)
   dph-words-opt(normal)

T3016(profasm) obviously wasn't run, without profiling support.

New are:

   ds022(normal)

an overlapping pattern warning used to report the first overlapping 
patterns, now the last; the expected stderr output has been updated 
meanwhile, but my testsuite was started before that.



   3307(normal)
   environment001(normal)

These two failed with (mutatis mutandis)

Actual stderr output differs from expected:
--- /dev/null   2011-05-15 19:13:45.604004218 +0200
+++ ./lib/IO/environment001.run.stderr.normalised   2011-05-16 
12:33:18.0 +0200
@@ -0,0 +1 @@
+/bin/sh: Zeile 0: echo: Schreibfehler: Datenübergabe unterbrochen (broken 
pipe).
*** unexpected failure for environment001(normal)

I think it's the testsuite driver interacting badly with my OS, because 
running `make TEST=XY' in the testsuite directory consistently fails with a 
broken pipe, but running the tests from the .../lib/IO directory, either by 
manually issuing the commands from the command line or by running
`make XY-test', consistently succeeds (including the production of the 
correct output).


Altogether, things still look good.

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


Re: Linking in Dead Code

2011-05-14 Thread Daniel Fischer
On Friday 13 May 2011 13:04:14, Guy wrote:
 If only 1% of an imported module is used, GHC will link in the entire
 module.

With split-objs, as far as I know, GHC only links in what you use (plus the 
module initialiser).

split-objs was disabled for some GHC/OS X combinations recently,
http://hackage.haskell.org/trac/ghc/ticket/4013 and 5008, maybe that 
applies to you, otherwise building GHC with object-splitting enabled and 
all libraries with split-objs should reduce code size significantly.

Linking still tends to use a lot of memory with ld, on the appropriate 
platforms you could try using gold as the linker, that's reported to use 
less memory (and be faster).

 Are there any plans, or at least some ideas, to rectify this?
 One severe example of this is qtHaskell, where importing the top-level
 module causes glacial compile (actually link) times and huge
 executables. Strip can fix the executable size (why does GHC not do
 this automatically?), but linking remains a problem.
 

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


Re: Linking in Dead Code

2011-05-14 Thread Daniel Fischer
On Saturday 14 May 2011 21:06:50, Guy wrote:
 On 14/05/2011 21:12, Don Stewart wrote:
  When compiled with split objs GHC makes it possible for the linker
  to do dead code stripping. Make sure your GHC has split-objs on.
 
 Thank you, I hadn't realised that the imported library could be built
 like this. How is this configured with cabal?

In your ~/.cabal/config file (translate the path to Windows, I've no idea 
where the config goes there), there's a field for that, set

split-objs: True

And from then on cabal (install) passes the -split-objs flag (or was that 
--split-objs?) to GHC when installing packages. You'd have to rebuild the 
packages you already have.

 (And do any packages actually do so?)
 

It's something the user decides, not the package author.

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


testsuite results

2011-05-12 Thread Daniel Fischer
Running the testsuite with today's HEAD (perf build, but without profiling 
to keep time bearable) resulted in:


OVERALL SUMMARY for test run started at Do 12. Mai 13:34:13 CEST 2011
2765 total tests, which gave rise to
9300 test cases, of which
   0 caused framework failures
1587 were skipped

7467 expected passes
 229 expected failures
   9 unexpected passes
   8 unexpected failures


Pretty cool, I can't remember having so few unexpected failures before.


Unexpected failures:
   T5084(normal)

That's  the compiler not complaining about an INLINE-pragma on a class 
method without default implementation. Patch is in ghc-generics branch, not 
yet in master, according to #5084. Anyway it's nothing serious (was a 
feature request, not a bug).

   dph-diophantine-opt(normal,threaded1,threaded2)

These are due to a missing Show instance for [:Int:], a library issue.

   dph-words-opt(normal)

Fails with dph-words-opt: libraries/vector/Data/Vector/Generic.hs:369 
(slice): invalid slice (1,2,2).
No idea whether that's a library or a compiler issue.

   hpc_markup_multi_001(normal)
   hpc_markup_multi_002(normal)
   hpc_markup_multi_003(normal)

Those are due to hpc looking in the wrong directory for the tix files, 
patch exists, but is not yet in the master branch, according to #5069.

So, of the eight unexpected failures, six are due to trivia (they *might* 
fail for other causes when the trivia are fixed, but there's no reason to 
expect that), one is a feature request whose test reached testsuite/master 
before the implementation reached ghc/master and only one may (but need 
not) indicate a compiler bug at present, that's rather awesome.



Unexpected passes:
   mc01(hpc,ghci)
   mc06(hpc,ghci)
   mc08(hpc,ghci)
   mc11(hpc)
   mc16(hpc)
   mc18(hpc)

All these involve the new MonadComprehensions extension, they're expected 
to work and do so for the normal and optasm ways, maybe they should also be 
expected to work for hpc and ghci.


Additionally, sometimes conc016(threaded2) passes unexpectedly; which 
thread first gets its exception to the other one is impossible to predict:

-- NB. this test is delicate since 6.14, because throwTo is now always
-- interruptible, so the main thread's killThread can be legitimately
-- interrupted by the child thread's killThread, rather than the other
-- way around.  This happens because the child thread is running on
-- another processor, so the main thread's throwTo is blocked waiting
-- for a response, and while waiting it is interruptible.


Summing up: Yay!

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


Re: testsuite results

2011-05-12 Thread Daniel Fischer
On Thursday 12 May 2011 17:49:16, Simon Peyton-Jones wrote:
 |hpc_markup_multi_001(normal)
 |hpc_markup_multi_002(normal)
 |hpc_markup_multi_003(normal)
 | 
 | Unexpected passes:
 |mc01(hpc,ghci)
 |mc06(hpc,ghci)
 |mc08(hpc,ghci)
 |mc11(hpc)
 |mc16(hpc)
 |mc18(hpc)
 
 I pushed patches for all of these today
 

Great!
Now I've built HEAD (7b3a746294d3d034da0052644237e4d1ab1f08c8, minus the 
patch removing the import Config from AsmCodeGen, cf #5194) with profiling, 
leading to


OVERALL SUMMARY for test run started at Do 12. Mai 20:47:35 CEST 2011
2766 total tests, which gave rise to
   11839 test cases, of which
   0 caused framework failures
2123 were skipped

9428 expected passes
 280 expected failures
   1 unexpected passes
   7 unexpected failures

Unexpected passes:
   conc016(threaded2)

Well, that one occasionally happens.

Unexpected failures:
   T3016(profasm)

timeout-killed, too much other stuff running, rerunning T3016 on a less 
busy machine made it pass, but I'm not too happy with the stats:

ghc: 29262116704 bytes, 55739 GCs, 88426196/318733428 avg/max bytes 
residency (35 samples), 668M in use, 0.00 INIT (0.00 elapsed), 81.46 MUT 
(104.38 elapsed), 42.76 GC (103.41 elapsed) :ghc

   T3064(normal)

This one failed due to ghc being too good:

bytes allocated 59305220 is less than minimum allowed 6500
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again
*** unexpected failure for T3064(normal)

On an almost idle machine, the figures are even lower:

 [(bytes allocated, 58378436)
 ,(num_GCs, 30)
 ,(average_bytes_used, 1594860)
 ,(max_bytes_used, 3064640)
 ,(num_byte_usage_samples, 2)
 ,(peak_megabytes_allocated, 8)
 ,(init_cpu_seconds, 0.00)
 ,(init_wall_seconds, 0.00)
 ,(mutator_cpu_seconds, 0.16)
 ,(mutator_wall_seconds, 0.17)
 ,(GC_cpu_seconds, 0.07)
 ,(GC_wall_seconds, 0.07)
 ]


   T5084(normal)
   dph-diophantine-opt(normal,threaded1,threaded2)

The same as before, nothing to worry about.

   dph-words-opt(normal)

This one was also timeout-killed on a busy machine, a later re-run let the 
compilation finish, but it took quite long:

[1 of 2] Compiling WordsVect( WordsVect.hs, WordsVect.o )
[2 of 2] Compiling Main ( Main.hs, Main.o )
Linking dph-words-opt ...
ghc: 52843523420 bytes, 101270 GCs, 53522750/118551624 avg/max bytes 
residency (67 samples), 282M in use, 0.00 INIT (0.01 elapsed), 153.19 MUT 
(163.87 elapsed), 70.10 GC (70.05 elapsed) :ghc

The run of the programme again ended with an invalid slice.


 | Summing up: Yay!
 
 Indeed!

Still very much yay, I can't find the new unexpected failure of T3064 
disappointing in the least, only T3016(profasm) and dph-words-opt leave 
something to be desired.

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-21 Thread Daniel Fischer
On Thursday 21 April 2011 17:18:47, Chris Kuklewicz wrote:
 I tried ghc --make -fforce-recomp simpleTest.hs with -O0 and -O1 and
 -O2 on OS X with 64-bit ghc-7.0.3
 
 All versions ran without printing errors.

I seem to recall that GHC produces sse2 code on x86_64. If that's correct, 
the effect probably won't be reproducible on that architecture, since it 
doesn't occur with -msse2 on x86 either (well, at least on my machine).

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-21 Thread Daniel Fischer
On Thursday 21 April 2011 13:08:22, Simon Marlow wrote:
 On 20/04/2011 18:28, Ian Lynagh wrote:
  On Wed, Apr 20, 2011 at 05:02:50PM +0200, Daniel Fischer wrote:
  So, is it possible that some change in ghc-7.0.3 vs. the previous
  versions
  
  Very little changed between 7.0.2 and 7.0.3. The only thing that jumps
  out to me as possibly being relevant is:
  
  diff -ur 7.0.2/ghc-7.0.2/compiler/nativeGen/X86/Instr.hs
  7.0.3/ghc-7.0.3/compiler/nativeGen/X86/Instr.hs ---
  7.0.2/ghc-7.0.2/compiler/nativeGen/X86/Instr.hs 2011-02-28
  18:10:06.0 + +++
  7.0.3/ghc-7.0.3/compiler/nativeGen/X86/Instr.hs 2011-03-26
  18:10:04.0 + @@ -734,6 +734,7 @@
  
 where p insn r = case insn of
 
CALL _ _ -  GFREE : insn : r
JMP _-  GFREE : insn : r
  
  +JXX_GBL _ _ -  GFREE : insn : r
  
_-  insn : r
 
 Right, it could be related to this.

I'm afraid it is. Comparing the dumped asm, after renaming identifiers, the 
only difference between the assembly produced by 7.0.2 and 7.0.3 is the 
appearance of 59

ffree %st(0) ;ffree %st(1) ;ffree %st(2) ;ffree %st(3)
ffree %st(4) ;ffree %st(5)

in 7.0.3's code which aren't in 7.0.2's.

 However this change was made to
 eliminate some causes of NaNs, see:
 
 http://hackage.haskell.org/trac/ghc/ticket/4914
 
 So I'm very depressed if it managed to introduce NaNs somehow.
 
 Could someone make a ticket for this, with the smallest test case found
 so far please?

http://hackage.haskell.org/trac/ghc/ticket/5149

 
 Cheers,
   Simon

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


Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
Investigating the appearance of NaN in criterion's output, I found that 
NaNs were frequently introduced into the resample vectors when the 
resamples were sorted.

Further investigation of the sorting code in vector-algorithms revealed no 
bugs there, and if the runtime was forced to keep a keen eye on the 
indices, by replacing unsafeRead/Write/Swap with their bounds-checked 
counterparts or by 'trace'ing enough of their uses, the NaNs did not 
appear.

I could not reproduce the behaviour with ghc-7.0.1 (using exactly the same 
versions of the involved libraries), ghc-7.0.2 (different criterion 
release, the other libraries identical) or unoptimised compilation with 
7.0.3 (no NaNs encountered in some 100+ testruns with varying input).

So, is it possible that some change in ghc-7.0.3 vs. the previous versions 
caused a bad interaction between ghc-optimisations and vector fusion 
resulting in bad vector reads/writes?

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 19:11:07, Roman Leshchinskiy wrote:
 Daniel Fischer wrote:
  Further investigation of the sorting code in vector-algorithms
  revealed no bugs there, and if the runtime was forced to keep a keen
  eye on the indices, by replacing unsafeRead/Write/Swap with their
  bounds-checked counterparts or by 'trace'ing enough of their uses,
  the NaNs did not appear.
 
 Did you replace them in vector-algorithms or in vector itself?
 

vector-algorithms only.

  So, is it possible that some change in ghc-7.0.3 vs. the previous
  versions caused a bad interaction between ghc-optimisations and vector
  fusion resulting in bad vector reads/writes?
 
 Am I right in assuming that this happens in code which uses only mutable
 vectors?

Yes, the sorting uses mutable vectors, in this case unboxed Double vectors.

 Fusion only works for immutable ones so it shouldn't really
 affect things here.

Ah, didn't know that. Another suspect gone.

 
 Have you tried playing around with code generation flags like -msse2?

No, not yet. So far only -O2 (with -fspec-constr-count=5 in the presence of 
many trace calls) and -O0.

 
 In any case, I would try to take a look at this if you tell me how to
 reproduce.

I'll prepare a bundle, I'm afraid it won't be small, though. And it might 
be architecture dependent, so I can't guarantee that you will be able to 
reproduce it. But Bryan said on IRC yesterday that others have reported 
similar issues with criterion output, so it may well be cross-platform 
reproducible.

Cheers,
Daniel

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 20:25:34, Bryan O'Sullivan wrote:
 On Wed, Apr 20, 2011 at 10:44 AM, Daniel Fischer 
 
 daniel.is.fisc...@googlemail.com wrote:
  I'll prepare a bundle, I'm afraid it won't be small, though. And it
  might be architecture dependent, so I can't guarantee that you will
  be able to reproduce it. But Bryan said on IRC yesterday that others
  have reported similar issues with criterion output, so it may well be
  cross-platform reproducible.
 
 Daniel, are you sure this is down to a 7.0.2/7.0.3 difference, and not
 perhaps due to just a bug in criterion itself?

I'm sure it's not criterion, because after I've found that NaNs were 
introduced to the resamples vectors during sorting (check the entire 
vectors for NaNs before and aftersorting, tracing the count; before: 0, 
afterwards often quite a number, sometimes close to 10%), the further tests 
didn't involve criterion anymore. criterion is simply the most obvious 
place to see the NaNs show up (with 5-10% NaNs among the resamples, it 
won't take too long to see one pop up).

It could be a bug in statistics, but I'm pretty sure this one's not due to 
statistics either, since fiddling with vector-algorithms made the NaNs 
disappear - btw., Bryan, using the heap sort instead of introsort, I 
haven't found any NaNs in my tests, so temporarily switching the algorithm 
might cure the symptoms.

Dan Doel and I spent not too little time scrutinising the vector-algorithms 
code without finding an issue. Also, replacing the unsafe access with 
bounds-checked access (apparently) eliminated the NaNs, and 7.0.1 and 7.0.2 
didn't produce any in my tests, yet more points to believe that it's none 
of these packages producing the behaviour, but rather something that 
changed between 7.0.2 and 7.0.3 -- however, so far in this matter my 
guesses as to what's responsible have been wrong, so I wouldn't be 
surprised if it's something entirely different.

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 21:55:51, Dan Doel wrote:
 
 It's not a statistics bug. I'm reproducing it here using just
 vector-algorithms.

Yep. Attached a simple testcasewhich reproduces it and uses only vector and 
vector-algorithms.

 
 Fill a vector of size N with [N..1], and (intro) sort it, and you get
 NaNs. But only with -O or above.

However, for me the NaNs disappear with the -msse2 option.

 Without optimization it doesn't
 happen (and nothing seems to be reading/writing out of bounds, as I
 compiled vector with UnsafeChecks earlier and it didn't complain).

Nor does it happen here with 7.0.2 or 7.0.1.

 
 Filling the vector with [1..N] also doesn't trigger the NaNs. [0,0..0]
 and [0,0..1] trigger it.
 
 I don't know what's going on yet. I have trouble believing it's a bug
 in vector-algorithms code, though, as I don't think I've written any
 RULEs (just INLINEs), and that's the one thing that comes to mind in
 library code that could cause a difference between -O0 and -O. So I'd
 tentatively suggest it's a vector, base or compiler bug.
 
 The above testing is on 64-bit windows running a 32-bit copy of GHC,
 for reference.

32-bit linux here

 
 My ability to investigate this will be a bit limited for the near
 future. If someone definitively tracks it down to bugs in my code,
 though, let me know, and I'll try and push a new release up on
 hackage.
 
 -- Dan
{-# LANGUAGE BangPatterns #-}
module Main where

import qualified Data.Vector.Unboxed.Mutable as MU
import Data.Vector.Unboxed.Mutable (IOVector, unsafeRead, unsafeWrite, new)
import qualified Data.Vector.Algorithms.Intro as I

import Control.Monad (when)
import System.Environment (getArgs)

countNaNs :: IOVector Double - IO Int
countNaNs a = go 0 0
  where
len = MU.length a
go !ct i
| i  len = do
x - unsafeRead a i
go (if isNaN x then ct+1 else ct) (i+1)
| otherwise = return ct

sample :: Int - IO (IOVector Double)
sample k = do
a - new k
let foo :: Double - Double
foo x = 1.0 + sin x / x
fill i x
| i  k = do
unsafeWrite a i (foo x)
fill (i+1) (x+1.0)
| otherwise = return a
fill 0 (fromIntegral k * 10)

main :: IO ()
main = do
args - getArgs
let k = case args of
  (arg:_) - read arg
  _   - 1
a - sample k
b - countNaNs a
when (b /= 0) (putStrLn $ Before sorting:  ++ show b ++  NaNs.)
I.sort a
c - countNaNs a
when (c /= 0) (putStrLn $ After sorting:  ++ show c ++  NaNs.)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Changing language options in ghci at runtime

2011-04-09 Thread Daniel Fischer
On Saturday 09 April 2011 13:50:03, Simon Hengel wrote:
 Hello,
 does anyone know whether you can somehow change the currently active
 language flags during a ghci session (say change what `:show languages'
 outputs)?

:set -Xlanguage

I suppose some languages wouldn't work/make sense (CPP, TH) but most you 
can toggle that way.

 If no, is this possible by using the GHC API?
 
 Cheers,
 Simon
 

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


T3738 allocation figures for 32-bit

2011-04-02 Thread Daniel Fischer
In 7.0.3's testsuite, allT in perf/should_run says:
test('T3738',
 [stats_num_field('peak_megabytes_allocated', 1,
  1),
 # expected value: 1 (amd64/Linux)
  # expected value: 12800 (x86/OS X):
  if_wordsize(32,
  stats_num_field('bytes allocated', 12700,
 14000)),
  if_wordsize(64,
  stats_num_field('bytes allocated', 6,
 8)),
 # expected value: 72608 (amd64/Linux)
  only_ways(['normal'])
  ],
 compile_and_run,
 ['-O'])

which looks quite amazing. On my linux box I consequently get

bytes allocated 60608 is more than maximum allowed 14000
*** unexpected failure for T3738(normal)

which looks quite horrible.
But considering that 6.12.3 allocated nearly 500,000 bytes for that, it's 
pretty fine.
In HEAD's testsuite, the figures have been adjusted to

  if_wordsize(32,
  stats_num_field('bytes allocated', 4,
 5)),

and HEAD does that, allocating 46008 bytes.

A trivial 'main = return ()'  produces

./nuff +RTS -s 
  47,496 bytes allocated in the heap
   1,376 bytes copied during GC
  34,036 bytes maximum residency (1 sample(s))
  19,212 bytes maximum slop

here

Apparently the allocation figures drastically vary by arch and OS, it would 
probably be necessary to test on several such and be more generous with the 
limits.

Cheers,
Daniel

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


T3738 allocation figures for 32-bit

2011-04-02 Thread Daniel Fischer
Hit send too soon:

 Apparently the allocation figures drastically vary by arch and OS, it 
 would probably be necessary to test on several such and be more
 generous with the limits.

The same holds for other tests, of course. I had unexpected failures due to 
allocation figures also for space_leak001, T4801 and T3064.

space_leak001 failing with
bytes allocated 9328745840 is more than maximum allowed 91
(allocation figures slightly vary among the different ways)
which is close enough to not worry about, considering the minimum allowed 
is 905000.

T4801 with
peak_megabytes_allocated 41 is less than minimum allowed 70
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again
bytes allocated 358364424 is more than maximum allowed 8000
max_bytes_used 17406288 is more than maximum allowed 400

and T3064 with
peak_megabytes_allocated 9 is less than minimum allowed 14
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again
bytes allocated 69984336 is less than minimum allowed 15000
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again
max_bytes_used 3368652 is less than minimum allowed 600
If this is because you have improved GHC, please
update the test so that GHC doesn't regress again

The figures in HEAD's testsuite are again close to what I get, while the 
7.0.3 figures are way off.

Cheers,
Daniel

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


Re: memory slop (was: Using the GHC heap profiler)

2011-03-22 Thread Daniel Fischer
On Wednesday 23 March 2011 03:32:16, Tim Docker wrote:
 On Mon, Mar 21, 2011 at 9:59 AM, I wrote:
  My question on the ghc heap profiler on stack overflow:
  
  http://stackoverflow.com/questions/5306717/how-should-i-interpret-the-
  output-of-the-ghc-heap-profiler
  
  remains unanswered :-( Perhaps that's not the best forum. Is there
  someone here prepared to explain how the memory usage in the heap
  profiler relates to the  Live Bytes count shown in the garbage
  collection statistics?
 
 I've made a little progress on this. I've simplified my program down to
 a simple executable that loads a bunch of data into an in-memory map,
 and then writes it out again. I've added calls to `seq` to ensure that
 laziness is not causing excessing memory consumption. When I run this on
 my sample data set, it takes ~7 cpu seconds, and uses ~120 MB of vm An
 equivalent python script, takes ~2 secs and ~19MB of vm :-(.
 
 The code is below. I'm mostly concerned with the memory usage rather
 than performance at this stage. What is interesting, is that when I turn
 on garbage collection statistics (+RTS -s), I see this:
 
10,089,324,996 bytes allocated in the heap
   201,018,116 bytes copied during GC
12,153,592 bytes maximum residency (8 sample(s))
59,325,408 bytes maximum slop
   114 MB total memory in use (1 MB lost due to
 fragmentation)
 
Generation 0: 19226 collections, 0 parallel,  1.59s, 
 1.64selapsed Generation 1: 8 collections, 0 parallel,  0.04s, 
 0.04selapsed
 
INIT  time0.00s  (  0.00s elapsed)
MUT   time5.84s  (  5.96s elapsed)
GCtime1.63s  (  1.68s elapsed)
EXIT  time0.00s  (  0.00s elapsed)
Total time7.47s  (  7.64s elapsed)
 
%GC time  21.8%  (22.0% elapsed)
 
Alloc rate1,726,702,840 bytes per MUT second
 
Productivity  78.2% of total user, 76.5% of total elapsed
 
 This seems strange. The maximum residency of 12MB sounds about correct
 
 for my data. But what's with the 59MB of slop? According to the ghc 
docs:
 | The bytes maximum slop tells you the most space that is ever wasted
 | due to the way GHC allocates memory in blocks. Slop is memory at the
 | end of a block that was wasted. There's no way to control this; we
 | just like to see how much memory is being lost this way.
 
 There's this page also:
 
 http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/Slop
 
 but it doesn't really make things clearer for me.
 
 Is the slop number above likely to be a significant contribution to net
 memory usage?

Yes, absolutely.

 Are there any obvious reasons why the code below could be
 generating so much?

I suspect packing a lot of presumably relatively short ByteStrings would 
generate (the lion's share of) the slop. I'm not familiar with the 
internals, though, so I don't know where GHC would put a 
newPinnedByteArray# (which is where your ByteString contents is), what 
alignement requirements those have.

 The data file in question has 61k lines, and is 6MB
 in total.
 
 Thanks,
 
 Tim
 
  Map2.hs 
 
 module Main where
 
 import qualified Data.Map as Map
 import qualified Data.ByteString.Char8 as BS
 import System.Environment
 import System.IO
 
 type MyMap = Map.Map BS.ByteString BS.ByteString
 
 foldLines :: (a - String - a) - a - Handle - IO a
 foldLines f a h = do
  eof - hIsEOF h
  if eof
then (return a)
else do
   l - hGetLine h
   let a' = f a l
   a' `seq` foldLines f a' h
 
 undumpFile :: FilePath - IO MyMap
 undumpFile path = do
  h - openFile path ReadMode
  m - foldLines addv Map.empty h
  hClose h
  return m
where
  addv m  = m
  addv m s = let (k,v) = readKV s
 in k `seq` v `seq` Map.insert k v m
 
  readKV s = let (ks,vs) = read s in (BS.pack ks, BS.pack vs)

It might be better to read the file in one go and construct the map in pure 
code (foldl' addv Map.empty $ lines filecontents).
Also, it will probably be better to do everything on ByteStrings.
The file format seems to be
(key,value)
on each line, with possible whitespace and empty lines.
If none of the keys or values may contain a '\',

undumpFile path = do
contents - BS.readFile path
return $! foldl' addv Map.empty (BS.lines contents)
  where
addv m s
  | BS.null s = m
  | otherwise = case BS.split '' s of
  (_ : k : _ : v : _) - Map.insert k v m
  _ - error malformed line

should perform much better.
If a key or value may contain '', it's more complicated, using a regex 
library to split might be a good option then.

 
 dump :: [(BS.ByteString,BS.ByteString)] - IO ()
 dump vs = mapM_ putV vs
where
  putV (k,v) = putStrLn (show (BS.unpack k, BS.unpack v))
 
 main :: IO ()
 main =  do
  args - getArgs
  case args of
[path] - do
v - undumpFile path

Documentation build failure

2011-03-05 Thread Daniel Fischer
make-ing 7.0.2 failed with:

-- everything fine up to here, users guide html okay

Build users_guide.ps
This is pdfTeX, Version 3.1415926-1.40.10 (TeX Live 2009/openSUSE)
entering extended mode
latex failed
users_guide_tmp.tex:1631: Undefined control sequence \Documents.
users_guide_tmp.tex:1631: leading text: }
users_guide_tmp.tex:1631: Undefined control sequence \user.
users_guide_tmp.tex:1631: leading text: }
users_guide_tmp.tex:3993: Undefined control sequence \Person.
users_guide_tmp.tex:3993: leading text:   or \nolinkurl{Data\Person.hs}
users_guide_tmp.tex:6185: Undefined control sequence \Documents.
users_guide_tmp.tex:6185: leading text: 
...ts~And~Settings\user\ghc\package.conf.d}
users_guide_tmp.tex:6185: Undefined control sequence \user.
users_guide_tmp.tex:6185: leading text: 
...ts~And~Settings\user\ghc\package.conf.d}
users_guide_tmp.tex:6185: Undefined control sequence \ghc.
users_guide_tmp.tex:6185: leading text: 
...ts~And~Settings\user\ghc\package.conf.d}
users_guide_tmp.tex:6185: Undefined control sequence \package.
users_guide_tmp.tex:6185: leading text: 
...ts~And~Settings\user\ghc\package.conf.d}
users_guide_tmp.tex: File ended while scanning use of \hyper@n@rmalise.
users_guide_tmp.tex: Emergency stop.
Error: latex compilation failed
make[1]: *** [docs/users_guide/users_guide.ps] Fehler 1
make: *** [all] Fehler 2

on openSUSE 11.3.

I don't know which programme is at fault here, maybe someone can check 
whether ps/pdf documentation building works on other systems.

Re ./configure-ing after setting

BUILD_DOCBOOK_PS = NO
BUILD_DOCBOOK_PDF = NO

in mk/build.mk said it would build ps and pdf documentation nevertheless, I 
had to edit the configure script to convince it not to try.
configure just checks for the existence of a dblatex command, so perhaps

$ dblatex --version
/usr/lib/python2.6/site-packages/dbtexmf/dblatex/grubber/util.py:8: 
DeprecationWarning: the md5 module is deprecated; use hashlib instead
  import md5
dblatex version 0.2.7

is helpful information.


Unrelated:

The build produces several

SpecConstr
Function `$j_s8qC{v} [lid]'
  has four call patterns, but the limit is 3
Use -fspec-constr-count=n to set the bound
Use -dppr-debug to see specialisations

warnings(?) (this is also very common building libraries).

a) What does that mean for code generation? Will the specialisations be 
generated nevertheless?
b) Would it be reasonable to have a higher default than 3 for spec-constr-
count?

Cheers,
Daniel

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


Re: Documentation build failure

2011-03-05 Thread Daniel Fischer
On Sunday 06 March 2011 02:03:12, Ian Lynagh wrote:
 On Sat, Mar 05, 2011 at 11:27:40AM +0100, Daniel Fischer wrote:
  
 
  $ dblatex --version
  /usr/lib/python2.6/site-packages/dbtexmf/dblatex/grubber/util.py:8: 
  DeprecationWarning: the md5 module is deprecated; use hashlib instead
 
import md5
 
  dblatex version 0.2.7
 
 I don't know if this is the problem, but I have
 
 $ dblatex --version
 dblatex version 0.3-2
 
 Debian's previous stable release had 0.2.9, so that's probably fine too.

That seems to be the problem, after installing dblatex-0.3-1.2:

$ make docs/users_guide/users_guide.ps
===--- updating makefiles phase 0
make -r --no-print-directory -f ghc.mk phase=0 just-makefiles
snip
[242] [243] [244] [245] [246] 
'users_guide.ps' successfully built
[ -f docs/users_guide/users_guide.ps ]

Check for dblatex = 0.2.9 in configure?

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


Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote:
 Why don't the rules fire, what can I change such that they do, and what
 to get rid of the warning for the second rule (which I think is the one
 I should use)?

Didn't spot that, sorry.


 Best regards,
 Sebastian

 Here is the output of -ddump-simple-stats (once with
 -fenable-rewrite-rules only and once with -O):

Users guide says:

(NB: enabling -fenable-rewrite-rules without -O may not do what you expect, 
though, because without -O GHC ignores all optimisation information in 
interface files;



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


Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote:
 Why don't the rules fire,

Because the 'match' is at the wrong type. In main, idGen appears as

idGen_anJ :: ([()] - [[()]]) - [[()]] - [[()]]

at some point (yay for ghc -v4), so it doesn't match g's polymorphic type.

 what can I change such that they do,

Type signatures.

 and what to get rid of the warning for the second rule (which I think
 is the one I should use)?

I'll let that for somebody else.

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


Re: How to #include into .lhs files?

2011-02-03 Thread Daniel Fischer
On Thursday 03 February 2011 10:33:23, Conal Elliott wrote:
 Does anyone have a working example of #include'ing Haskell code into a
 bird-tracks-style .lhs file with GHC? Every way I try leads to parsing
 errors. Is there documentation about how it's supposed to work?

 Help much appreciated.   - Conal

Stupid example:

-- Main:

 {-# LANGUAGE CPP #-}
 module Main (main) where

#include MachDeps.h

 main :: IO ()
 main = do

#if WORD_SIZE_IN_BITS == 32

 putStrLn 32 bits

#include Stuff32

# else

 putStrLn 64 bits

#include Stuff64
#endif

-- Stuff32:

  putStrLn Included from Stuff32

-- Stuff64:

  putStrLn Included from Stuff64


It's a bit tricky. Since the C preprocessor is run after the unlit, the 
included code should not have bird-tracks, also you have to get the 
indentation right. There's probably a way to run cpp before unlit, which 
would allow you to have bird-tracks in the #include'd code.

Much easier with LaTeX-style literate code.

Cheers,
Daniel

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


Re: Type system compiler flags

2011-02-01 Thread Daniel Fischer
On Tuesday 01 February 2011 10:20:26, Carsten Schultz wrote:
 Hello everyone,

 I am trying to compile some code that I have written a long time ago
 (might have been for ghc 6.3), and I have not done much Haskell in the
 meantime.  I have trouble compiling the code, maybe only because I do
 not remember the necessary flags (yes, these should be in the source
 files), maybe because ghc has changed.

GHC has changed pretty much. I don't know whether there's a way to make 
your code compile with flags, without changing the code itself.

 I do for example have functions like this:


 getnArray :: Int - [Word8] - Maybe (UArray Int Word8, [Word8])
 getnArrayST :: Int - [Word8] -
  (forall s . ST s (Maybe (UArray Int Word8, [Word8])))

 getnArrayST n bs :: ST s (Maybe (UArray Int Word8, [Word8])) =

Get rid of such signatures, this is where you get a parse error, I don't 
know if there's a way to make GHC parse it at all. I doubt it.

 do
 (a :: STUArray s Int Word8) - newArray_ (0,n-1)

Move the signature to the RHS,

  a - newArray_ (0,n-1) :: ST s (STUArray s Int Word8)

 let loop k bs

| k == n = do fa - freeze a

  return $ Just (fa, bs)

| k  n = case bs of

  (b:bs) - do
writeArray a k b
loop (k+1) bs
  [] - return Nothing
 loop 0 bs

 getnArray n bs = runST (getnArrayST n bs)


With those changes (and ScopedTypeVariables), it compiles.



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


Re: Type system compiler flags

2011-02-01 Thread Daniel Fischer
On Tuesday 01 February 2011 11:45:58, Julian Bean wrote:
  It indeed does, even though I doubted it at first.  As far as I
  remember the type in
 
 getnArrayST n bs :: ST s (Maybe (UArray Int Word8, [Word8])) =
 
  used to be necessary to bind the type variable s.  Apparently things
  have become easier.

 The higher-rank inference has been changed quite a bit, but I think
 -XPatternSignatures is all you were missing to get your original code to
 compiler (well, at least to parse).

No, I tried, the parser still choked on the above signature. You can get 
the other one, (a :: STUArray s Int Word8), to be parsed with 
PatternSignatures, but

A pattern type signature cannot bind scoped type variables `s'
  unless the pattern has a rigid type context
In the pattern: a :: STUArray s Int Word8
In a stmt of a 'do' expression:
(a :: STUArray s Int Word8) - newArray_ (0, n - 1)
In the expression:
do { (a :: STUArray s Int Word8) - newArray_ (0, n - 1);
 let loop k bs
| k == n = ...
| k  n = ...;
 loop 0 bs }

even if you remove the forall from getnArrayST's type signature. I don't 
know why `s' is a scoped type variable without the forall and 
ScopedTypeVariables, but that's what 6.12.3 says. 7.0.1 complains about

No instance for (MArray (STUArray s) Word8 (ST s1))

which I understand.


 Jules


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


Re: Stack overflow weirdness

2011-01-28 Thread Daniel Fischer
On Friday 28 January 2011 11:40:33, Simon Marlow wrote:
 I think you may have had an encounter with this bug:

    http://hackage.haskell.org/trac/ghc/ticket/4924


That seems not unlikely. the offending Main contained a couple of near-
identical loops, and that bug doesn't reliably occur (I compiled your 
example Test module a few times with -O2 [ghc-7.0.1] and always got
  Str=DmdType U(L)U(L)m,
for both, f and g).

 I reported it yesterday, and Simon has already fixed it.  The fix will
 be in 7.0.2.

Great.

Cheers,
Daniel

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


Stack overflow weirdness

2011-01-27 Thread Daniel Fischer
While tuning some code, the test programme suddenly started producing stack 
overflows.
Reverting the code to a previous version did not revert that behaviour, 
code that previously produced a well-behaved binary now produced stack 
overflowing ones.
But only with ghc-7.0.1, not with ghc-6.12.3 and ghc-6.12.1, and when 
compiled with optimisations (both, -O and -O2) and without profiling.
A HEAD from October and a freshly darcs pulled HEAD displayed the same 
behaviour as 7.0.1.
At some point I tried compiling with -fno-strictness (+ -O or -O2) which 
again produced well-behaved albeit somewhat slower binaries.
An hour or so later, I again compile with -O2 without -fno-strictness to 
see whether the Core revealed something and, as suddenly as the stack 
overflows started, they disappeared, for the time being, I consistently get 
well-behaved binaries.

A run of an overflowing binary with -hT -K32M produced a triangular graph 
with  10MB Blackhole allocation and  30MB TSO allocation in the peak.

Obviously the behaviour is not reproducible, nevertheless, perhaps somebody 
has an idea what went on. Or should I attribute it to cosmic rays?

Cheers,
Daniel

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


Re: Oversized libraries

2010-12-14 Thread Daniel Fischer
On Tuesday 14 December 2010 17:50:30, Simon Marlow wrote:
 This particular example seems to be fixed, at least with the current
 HEAD:

Also with 7.0.1. On my 32-bit system, -O increases the Types.o size from 
37K to 45K which is reasonable, while with 6.12.3 it goes from 38K to 543K.

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


Re: Cabal constraint solver

2010-10-02 Thread Daniel Fischer
On Sunday 03 October 2010 00:07:24, Christian Höner zu Siederdissen wrote:
 Hi,

 does the Cabal constraint solver always try to solve the complete graph?

 example: (ghc-7.0.0-rc1)

 $ cabal install parsec-3.1.0
 cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3

 cd syb-0.2.1
 * remove base4.3 constraint from syb.cabal
 cabal install
 * syb-0.2.1 is now installed and works!

 $ cabal install parsec-3.1.0
 cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3


Yes, cabal looks at the package-index to find out the required 
dependencies, it doesn't know where you have local source files.

When you edit a .cabal file, always increment the version of the package, 
in this case making the version 0.2.1.1 or 0.2.1.0.1 would be a good 
choice.

Then cabal sees you have a newer version of syb installed and unless 
parsec-3.1.0 asks explicitly for version 0.2.1 (or = 0.2.1), it will 
choose the newer installed version (since the package index knows nothing 
about that, it doesn't see an inconsistency and assumes it'll be alright).
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Cabal constraint solver

2010-10-02 Thread Daniel Fischer
On Sunday 03 October 2010 02:10:11, Felipe Lessa wrote:
 On Sat, Oct 2, 2010 at 8:29 PM, Daniel Fischer daniel.is.fisc...@web.de 
wrote:
  Yes, cabal looks at the package-index to find out the required
  dependencies, it doesn't know where you have local source files.

 Actually, this is cabal-install.  If you 'cabal unpack' then
 'runhaskell Setup.hs configure' and 'runhaskell Setup.hs build', maybe
 it works =).

Worked for me with cabal (as in, the executable provided by cabal-install).

$ cabal unpack package-with-bad-constraints
$ cd package-with-bad-constraints
-- change constraints in package-with-bad-constraints.cabal
$ cabal install
$ cabal install package-which-depends-on-previous

If I changed the version, it worked (unless I overlooked a package with bad 
constraints), if not, it tried to reinstall (and failed of course).


 But the suggestion about increasing the version number is good anyways.

 Cheers! =)

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


Re: ANNOUNCE: GHC 7.0.1 Release Candidate 1

2010-09-29 Thread Daniel Fischer
On Wednesday 29 September 2010 16:51:35, Antoine Latter wrote:
 Here's a boiled-down equivalent to what the issue is in uvector:

 http://hpaste.org/40213/doesnt_work_in_ghc_7

 In GHC 6.12, this would have type-checked. In GHC 7, I need to add a
 type-signature to the 'helper' function, except I 'm not sure how to
 do it.

 So the function in uvector might need a larger refactoring.

 Antoine

It works if you define helper inside the runST via a let (no type 
signature).
I suspect that would become a larger refactoring in uvector, but at least 
there's a simple way.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 7.0.1 Release Candidate 1

2010-09-27 Thread Daniel Fischer
On Monday 27 September 2010 12:58:08, Christian Maeder wrote:

 I've tried to install HTTP (for cabal-install) and get the following
 error:

 Configuring HTTP-4000.0.9...
 Setup: At least the following dependencies are missing:
 base ==3.*

 What is the problem? The Build-depends of HTTP's cabal file look correct
 (and fulfilled):
 Build-depends: base = 3, array, old-time, bytestring

 Cheers Christian

Probably it's the preferred versions on hackage:
-- A global set of preferred versions.
--
-- This is to indicate a current recommended version, to allow stable and
-- experimental versions to co-exist on hackage and to help transitions
-- between major API versions.
--
-- Tools like cabal-install take these preferences into account when 
-- constructing install plans.
--
base  4
parsec  3
cabal-install  0.10


Try installing it with --constraint=base = 4 and if that doesn't 
suffice, --preference=base = 4.

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


Re: ANNOUNCE: GHC 7.0.1 Release Candidate 1

2010-09-27 Thread Daniel Fischer
On Monday 27 September 2010 13:44:07, Christian Maeder wrote:
 The HTTP.cabal file is not correct!
   Build-depends: base = 2   4, network, parsec, mtl

 (an additional constraint does not help)

 Cheers Christian

In that case, change the local .cabal file as an immediate measure and 
notify the maintainer.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unicode characters in operator name

2010-09-10 Thread Daniel Fischer
On Saturday 11 September 2010 03:12:11, Greg wrote:

 If I read the Haskell Report correctly, operators are named by (symbol
 {symbol | : }), where symbol is either an ascii symbol (including *) or
 a unicode symbol (defined as any Unicode symbol or punctuation).  I'm
 pretty sure º is a unicode symbol or punctuation.

No,

Prelude Data.Char generalCategory 'º'
LowercaseLetter

weird, but that's how it is. If it were a symbol or punctuation, you 
couldn't use it in function names like fº.

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


Re: HEAD: Deterioration in ByteString I/O

2010-09-09 Thread Daniel Fischer
On Thursday 09 September 2010 13:19:23, Simon Marlow wrote:
 I think I've found the problem, GHC.IO.Handle.Text:

 bufReadNBEmpty :: Handle__ - Buffer Word8 - Ptr Word8 - Int - Int -
 IO Int
 bufReadNBEmpty   h...@handle__{..}
                   b...@buffer{ bufRaw=raw, bufR=w, bufL=r, bufSize=sz }
                   ptr so_far count
    | count  sz, False,
      Just fd - cast haDevice = do
         m - RawIO.readNonBlocking (fd::FD) ptr count
         case m of
           Nothing - return so_far
           Just n  - return (so_far + n)


 See if you can spot it.

Yes, that's it. Removing the literal False to make that branch reachable 
more or less reinstates old behaviour.

For I/O of (lazy) ByteStrings only, the allocation figures of HEAD are 
consistently slightly higher than those of 6.12.3, but the difference is 
less than 1%, well within the normal fluctuation due to changes in 
implementation. Timings seem to be identical.

When performing work on the ByteStrings (finding/replacing substrings), 
however, things change a bit.
The allocation figures observed so far range from almost identical ( 1% 
difference) to above 15% higher (90,146,508 bytes allocated vs. 
106,237,456), most of the differences I observed so far are between 5% and 
10%.
The wall clock time (elapsed, per +RTS -s or time) seems to be identical 
(very stable timings for multiple runs of the same benchmark), but the MUT 
times reported by +RTS -s differ for some benchmarks (between 10% less for 
HEAD and 20% more observed, but identical for most).

That might be worthy of examination, though it's not alarming.

Cheers,
Daniel

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


HEAD: Deterioration in ByteString I/O

2010-09-08 Thread Daniel Fischer
Trying out HEAD (specifically, ghc-6.13.20100831-src.tar.bz2 built with 
6.12.3) investigating an issue with the text package, I found that I/O of 
ByteStrings has become significantly slower (on my machine at least:

$ uname -a
Linux linux-mkk1 2.6.27.48-0.2-pae #1 SMP 2010-07-29 20:06:52 +0200 i686 
i686 i386 GNU/Linux

Pentium 4, 3.06GHz).

Timings for reading and outputting a 74.3MB file:

cat:
$ time cat bigfile  /dev/null
0.00user 0.04system 0:00.06elapsed 83%CPU

ghc-6.12.3:
$ time ./nbench lazyBSNull bigfile a b  /dev/null
0.01user 0.09system 0:00.10elapsed 100%CPU

ghc-6.13.20100831:
$ time ./hdbench lazyBSNull bigfile a b  /dev/null
0.07user 0.10system 0:00.18elapsed 96%CPU

In addition to the slowdown, the allocation behaviour has become quite bad:

ghc-6.12.3:
  89,330,672 bytes allocated in the heap
  15,092 bytes copied during GC
  35,980 bytes maximum residency (1 sample(s))
  29,556 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

ghc-6.13.20100831:
 475,305,720 bytes allocated in the heap
  89,272 bytes copied during GC
  68,860 bytes maximum residency (1 sample(s))
  29,444 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HEAD: Deterioration in ByteString I/O

2010-09-08 Thread Daniel Fischer
On Wednesday 08 September 2010 18:10:26, Don Stewart wrote:
 Can you put your benchmark code somewhere?

Boiled down to the bare minimum,

module Main (main) where

import System.Environment (getArgs)
import qualified Data.ByteString.Lazy as L

main :: IO ()
main = do
(file : _) - getArgs
L.readFile file = L.putStr


Then all you need is a file of nontrivial size (a few 10KB is enough to 
show it).

   Likely a GHC regression.

That's what I think.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HEAD: Deterioration in ByteString I/O

2010-09-08 Thread Daniel Fischer
On Wednesday 08 September 2010 23:55:35, Don Stewart wrote:
 simonpj:
  |   ghc-6.12.3:
  | 89,330,672 bytes allocated in the heap
  | 15,092 bytes copied during GC
  | 35,980 bytes maximum residency (1 sample(s))
  | 29,556 bytes maximum slop
  |  2 MB total memory in use (0 MB lost due to
  |   fragmentation)
  |  
  |   ghc-6.13.20100831:
  |475,305,720 bytes allocated in the heap
  | 89,272 bytes copied during GC
  | 68,860 bytes maximum residency (1 sample(s))
  | 29,444 bytes maximum slop
  |  2 MB total memory in use (0 MB lost due to
  |   fragmentation)
  |
  |  Can you put your benchmark code somewhere?  Likely a GHC
  | regression.
 
  Indeed bad. If someone could characterise the regression more
  precisely (e.g. fusion isn't happening here) that would be jolly
  helpful.

 Shouldn't be fusion. Is this a straight IO function. Something to do
 with buffering/encoding?

Maybe the following observation helps:

ghc-6.13.20100831 reads lazy ByteStrings in chunks of 8192 bytes.

If I understand correctly, that means (since defaultChunkSize = 32760)
- bytestring allocates a 32K buffer to be filled and asks ghc for 32760 
bytes in that buffer
- ghc asks the OS for 8192 bytes (and usually gets them)
- upon receiving fewer bytes than requested, bytestring copies them to a 
new smaller buffer
- since the number of bytes received is a multiple of ghc's allocation 
block size (which I believe is 4K), there's no space for the bookkeeping 
overhead, hence the new buffer takes up 12K instead of 8, resulting in 44K 
allocation for 8K bytes

That factor of 5.5 corresponds pretty well with the allocation figures 
above, and the extra copying explains the approximate doubling of I/O time.

Trying to find out why ghc asks the OS for only 8192 bytes instead of 32760 
hasn't brought enlightenment yet.

Cheers,
Daniel

Excerpt of strace log:

read(3, %!PS-Adobe-2.0\n%%Title: nbench\n%..., 8192) = 8192
open(/usr/lib/gconv/UTF-32.so, O_RDONLY) = 4
read(4, 
\177ELF\1\1\1\0\0\0\0\0\0\0\0\0\3\0\3\0\1\0\0\0`\4\0\0004\0\0\0..., 512) 
= 512
fstat64(4, {st_mode=S_IFREG|0755, st_size=9672, ...}) = 0
mmap2(NULL, 12328, PROT_READ|PROT_EXEC, MAP_PRIVATE|MAP_DENYWRITE, 4, 0) = 
0xb7852000
fadvise64(4, 0, 12328, POSIX_FADV_WILLNEED) = 0
mmap2(0xb7854000, 8192, PROT_READ|PROT_WRITE, MAP_PRIVATE|MAP_FIXED|
MAP_DENYWRITE, 4, 0x1) = 0xb7854000
close(4)= 0
mprotect(0xb7854000, 4096, PROT_READ)   = 0
ioctl(1, SNDCTL_TMR_TIMEBASE or TCGETS, 0xbff37cb0) = -1 ENOTTY 
(Inappropriate ioctl for device)
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1, , 0) = 0
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1, %!PS-Adobe-2.0\n%%Title: nbench\n%..., 8192) = 8192
read(3,  20.00 lineto\n121.153524 20, 8192) = 8192
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1, , 0) = 0
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1,  20.00 lineto\n121.153524 20, 8192) = 8192
read(3, 30.542315 21.394403 lineto\n125.3..., 8192) = 8192
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1, , 0) = 0
select(2, [], [1], NULL, {0, 0})= 1 (out [1], left {0, 0})
write(1, 30.542315 21.394403 lineto\n125.3..., 8192) = 8192
read(3, neto\n308.929337 21.969871 lineto..., 8192) = 8192
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: HEAD: Deterioration in ByteString I/O

2010-09-08 Thread Daniel Fischer
On Thursday 09 September 2010 01:28:04, Daniel Fischer wrote:
 Maybe the following observation helps:

 ghc-6.13.20100831 reads lazy ByteStrings in chunks of 8192 bytes.

 If I understand correctly, that means (since defaultChunkSize = 32760)
 - bytestring allocates a 32K buffer to be filled and asks ghc for 32760
 bytes in that buffer
 - ghc asks the OS for 8192 bytes (and usually gets them)
 - upon receiving fewer bytes than requested, bytestring copies them to a
 new smaller buffer
 - since the number of bytes received is a multiple of ghc's allocation
 block size (which I believe is 4K), there's no space for the bookkeeping
 overhead, hence the new buffer takes up 12K instead of 8, resulting in
 44K allocation for 8K bytes

 That factor of 5.5 corresponds pretty well with the allocation figures
 above,

That seems to be correct, but probably not the whole story.
I've played with defaultChunkSize, setting it to (64K - overhead), ghc 
still reads in 8192 byte chunks, the allocation figures are nearly double 
those for (32K - overhead). Setting it to (8K - overhead), ghc reads in 
8184 byte chunks and the allocation figures go down to approximately 1.4 
times those of 6.12.3.
Can a factor of 1.4 be explained by the smaller chunk size or is something 
else going on?

 and the extra copying explains the approximate doubling of I/O time.

Apparently not. With the small chunk size which should avoid copying, the 
I/O didn't get faster.


 Trying to find out why ghc asks the OS for only 8192 bytes instead of
 32760 hasn't brought enlightenment yet.

No progress on that front.

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


Re: GADT related bug in GHC type checker

2010-07-13 Thread Daniel Fischer
On Wednesday 14 July 2010 00:11:00, George Giorgidze wrote:
 Hi,

 I have encountered a bug in GHC type checker. I have stripped down my
 code to small manageable example that illustrates the bug:

 {-# LANGUAGE GADTs #-}
 {-# OPTIONS -Wall #-}

 module StrangeGADT where

 data Q a where
   ToQ :: (QA a) = a - Q a
   Sum :: (QA a, Num a) = Q [a] - Q a

 class QA a where
   toQ :: a - Q a
   fromQ :: Q a - a

 instance QA Int where
   toQ = ToQ
   fromQ q = case q of
  ToQ a - a
  Sum as - sum (fromQ as)

 instance QA a = QA [a] where
   toQ = ToQ
   fromQ q = case q of
  ToQ a - a
  -- Sum _ - ([] + 13)

 The above program typechecks but GHC wrongly warns that last pattern
 match is not exhaustive.

That warning is correct. Uncommenting the Sum case:

*StrangeGADT fromQ (Sum $ ToQ [[1 :: Int .. 10]])
[]

Of course, to make it work, I needed

instance (Num a) = Num [a] where
(+) = zipWith (+)
and so on
fromInteger = repeat . fromInteger

But since that instance is possible, both constructors can appear as 
arguments to fromQ for the list instance, hence the warning.


 Furthermore, if I uncomment the last line of the code it typechecks
 (without warnings) and does not reject ([] + 13) as type incorrect
 expression.

It's type correct:

Prelude :t [] + 13
[] + 13 :: (Num [a]) = [a]

It's usable only when a Num instance for a list is in scope, though.


 It would be very much appreciated if someone could suggest how to
 circumvent the problem.

For the code you posted, there is no problem to circumvent. GHC behaves 
correctly since it works on an open world assumption, it doesn't rely on 
the instances in scope but takes other possible instances into account.


 Is there a version of GHC that behaves correctly in this case?

 Is this yet another instance of GADT related bugs already reported in
 GHC trac? or it is unrelated and I better report it as a separate
 ticket.

 Cheers, George


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


unsafeCoerce# between integral and floating point types

2010-07-08 Thread Daniel Fischer
The docs for unsafeCoerce# say:

The following uses of unsafeCoerce# are supposed to work (i.e. not lead to 
spurious compile-time or run-time crashes):

# Casting any lifted type to Any
# Casting Any back to the real type
# Casting an unboxed type to another unboxed type of the same size (but not 
coercions between floating-point and integral types)
...

My experience so far is consistent with the assumption that e.g.

unsafeCoerce# :: Word64 - Double

is like a cast from (uint64_t *) to (double *), i.e. a bit-pattern-
preserving transformation (although by the docs, that use is undefined).

Would that assumption generally hold for
unsafeCoerce :: a - b
where a and b are single constructor data types wrapping unboxed types of 
the same bit-size and hence the use of unsafeCoerce# between such types 
would produce reliable results *on the same machine with the same OS (and 
GHC version?)* ?

And what about e.g.

unsafeCoerce# :: Word64# - Double# ?

By the docs, that isn't supposed to work. Is it not supposed to work only 
because it's not value-preserving (unsafeCoerce# 1## /=## 1.0##) or are 
there more pitfalls?

If there are more pitfalls, is there any chance of getting a function which 
reinterprets the bit-patterns?

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


Re: unsafeCoerce# between integral and floating point types

2010-07-08 Thread Daniel Fischer
On Thursday 08 July 2010 18:15:44, Ian Lynagh wrote:
 On Thu, Jul 08, 2010 at 04:49:00PM +0200, Daniel Fischer wrote:
  unsafeCoerce# :: Word64# - Double# ?
 
  By the docs, that isn't supposed to work. Is it not supposed to work
  only because it's not value-preserving (unsafeCoerce# 1## /=## 1.0##)
  or are there more pitfalls?

 It can fail to compile, even; see
 http://hackage.haskell.org/trac/ghc/ticket/2209


Yeah, tried that myself, with optimisations:

[2 of 2] Compiling Main ( testUCastD.hs, testUCastD.o ) 

ghc: panic! (the 'impossible' happened) 

  (GHC version 6.12.3 for i386-unknown-linux):  

getRegister(x86) I64[R1 + 3]


Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

But without optimisations, it compiles and seems to work (I won't rely on 
that, was just curious).

Should I report it or is the panic okay since unsafeCoerce# isn't supposed 
to work for those types?

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


Re: laziness in `length'

2010-06-15 Thread Daniel Fischer
On Tuesday 15 June 2010 16:52:04, Denys Rtveliashvili wrote:
 Hi Daniel,

 Thank you very much for the explanation of this issue.

 While I understand the parts about rewrite rules and the big thunk, it
 is still not clear why it is the way it is.

 Please could you explain which Nums are not strict? The ones I am aware
 about are all strict.

There are several implementations of lazy (to different degrees) Peano 
numbers on hackage.
The point is that it's possible to have lazy Num types, and the decision 
was apparently to write genericLength so that lazy Num types may profit 
from it.
Arguably, one should have lazyGenericLength for lazy number types and 
strictGenericLength for strict number types (Integer, Int64, Word, Word64, 
...).
On the other hand, fromIntegral . length works fine in practice (calling 
length on a list exceeding the Int range would be doubtful on 32-bit 
systems and plain madness on 64-bit systems).


 Also, why doesn't it require building the full thunk for non-strict
 Nums? Even if they are not strict, an addition requires both parts to be
 evaluated.

Not necessarily for lazy numbers.

 This means the thunk will have to be pre-built, doesn't it?

For illustration, the very simple-minded lazy Peano numbers:

data Peano
= Zero
| Succ Peano
  deriving (Show, Eq)

instance Ord Peano where
compare Zero Zero = EQ
compare Zero _= LT
compare _Zero = GT
compare (Succ m) (Succ n) = compare m n
min Zero _ = Zero
min _ Zero = Zero
min (Succ m) (Succ n) = Succ (min m n)
max Zero n = n
max m Zero = m
max (Succ m) (Succ n) = Succ (max m n)

instance Num Peano where
Zero + n = n
(Succ m) + n = Succ (m + n)
-- omitted other methods due to laziness (mine, not Haskell's)
fromInteger n
| n  0 = error Peano.fromInteger: negative argument
| n == 0 = Zero
| otherwise = Succ (fromInteger (n-1))

one, two, three, four :: Peano
one = Succ Zero
two = Succ one
three = Succ two
four = Succ three

min two (genericLength [1 .. ])
~ min (Succ one) (genericLength [1 .. ])
~ min (Succ one) (1 + (genericLength [2 .. ]))
~ min (Succ one) ((Succ Zero) + (genericLength [2 .. ]))
~ min (Succ one) (Succ (Zero + (genericLength [2 .. ])))
~ Succ (min one (Zero + (genericLength [2 .. ])))
~ Succ (min (Succ Zero) (Zero + (genericLength [2 .. ])))
~ Succ (min (Succ Zero) (genericLength [2 .. ]))
~ Succ (min (Succ Zero) (1 + (genericLength [3 .. ])))
~ Succ (min (Succ Zero) ((Succ Zero) + (genericLength [3 ..])))
~ Succ (min (Succ Zero) (Succ (Zero + (genericLength [3 .. ]
~ Succ (Succ (min Zero (Zero + (genericLength [3 .. ]
~ Succ (Succ Zero)


 With kind regards,
 Denys
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: laziness in `length'

2010-06-14 Thread Daniel Fischer
On Monday 14 June 2010 16:25:06, Serge D. Mechveliani wrote:
 Dear people and GHC team,

 I have a naive question about the compiler and library of  ghc-6.12.3.
 Consider the program

   import List (genericLength)
   main = putStr $ shows (genericLength [1 .. n]) \n
  where
  n = -- 10^6, 10^7, 10^8 ...

 (1) When it is compiled under  -O,  it runs in a small constant space
 in  n  and in a time approximately proportional to  n.
 (2) When it is compiled without -O,  it takes at the run-time the
 stack proportional to  n,  and it takes enormousely large time
 for  n = 10^7.
 (3) In the interpreter mode  ghci,   `genericLength [1 .. n]'
 takes as much resource as (2).

 Are the points (2) and (3) natural for an Haskell implementation?

 Independently on whether  lng  is inlined or not, its lazy evaluation
 is, probably, like this:
  lng [1 .. n] =
  lng (1 : (list 2 n)) =  1 + (lng $ list 2 n) =
  1 + (lng (2: (list 3 n))) = 1 + 1 + (lng $ list 3 n) =
  2 + (lng (3: (list 4 n)))   -- because this + is of Integer
  = 2 + 1 + (lng $ list 4 n) =
  3 + (lng $ list 4 n)
  ...
 And this takes a small constant space.

Unfortunately, it would be

lng [1 .. n]
~ 1 + (lng [2 .. n])
~ 1 + (1 + (lng [3 .. n]))
~ 1 + (1 + (1 + (lng [4 .. n])))
~

and that builds a thunk of size O(n).

The thing is, genericLength is written so that for lazy number types, the 
construction of the result can begin before the entire list has been 
traversed. This means however, that for strict number types, like Int or 
Integer, it is woefully inefficient.

In the code above, the result type of generic length (and the type of list 
elements) is defaulted to Integer.
When you compile with optimisations, a rewrite-rule fires:

-- | The 'genericLength' function is an overloaded version of 'length'.  In
-- particular, instead of returning an 'Int', it returns any type which is
-- an instance of 'Num'.  It is, however, less efficient than 'length'.
genericLength   :: (Num i) = [b] - i
genericLength []=  0
genericLength (_:l) =  1 + genericLength l

{-# RULES
  genericLengthInt genericLength = (strictGenericLength :: [a] - 
Int);
  genericLengthInteger genericLength = (strictGenericLength :: [a] - 
Integer);
 #-}

strictGenericLength :: (Num i) = [b] - i
strictGenericLength l   =  gl l 0
  where
gl [] a = a
gl (_:xs) a = let a' = a + 1 in a' `seq` gl xs a'

which gives a reasonabley efficient constant space calculation.

Without optimisations and in ghci, you get the generic code, which is slow 
and thakes O(n) space.

 Thank you in advance for your explanation,

 -
 Serge Mechveliani
 mech...@botik.ru

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


Re: Unexpected NoImplicitPrelude behaviour in GHCi (bug?)

2010-06-10 Thread Daniel Fischer
On Thursday 10 June 2010 14:02:10, Philip K.F. Hölzenspies wrote:
 Dear GHCers,

snip


 Shouldn't the expected behaviour of GHCi be that the entry module
 determines the entire context? In other words, if module X in

 ghci X

 or in

 ghci

  :l X

 contains the LANGUAGE-pragma NoImplicitPrelude, should the Prelude not
 be unloaded from ghci?

I don't think so. LANGUAGE-pragmata are a per-module thing. If you want to 
do some NoImplicitPrelude stuff in one module and test that module in ghci, 
most of the time you still want to have the Prelude functions around.
Your use-case seems more an exception to me.


 I would argue that this might also be seen as an example of why Ticket
 #124 for haskell-prime is a good idea for GHC:

 http://hackage.haskell.org/trac/haskell-prime/ticket/124

Hmm, I'd then have to explicitly import the Prelude in all my source files.
I could live with it, but I prefer the current behaviour.


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


Re: three dots of :browse

2010-04-24 Thread Daniel Fischer
Am Samstag 24 April 2010 07:07:15 schrieb Kazu Yamamoto:
 Hello,

 If I use :browse a module with GHC 6.12, it sometimes displays
 garbage. Here is an example:

 Prelude :browse Data.IP
 data AddrRange a
   = iproute-0.2.0:Data.IP.Range.AddrRange {addr :: a,
mask :: a,
mlen :: Int}
 (snip)
 data AddrRange a
   = iproute-0.2.0:Data.IP.Range.AddrRange {..., mask :: a, ...}
 data AddrRange a
   = iproute-0.2.0:Data.IP.Range.AddrRange {..., mlen :: Int}


 ... is the garbage. Due to this, I cannot parse the output of

 :browse. This is not displayed with GHC 6.10.

 Q1) What is the intention of ...?
 Q2) How to prevent it so that I can obtain output which I can parse?

Perhaps

*Test :browse! Test
-- defined locally
data R = R {x :: Char, y :: Int, z :: Float}
R :: Char - Int - Float - R
x :: R - Char
y :: R - Int
z :: R - Float

is the answer?


 --Kazu

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


Re: [Haskell-cafe] Different behavior of GHC 6.10.1 and Hugs (Sep 2006)

2010-04-03 Thread Daniel Fischer
Am Samstag 03 April 2010 15:40:03 schrieb Vladimir Reshetnikov:
 Hi list,

 GHC 6.10.1:

 Prelude :t let f x y = return x == return y in f
 let f x y = return x == return y in f :: (Eq (m a), Monad m) = a - a
 - Bool

 Hugs (Sep 2006):

 Hugs :t let f x y = return x == return y in f
 ERROR - Ambiguous type signature in inferred type
 *** ambiguous type : (Eq (a b), Monad a) = b - b - Bool
 *** assigned to: f

 Who is right?

I think hugs is righter. GHC lets you define f, but you can't use it; if 
you try, you'll get

No instance for (Eq (m Bool))
  arising from a use of `f' at TypeTest.hs:5:6-17
Possible fix: add an instance declaration for (Eq (m Bool))
In the expression: f True False
In the definition of `res': res = f True False

and if you provide e.g.

instance (Monad m) = Eq (m Bool) where
_ == _ = False

, you'll get

Ambiguous type variable `m' in the constraint:
  `Monad m' arising from a use of `f' at interactive:1:0-11
Probable fix: add a type signature that fixes these type variable(s)


The only difference is that GHC fails more lazily for such ambiguous types. 
than hugs.

I think, according to http://haskell.org/onlinereport/decls.html#sect4.3.4 
, GHC also should fail on the definition and not only on use.


 --
 Thanks
 Vladimir

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


Re: Issue with type families

2010-03-03 Thread Daniel Fischer
Am Donnerstag 04 März 2010 02:39:30 schrieb Tyson Whitehead:
 On March 3, 2010 18:35:26 Daniel Fischer wrote:
  Because:
 
  instance Applicative ((-) a) -- Defined in Control.Applicative
 
  so, from the instance Z (a - b), with b == c - d, we have an
 
  instance Z (a - (b - c))
 
  and from instance Z (m (u - v)), we have, with m == ((-) x), an
 
  instance Z (x - (u - v))

 Thanks Daniel,

 That makes sense.  Strangely enough though, I had actually originally
 tried it with my own Applicative class just in case I was being tripped
 up by something like the (-) instance you pointed out, and it still
 didn't work.

Well, GHC takes only the class head into account for instance selection, 
and

u - (v - w)

matches both,

a - b   --  (a == u, b == v - w)

and

m (c - d)-- (m == ((-) u), c == v, d == w),

so there's the overlap without any other type classes involved.
And since u - (v - w) matches both instance heads,

type W (u - (v - w)) = u - (v - w)

and

type W (((-) u) (v - w)) = (u - v) - (u - w)

are indeed conflicting, so you can't even use OverlappingInstances etc. to 
make it work.

 That is

   {-# LANGUAGE FlexibleInstances, TypeFamilies #-}

   newtype I a = I a

   class A t where
   ap :: t (a - b) - t a - t b

   class Z t where
   type W t
   z :: t - W t

   instance A I where
   ap (I f) (I x) = I $ f x

   instance Z (a - b) where
   type W (a - b) = a - b
   z = id

   instance A t = Z (t (a - b)) where
   type W (t (a - b)) = t a - t b
   z = ap

 also gives me

   Temp.hs:17:9:
   Conflicting family instance declarations:
 type instance W (a - b) -- Defined at Temp.hs:17:9
 type instance W (t (a - b)) -- Defined at Temp.hs:21:9
   Failed, modules loaded: none.

 Is the compiler somehow anticipating that I could add an instance for
 (-) to A and thus be back to the Applicative class situation?

The compiler works on an open-world assumption, if the kinds match, there 
could be an instance defined somewhere.


 Thanks!  -Tyson

 PS:  I asked this here because type classes is a GHC issue, would the
 haskell- cafe list been a more appropriate place?

Either is fine.

Cheers,
Daniel

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


Re: integer-simple by default

2010-02-21 Thread Daniel Fischer
Am Sonntag 21 Februar 2010 19:56:54 schrieb Isaac Dupree:
 We could try to find out how large Integers get, in practice, in
 existing Haskell code (this may be difficult to find out).

Just as a data-point, my code rarely exceeds 128 bits (at least, beyond 
that performance isn't so important anymore).
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Removing/deprecating -fvia-c

2010-02-17 Thread Daniel Fischer
Am Mittwoch 17 Februar 2010 15:19:33 schrieb Simon Marlow:
 I should point out that for most Haskell programs, the NCG is already as
 fast (in some cases faster) than via C.  The benchmarks showing a
 difference are all of the small tight loop kind - which are important to
 some people, I don't dispute that, but I expect that most people
 wouldn't notice the difference.

Probably. And where the tight loop takes a significant amount of the 
running time, one can usually write that in C and use the FFI if the NCG 
doesn't produce comparable code. Granted, it's not as nice, but removing 
the via-C route won't be a show-stopper for those loops either, I think.


 Cheers,
 Simon

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


Re: Removing/deprecating -fvia-c

2010-02-15 Thread Daniel Fischer
Am Montag 15 Februar 2010 17:37:55 schrieb Simon Marlow:
 On 14/02/2010 17:58, Don Stewart wrote:
  igloo:
  Hi all,
 
  We are planning to remove the -fvia-c way of compiling code
  (unregisterised compilers will continue to compile via C only, but
  registerised compilers will only use the native code generator).
  We'll probably deprecate -fvia-c in the 6.14 branch, and remove it in
  6.16.
 
  Simon Marlow has recently fixed FP performance for modern x86 chips
  in the native code generator in the HEAD. That was the last reason we
  know of to prefer via-C to the native code generators. But before we
  start the removal process, does anyone know of any other problems
  with the native code generators that need to be fixed first?
 
  Do we have the blessing of the DPH team, wrt. tight, numeric inner
  loops?
 
  As recently as last year -fvia-C -optc-O3 was still useful for some
  microbenchmarks -- what's changed in that time, or is expected to
  change?

 If you have benchmarks that show a significant difference, I'd be
 interested to see them.

I have a benchmark (or a couple) from the Beginners mailing list two weeks 
ago (thread starting in January at 
http://www.haskell.org/pipermail/beginners/2010-January/003356.html and 
continued in February at 
http://www.haskell.org/pipermail/beginners/2010-February/003373.html ff) 
which show a significant difference.

Loop.hs:

{-# LANGUAGE BangPatterns #-}
module Main (main) where

main :: IO ()
main = do
putStrLn EPS: 
eps - readLn :: IO Double
let !mx = (4/eps)
!pi14 = pisum mx
putStrLn $ PI mit EPS ++(show eps)++ = ++ show(4*pi14)

pisum :: Double - Double
pisum cut = go True 1 0
  where
go b n s | cut  n = if b then s+1/(2*n) else s-1/(2*n)
go True n !s = go False (n+2) (s+recip n)
go False n !s = go True (n+2) (s-recip n)


$ echo '1e-8' | time ./Loop

ghc -O2 --make:
4.53s
ghc -O2 -fexcess-precision --make:
4.54s
ghc -O2 -fvia-C -optc-O3 --make:
7.52s
ghc -O2 -fvia-C -optc-O3 -optc-ffast-math --make:
7.53s
ghc -O2 -fvia-C -optc-O3 -optc-ffast-math -optc-fno-float-store --make:
3.02s
ghc -O2 -fvia-C -optc-O3 -optc-fno-float-store --make:
3.02s
ghc -O2 -fexcess-precision -fvia-C -optc-O3 --make:
3.02s

The loop coded in C and compiled with gcc -O3 [-ffast-math, -fno-float-
store, -msse2 make no difference there] also takes 3.02s (gcc-4.3.2), 2.70s 
with icc -O3 (icc 11.0).

It is probably worth pointing out, however, that on Markus Böhm's box 
running Windows XP, the native code generator produced better code than the 
via-C route (NCG code was faster there than on my box [openSUSE 11.1], 
while -O2 -fexcess-precision -fvia-C -optc-O3 on his box was slower than 
NCG on mine).

Similar results for

Fusion.hs (uses stream-fusion package)

module Main (main) where

import qualified Data.List.Stream as S

main :: IO ()
main = do
putStrLn EPS: 
eps - readLn :: IO Double
let !mx = floor (4/eps)
!k = (mx+1) `quot` 2
putStrLn $ PI mit EPS  ++ (show eps) ++  =  ++ show (leibniz k)

leibniz n = (4 *) $ S.sum $ S.take n step

step :: [Double]
step = S.unfoldr phi (True,1) where
   phi (sig,d) | sig = Just (1/d, (False,d+2))
               | otherwise   = Just (negate (1/d), (True,d+2))


ghc -O2 [-fexcess-precision] --make:
4.22s
ghc -O2 -fexcess-precision -fvia-C -optc-O3 --make:
3.02s

Using lists instead of loops,

List.hs

module Main (main) where

import Data.List (unfoldr)

main :: IO ()
main = do
    putStrLn EPS: 
    eps - readLn :: IO Double
    let mx = floor (4/eps)
        !k = (mx+1) `quot` 2
    putStrLn $ PI mit EPS  ++ (show eps) ++  =  ++ show (leibniz k)

leibniz n = (4 *) $ sum $ take n step

step :: [Double]
step = unfoldr phi (True,1) where
   phi (sig,d) | sig         = Just (1/d, (False,d+2))
               | otherwise   = Just (negate (1/d), (True,d+2))


things are much slower, 23.60s vs. 18.15s, but the via-C route is again 
significantly faster.


 What I've done for 6.14.1 is to add the -msse2 flag to the x86 backend,
 so where previously we had to use -fvia-C -fexcess-precision -optc-O3
 etc. to get reasonable floating point performance, now we can use -msse2
 with the native code gen and get about the same results.

Can I test whether I get about the same results as with -fvia-C ... for the 
above?
I.e., is it in the HEAD, and would I have to pass -msse2 on the command 
line or is it implied by -O2 already?


 In the future we have a couple of ways that things could get better:

   1. The new back-end, which eventually will incorporate more
  optimisations at the C-- level, and potentially could produce
  good loop code.  It will also free up some registers.

   2. Compiling via LLVM.

 Dropping the C 

Re: forgetting SCC

2010-02-07 Thread Daniel Fischer
Am Sonntag 07 Februar 2010 13:06:14 schrieb Serge D. Mechveliani:
 I am sorry,
 indeed,  ghc-6.12.1  warns of  Unrecognised pragma  on  {-# foo #-}.
 I have just missed this warning.

 The next question is:  why it is a warning and not an error break?

Because it might be a valid pragma for some other implementation, so 
erroring on unrecognised pragmas is not a good option.
It would be nice if there was a commandline switch 

-ferror-unrecognised-pragmas

(similarly for other warnings, -ferror-incomplete-patterns, ...), but if 
your code is otherwise clean enough, something like

-Wall -Werror -fno-warn-type-defaults -fno-warn-simple-patterns

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


Re: forgetting SCC

2010-02-07 Thread Daniel Fischer
Am Sonntag 07 Februar 2010 14:05:48 schrieb Serge D. Mechveliani:
 On Sun, Feb 07, 2010 at 01:22:07PM +0100, Daniel Fischer wrote:
  Am Sonntag 07 Februar 2010 13:06:14 schrieb Serge D. Mechveliani:
   I am sorry,
   indeed,  ghc-6.12.1  warns of  Unrecognised pragma  on  {-# foo
   #-}. I have just missed this warning.
  
   The next question is:  why it is a warning and not an error break?
 
  Because it might be a valid pragma for some other implementation, so
  erroring on unrecognised pragmas is not a good option.
  [..]

 Some of earlier implementations or only future?

I know of no implementation that used {-# string #-} as a pragma, so 
future.

 Do you expect for future to appear a pragma without its keyword?

No. But you can't be sure, can you?


 -
 Serge Mechveliani
 mech...@botik.ru


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


Re: profiling,-O in 6.12.1

2010-02-03 Thread Daniel Fischer
Am Mittwoch 03 Februar 2010 16:44:31 schrieb Serge D. Mechveliani:
 Dear GHC team,

 It looks like  ghc-6.12.1  reports erroneous time profiling --
 when the Main module of the project is made under  -O.

 This is for  ghc-6.12.1  made from source for Debian Linux and
 i386-like.

 Main.main  calls for  Complete.complete,  `complete' calls for
 eLoop  inside its source.
 eLoop  must take almost all the time.
 My whole user library is made under  -O -prof,  and
  --enable-library-profiling.
 Main  is compiled by
  ghc $dmCpOpt -prof --make Main
 and run by   ./Main +RTS -M400m -pT -RTS
 For this key, the profiling report Main.prof looks natural and shows
eLoop -- 97%.

 But forghc $dmCpOpt  -O  -prof --make Make,

 it shows a different thing:  zero  for  eLoop  and  99%  for `main'.

Could be that eLoop is inlined with -O.

Try

ghc $dmCpOpt -O -prof -auto-all --make

That should show eLoop (if that's a top-level declaration, otherwise you'd 
have to insert a pragma {-# SCC eLoop #-} manually).


 How could this additional  -O  mislead the compiler?
 Also, as I recall,  -O  is still by default -- ?

No, default is comile as fast as possible, no optimisations (-O0).


 Could you explain, please?

 Regards,

 -
 Serge Mechveliani
 mech...@botik.ru
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: profiling,-O in 6.12.1

2010-02-03 Thread Daniel Fischer
Am Mittwoch 03 Februar 2010 18:59:01 schrieb Serge D. Mechveliani:
 To my

   Dear GHC team,
  
   It looks like  ghc-6.12.1  reports erroneous time profiling --
   when the Main module of the project is made under  -O.
   [..]
   This is for  ghc-6.12.1  made from source for Debian Linux and
   i386-like.
  
   Main.main  calls for  Complete.complete,  `complete' calls for
   eLoop  inside its source.
   eLoop  must take almost all the time.
   My whole user library is made under  -O -prof,  and
--enable-library-profiling.
   Main  is compiled by
ghc $dmCpOpt -prof --make Main
   and run by   ./Main +RTS -M400m -pT -RTS
   For this key, the profiling report Main.prof looks natural and shows
  eLoop -- 97%.
  
   But forghc $dmCpOpt  -O  -prof --make Make,
  
   it shows a different thing:  zero  for  eLoop  and  99%  for `main'.

 On Wed, Feb 03, 2010 at 05:38:36PM +0100, Daniel Fischer wrote:
  Could be that eLoop is inlined with -O.

 Thank you.
 I also thought about this. But the question still looks difficult.

  Try
 
  ghc $dmCpOpt -O -prof -auto-all --make
 
  That should show eLoop (if that's a top-level declaration, otherwise
  you'd have to insert a pragma {-# SCC eLoop #-} manually).

 eLoop  is not a top-level declaration, and I do set {-# SCC eLoop #-}.

I had a similar issue recently, whether a cost centre shows in the profile 
depends on where exactly you put it, it might be worthwhile to move it 
around a bit or add {-# SCC eLoop #-} to a few more places in eLoop.

 The key combination
ghc $dmCpOpt -prof --make Main
 shows  95% for  eLoop,
 and adding  -O  to this line shows  0%  for  eLoop,  independently on
 presence of  -auto-all  in this line
 (the whole library is made under  -O -prof).

 Yes, I recall that the effect may be of inlining.
 But, generally, how to detect sensibly the time consuming functions?

Insert lots of cost centres. The downside is, the more cost centres you 
have, the less optimisations are possible. Sometimes that changes the 
code's behaviour much, so it is possible that things show up as consuming 
much time which would be optimised to low-cost without profiling. But that 
should be rare, in general, what shows up as expensive in the profile is 
also expensive in production code, just somewhat less (or more).

 This inlining presents a puzzle here.

 Is it possible to
compile  Main.hs and Complete.hs  under  -O0 -inline-not,
compile all the other modules under  -O
 ?
 (how?).

Put

{-# OPTIONS_GHC -O1 #-}

at the top (but after LANGUAGE pragmas) of all modules except Main and 
Complete. Then don't give an -O flag on the command line (touch Main.hs and 
Complete.hs to make sure those are recompiled, perhaps pass -fforce-recomp 
to recompile everything).

 If it is possible, will this make easier to understand the profiling
 report?

Hopefully :)


 Regards,

 -
 Serge Mechveliani
 mech...@botik.ru

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


Re: Type families and type inference - a question

2010-01-10 Thread Daniel Fischer
Am Sonntag 10 Januar 2010 17:09:33 schrieb Dmitry Tsygankov:
 Dear all,

 I was playing around recently with translating the dependency injection
 idea (http://martinfowler.com/articles/injection.html) into Haskell, and
 got to the following code:


 {-# LANGUAGE TypeFamilies, FlexibleContexts #-}

What you need is also

{-# LANGUAGE NoMonomorphismRestriction #-}

Read http://haskell.org/onlinereport/decls.html#sect4.5.5

and http://www.haskell.org/haskellwiki/Monomorphism_restriction

for background.


 data Movie = Movie { getDirector :: String }
 data (MovieFinder f) = MovieLister f = MovieLister { getFinder :: f }

Don't do that. Type class constraints on data types probably do not what 
you think.
You'll have to put the constraint on the functions using MovieLister 
nevertheless.


 -- Cannot remove the type signature here
 createLister :: (MovieFinder f) = (FinderResultMonad f) (MovieLister f)
 createLister = fmap MovieLister createFinder

createLister is a top-level binding which is bound by a simple pattern 
binding. By the monomorphism restriction, such things must have a 
monomorphic type unless a type signature is given. The monomorphic type 
assigned to such an entity (if possible) is determined via the defaulting 
rules http://haskell.org/onlinereport/decls.html#sect4.3.4

Here, the inferred type is

createLister ::
  (f ~ FinderResultMonad a, MovieFinder a, Functor f) =
  f (MovieLister a)

which hasn't the form allowed by the defaulting rules, monomorphising fails 
(even if f is resolved to FinderResultMonad a, and the type is written as
createLister :: (MovieFinder a) = FinderResultMonad a (MovieLister a), the 
problem remains that MovieFinder is not a class defined in the standard 
libraries, hence defaulting isn't possible).


 class (Monad (FinderResultMonad f), Functor (FinderResultMonad f)) =
 MovieFinder f where
 type FinderResultMonad f :: * - *
 createFinder :: (FinderResultMonad f) f
 findAll :: f - (FinderResultMonad f) [Movie]


 It may be dumb (well, the Java version isn't particularly useful
 either), but the thing I really do not understand is the type signature
 - why can't I simply remove it?

Monomorphism restriction.
If you can't remove a type signature, it's almost always that (sometimes 
it's polymorphic recursion).

 Some output from GHCi:

 GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
 *IfaceInj :t fmap MovieLister
 fmap MovieLister

   :: (MovieFinder a, Functor f) = f a - f (MovieLister a)

 *IfaceInj :t createFinder
 createFinder :: (MovieFinder f) = FinderResultMonad f f

 Looks reasonable so far...

 *IfaceInj :t fmap MovieLister createFinder
 fmap MovieLister createFinder

   :: (f ~ FinderResultMonad a, MovieFinder a, Functor f) =

  f (MovieLister a)

 Here's the first WTF. If the type inference engine knows that f ~
 FinderResultMonad a, it can 'guess' the type
 (MovieFinder a, Functor (FinderResultMonad a)) = (FinderResultMonad a)
 (MovieLister a)
 , can't it?

It can, see below. It just chose to display it in a different form.

 And since there's a constraint on the MovieFinder type
 class, it can further 'guess'
 (MovieFinder a) = (FinderResultMonad a) (MovieLister a)
 , which is exactly the type signature I have written by hand, but it
 doesn't. Is it a bug, a missing feature, or just my lack of knowledge?

It's the dreaded MR. That and the often surprising ways of ghci to display 
inferred types.

 OK, so far, so good, let's call it a missing feature or something that
 is impossible to implement.

 *IfaceInj let q = fmap MovieLister createFinder

 interactive:1:25:
 Couldn't match expected type `FinderResultMonad a'
against inferred type `f'
   NB: `FinderResultMonad' is a type function, and may not be
 injective In the second argument of `fmap', namely `createFinder'
 In the expression: fmap MovieLister createFinder
 In the definition of `q': q = fmap MovieLister createFinder

(Note: Surprisingly (?), if you load a module with 
{-# LANGUAGE NoMonomorphismRestriction #-}
, the monomorphsm restriction is still enabled at the ghci prompt, so we 
have to disable it for that again - or we could have loaded the module with
$ ghci -XNoMonomorphismRestriction Movie)

*Movie :set -XNoMonomorphismRestriction
*Movie let q = fmap MovieLister createFinder
*Movie :t q
q :: (MovieFinder a) = FinderResultMonad a (MovieLister a)

Okay, what happened there?
 *IfaceInj :t fmap MovieLister
 fmap MovieLister

   :: (MovieFinder a, Functor f) = f a - f (MovieLister a)

 *IfaceInj :t createFinder
 createFinder :: (MovieFinder a) = FinderResultMonad a a

Now, to infer the type of

fmap MovieLister createFinder,

the type of (fmap MovieLister)'s argument, f a [we ignore contexts for a 
moment], has to be unified with the type of createFinder, 
FinderResultMoad a a.
That gives, obviously,
f ~ FinderResultMonad a, a further constraint. Joining the constraints, we 
get

fmap MovieLister createFinder
  :: (f ~ 

Re: Type families and type inference - a question

2010-01-10 Thread Daniel Fischer
Am Montag 11 Januar 2010 05:08:30 schrieb Dmitry Tsygankov:
 2010/1/10 Yitzchak Gale

  IMHO, the monomorphism restriction does not make sense at the
  GHCi prompt in any case, no matter what you have or haven't
  loaded, and no matter what your opinion of MR in general.

 Looks reasonable to me, that's why I intuitively expected
 let q = fmap MovieLister createFinder
 to work.
 Not sure I would want that behaviour when I ':load' a file though, as
 it may provide a false sense of security. -XTypeFamilies isn't turned
 on automatically, why should -XNoMonomorphismRestriction be?


You're more likely to omit (forget) type signatures for quick bindings at 
the prompt. The monomorphism restriction is inconvenient then.

  I recommend that you create a file called .ghci
 
  in your home directory, and put into it the line:
  :set -XNoMonomorphismRestriction

 That seems to also affect how the file is ':load'-ed, not sure I would
 want to do that.

If you want the MR in some module, you can enable it via
{-# LANGUAGE MonomorphismRestriction #-}
there.

It's a question of what you deem more (in)convenient. Since the MR is not 
entirely unlikely to be removed from the (default) language, the latter is 
more future-proof.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 6.12.1

2009-12-15 Thread Daniel Fischer
Am Dienstag 15 Dezember 2009 10:43:10 schrieb Simon Marlow:

 Please submit a bug report.  Presumably we need a configure test for -lz
 somewhere.

http://hackage.haskell.org/trac/ghc/ticket/3756

Yes, passing -optl-lz to all tests gave only 3 unexpected failures for 
threaded1.


 Cheers,
   Simon

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


Re: ANNOUNCE: GHC version 6.12.1

2009-12-14 Thread Daniel Fischer
Am Montag 14 Dezember 2009 17:47:35 schrieb Luca Ciciriello:
 Installed 6.12.1 on MacOS X 10.6Now I'm unable to load in GHCi of that
 modules containing import Control.ParallelI'm missing something? Luca

cabal install parallel

Control.Parallel is now in the parallel package.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 6.12.1

2009-12-14 Thread Daniel Fischer
Am Montag 14 Dezember 2009 14:36:14 schrieb Ian Lynagh:
==
 The (Interactive) Glasgow Haskell Compiler -- version 6.12.1
==

Hooray! Built from source on
$ uname -a
Linux linux-mkk1 2.6.27.39-0.2-pae #1 SMP 2009-11-23 12:57:38 +0100 i686 i686 
i386 
GNU/Linux
(openSuse 11.1)

Running the testsuit gave

OVERALL SUMMARY for test run started at Mo 14. Dez 18:06:00 CET 2009
2352 total tests, which gave rise to
   13034 test cases, of which   
   0 caused framework failures  
2760 were skipped   

9471 expected passes
 328 expected failures
   0 unexpected passes
 475 unexpected failures

Is that good or bad?
Almost all unexpected failures are with threaded1, the vast majority of them 
due to

/usr/src/packages/BUILD/binutils-2.19/build-dir/bfd/../../bfd/compress.c:96:0:
 undefined reference to `inflateInit_'

/usr/src/packages/BUILD/binutils-2.19/build-dir/bfd/../../bfd/compress.c:103:0:
 undefined reference to `inflate'  

/usr/src/packages/BUILD/binutils-2.19/build-dir/bfd/../../bfd/compress.c:106:0:
 undefined reference to `inflateReset' 

/usr/src/packages/BUILD/binutils-2.19/build-dir/bfd/../../bfd/compress.c:108:0:
 undefined reference to `inflateEnd'   
collect2: ld returned 1 exit status

*** unexpected failure for fileStatus(threaded1)

Missing -lz option for the linker?

Unexpected failures:
   10queens(threaded1)
   1185(threaded1)
   1548(threaded1)
   1679(threaded1)
   1744(threaded1)
   1852(threaded1)
   1861(threaded1)
   1980(threaded1)
   2047(threaded1)
   2080(threaded1)
   2122(threaded1)
   2469(threaded1)
   2594(threaded1)
   2783(threaded1)
   2838(threaded1)
   2910(threaded1)
   2917a(threaded1)   
   3207(threaded1)
   3236(threaded1)
   3279(threaded1)
   3424(threaded1)
   3429(threaded1)
   3561(threaded1)
   3677(threaded1)
   CPUTime001(threaded1)
   IOError001(threaded1)
   IOError002(threaded1)
   OldException001(threaded1)
   T1624(threaded1)  
   T1735(threaded1)  
   T246(threaded1)   
   T2529(threaded1)  
   T3087(threaded1)  
   T3126(threaded1)  
   T3382(threaded1)  
   ThreadDelay001(threaded1) 
   addr001(threaded1)
   andre_monad(threaded1)
   andy_cherry(threaded1)
   annrun01(threaded1,dyn)   
   arith001(threaded1)   
   arith002(threaded1)   
   arith003(threaded1)   
   arith004(threaded1)   
   arith005(threaded1)   
   arith006(threaded1)   
   arith007(threaded1)   
   arith008(threaded1)   
   arith009(threaded1)   
   arith010(threaded1)   
   arith011(threaded1)   
   arith012(threaded1)   
   arith013(threaded1)   
   arith014(threaded1)   
   arith015(threaded1)   
   arith016(threaded1)   
   arith017(threaded1)   
   arith018(threaded1)   
   arith019(threaded1)   
   arr001(threaded1) 
   arr002(threaded1) 
   arr003(threaded1) 
   arr004(threaded1) 
   arr005(threaded1) 
   arr006(threaded1) 
   arr007(threaded1) 
   arr008(threaded1) 
   arr009(threaded1) 
   arr010(threaded1) 
   arr011(threaded1) 
   arr012(threaded1) 
   arr013(threaded1) 
   arr014(threaded1) 
   arr015(threaded1) 
   arr016(threaded1) 
   arr017(threaded1) 
   arr018(threaded1) 
   arr019(threaded1) 
   arrowrun001(threaded1)
   arrowrun002(threaded1)
   arrowrun003(threaded1)
   arrowrun004(threaded1)
   barton-mangler-bug(profc,threaded1)
   break024(ghci) 
   bug1010(threaded1) 
   bytestring002(threaded1)   
   bytestring003(threaded1)   
   bytestring006(threaded1)   
   cg001(threaded1)   
   cg002(threaded1)   
   cg003(threaded1)   
   cg004(threaded1)   
   cg005(threaded1)   
   cg006(threaded1)   
   cg007(threaded1)   
   cg008(threaded1)   
   cg009(threaded1)   
   cg010(threaded1)   
   cg011(threaded1)   
   cg012(threaded1)   
   cg013(threaded1)   
   cg014(threaded1)   
   cg015(threaded1)   
   cg016(threaded1)   
   cg017(threaded1)  

Re: ANNOUNCE: GHC version 6.12.1

2009-12-14 Thread Daniel Fischer
Oh great, that's not what I expected:

$ cabal install cabal-install
cabal: This version of the cabal program is too old to work with ghc-6.12+.
You will need to install the 'cabal-install' package version 0.8 or higher.
If you still have an older ghc installed (eg 6.10.4), run:
$ cabal install -w ghc-6.10.4 'cabal-install = 0.8'
$ cabal install -w ghc-6.10.3 'cabal-install = 0.8'
Resolving dependencies...
cabal: There is no available version of cabal-install that satisfies =0.8

Oops, nothing higher than 0.6.4 on Hackage, even 
darcs.haskell.org/cabal-install is only 
version 0.7.5. 
That seems to work, though, but I needed to manually install network, mtl and 
parsec 
before bootstrap.sh ran.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: inferred type doesn't type-check (using type families)

2009-11-03 Thread Daniel Fischer
Am Dienstag 03 November 2009 19:28:55 schrieb Roland Zumkeller:
 Hi,

 Compiling

  class WithT a where
type T a
 
  f :: T a - a - T a
  f = undefined
 
  g x = f x 42

 with -XTypeFamilies -fwarn-missing-signatures gives:

  Inferred type: g :: forall a. (Num a) = T a - T a

 Adding

  g :: Num a = T a - T a

 results in:

 Couldn't match expected type `T a' against inferred type `T a1'
 In the first argument of `f', namely `x'

 Is the inferred type not the right one? Is g typeable?

The type function T isn't injective (or, it isn't guaranteed to be), so there's 
no way to 
determine which type a to use for 42.


 Best,

 Roland

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


Re: Type checker's expected and inferred types (reformatted)

2009-10-24 Thread Daniel Fischer
Am Samstag 24 Oktober 2009 21:21:51 schrieb Albert Y. C. Lai:
 For the record, and to speak up as part of a possible silent majority,

 I completely understand the type error messages.

Mostly, I do, too. But I can't get why IO () is *expected* and Maybe () is 
*inferred* for 
bar in fun2.
Can you explain?

 I find enough information in them. I like them.

Generally, it's the same for me, though some are better than others.
Even if one doesn't completely understand them, it's rare that one can't get 
enough out of 
them to start fixing the code.


 I find it unnecessary to decrypt the two words expected and
 inferred. They have their own definitions and they stand for
 themselves; external and internal are helpful mnemonics, useful
 approximation, but not decryption.

 I support work on ghc to prioritize professional use over pedagogical
 use, that is, if a proposed pedagogical improvement conflicts with
 professional use concerns, or even if simply no one has time to
 implement, I support sacrificing the pedagogical improvement.

Seconded.

 To mitigate the sacrifice, we users write tutorials for each other.


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


Re: Type checker's expected and inferred types

2009-10-23 Thread Daniel Fischer
Am Samstag 24 Oktober 2009 03:12:14 schrieb C Rodrigues:
 I came across a type error that misled me for quite a while, because the
 expected and inferred types were backwards (from my point of view).  A
 simplified example is below.  Can someone explain how GHC's type checker
 creates the error message? In this example, fun1 and fun2 are basically the
 same.  The type error is because they try to run an IO () together with a
 Maybe ().

 

import Control.Monad
foo :: Maybe ()
foo = return ()

bar :: IO ()
bar = return ()

fun1 = let fooThen m = foo  m
 in fooThen (bar  undefined)


fun2 = let fooThen m = foo  m
 in fooThen (do {bar; undefined})


 With ghc 6.10.4, both functions attribute the error message to `bar'.
 However, the expected and inferred monads are swapped.fun1 produces the
 error message:

 Couldn't match expected type `Maybe a' against inferred type `IO ()'
 In the first argument of `(=)', namely `bar'

 fun2 produces the error message:

 Couldn't match expected type `IO ()' against inferred type `Maybe ()'
 In a stmt of a 'do' expression: bar 


 It's confusing because 'bar'
 is inferred to have type Maybe (), even though it's explicitly declared to
 be an IO ().

I don't know the intricate details, but the order in which type inference/type 
checking 
proceeds has something to do with it.

In fun1, apparently first the type of fooThen is inferred to be `Maybe a - 
Maybe a'.
Then, in the body of the let-expression, fooThen *expects* a `Maybe a'.
Thus the () in fooThen's argument is inferred to have the type 
`Maybe a - Maybe b - Maybe b'.
Hence the first argument of () [or (=), apparently it has been expanded to 
that]
is *expected* to have type `Maybe a'.
But from bar's definition, its type is *inferred* to be `IO ()'.

Perfectly clear and transparent (not really). Had the type of fooThen's 
argument been 
inferred before fooThen's type, it would've said that it expected fooThen to 
have type `IO 
a - b', but inferred it to have type `Maybe a - Maybe a'.

The error for fun2 is baffling. I can't explain how ghci comes to *expect* bar 
to have 
type `IO ()'.

Also intriguing is that if you swap bar and undefined in the do-expression, you 
get the 
error message you'd expect:

Couldn't match expected type `Maybe b'
   against inferred type `IO ()'  
In the expression: bar
In the first argument of `fooThen', namely
`(do undefined
 bar)'
In the expression:
fooThen   
  (do undefined   
  bar)

But if you sandwich bar between two actions which may have type `Maybe a', it's 
back to 
expecting `IO ()':

Couldn't match expected type `IO ()'
   against inferred type `Maybe ()'
In a stmt of a 'do' expression: bar
In the first argument of `fooThen', namely
`(do Just 1
 bar
 Nothing)'
In the expression:
fooThen
  (do Just 1
  bar
  Nothing)

Seems typechecking do-expressions has some strange corners.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: beginner question

2009-10-14 Thread Daniel Fischer
Am Mittwoch 14 Oktober 2009 08:26:10 schrieb Luca Ciciriello:
 Just a Haskell beginner question.

This sort of generic question has a higher probability of receiving a quick 
answer on 
haskell-c...@haskell.org or beginn...@haskell.org, where more people are 
reading.


 If I load in GHCi the code below all works fine, I load a file and its
 content is shown on screen. But if I use the second version of my
 load_by_key (the commented one) no error is reported loading and
 executing this code, but nothing is shown on screen. Where is my mistake?

You're bitten by laziness. It's a very common problem you're having.

In the working version, you explicitly open the file, lazily get its contents, 
then print 
it out and after that is done, close the file.

 load_by_key table key = do
   inh - openFile table ReadMode
   contents - hGetContents inh
   get_record (get_string contents) key
   hClose inh



Here you use bracket, which doesn't interact well with hGetContents.
hGetContents is lazy and returns immediately, without reading any of the file's 
contents 
yet. Once hGetContents returns, bracket performs its exit action, here it 
closes the file 
- before you've read anything from it. Then you try to print the file contents 
and 
hGetContents tries to read the file. That is now closed, hence hGetContents 
can't read 
anything and returns , which then is output.

Don't mix bracket and hGetContents. Consider using readFile instead.


 {-
 load_by_key table key = do
   contents - getTableContent table
   get_record (get_string contents) key
 -}



 get_string :: String - String
 get_string = (\x - x)



 get_record :: String - String - IO ()
 get_record contents key = putStr( contents )



 getTableContent :: String - IO String
 getTableContent table = bracket (openFile table ReadMode)
 hClose
 (\h - (hGetContents h))


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


Re: Snow Leopard GHC

2009-09-25 Thread Daniel Fischer
Am Freitag 25 September 2009 11:56:54 schrieb Barney Stratford:
 As you can see, it doesn't even attempt to tell gcc where to find  
 libgmp.

 This has the feeling of an RTM question, and if it is then I  
 apologise. I've not seen anything about this in the M, though.

 Cheers,
 Barney.

As a workaround, you might try to set the appropriate enironment variables 
(check with man 
gcc which ones are required) to include /sw/include resp. /sw/lib
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Data.List permutations

2009-08-04 Thread Daniel Fischer
Am Dienstag 04 August 2009 19:48:25 schrieb Slavomir Kaslev:
 A friend mine, new to functional programming, was entertaining himself by
 writing different combinatorial algorithms in Haskell. He asked me for some
 help so I sent him my quick and dirty solutions for generating variations
 and

 permutations:
  inter x [] = [[x]]
  inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
 
  perm [] = [[]]
  perm (x:xs) = concatMap (inter x) (perm xs)
 
  vari 0 _ = [[]]
  vari _ [] = []
  vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs

 After that I found out that nowadays there is a permutation function in the

 Data.List module:
  permutations:: [a] - [[a]]
  permutations xs0=  xs0 : perms xs0 []
where
  perms [] _  = []
  perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations
  is) where interleavexs r = let (_,zs) = interleave' id xs r in zs
  interleave' _ [] r = (ts, r)
  interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:))
  ys r in  (y:us, f (t:y:us) : zs)

 I was surprised to find that not only my version is much simpler from the
 one in Data.List but it also performs better. Here are some numbers from my
 rather old ghc 6.8.1 running ubuntu on my box:

 *Main length $ permutations [1..10]
 3628800
 (10.80 secs, 2391647384 bytes)
 *Main length $ perm [1..10]
 3628800
 (8.58 secs, 3156902672 bytes)

But you compare *interpreted* code here, that's not what counts.

Prelude Perms length $ perm [1 .. 10]
3628800
(1.20 secs, 1259105892 bytes)
Prelude Perms length $ permutations [1 .. 10]
3628800
(0.56 secs, 551532668 bytes)
Prelude Perms length $ perm [1 .. 11]
39916800
(13.18 secs, 14651808004 bytes)
Prelude Perms length $ permutations [1 .. 11]
39916800
(4.30 secs, 5953485728 bytes)

Apparently the library code is more amenable to the optimiser (note that the 
actual 
library is faster still:

Prelude Data.List length $ permutations [1 .. 10]
3628800
(0.49 secs, 551532812 bytes)
Prelude Data.List length $ permutations [1 .. 11]
39916800
(3.73 secs, 5953485816 bytes)

I have no idea why).


 I would like to suggest to change the current implementation in Data.List
 with the simpler one. Also, it would be nice to add variations and
 combinations in the Data.List module.

 Cheers.

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


Re: Data.List permutations

2009-08-04 Thread Daniel Fischer
Am Dienstag 04 August 2009 20:30:58 schrieb Slavomir Kaslev:
 On Tue, Aug 4, 2009 at 9:23 PM, Daniel Fischerdaniel.is.fisc...@web.de 
 wrote:


 Which version of ghc are you testing on? I guess, it's more recent than
 mine.

6.10.3. But I think if you compiled it with 6.8.*, the library code would still 
be faster, 
perhaps by a smaller margin.


  Apparently the library code is more amenable to the optimiser (note that
  the actual library is faster still:
 
  Prelude Data.List length $ permutations [1 .. 10]
  3628800
  (0.49 secs, 551532812 bytes)
  Prelude Data.List length $ permutations [1 .. 11]
  39916800
  (3.73 secs, 5953485816 bytes)
 
  I have no idea why).

 Probably because it's compiled (and not interpreted) in this case.

All my times were from compiled (with -O2) code. The question is, why does the 
same source 
code produce slower object code in module Perms than in Data.List?
I suppose it's because Data.List was compiled with different command line 
options, but 
I've no idea which.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Fwd: exposing hidden packages with runghc

2009-06-30 Thread Daniel Fischer
Am Mittwoch 01 Juli 2009 01:11:44 schrieb Iain Barnett:
 I think I posted this to the wrong list (libraries), so I've forwarded it
 here.
 

 I'm trying to install HTTP-3000.0.0 (because I don't have cabal-install,
 and it's a dependency for cabal-install 0.4.9)

 This is on a Debian 5.1 machine with GHC 6.8.2 and 6.8.3 on it.

 The command:
 sudo runghc Setup configure -p  sudo runghc Setup build  sudo runghc
 Setup install

 The error:
 Could not find module `Data.Array.MArray':
   it is a member of package array-0.1.0.0, which is hidden

 ghc-pkg does list the hidden package.

In the 6.8 series, the base package was split up. Prior to that, the Array 
modules were 
part of base.
HTTP-3000.0.0 seems to be from before 6.8, so it doesn't list the array package 
among its 
build dependencies.
Cabal hides all packages which aren't listed when building a library.

Quick fix: add array to the build dependencies in the .cabal file.

But why are you trying to build such an outdated cabal-install?


 I've seen other threads on this hiding problem and searched through the
 GHC user guide, but I haven't actually found a solution, just explanation.
 I've tried sending the -package flag through to GHC by adding it to the
 runghc command, but I'm not doing this right, obviously.

 Would someone be able to point me in the right direction? It would be much
 appreciated.


 Iain

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


Re: [Haskell-cafe] A problem with par and modules boundaries...

2009-05-23 Thread Daniel Fischer
Am Samstag 23 Mai 2009 13:06:04 schrieb Duncan Coutts:
 On Fri, 2009-05-22 at 16:34 +0200, Daniel Fischer wrote:
 That's great, thank you. I am still baffled, though.

 I'm baffled too! I don't see the same behaviour at all (see the other
 email).

   Must every exported function that uses `par' be INLINEd? Does every
   exported caller of such a function need the same treatment?

 It really should not be necessary.

   Is `par' really a macro, rather than a function?

 It's a function.

  As far as I understand, par doesn't guarantee that both arguments are
  evaluated in parallel, it's just a suggestion to the compiler, and if
  whatever heuristics the compiler uses say it may be favourable to do
  it in parallel, it will produce code to calculate it in parallel
  (given appropriate compile- and run-time flags), otherwise it produces
  purely sequential code.
 
  With parallelize in a separate module, when compiling that, the
  compiler has no way to see whether parallelizing the computation may
  be beneficial, so doesn't produce (potentially) parallel code. At the
  use site, in the other module, it doesn't see the 'par', so has no
  reason to even consider producing parallel code.

 I don't think this is right. As I understand it, par always creates a
 spark. It has nothing to do with heuristics.

Quite possible.
I was only guessing from the fact that sometimes par evaluates things in 
parallel and 
sometimes not, plus when thinking what might cause the described behaviour, 
cross-module 
inlining came to mind, I tried adding an INLINE pragma and it worked - or so it 
seemed. 
Then I threw together an explanation of the observed behaviour. That 
explanation must be 
wrong, though, see below.


 Whether the spark actually gets evaluated in parallel depends on the
 runtime system and whether the spark fizzles before it gets a chance
 to run. Of course when using the single threaded rts then the sparks are
 never evaluated in parallel. With the threaded rts and given enough
 CPUs, the rts will try to schedule the sparks onto idle CPUs. This
 business of getting sparks running on other CPUs has improved
 significantly since ghc-6.10. The current development version uses a
 better concurrent queue data structure to manage the spark pool. That's
 probably the underlying reason for why the example works well in
 ghc-6.11 but works badly in 6.10. I'm afraid I'm not sure of what
 exactly is going wrong that means it doesn't work well in 6.10.

I have tried with 6.10.3 and 6.10.1,  with parallelize in the same module and 
in a 
separate module
- with no pragma
- with an INLINE pragma
- with a NOINLINE pragma

6.10.1 did not parallelize in any of these settings
6.10.3 parallelized in all these settings except separate module, no pragma.

Then I tried a few other settigns with 6.10.3, got parallel evaluation if 
there's an 
INLINE or a NOINLINE pragma on parallelize, or the module header of Main is 
module Main (main) where,
not if Main exports all top level definitions and parallelize is neither 
INLINEd nor 
NOINLINEd.

Weird.


 Generally I'd expect the effect of par to be pretty insensitive to
 inlining. I'm cc'ing the ghc users list so perhaps we'll get some expert
 commentary.

That would be good.


 Duncan


Daniel

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


Re: type checking fails with a correct type

2009-04-30 Thread Daniel Fischer
Am Donnerstag 30 April 2009 15:52:12 schrieb Jan Jakubuv:
 Hi,

 I have the following problem. Below is the smallest program I have found
 that shows the problem. That is why the program makes no sense (I have also
 meaningful but more complicated program). When I run this program in ghci:

 class SUBST s where
 empty :: s

 --nonsense :: SUBST s = t - Maybe s
 nonsense t = case nonsense t of
 Nothing - Just empty

 then everything is fine and I can see the type signature of `nonsense`
 inferred by ghci:

 *Main :t nonsense
 nonsense :: (SUBST s) = t - Maybe s

 But, when I put this signature into the code (that is, when the commented
 line above is uncommented) then type checking fails with the following
 error:

 Ambiguous type variable `s' in the constraint:
   `SUBST s'
 arising from a use of `nonsense' at problem-type.hs:6:18-27
 Probable fix: add a type signature that fixes these type variable(s)

 Now, what is the problem here? Why does type checking fail with the
 signature that the type inference itself inferred?

In

nonsense t = case nonsense t of
Nothing - Just empty

, which type has the Nothing? 
It can have the type Maybe s1 for all s1 belonging to SUBST, that is the 
ambiguous type 
variable.


 BTW, I don't understand why but everything works fine with the following
 addition:

 nonsense' :: SUBST s = t - Maybe s
 nonsense' t = case nonsense' t of
 Nothing - Just empty
 x   - x


Here, Nothing must have the same type as x. Since x may be returned, x must 
have type 
Maybe s, for the type variable s of the signature, so the types are completely 
determined.

 I am developing kind of generic interface and I don't want to fix the type
 `s`. I want `nonsense` to work possibly for any instance of SUBST and the
 concrete instance to be determined by the context where `nonsense` is used.

 In my original, meaningful but more complicated example I had the following
 error:

 Couldn't match expected type `STerm s'
against inferred type `STerm s1'
 When generalising the type(s) for `refute'

 (this message does not provide any information where `s1` comes from)

Probably something like the above.
To fix the error, you could use asTypeOf:

nonsense :: SUBST s = t - Maybe s
nonsense t = res
  where
res = case nonsense t `asTypeOf` res of
Nothing - Just empty

or 

{-# LANGUAGE ScopedTypeVariables #-}

nonsense :: forall s. SUBST s = t - Maybe s
nonsense t = case nonsense t :: Maybe s of
Nothing - Just empty


 The original example shares with the above one the property that the type
 `s` is not mentioned in types of arguments, just in the type of a result
 (although, in the original example, some relation between types `t` and `s`
 is expressed in the type context via equality constrains on associated
 types (STerm from the error message) ).

 I tested this with ghc-6.6.1, ghc-6.10.1, ghc-6.10.2 obtaining the same
 result.

 I'll be grateful for any explanation of this issue.

 Sincerely,
   Jan.

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


Re: type checking fails with a correct type

2009-04-30 Thread Daniel Fischer
Am Donnerstag 30 April 2009 18:25:43 schrieb Jan Jakubuv:
 Hello Daniel,

 On Thu, Apr 30, 2009 at 05:17:42PM +0200, Daniel Fischer wrote:
  In
 
  nonsense t = case nonsense t of
  Nothing - Just empty
 
  , which type has the Nothing?
  It can have the type Maybe s1 for all s1 belonging to SUBST, that is the
  ambiguous type variable.

 thanks for the explanation. Maybe I'm starting to understand what is going
 on. Now I understand it thus the call of `nonsense` inside the case
 construct can potentially result in a different `SUBST`-type `s1` than the
 top-level `nonsense`. That is why it has to be explicitly typed.

 But I am still not following why the type inference works fine without the
 signature. Isn't it still ambiguous?

Ah, that's a tricky one :)

Without the type signature, the type of nonsense has to be inferred from 
scratch.
We start with

nonsense t = rhs

so nonsense is a function, taking an argument of type argT, giving a result of 
type resT:

nonsense :: argT - resT

Now we infer the type of the rhs, resT.

case nonsense t of
  Nothing - Just empty

or, rewritten,

let r = nonsense t in
case r of
  Nothing - Just empty

now r is the result of applying nonsense to t, hence r :: resT.
So Nothing has type resT. Since Nothing :: forall a. Maybe a, we can now deduce

resT === Maybe b

for some b we don't know anything about yet.
In case r matches Nothing, the result is (Just empty), so b is the type of 
empty.
empty has type (SUBST s = s), giving

resT === SUBST s = Maybe s

and

nonsense :: SUBST s = argT - Maybe s

*Now* the free type variables are quantified, giving

nonsense :: forall argT s. SUBST s = argT - Maybe s

Since in Haskell, type variables are implicitly universally quantified, the 
forall argT s. part isn't necessary and not displayed.

Here comes the snag:
If you give the (implicitly universally quantified) type signature, you 
explicitly say 
that nonsense can return a value of type Maybe s, whatever s is, as long as 
it's a member 
of SUBST. But then the type-checker cannot assume that r and Just empty have 
the same 
type, thus it sees

let r = nonsense t

, from which it finds

r :: forall s1. SUBST s1 = Maybe s1

on the other hand, it finds

Just empty :: forall s2. SUBST s2 = Maybe s2, giving nonsense the ambiguous 
type

nonsense :: forall t s1 s2. (SUBST s1, SUBST s2) = t - Maybe s2

You can ask GHC by compiling the module without the type signature and with the 
flag 
-ddump-simpl
, the relevant part of the core is:

==

Nonsense.nonsense :: forall t_agD s_agJ.
 (Nonsense.SUBST s_agJ) =
 t_agD - Data.Maybe.Maybe s_agJ
[GlobalId]
[Arity 2]
Nonsense.nonsense =
  \ (@ t_agD)-- type of argument
(@ s_agJ)-- type of result is (Maybe s_agJ)
($dSUBST_agL :: Nonsense.SUBST s_agJ)   -- SUBST dictionary for s_agJ
(eta_shh :: t_agD) -
letrec {
  nonsense1_agA :: t_agD - Data.Maybe.Maybe s_agJ
  -- inner nonsense, the type is fixed as that at which the outer nonsense 
is called,
  -- there is *no* forall here!
  [Arity 1]
  nonsense1_agA =
\ (t_afx :: t_agD) -
  case nonsense1_agA t_afx of wild_Xk {
Data.Maybe.Nothing -
  Data.Maybe.Just
@ s_agJ
($dSUBST_agL
 `cast` ((Nonsense.:Co:TSUBST) s_agJ
 :: (Nonsense.:TSUBST) s_agJ ~ s_agJ));
Data.Maybe.Just ipv_shd -
  Control.Exception.Base.patError
@ (Data.Maybe.Maybe s_agJ) Nonsense.hs:(16,13)-(17,36)|case
  }; } in
nonsense1_agA eta_shh

==

  {-# LANGUAGE ScopedTypeVariables #-}
 
  nonsense :: forall s. SUBST s = t - Maybe s
  nonsense t = case nonsense t :: Maybe s of
  Nothing - Just empty

 Great, ScopedTypeVariables is exactly what I was looking for. It solves all
 my problems.

Great :D


 Thank you,
   Jan.

Cheers,
Daniel

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


  1   2   >