SourceNotes are not applied to all identifiers
Compiling
module Foo where
foo x = x + 1
bar y = foo y
with -g
produces
$ ghc -g -ddump-ticked test.hs
[1 of 1] Compiling Foo ( test.hs, test.o )
AbsBinds [a_avC] [$dNum_avD]
{Exports: [foo <= foo_amB
<>]
Exported types: foo :: forall a_avC. Num a_avC => a_avC -> a_avC
[LclId, Str=DmdType]
Binds: -- ticks = [src<test.hs:3:1-13>]
foo_amB x_alA
= src<test.hs:3:9-13> (+)
src<test.hs:3:9> x_alA src<test.hs:3:13> 1}
AbsBinds [a_avV] [$dNum_avW]
{Exports: [bar <= bar_avN
<>]
Exported types: bar :: forall a_avV. Num a_avV => a_avV -> a_avV
[LclId, Str=DmdType]
Binds: -- ticks = [src<test.hs:5:1-13>]
bar_avN y_amz = src<test.hs:5:9-13> foo (src<test.hs:5:13> y_amz)}
Note that neither the occurrence of (+)
in foo
, nor the occurrence of foo
in bar
have their own Ticks. Instead they are only covered by the Tick for the entire application x + 1
(resp. foo y
).
I'm trying to use the new SourceNote infrastructure to map CoreExprs back to their original source location, but unfortunately I need these locations for each identifier in the source.
Would it be reasonable to add a SourceNote to each occurrence of an identifier?
Trac metadata
Trac field | Value |
---|---|
Version | 7.10.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |