Re: [GHC] #3198: inliner fails to kick in for Double (*)

2009-04-28 Thread GHC
#3198: inliner fails to kick in for Double (*)
--+-
 Reporter:  JulesBean |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  Compiler  |Version:  6.11
 Severity:  normal| Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Comment (by JulesBean):

 Neither do {{{-fdicts-strict}}} or {{{-fdicts-cheap}}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: Linking hsc2hs .c output on Windows w/ build system: is it just me..?

2009-04-28 Thread Sigbjorn Finne

Thanks Simon,

sorry for not noticing your reply amidst the flow of g-h-b ticket reports
before now. As there is no need to sail that close to the wind of
playing with the delicate linking & loading orders of the CRT and
base DLLs like kernel32, my suggestion would be simply to avoid
it. You don't do any explicit "-lgcc -lc" trickery when invoking gcc/ld
on other platforms, so why be different?

Apart from the changes to Win32.cabal and base.cabal mentioned
in the original e-mail, injecting addDLL() calls for kernel32 and
msvcrt in initLinker() ought to do it.

--sigbjorn

On 4/27/2009 04:58, Simon Marlow wrote:

On 24/04/2009 23:04, Sigbjorn Finne wrote:

I've been experiencing repeated woes over the past 4-5 months
when trying to spin up build trees on Windows with the new build
system. This is happening on the 3-4 boxes that I regularly develop on,
which leads me to believe that this may not be limited to just me..

The problem is that hsc2hs generated .c files (Foo_hsc_make.c) when
compiled and linked via the 'ghc' that's configured against, will 
produce
.exe's that crashes right out of the gates. gdb'ing the generated 
binaries,
the crash is happening in the CRT startup code & with some further 
poking
around I've been able to determine that it is the explicit presence 
of "-l"
options for 'kernel32' and 'msvcrt' when linking that's the cause. 
This is
with a variety of versions of 'ld' and binutils snapshots (2.17.x -- 
2.19).

Using the 2.19.1 version that ships with gcc4.3.3 snapshots for mingw is
well-behaved, but ghc is still using gcc-3.4.5.


We have seen this problem here on Satnam Singh's machine, but we 
eventually put it down to a conflict between versions of certain MSYS 
bits.  There may indeed be a real problem here, I don't know.


On Satnam's machine we established that the problem was provoked by 
updating binutils, and the solution was "don't do that" (Satnam had 
originally done this because the windres that comes with MSYS was 
incompatible with GHC, but that can be worked around by just copying 
in a suitable windres).


We also tracked it down as far as compiling a trivial C program with 
-lmsvcrt.


Incedentally if you follow the instructions on the wiki exactly, you 
won't run into this problem: 
http://hackage.haskell.org/trac/ghc/wiki/Building/Preparation/Windows.



There's a couple of things that are odd here:

* base.cabal files have kernel32 and msvcrt as extra-libraries. This is
clearly
not required when doing invocations via ld(1), and causes considerable
mischief,
so it'd be good if there was a way in .cabal files to distinguish
between stuff that
goes into 'extraLibraries' and 'extraGHCiLibraries' in package.conf's
InstalledPackageInfos. (Is there? Couldn't locate anything appropriate
while
working with the Cabal sources..)

* 'base' needing to include these two dependencies even for GHCi 
usage. A

running RTS will have these loaded already, so it really ought to have
primed
the list of opened DLLs by explicitly loading them upon initialization
of the linker.
[I've got a trivial patch against rts/Linker.c that does this; can
forward/commit if
of interest..]


I've no idea why these library dependencies are there.  It might well 
be historical.  I'm happy to defer to Windows experts such as yourself 
on whether we should have them or not (I guess not?).



* In addition to the patch referred to above, to solve these problems, I
had to scrub
libraries/base/base.cabal of 'kernel32' and 'msvcrt' + the
package.conf's for the
versions of ghc I'm building against had to be edited, limiting the use
of 'kernel32'
and 'msvcrt' to extraGHCiLibraries for both the 'base' and 'Win32'
packages.

Long and rambling..hope you made it this far ;-) Is anyone else running
into this issue &
should we do something about it? If not, details of compilation
environment that
you've got that avoids running into this issue would be most welcome.
It's a bit of a
chore spinning up new builds, as is.


