
Hi Tom, The problem is that GHC lazily loads non-orphan instances, so they won't be in the environment until you load the interface which would have caused the instance to come into scope. I'm not sure exactly what you are actually trying to do. But if you really need all instances, you will have to first arrange to load the interfaces of ALL modules transitively imported by your module. Edward Excerpts from Tom Sydney Kerckhove's message of 2017-05-18 14:39:38 +0200:
Dear GHC Devs.
I am trying to use the GHC API as part of the work that I am doing for my thesis. Currently I am looking for a way to find all the type class instances that are in scope in a given module.
Here's what I've tried:
``` getInstancesFromTcmodule :: GhcMonad m => TypecheckedModule -> m () getInstancesFromTcmodule tmod = do let (tcenv, md) = tm_internals_ tmod let insts = tcg_insts tcenv getInsts >>= printO printO $ modInfoInstances $ tm_checked_module_info tmod printO insts printO $ md_insts md printO $ tcg_inst_env tcenv
printO :: (GhcMonad m, Outputable a) => a -> m () printO a = showGHC a >>= (liftIO . putStrLn) ```
Unfortunately the output that I get is empty:
``` ([], []) [] [] [] [] ```
For the record, I ran this on the following module:
``` {-# LANGUAGE NoImplicitPrelude #-} module Ints where
import Prelude (Int, (+), (-))
f :: Int -> Int f x = x + 1
g :: Int -> Int g x = x - 1
double :: Int -> Int double x = x + x
zero :: Int zero = 0 ```
Because I'm using '+' and '-', I definitely expect the instances of 'Num' to be available, but I am also expecting to find ALL the other instances that are available for type checking.
Is there any documentation on this matter? Failing that, is there anyone who is willing to help me with this problem?
Thank you for your time.