#9938: cryptarithm2 fails with undefined reference to
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.11
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
I am observing this right now:
{{{
==nofib== cryptarithm2: size of Main.o follows...
text data bss dec hex filename
25423 1304 0 26727 6867 Main.o
==nofib== cryptarithm2: time to link cryptarithm2 follows...
Main.o: In Funktion `c79k_info':
(.text+0x1a5b): Nicht definierter Verweis auf
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
Main.o: In Funktion `c7cP_info':
(.text+0x2283): Nicht definierter Verweis auf
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
Main.o: In Funktion `c7ll_info':
(.text+0x2f53): Nicht definierter Verweis auf
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
Main.o: In Funktion `c7p2_info':
(.text+0x37cb): Nicht definierter Verweis auf
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
collect2: error: ld returned 1 exit status
<>
make[2]: *** [cryptarithm2] Fehler 1
Failed making all in cryptarithm2: 1
make[1]: *** [all] Fehler 1
Failed making all in spectral: 1
make: *** [all] Fehler 1
make: Verlasse Verzeichnis '/data1/ghc-builder/logs/ghc-tmp-REV/nofib'
}}}
Trying to minimize the problem, I came up with this file:
{{{
module Main where
import Control.Monad
import Control.Monad.Trans.State
solve :: Int -> StateT () [] ()
solve carry | carry > 0 =
do guard (0 == carry)
solve (carry -1)
solve 0 = mzero
main :: IO ()
main = return ()
}}}
It only occurs when using this sequence (I’m also pasting the DEBUG
output, in case it is useful):
{{{
$ /home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2 -O2 -c Main.hs
WARNING: file compiler/specialise/Specialise.hs, line 677
specImport discarding: $w$cmany :: forall s_a1an
(m_a1ao :: * -> *).
MonadPlus m_a1ao =>
forall a_a1ap.
StateT s_a1an m_a1ao a_a1ap -> StateT
s_a1an m_a1ao [a_a1ap]
want: False
stable: False
calls: $w$cmany _ @ [] $fMonadPlus[]
WARNING: file compiler/specialise/Specialise.hs, line 677
specImport discarding: $w$csome :: forall s_a1ax
(m_a1ay :: * -> *).
MonadPlus m_a1ay =>
forall a_a1az.
StateT s_a1ax m_a1ay a_a1az -> StateT
s_a1ax m_a1ay [a_a1az]
want: False
stable: False
calls: $w$csome _ @ [] $fMonadPlus[]
WARNING: file compiler/specialise/Specialise.hs, line 677
specImport discarding: $w$cp0Alternative :: forall s_a1aT
(m_a1aU :: * -> *).
MonadPlus m_a1aU =>
(# Functor (StateT s_a1aT
m_a1aU),
forall a_a1aV.
a_a1aV -> StateT s_a1aT
m_a1aU a_a1aV,
forall a_a1aW b_a1aX.
StateT s_a1aT m_a1aU
(a_a1aW -> b_a1aX)
-> StateT s_a1aT m_a1aU
a_a1aW
-> StateT s_a1aT m_a1aU
b_a1aX,
forall a_a1aY b_a1aZ.
StateT s_a1aT m_a1aU
a_a1aY
-> StateT s_a1aT m_a1aU
b_a1aZ
-> StateT s_a1aT m_a1aU
b_a1aZ,
forall a_a1b0 b_a1b1.
StateT s_a1aT m_a1aU
a_a1b0
-> StateT s_a1aT m_a1aU
b_a1b1
-> StateT s_a1aT m_a1aU
a_a1b0 #)
want: False
stable: False
calls: $w$cp0Alternative _ @ [] $fMonadPlus[]
WARNING: file compiler/specialise/Specialise.hs, line 1093
Missed specialisation opportunity for $fMonadStateT_$c>>
[] 2 [] 1 [ALWAYS]
$ /home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2 -O2 -o cryptarithm2
Main.o
Main.o: In function `r3He_info':
(.text+0x52): undefined reference to
`transzuH9c1w14lEUN3zzdWCTsn8jG_ControlziMonadziTransziStateziLazzy_zdwzdcp0Alternative_info'
collect2: error: ld returned 1 exit status
}}}
It works fine if I compile directly using
{{{
$ /home/jojo/build/haskell/ghc/inplace/bin/ghc-stage2 -O2 -o cryptarithm2
Main.hs
}}}
Changing the order of the cases in `solve` also makes the problem go away.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9938
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler