Type class instances in scope

Tom Sydney Kerckhove syd.kerckhove at gmail.com
Thu May 18 12:39:38 UTC 2017


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
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 833 bytes
Desc: not available
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20170518/9dbfe561/attachment.sig>


More information about the ghc-devs mailing list