One open question is whether we should expect "gcc foo.c -lmsvcrt" to 
work.  It works with older versions of MSYS/mingw, but apparently not 
with more recent versions.  On the face of it this seems like it ought 
to be harmless, since msvcrt will eventually be linked in anyway.


Cheers,
Simon


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


Re: [GHC] #3198: inliner fails to kick in for Double (*)

2009-04-28 Thread GHC
#3198: inliner fails to kick in for Double (*)
--+-
 Reporter:  JulesBean |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  Compiler  |Version:  6.11
 Severity:  normal| Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Comment (by JulesBean):

 Adding an explicit -# INLINE timesDouble #- to Float.lhs doesn't
 change the result.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3199: System.Environment provides no access to argv[0]

2009-04-28 Thread GHC
#3199: System.Environment provides no access to argv[0]
--+-
 Reporter:  guest |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  libraries/base|Version:  6.10.2  
 Severity:  normal| Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Comment (by sof):

 This might be of some utility..

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}
 -- What GHC.Environment leaves out.
 module Main where

 import Foreign
 import Foreign.C

 getFullProgName :: IO String
 getFullProgName =
   alloca $ \ p_argc ->
   alloca $ \ p_argv -> do
getFullProgArgv p_argc p_argv
peek p_argv >>= peek >>= peekCString

 foreign import ccall unsafe "getFullProgArgv"
 getFullProgArgv :: Ptr CInt -> Ptr (Ptr CString) -> IO ()

 main = getFullProgName >>= putStrLn
 }}}

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #3199: System.Environment provides no access to argv[0]

2009-04-28 Thread GHC
#3199: System.Environment provides no access to argv[0]
--+-
 Reporter:  guest |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Milestone:  
Component:  libraries/base|Version:  6.10.2  
 Severity:  normal| Resolution:  
 Keywords:|   Testcase:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
--+-
Changes (by NeilMitchell):

 * cc: ndmitch...@gmail.com (added)

Comment:

 I agree - a best try result would be desirable, then if the user only
 wants the leaf name they can always call {{{takeBaseName}}}.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3200: System.Environment.withProgName strips everything before the last slash

