[GHC] #5968: GHC Panic: "AThing evaluated unexpectedly"

2012-03-25 Thread GHC
#5968: GHC Panic: "AThing evaluated unexpectedly"
--+-
 Reporter:  goldfire  |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Template Haskell
  Version:  7.5   |   Keywords:  TemplateHaskell 
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 Using an unmodified build from March 13, 2012, I compiled the following:

 {{{
 {-# LANGUAGE TemplateHaskell #-}
 data Bar a = Bar $( [t| a |] )
 }}}

 I got the following panic:

 {{{
 ghc-stage2: panic! (the 'impossible' happened)
   (GHC version 7.5.20120313 for x86_64-unknown-linux):
 AThing evaluated unexpectedly tcTyVar a{tv aKM}
 }}}

 I observed this exact same panic on a modified 3/25/12 build.

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-03-25 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by Irene):

 I did the more thorough test, and the trivial program runs without a
 crash, producing correct output.  Excellent!  This means that the problem
 does indeed consist only of the TNTC thing, which is what I was trying to
 verify.

-- 
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] #5967: incompatible implicit declaration of function 'memcpy'

2012-03-25 Thread GHC
#5967: incompatible implicit declaration of function 'memcpy'
--+-
 Reporter:  nomeata   |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  normal|  Component:  Compiler
  Version:  7.4.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  Other |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
 In various build logs of Haskell packages on (at least) mips, mipsel, s390
 and s390x, I find the above warnings for the generated .hc files. In one
 case (aeson), it even leads to an error, aborting the build. Here is the
 full build log:
 https://buildd.debian.org/status/fetch.php?pkg=haskell-
 aeson&arch=mips&ver=0.6.0.0-4&stamp=1330462970
 and here are more of those:
 https://buildd.debian.org/status/package.php?p=haskell-aeson

 It does not occur on other “strange” architectures such as arm and armel.

 Thanks,
 Joachim

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-03-25 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by Irene):

 Yes, that is correct - I didn't think of doing it for libraries and the
 RTS.  I'll put together another test that does, and report back.  Good
 catch!

-- 
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] #5899: RTS crash w/ strange closure type 603975781 on OS X 10.8

2012-03-25 Thread GHC
#5899: RTS crash w/ strange closure type 603975781 on OS X 10.8
---+
Reporter:  dylukes |   Owner:   

Type:  bug |  Status:  new  

Priority:  high|   Milestone:  
7.4.2
   Component:  Runtime System  | Version:  
7.4.1
Keywords:  rts, strange closure, internal error, os x  |  Os:  
MacOS X  
Architecture:  x86_64 (amd64)  | Failure:  
Runtime crash
  Difficulty:  Unknown |Testcase:   

   Blockedby:  |Blocking:   

 Related:  |  
---+

Comment(by simonmar):

 I think you only forced ordering for the `Main.o` module, and not the
 libraries or the RTS, correct?  I observed the ordering being mangled for
 one object file in the `base` package, so you would need to force the
 correct order for all the symbols in the libraries too.

-- 
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] #5966: getAppUserDataDirectory does not respect XDG specification

2012-03-25 Thread GHC
#5966: getAppUserDataDirectory does not respect XDG specification
-+--
 Reporter:  ordcoder |  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  libraries/directory
  Version:  7.4.1|   Keywords: 
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple   
  Failure:  Incorrect result at runtime  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--
 getAppUserDataDirectory function from System.Directory module returns path
 to a dot-dir under home directory. This swamps home with many hidden
 directories, when there are many applications installed. There is
 [http://standards.freedesktop.org/basedir-spec/basedir-spec-latest.html
 XDG specification] for this situation, which suggests using $XDG_DATA_HOME
 environment variable.

 So, getAppUserDataDirectory should behave approximately like this when
 $XDG_DATA_HOME is set:
 {{{
 getAppUserDataDirectory appName = do
 path <- getEnv "XDG_DATA_HOME"
 return (path++'/':appName)
 }}}

-- 
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] #5965: pref-llvm failed at integer-gmp-0.3.0.0: stored value and pointer type do not match (was: pref-llvm error: stored value and pointer type do not match)

2012-03-25 Thread GHC
#5965: pref-llvm failed at integer-gmp-0.3.0.0: stored value and pointer type do
not match
-+--
 Reporter:  Favonia  |  Owner:  dterei 
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  Compiler (LLVM)
  Version:  7.5  |   Keywords: 
   Os:  Linux|   Architecture:  x86_64 (amd64) 
  Failure:  Building GHC failed  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--

-- 
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] #5965: pref-llvm error: stored value and pointer type do not match

2012-03-25 Thread GHC
#5965: pref-llvm error: stored value and pointer type do not match
-+--
 Reporter:  Favonia  |  Owner:  dterei 
 Type:  bug  | Status:  new
 Priority:  normal   |  Component:  Compiler (LLVM)
  Version:  7.5  |   Keywords: 
   Os:  Linux|   Architecture:  x86_64 (amd64) 
  Failure:  Building GHC failed  |   Testcase: 
Blockedby:   |   Blocking: 
  Related:   |  
-+--
 The GHC in the trunk (revision [bcb599506764d551e0e6b9084e0e9580f3f00336])
 does not build in the final stage with "pref-llvm":

 {{{
 "inplace/bin/ghc-stage1" -fPIC -dynamic  -O -H64m -fllvm
 -package-name integer-gmp-0.3.0.0 -hide-all-packages
 (...snipped...)
 -package-name integer-gmp -XHaskell98 -XCPP -XMagicHash
 -XUnboxedTuples -XNoImplicitPrelude -XForeignFunctionInterface
 -XUnliftedFFITypes -O2  -no-user-package-conf -rtsopts
 -c libraries/integer-gmp/cbits/gmp-wrappers.cmm
 -o libraries/integer-gmp/dist-install/build/cbits/gmp-wrappers.dyn_o
 /usr/bin/opt: /tmp/ghc2438_0/ghc2438_0.ll:3766:9: error: stored value and
 pointer type do not match
   store i32 %ln1fM, i64* %lc1dk
 ^
 }}}

 Here is the output of configure:

 {{{
 Configure completed successfully.

Building GHC version  : 7.5.20120324

Build platform: x86_64-unknown-linux
Host platform : x86_64-unknown-linux
Target platform   : x86_64-unknown-linux

Bootstrapping using   : /usr/bin/ghc
   which is version   : 7.4.1

Using GCC : /usr/bin/gcc
   which is version   : 4.6.3
Building a cross compiler : NO
Porting to foreign arch   : NO
Alien script  :
 }}}

 While it is clear to me that the offending LLVM line is wrong, sorry that
 I do not know how to trace back to the source of the problem. If providing
 any other information will help, please let me know.

-- 
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