[GHC] #13616: Old file used when later calls to GHC omit -dynamic-too
GHC
ghc-devs at haskell.org
Wed Apr 26 16:24:45 UTC 2017
#13616: Old file used when later calls to GHC omit -dynamic-too
-------------------------------------+-------------------------------------
Reporter: nomeata | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
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:
-------------------------------------+-------------------------------------
This may possibly only hurt few people who develop Plugins, but it is
still quite annoying: If `ghc`, in `--make` mode, recompiles a plugin that
it is going to use, but without `-dynamic-too`, it will create new `.dyn`
and `.o` files, but it will happily use the old `.dyn_hs` or `.dyn_o`
files that are still lying around.
I guess the desired behavior is: If it determines that it needs the
dynamically compiled version of some module, and it is recompiling the
module, then it should complain instead of later either ungracefully
falling over the missing `.dyn_o` file or – worse – using an old one.
This script reproduces the issue:
{{{
#!/bin/bash
rm -f *.o *.hi *.dyn_o *.dyn_hi
cat > Plugin.hs <<__END__
module Plugin where
import GhcPlugins
plugin :: Plugin
plugin = defaultPlugin { installCoreToDos = install }
install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
install _ _ = error "First version"
__END__
cat > Code.hs <<__END__
{-# OPTIONS_GHC -O -fplugin Plugin #-}
module Code where
__END__
echo "No dynamic file found (fine, but the error message could be more
helpful)"
ghc -package ghc Code.hs -fforce-recomp
echo "Compiling with -dynamic-too"
ghc -dynamic-too -package ghc Code.hs -fforce-recomp
cat > Plugin.hs <<__END__
module Plugin where
import GhcPlugins
plugin :: Plugin
plugin = defaultPlugin { installCoreToDos = install }
install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]
install _ _ = error "Second version"
__END__
echo "Recompiling without -dynamic-too, it still uses the old file"
ghc -package ghc Code.hs -fforce-recomp
echo "Recompiling with -dynamic-too, now it works"
ghc -dynamic-too -package ghc Code.hs -fforce-recomp
}}}
And here is the slightly redacted output:
{{{
$ ./repro.sh
No dynamic file found (fine, but the error message could be more helpful)
[1 of 2] Compiling Plugin ( Plugin.hs, Plugin.o )
[2 of 2] Compiling Code ( Code.hs, Code.o )
<no location info>: fatal:
cannot find object file ‘./Plugin.dyn_o’
while linking an interpreted expression
Compiling with -dynamic-too
[1 of 2] Compiling Plugin ( Plugin.hs, Plugin.o )
[2 of 2] Compiling Code ( Code.hs, Code.o )
ghc: panic! (the 'impossible' happened)
First version
Recompiling without -dynamic-too, it still uses the old file
[1 of 2] Compiling Plugin ( Plugin.hs, Plugin.o )
[2 of 2] Compiling Code ( Code.hs, Code.o )
ghc: panic! (the 'impossible' happened)
First version
Recompiling with -dynamic-too, now it works
[1 of 2] Compiling Plugin ( Plugin.hs, Plugin.o )
[2 of 2] Compiling Code ( Code.hs, Code.o )
ghc: panic! (the 'impossible' happened)
Second version
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13616>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list