2009-04-28 Thread GHC
#3200: System.Environment.withProgName strips everything before the last slash
-+--
Reporter:  guest |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  libraries/base  
 Version:  6.10.2|   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 The documentation for `withProgName` says:

   withProgName name act - while executing action act, have getProgName
 return name.

 However:
 {{{
 % ghc -e 'System.Environment.withProgName "Hello / World///."
 System.Environment.getProgName'
 "."
 }}}

 I discovered this while trying to work around bug #3199 like this:
 {{{
 main = do
 exe <- readSymbolicLink "/proc/self/exe"
 withProgName exe main'
 ...
 }}}

 So... I need to re-exec my program. Fortunately, there is `argv[0]`
 containing exactly the information I need. Unfortunately, Haskell doesn't
 let me access it. Fortunately, Linux provides the full path to my program
 in a special file and Haskell lets me "fix" the program name at startup.
 Unfortunately, this functionality is broken: `withProgName` only takes the
 part after the last slash. Back to square one. :-(

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3199: System.Environment provides no access to argv[0]

2009-04-28 Thread GHC
#3199: System.Environment provides no access to argv[0]
-+--
Reporter:  guest |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  libraries/base  
 Version:  6.10.2|   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 The docs for `getProgName` say:

   Computation getProgName returns the name of the program as it was
 invoked.

   However, this is hard-to-impossible to implement on some non-Unix OSes,
 so instead, for maximum portability, we just return the leafname of the
 program as invoked. Even then there are some differences between
 platforms: on Windows, for example, a program invoked as foo is probably
 really FOO.EXE, and that is what getProgName will return.

 I think the "just return the leafname" part is stupid, because it means
 there is no way for me to get at C's `argv[0]`. How does mangling
 `argv[0]` increase portability? It just makes Haskell incompatible with
 everything else out there. Also, if your platform has `argv[0]`, you might
 as well return it as-is.

 Why do I want `argv[0]` at all? Well, the ability to write a drop-in
 replacement for a C program that does something like `fprintf(stderr, "%s:
 %s: %s\n", argv[0], filename, strerror(errno))` would be nice (where
 "drop-in" = character for character the same output). My current project
 is an IRC bot that can restart itself via `exec()`, preserving state in
 its command line arguments. However, I usually don't "install" the bot, I
 just run it from some directory. In this case `argv[0]` would be perfect:
 if it contains slashes, the bot was run from some directory (and `exec()`
 will find it there); if it doesn't, the executable was found in the path
 (and `exec()` will find that too).

 To summarize: I think the inability to get at argv[0] from Haskell is a
 bug. If you don't want to change `getProgName`, please consider adding
 another function (`getNativeProgName`?).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3198: inliner fails to kick in for Double (*)

2009-04-28 Thread GHC
#3198: inliner fails to kick in for Double (*)
-+--
Reporter:  JulesBean |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  6.11  |   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 In GHC HEAD as of approx March 2009, the following very simple code fails
 to inline the (*), which means it fails to generate FPU code:

 {{{
 module Print where

 printTimes :: Double -> Double -> IO ()
 printTimes f g = print (f*g)
 }}}

 My evidence for this is that the generated asm (from -O2 -ddump-asm)
 includes

 {{{
 movl %esi,-4(%ebp)
 movl 12(%esi),%eax
 movl %eax,-16(%ebp)
 movl 8(%esi),%eax
 movl %eax,-20(%ebp)
 movl $_sC3_info,-12(%ebp)
 addl $-20,%ebp
 jmp _base_GHCziFloat_timesDouble_info
 }}}

 ...which calls 'GHC.Float.timesDouble' as a regular function with regular
 stack calling.

 Someone confirmed for me that this also happens for them with the released
 GHC 6.10 versions.

 On my copy of 6.8.3 the inlining is fine, and I get proper x87 opcodes:

 {{{
 #   gmull %fake0,%fake1,%fake0
 #GMUL-xxxcase1
 ffree %st(7) ; fld %st(1) ; fmulp %st(0),%st(1)
 }}}

 Now, if I try a pure version of the code, that is very simply:

 {{{
 module Times where

 f :: Double -> Double -> Double
 f x y = x * y
 }}}

 I don't find it inlines in either HEAD or 6.8. It compiles again to a jump
 to _base_GHCziFloat_timesDouble_info.

 In all cases (that is, HEAD, 6.8, pure code and print code) simply
 replacing {{{x*y}}} with {{{1+x*y}}} solves the problem.

 It seems this is some kind of inliner fragility but I'm reporting it as a
 bug since it is also a regression from 6.8, in the first form I
 discovered.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3197: disambiguating type family instances with qualified names not possible

2009-04-28 Thread GHC
#3197: disambiguating type family instances with qualified names not possible
-+--
Reporter:  claus |  Owner: 
Type:  bug   | Status:  new
Priority:  normal|  Component:  Compiler (Type checker)
 Version:  6.11  |   Severity:  normal 
Keywords:|   Testcase: 
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple   
-+--
 While reading [http://www.haskell.org/pipermail/haskell-
 cafe/2009-April/060665.html 1], it occured to me that type families could
 be used to parameterize modules by types. So I modified my example from
 [http://www.haskell.org/pipermail/haskell-cafe/2009-April/060324.html 2],
 trying to parameterize two modules `A` and `B` with a shared type `Label`
 (sharing expressed in `C)`, but ran into a few issues:
 {{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE EmptyDataDecls #-}
 module LA where
 data MyLabel
 y = undefined::MyLabel

 type family Label a
 z = undefined::Label ()
 }}}
 {{{
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE EmptyDataDecls #-}
 module LB where
 data MyLabel
 y = undefined::MyLabel

 type family Label a
 z = undefined::Label ()
 }}}
 {{{
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE TypeFamilies #-}
 module LC where
 import LA
 import LB

 -- fails = [LA.y,LB.y]

 -- express type sharing while leaving actual type open
 type family Label a
 type instance LA.Label a = LC.Label a
 type instance LB.Label a = LC.Label a
 ok2 = [LA.z,LB.z]

 -- for testing only
 -- type instance Label a = () -- can't use with or without qualifier:-(
 }}}
 Issues:
  - is it really necessary for type families to have at least one index?
 Without that, type constants could be expressed directly

  - uncommenting that last line demonstrates a couple of bugs:

  * as it stands, the type instance is ambiguous, but the error message
 has an incorrect source location (`1:0`)

  * trying to disambiguate by defining `type instance LC.Label` results
 in : "Qualified name in binding position: LC.Label" (note that this is
 permitted a couple of lines up, so it is related to whether the qualifier
 refers to the current module or an imported one)

 [the bug is not really in the type checker, but specific to type
 families..]

 Bug aside, it works (`length ok2` gives two, not an error, as `fail`
 would).

 This could be a useful type family programming pattern (it is probably
 implicit in the comparisons of SML functors vs Haskell type
 classes/families, I just don't recall it being made so explicit before,
 just focussing on type parameterization and sharing)!-)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: Inter-module links with Haddock broken?

2009-04-28 Thread David Waern
2009/4/28 Sven Panne :
> Am Samstag, 25. April 2009 14:48:03 schrieb Sven Panne:
>> Currently I am unable to make inter-module links (of the form
>> 'Foo.Bar.baz') work with the Haddock shipped with GHC 6.10.2. [...]
>
> Until a few moments ago, I wasn't aware of the fact that Haddock has a trac
> for itself nowadays, so I guess my problem is a symptom of:
>
>   http://trac.haskell.org/haddock/ticket/78
>
> What is the schedule for the Haddock milestone 2.5.0 mentioned in that ticket?
> When can we expect that fix in a shipped GHC?

We have no schedule yet. I will just release it when I have had time
to fix enough bugs that it's worth making a release. Help wanted :-)

I'm not sure if we can do Haddock fixes for 6.10.3. Can we? Otherwise
an updated Haddock will not ship with GHC until 6.12.1.

Not sure if Haddock will be installed by GHC installations in the
future though, since I think the Haskell Platform is supposed to
manage that. Is this correct?

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


Re: Inter-module links with Haddock broken?

2009-04-28 Thread Sven Panne
Am Samstag, 25. April 2009 14:48:03 schrieb Sven Panne:
> Currently I am unable to make inter-module links (of the form
> 'Foo.Bar.baz') work with the Haddock shipped with GHC 6.10.2. [...]

Until a few moments ago, I wasn't aware of the fact that Haddock has a trac 
for itself nowadays, so I guess my problem is a symptom of:

   http://trac.haskell.org/haddock/ticket/78

What is the schedule for the Haddock milestone 2.5.0 mentioned in that ticket? 
When can we expect that fix in a shipped GHC?

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


Re: [GHC] #2965: GHC on OS X does not compile 64-bit

2009-04-28 Thread GHC
#2965: GHC on OS X does not compile 64-bit
+---
Reporter:  Axman6   |Owner:  thoughtpolice
Type:  feature request  |   Status:  new  
Priority:  normal   |Milestone:  6.12 branch  
   Component:  Compiler |  Version:   
Severity:  normal   |   Resolution:   
Keywords:  64bit|   Difficulty:  Unknown  
Testcase:   |   Os:  MacOS X  
Architecture:  x86_64 (amd64)   |  
+---
Changes (by beastaugh):

 * cc: ionf...@gmail.com (added)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2971: readFile "/proc/mounts" hangs on an amd64 machine

2009-04-28 Thread GHC
#2971: readFile "/proc/mounts" hangs on an amd64 machine
-+--
Reporter:  dsf   |Owner:  igloo  
Type:  merge |   Status:  closed 
Priority:  high  |Milestone:  6.10.2 
   Component:  Compiler  |  Version:  6.10.1 
Severity:  critical  |   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  Unknown/Multiple  |  
-+--
Comment (by jimbob):

 [http://www.satisfyenhancers.com/male-enhancement-cream/vigrx-oil-reviews/
 vigrx oil] [http://www.kopaviagra.net/ billig generisk viagra]

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2009-04-28 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by fasta):

 * cc: r...@gamr7.com (removed)

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2009-04-28 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by NeilMitchell):

 * cc: ndmitch...@gmail.com (added)

