[GHC] #11505: Boot file problem

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Here are two modules and a boot file. Compile by {{{ ghc -c Foo.hs-boot; ghc -c Bar.hs; ghc -c Foo.hs }}} and observe this error message {{{ Foo.hs:12:1: Type constructor `Foo' has conflicting definitions in the module and its hs-boot file Main module: data Foo = Foo {x :: {-# UNPACK #-} !Int} Boot file: data Foo = Foo {x :: !Int} }}} But the definitions are not conflicting, they are identical. Foo.hs-boot: {{{ module Foo where data Foo = Foo { x :: {-# UNPACK #-} !Int } }}} Foo.hs: {{{ module Foo where import Bar data Foo = Foo { x :: {-# UNPACK #-} !Int } }}} Bar.hs: {{{ module Bar where import {-# SOURCE #-} Foo }}} Removing the unbox pragma gives the even more perplexing: {{{ Foo.hs:3:1: Type constructor `Foo' has conflicting definitions in the module and its hs-boot file Main module: data Foo = Foo {x :: !Int} Boot file: data Foo = Foo {x :: !Int} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jstolarek): I can confirm this error in GHC 7.10.3 but not in HEAD. Can someone verify whether it exists on ghc-8.0 branch? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): I can confirm that the error does not occur in 8.0. {{{ rwbarton@morphism:/tmp/boot$ ls Bar.hs Foo.hs Foo.hs-boot rwbarton@morphism:/tmp/boot$ GHC=~/ghc-8.0-install/bin/ghc rwbarton@morphism:/tmp/boot$ $GHC --version The Glorious Glasgow Haskell Compilation System, version 8.0.0.20160123 rwbarton@morphism:/tmp/boot$ $GHC -c Foo.hs-boot; $GHC -c Bar.hs; $GHC -c Foo.hs rwbarton@morphism:/tmp/boot$ rm *.hi* *.o*; ls Bar.hs Foo.hs Foo.hs-boot rwbarton@morphism:/tmp/boot$ GHC=ghc-7.10.1 rwbarton@morphism:/tmp/boot$ $GHC --version The Glorious Glasgow Haskell Compilation System, version 7.10.1 rwbarton@morphism:/tmp/boot$ $GHC -c Foo.hs-boot; $GHC -c Bar.hs; $GHC -c Foo.hs Foo.hs:4:2: Type constructor ‘Foo’ has conflicting definitions in the module and its hs-boot file Main module: data Foo = Foo {x :: !Int} Boot file: data Foo = Foo {x :: !Int} The constructors do not match: The strictness annotations for ‘Foo’ differ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): But the message is a bit strange: it claims that the annotations differ, but then prints out the identical annotations... Something still looks wrong there. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): My last comment was possibly confusing. The error with the identical declarations is from 7.10, not 8.0. I've edited it to try to make it more clear. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11505: Boot file problem
-------------------------------------+-------------------------------------
Reporter: augustss | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.8.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by jberryman):
I can repro what looks like a similar issue on HEAD, but I don't have a
good test yet. I'm experimenting building GHC with the following build
flavour:
{{{
SRC_HC_OPTS = -O -H64m
GhcStage1HcOpts = -O
GhcStage2HcOpts = -O2 -XStrictData -XUnboxedSums -funbox-strict-fields
-fexpose-all-unfoldings -flate-dmd-anal -fmax-simplifier-iterations=8
-funfolding-use-threshold=120 -fstatic-argument-transformation -fsimpl-
tick-factor=100000
GhcLibHcOpts = -O2 -XUnboxedSums -funbox-strict-fields -flate-dmd-
anal -fmax-simplifier-iterations=8 -funfolding-use-threshold=120 -fsimpl-
tick-factor=100000
BUILD_PROF_LIBS = NO
HADDOCK_DOCS = NO
BUILD_SPHINX_HTML = NO
BUILD_SPHINX_PDF = NO
BUILD_MAN = NO
}}}
Where the error pops up building stage2:
{{{
"inplace/bin/ghc-stage1" -hisuf hi -osuf o -hcsuf hc -static -O -H64m
-Wall -Iincludes -Iincludes/dist -Iincludes/dist-derivedconstants/header
-Iincludes/dist-ghcconstants/header -this-unit-i
d ghc-8.1 -hide-all-packages -i -icompiler/basicTypes -icompiler/cmm
-icompiler/codeGen -icompiler/coreSyn -icompiler/deSugar -icompiler/ghci
-icompiler/hsSyn -icompiler/iface -icompiler/llvmGen -i
compiler/main -icompiler/nativeGen -icompiler/parser -icompiler/prelude
-icompiler/profiling -icompiler/rename -icompiler/simplCore
-icompiler/simplStg -icompiler/specialise -icompiler/stgSyn -icom
piler/stranal -icompiler/typecheck -icompiler/types -icompiler/utils
-icompiler/vectorise -icompiler/stage2/build -Icompiler/stage2/build
-icompiler/stage2/build/./autogen -Icompiler/stage2/build/.
/autogen -Icompiler/. -Icompiler/parser -Icompiler/utils
-Icompiler/../rts/dist/build -Icompiler/stage2 -optP-DGHCI -optP-include
-optPcompiler/stage2/build/./autogen/cabal_macros.h -package-id a
rray-0.5.1.1 -package-id base-4.9.0.0 -package-id binary-0.8.3.0 -package-
id bytestring-0.10.8.1 -package-id containers-0.5.7.1 -package-id
deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id
filepath-1.4.1.0 -package-id ghc-boot-8.1 -package-id ghci-8.1 -package-
id hoopl-3.10.2.1 -package-id hpc-0.6.0.3 -package-id process-1.4.2.0
-package-id template-haskell-2.11.0.0 -package-id time
-1.6.0.1 -package-id transformers-0.5.2.0 -package-id unix-2.7.2.0 -Wall
-fno-warn-name-shadowing -this-unit-id ghc -XHaskell2010 -optc-
DTHREADED_RTS -DGHCI_TABLES_NEXT_TO_CODE -DSTAGE=2 -Rghc-timi
ng -O2 -XStrictData -XUnboxedSums -funbox-strict-fields -fexpose-all-
unfoldings -flate-dmd-anal -fmax-simplifier-iterations=8 -funfolding-use-
threshold=120 -fstatic-argument-transformation -fsimpl
-tick-factor=100000 -no-user-package-db -rtsopts -Wnoncanonical-
monad-instances -odir compiler/stage2/build -hidir compiler/stage2/build
-stubdir compiler/stage2/build -dynamic-too -c comp
iler/basicTypes/ConLike.hs -o compiler/stage2/build/ConLike.o -dyno
compiler/stage2/build/ConLike.dyn_o
compiler/basicTypes/ConLike.hs:50:1: error:
Type constructor ‘ConLike’ has conflicting definitions in the module
and its hs-boot file
Main module: data ConLike
= RealDataCon {-# UNPACK #-}DataCon
| PatSynCon {-# UNPACK #-}PatSyn
Boot file: data ConLike
= RealDataCon !DataCon | PatSynCon !PatSyn
The constructors do not match:
The strictness annotations for ‘RealDataCon’ differ
The strictness annotations for ‘PatSynCon’ differ
<

#11505: Boot file problem -------------------------------------+------------------------------------- Reporter: augustss | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by jberryman): FWIW freezing stage1 and adding the following to the top of `compiler/basicTypes/ConLike.hs` and `compiler/basicTypes/ConLike.hs-boot` got me past that to a successfully built (though panic-throwing stage2) {{{ {-# LANGUAGE NoStrictData #-} }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11505#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC