[GHC] #14829: Linking error with ANN pragma
GHC
ghc-devs at haskell.org
Tue Feb 20 14:17:01 UTC 2018
#14829: Linking error with ANN pragma
-------------------------------------+-------------------------------------
Reporter: ehubinette | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
Keywords: | Operating System: Linux
Architecture: | Type of failure: Compile-time
Unknown/Multiple | crash or panic
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
There seems to be an issue with the ANN pragma, with fatal compilation
errors.
To reproduce, setup two modules as such:
{{{#!hs
module Test where
import Weights (Weight(..))
{-# ANN mainTest (Weight 2) #-}
mainTest :: IO ()
mainTest = return ()
}}}
{{{#!hs
{-# LANGUAGE DeriveDataTypeable #-}
module Weights (Weight(..)) where
import Data.Data (Data(..))
newtype Weight = Weight Integer deriving Data
}}}
Compiling with GHC version `8.2.2` yields:
{{{
λ ghc Test.hs
[2 of 2] Compiling Test ( Test.hs, Test.o )
Test.hs:5:1: fatal:
cannot find object file ‘./Weights.dyn_o’
while linking an interpreted expression
}}}
The issue persists with `-dynamic-too`:
{{{
λ ghc -dynamic-too Test.hs
[2 of 2] Compiling Test ( Test.hs, Test.o )
Test.hs:5:1: fatal:
cannot find object file ‘./Weights.dyn_o’
while linking an interpreted expression
}}}
...but disappears with `-dynamic`:
{{{
λ ghc -dynamic Test.hs
[1 of 2] Compiling Weights ( Weights.hs, Weights.o )
[2 of 2] Compiling Test ( Test.hs, Test.o )
}}}
Sidenote: with GHC version `8.5.20180219`, the issue disappears with
`-dynamic-too` ''or'' `-dynamic`:
{{{
λ ../../ghc/inplace/bin/ghc-stage2 -dynamic-too Test.hs
[1 of 2] Compiling Weights ( Weights.hs, Weights.o )
[2 of 2] Compiling Test ( Test.hs, Test.o )
}}}
Remove the ANN pragma, and the compiler behaves just fine with both GHC
versions. Please tell me if I can provide more information. Cheers.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14829>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list