Comment:

 The -boot files are particularly annoying if you don't use {{{--make}}},
 since then you need to write some reasonably complex build rules to get
 everything working. Having GHC perform this magic, even at the cost of
 essentially moving the -boot file in to the source file, would be nice.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2009-04-28 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by augustss):

 Reply to simonmar:

 I guess it's a matter of style.  I use import list on most modules I
 import.  Even so, I'm willing to tolerate some pain to get rid of the very
 annoying -boot file.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2770: Missing check that C compiler is C99 compatible

2009-04-28 Thread GHC
#2770: Missing check that C compiler is C99 compatible
-+--
Reporter:  jputcu|Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone:  6.12.1 
   Component:  Build System  |  Version:  6.10.1 
Severity:  blocker   |   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
Testcase:|   Os:  Linux  
Architecture:  x86   |  
-+--
Changes (by simonmar):

  * status:  new => closed
  * resolution:  => fixed

Comment:

 I've updated the configure script to require gcc 3.  Lacking a machine
 with gcc 2.95 installed that's the best we can do for now.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2009-04-28 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonmar):

 Replying to [comment:18 augustss]:
 > Well, I suggested that when using SOURCE you have to supply the import
 list.
 > And I would also require the imported values to have type signatures in
 the other module.  With those premises I can write a dodgy sed script that
 kinda does the work.

 Ah, I took that to mean that only SOURCE imports would need import lists,
 but now I see that you meant all imports - or at least all imports of
 entities referred to by an entity in the loop.  I'm not keen on this, it
 seems worse than `.hs-boot` files.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3196: libHSffi_p.a should not be created when profiled libs are disabled

