[GHC] #8489: clean up dependency and usages handling in interface files
GHC
ghc-devs at haskell.org
Thu Nov 20 13:23:02 UTC 2014
#8489: clean up dependency and usages handling in interface files
-------------------------------------+-------------------------------------
Reporter: errge | Owner: errge
Type: task | Status: new
Priority: normal | Milestone: 7.10.1
Component: Template | Version: 7.7
Haskell | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Moderate (less
Unknown/Multiple | than a day)
Type of failure: | Blocked By:
None/Unknown | Related Tickets:
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by errge):
Simon, yes of course, it is important to first agree on what we want.
On the other hand, this is a much smaller change than my changes from
previous year, so I do not think that we need a whole wiki page again.
Let me put it here what I think the issue is and then you can point it out
where I was not precise enough and we can complete this to a
"specification".
Take the following program:
{{{#!haskell
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
$(do let mod = Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary")
ModuleInfo info <- reifyModule mod
runIO $ mapM_ print info
return [])
main = return ()
}}}
On my machine, the output is:
{{{
Module (PkgName "base") (ModName "Data.Either")
Module (PkgName "base") (ModName "Data.Maybe")
Module (PkgName "base") (ModName "Data.Word")
Module (PkgName "base") (ModName "GHC.Base")
Module (PkgName "base") (ModName "GHC.IO")
Module (PkgName "base") (ModName "GHC.IO.IOMode")
Module (PkgName "base") (ModName "GHC.Word")
Module (PkgName "base") (ModName "Prelude")
Module (PkgName "base") (ModName "System.IO")
Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary.Class")
Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary.Generic")
Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary.Get")
Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary.Get.Internal")
Module (PkgName "binary-0.7.1.0") (ModName "Data.Binary.Put")
Module (PkgName "bytestring-0.10.4.0") (ModName "Data.ByteString")
Module (PkgName "bytestring-0.10.4.0") (ModName "Data.ByteString.Lazy")
Module (PkgName "bytestring-0.10.4.0") (ModName
"Data.ByteString.Lazy.Internal")
Module (PkgName "ghc-prim") (ModName "GHC.Types")
}}}
And looking at http://hackage.haskell.org/package/binary-0.7.1.0/docs/src
/Data-Binary.html it can be seen that we do not import GHC.Types in
binary.
So from the programmer point of view, this change should make the
ModuleInfo list returned by module reification only contain the actual
direct imports.
So this is my goal, before discussing implementation details inside GHC,
may I ask if this description is clear enough and if others agree with the
goal?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8489#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list