On 14/12/13 15:02, Roman Cheplyaka
wrote:
haskell-names can also do this (it's used in halberd to solve a similar
task: https://github.com/haskell-suite/halberd)
This is quite useful, thanks.
For the benefit of the list archive, here is what I have worked out
so far.
I took the example from
http://www.haskell.org/haskellwiki/GHC/As_a_library
which uses getNamesInScope (I thought that this was promising). But
it returned an empty list for the list of names (variable 'n'). I
found out that you have to set the context before the call to
getNamesInScope, like so:
https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/A.hs
target <- guessTarget targetFile Nothing
setTargets [target]
load LoadAllTargets
--
http://stackoverflow.com/questions/11571520/reify-a-module-into-a-record
setContext [IIDecl (simpleImportDecl (mkModuleName
"B"))]
modSum <- getModSummary $ mkModuleName "B"
For example on this file,
-- B.hs
module B where
import Data.Maybe
f :: a -> Maybe a
f x = Just x
s = "boo" :: String
main = print "Hello, World!"
we can get the list of names and also the imports:
$ runhaskell A.hs
([B.main, B.f, B.s],
[main, B.main, f, B.f, s, B.s],
[],
[import (implicit) Prelude, import Data.Maybe])
I'm not sure why, but the "source imports" is an empty list, while
the "textual imports" gives the implicit Prelude and Data.Maybe.
Also the names are the program names like f, s, and main, and don't
include things like String, Int, Just, and so on.
Independently of that, I tweaked an example from the haskell-names
docs and this lets me see where String comes from, e.g.
https://github.com/carlohamalainen/playground/blob/master/haskell/ghc_symbol_lookup/haskell_names_example.hs
$ cat B.hs | runhaskell haskell_names_example.hs
Relevant bits:
"Prelude"
SymType {st_origName = OrigName { origPackage = Just
(PackageIdentifier { pkgName = PackageName "base"
, pkgVersion = Version {versionBranch = [4,7,0,0]
, versionTags = []}})
, origGName = GName {
gModule = "GHC.Base"
,
gName = "String"}}
, st_fixity = Nothing}
"Data.Maybe"
SymConstructor {sv_origName = OrigName { origPackage = Just
(PackageIdentifier { pkgName = PackageName "base"
, pkgVersion = Version {versionBranch = [4,7,0,0]
, versionTags = []}})
, origGName = GName {
gModule = "Data.Maybe"
, gName
= "Just"}}
,
sv_fixity = Nothing
,
sv_typeName = OrigName { origPackage = Just (PackageIdentifier {
pkgName = PackageName "base"
, pkgVersion = Version { versionBranch = [4,7,0,0]
, versionTags = []}})
, origGName = GName { gModule = "Data.Maybe"
, gName = "Maybe"}}}
This is pretty much what I'm after. The first block shows us that
String is exported from the Prelude, even though it's defined in
GHC.Base. The second block says that the constructor Just is
actually exported from Data.Maybe.
So these ought to able to be stitched together: work through the
textual imports one at a time until a symbol appears and then find
the haddock_html field for the package using ghc-pkg.
--
Carlo Hamalainen
http://carlo-hamalainen.net