Type class instances in scope

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. -- Tom Sydney Kerckhove

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.

On 18-05-17 20:41:13, Edward Z. Yang wrote:
Hi Tom,
Hi Edward,
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.
Oh, that's annoying. I have a feeling there is room for an optimisation here. ... or maybe this was already an optimisation, I don't really know.
I'm not sure exactly what you are actually trying to do.
More concretely, I need to generate a line of code for every 'Arbitrary' instance in scope. Later I'll also need to use other instances but this is the first part.
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.
I don't really mind the time it takes to do this, but that's annoying to write. Thank you for your help! I will look into it.
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.
-- Tom Sydney Kerckhove

Excerpts from Tom Sydney Kerckhove's message of 2017-05-19 11:05:17 +0200:
Oh, that's annoying. I have a feeling there is room for an optimisation here. ... or maybe this was already an optimisation, I don't really know.
It's an optimization. Without, we would have to eagerly load every interface you transitively import, even if you didn't end up using them. That would be really slow.
I'm not sure exactly what you are actually trying to do.
More concretely, I need to generate a line of code for every 'Arbitrary' instance in scope.
Later I'll also need to use other instances but this is the first part.
OK...
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.
I don't really mind the time it takes to do this, but that's annoying to write.
Thank you for your help! I will look into it.
Another possibility is, if you can programatically list the types that you are interested in, you can load all of those, and then the instances for those types will be ready.

On 19-05-17 08:35:32, Edward Z. Yang wrote:
Excerpts from Tom Sydney Kerckhove's message of 2017-05-19 11:05:17 +0200:
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.
I don't really mind the time it takes to do this, but that's annoying to write.
Thank you for your help! I will look into it.
Another possibility is, if you can programatically list the types that you are interested in, you can load all of those, and then the instances for those types will be ready.
That's probably the most feasible approach. Then I'd have to find all the types in scope, and find their interfaces. I know how to get all the TyThing's in scope, so it should be easy-ish to get started. Thanks! -- Tom Sydney Kerckhove

Hi Edward, I'm sorry to have to bother you with this again, but I seem to be stuck with this approach. I think I don't really understand what 'load the interfaces' means. Here's what I tried: ``` Haskell getInstancesFromTcmodule :: GhcMonad m => TypecheckedModule -> m () getInstancesFromTcmodule tmod = do let (tcenv, md) = tm_internals_ tmod let insts = tcg_insts tcenv printO insts printO $ md_insts md printO $ tcg_inst_env tcenv graph <- depanal [] True printO graph forM_ graph $ \mod_ -> do forM_ (ms_textual_imps mod_) $ \(_, imp) -> do let modname = unLoc imp addTarget (Target { targetId = TargetModule modname , targetAllowObjCode = True , targetContents = Nothing }) loadSuccessfully $ LoadUpTo modname getModSummary (unLoc imp) >>= printO tcmod <- parseModule mod_ >>= typecheckModule >>= loadModule let (tcenv', md') = tm_internals_ tcmod printO $ tcg_insts tcenv' printO $ md_insts md' printO $ tcg_inst_env tcenv' ``` I just wanted to see if I could find all the relevant instances. I do find all the instances in the current `TypecheckedModle`, but none of the others because at `loadSuccessfully $ loadUpTo modname`, I get an error saying that `Test.QuickCheck a package module`. I think that means that it's not locally defined, but rather part of a package that I'm using. Unfortunately that means that I don't really understand how I can load it to find the instances. Would you please hint me at the next step? Thank you for your time. On 19-05-17 23:00:41, Tom Sydney Kerckhove wrote:
On 19-05-17 08:35:32, Edward Z. Yang wrote:
Excerpts from Tom Sydney Kerckhove's message of 2017-05-19 11:05:17 +0200:
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.
I don't really mind the time it takes to do this, but that's annoying to write.
Thank you for your help! I will look into it.
Another possibility is, if you can programatically list the types that you are interested in, you can load all of those, and then the instances for those types will be ready.
That's probably the most feasible approach. Then I'd have to find all the types in scope, and find their interfaces.
I know how to get all the TyThing's in scope, so it should be easy-ish to get started.
Thanks!
-- Tom Sydney Kerckhove
-- Tom Sydney Kerckhove

Hi Tom, Here is what I was thinking when I made the suggestion: 1. Determine the transitive set of 'Module' that you need to load 2. Load each one using 'loadInterface' So, there are a few problems with your code below: - For external packages, it's sufficient to use 'loadInterface' to load a module, since this will suck the module's interface (and instances) into the EPS. - But you are not looking at the EPS. You need to use something like tcGetInstEnvs (that is in the wrong monad; but you can still look at this code) to get instances from the EPS. - But to run 'loadInterface', you need a 'Module', not a 'ModuleName' as in your code below. You should read off the 'Module' from the dependencies and usages of the module interface: look at 'ModIface'. - By looking at only imports of your local modules, you will only get the immediate set of imports, not the transitive closure. So you need to recursively do this for each 'ModIface' you load. Edward Excerpts from Tom Sydney Kerckhove's message of 2017-05-22 05:20:37 +0200:
Hi Edward,
I'm sorry to have to bother you with this again, but I seem to be stuck with this approach. I think I don't really understand what 'load the interfaces' means.
Here's what I tried:
``` Haskell getInstancesFromTcmodule :: GhcMonad m => TypecheckedModule -> m () getInstancesFromTcmodule tmod = do let (tcenv, md) = tm_internals_ tmod let insts = tcg_insts tcenv printO insts printO $ md_insts md printO $ tcg_inst_env tcenv graph <- depanal [] True printO graph forM_ graph $ \mod_ -> do forM_ (ms_textual_imps mod_) $ \(_, imp) -> do let modname = unLoc imp addTarget (Target { targetId = TargetModule modname , targetAllowObjCode = True , targetContents = Nothing }) loadSuccessfully $ LoadUpTo modname getModSummary (unLoc imp) >>= printO tcmod <- parseModule mod_ >>= typecheckModule >>= loadModule let (tcenv', md') = tm_internals_ tcmod printO $ tcg_insts tcenv' printO $ md_insts md' printO $ tcg_inst_env tcenv' ```
I just wanted to see if I could find all the relevant instances.
I do find all the instances in the current `TypecheckedModle`, but none of the others because at `loadSuccessfully $ loadUpTo modname`, I get an error saying that `Test.QuickCheck a package module`. I think that means that it's not locally defined, but rather part of a package that I'm using. Unfortunately that means that I don't really understand how I can load it to find the instances.
Would you please hint me at the next step?
Thank you for your time.
On 19-05-17 23:00:41, Tom Sydney Kerckhove wrote:
On 19-05-17 08:35:32, Edward Z. Yang wrote:
Excerpts from Tom Sydney Kerckhove's message of 2017-05-19 11:05:17 +0200:
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.
I don't really mind the time it takes to do this, but that's annoying to write.
Thank you for your help! I will look into it.
Another possibility is, if you can programatically list the types that you are interested in, you can load all of those, and then the instances for those types will be ready.
That's probably the most feasible approach. Then I'd have to find all the types in scope, and find their interfaces.
I know how to get all the TyThing's in scope, so it should be easy-ish to get started.
Thanks!
-- Tom Sydney Kerckhove
participants (2)
-
Edward Z. Yang
-
Tom Sydney Kerckhove