2009-04-28 Thread GHC
#3196: libHSffi_p.a should not be created when profiled libs are disabled
-+--
Reporter:  juhpetersen   |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  6.11  |   Severity:  normal  
Keywords:|   Testcase:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
-+--
 When building ghc-6.11 without profiling libHSffi_p.a is still created.  I
 guess it need not be.

 Attaching a small patch to fix that.

 ps IMHO it would would be nice to have a configure switch to turn off
 profiling (--disable-profiling?).

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #3195: runghc failing sometimes

2009-04-28 Thread GHC
#3195: runghc failing sometimes
+---
Reporter:  juhpetersen  |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  Runtime System  
 Version:  6.10.2   |   Severity:  normal  
Keywords:   |   Testcase:  
  Os:  Linux|   Architecture:  Unknown/Multiple
+---
 ghc-6.10.2 runghc fails on ppc sometimes:

 http://koji.fedoraproject.org/koji/getfile?taskID=1320158&name=build.log
 (haddock)

 http://koji.fedoraproject.org/koji/getfile?taskID=1319083&name=build.log
 (HTTP)

 Also reproduced first-hand on a ppc box.

 Furthermore (may be a different issue) runghc fails for me with
 recent ghc-6.11 snapshots I have built on x86_64.

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2009-04-28 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |Owner:  
Type:  feature request   |   Status:  new 
Priority:  normal|Milestone:  _|_ 
   Component:  Compiler  |  Version:  6.10.2  
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Comment (by simonpj):

 "I absolutely hate it if I have to write a .hc-boot file" (I assume you
 mean hs-boot file).  I'm interested in identifying precisely what it is
 that you hate, lest we fix the wrong thing:

  * Do you hate writing the type signatures of the functions that the
 module exports?  (After all, most Haskell programmers do that routinely.)
  * Do you hate putting those type signatures in a physically different
 file?  That is would the hate be alleviated if the signatures were in the
 same file as the module implementation?
  * Or perhaps you hate something else?  Such as having to pick a place to
 cut the recursive loop at all?

 I'm interested in this because the ML community regards it as a ''major''
 virtue that module signatures and implementations are separate, so that
 you can
   * Import a module (via its signature) before you have written its
 implementation
   * Provide more than one implementation of a common signature, and
 thereby be confident that switching implementations will not cause errors.

 Being clear about goals will help the design.

 Simon

-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs