Re: Type class instances in scope

2017-05-21 Thread 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


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Type class instances in scope

2017-05-19 Thread Tom Sydney Kerckhove
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


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Type class instances in scope

2017-05-19 Thread Tom Sydney Kerckhove
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


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Type class instances in scope

2017-05-18 Thread Tom Sydney Kerckhove
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


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Translation of GHC typechecker output to haskell-src-exts's 'Type'

2017-04-02 Thread Tom Sydney Kerckhove
On 02-04-17 14:40:05, Tom Sydney Kerckhove wrote:
> Is there a way to access the types before this translation happens?
> It's okay if I have to assume that type-checking succeeds...

I have found a way to do what I want, even after this translation.
It relies on the fact that type class constraints always occur on the
left side of the result of splitFunTy.

Thank you for your help!

-- 
Tom Sydney Kerckhove


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Translation of GHC typechecker output to haskell-src-exts's 'Type'

2017-04-02 Thread Tom Sydney Kerckhove
On 01-04-17 19:47:15, Ben Gamari wrote:
> Tom Sydney Kerckhove <syd.kerckh...@gmail.com> writes:
> 
> > Dear GHC Devs,
> 
> Hi Tom,

Hi Mr Gamari

> I'm afraid the notes in TyCoRep are really all we have. Note that you
> should also familiarize yourself with the TyCon type (for reasons you'll
> see below).
> 
> > In particular, I am having trouble finding type class constraints in the
> > 'Type'.
> >
> During typechecking class constraints are turned into dictionary
> arguments.

Oh, that's already done by then? It makes a lot more sense now why I get
this:

ghcs translation: Ord a -> [a] -> [a]
haskell-src-exts: Ord a => [a] -> [a]

I'm guessing that this 'Ord a' that I get, is the type of the dictionary
for 'Ord' in the case of 'a'.

Is there a way to access the types before this translation happens?
It's okay if I have to assume that type-checking succeeds...

> If I'm not mistaken you can pick these out by looking for
> AlgTyCons (a constructor of the TyCon type, see TyCon.hs) with a
> algTcParent matching (ClassTyCon cls _). cls will be the name of the
> associated class.
> 
> I hope this helps.

This does help, thank you!
 
> Cheers,

Thank you for your time.

> - Ben
> 



-- 
Tom Sydney Kerckhove


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Translation of GHC typechecker output to haskell-src-exts's 'Type'

2017-04-01 Thread Tom Sydney Kerckhove
Dear GHC Devs,

Because of the unwieldy nature of the data that the GHC type checker
outputs, I am trying to convert a GHC 'Type' [1] to a haskell-src-ext
'Type' [2].

The translation does not need to be perfect for now, but I would at
least like to be able to translate function types and types that involve
type-class constraints. (See my initial attempt in attachment)

Has this ever been done before?
Could you point me to some documentation on GHC's 'Type' [1] that could
help me with writing this function? (The comments in code aren't nearly
enough for me.)

In particular, I am having trouble finding type class constraints in the
'Type'.

Thank you for your time.

[1]: 
https://downloads.haskell.org/~ghc/8.0.2/docs/html/libraries/ghc-8.0.2/src/TyCoRep.html#Type
[2]: 
https://hackage.haskell.org/package/haskell-src-exts-1.18.2/docs/Language-Haskell-Exts-Syntax.html#t:Type

-- 
Tom Sydney Kerckhove
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}

module EasySpec.Discover.Gather where

import Import

import GHC
import GHC.Paths (libdir)
import OccName
import RdrName
import TcRnTypes
import TyCoRep
import TyCon
import Type
import Var

import Language.Haskell.Exts.Syntax as H

data EasyId = EasyId
{ easyName :: EasyName
, easyType :: EasyType
} deriving (Show, Eq)

type EasyName = H.Name ()

type EasyType = H.Type ()

toEasyId :: GHC.Id -> EasyId
toEasyId i =
EasyId
{ easyName = toEasyName $ Var.varName i
, easyType = toEasyType $ Var.varType i
}

toEasyName :: Monoid a => GHC.Name -> H.Name a
toEasyName n = Ident mempty $ showName n

toEasyType :: Monoid a => GHC.Type -> H.Type a
toEasyType ty =
case splitFunTy_maybe ty of
Nothing -> go ty
Just (tf, tt) -> H.TyFun mempty (toEasyType tf) (toEasyType tt)
  where
go t =
case t of
TyVarTy i -> TyVar mempty $ toEasyName $ Var.varName i
AppTy t1 t2 -> TyApp mempty (toEasyType t1) (toEasyType t2)
TyConApp tc kots ->
let dres =
foldl
(TyApp mempty)
(TyCon mempty $
 UnQual mempty $ toEasyName $ tyConName tc)
(map toEasyType kots)
in case tyConClass_maybe tc of
   Just _ -> dres
   Nothing ->
   case (showName (tyConName tc), kots) of
   ("[]", [lt]) -> TyList mempty $ toEasyType lt
   _ -> dres
ForAllTy _ t' -> toEasyType t'
_ -> error "Not implemented yet"


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why are there no Show instances for internal types

2017-03-18 Thread Tom Sydney Kerckhove
On 18-03-17 16:13:52, Ben Gamari wrote:
> 
> 
> On March 18, 2017 9:03:48 AM EDT, Tom Sydney Kerckhove 
> <syd.kerckh...@gmail.com> wrote:
> 
> Snip.
> >
> >My questions for you:
> >
> >- Is there a reason that there are no derived 'Show' instances for most
> >  types?
> 
> As Richard mentioned, we don't derive Show due to code size and compilation 
> time concerns.

Okay.

> Show in particular is rather expensive to derive and seeing as we already 
> have Outputable I don't it would make sense to derive it by default.

Show and Outputable have very different goals though.

> I would really like to avoid introducing more CPP into the code base for this 
> particular problem.

Fair enough.

> One alternative which will work in many cases is to simply derive Show 
> yourself using StandaloneDeriving. Does this help?

That doesn't work if some type doesn't have the constructors exposed.
I tried this already, and it would be a good solution if all
constructors were exposed, ...

> Cheers,
> 
> - Ben 
> 
> -- 
> Sent from my Android device with K-9 Mail. Please excuse my brevity.

-- 
Tom Sydney Kerckhove


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Why are there no Show instances for internal types

2017-03-18 Thread Tom Sydney Kerckhove
On 19-03-17 02:08:56, Rahul Muttineni wrote:
> Syd, can you tell us what kind of things you were trying to print out?

Maybe I wasn't very clear.
I'm trying to visualise the internal structure of some of the
typechecker's output.
I specifically do NOT need to see the output of Outputable's functions.
They show the human-readibly version and not the internal structure.

Does that answer your question?
> Hope that helps,
> Rahul
> 
> On Sun, Mar 19, 2017 at 1:14 AM, Edward Z. Yang <ezy...@mit.edu> wrote:
> 
> > We can't add Show instances for these types because many types
> > below them, e.g., Type, are cyclic, and would result in infinite
> > output.
> >
> > Perhaps we can add a new type class which a) faithfully represents
> > the Haskell syntax, but b) can deal with cyclic data.  I think that's
> > something people would like (extra compilation time not withstanding).
> > But it sounds annoying to do since the deriving mechanism is not going
> > to help you.
> >
> > Edward
> >
> > Excerpts from Tom Sydney Kerckhove's message of 2017-03-18 14:03:48 +0100:
> > > Dear GHC Devs,
> > >
> > > I am trying to use GHC as a library but I'm having a lot of trouble with
> > > understanding what everything means.
> > > Up to now, I have been able to figure out what to do by reading the
> > > sources, but it ocured to me that much of my struggles could have been
> > > mitigated if the relevant types had Show instances.
> > >
> > > I am specifically talking about the types concerning type checking.
> > > TypecheckedModule and everything below that.
> > > I am aware that most of the types have an Outputable instance, but
> > > there are two problems with that:
> > >
> > > - 'Outputting' a value requires DynFlags. (yes, I know about pprTrace)
> > > - These instances are not intended to show the internal structure of a
> > >   value, but rather a 'human readable' representation of a value.
> > >
> > > My questions for you:
> > >
> > > - Is there a reason that there are no derived 'Show' instances for most
> > >   types?
> > > - Would you accept a diff that adds these?
> > >
> > > Thank you for your time.
> > >
> > ___
> > ghc-devs mailing list
> > ghc-devs@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> >
> 
> 
> 
> -- 
> Rahul Muttineni

-- 
Tom Sydney Kerckhove


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Why are there no Show instances for internal types

2017-03-18 Thread Tom Sydney Kerckhove
Dear GHC Devs,

I am trying to use GHC as a library but I'm having a lot of trouble with
understanding what everything means.
Up to now, I have been able to figure out what to do by reading the
sources, but it ocured to me that much of my struggles could have been
mitigated if the relevant types had Show instances.

I am specifically talking about the types concerning type checking.
TypecheckedModule and everything below that.
I am aware that most of the types have an Outputable instance, but
there are two problems with that:

- 'Outputting' a value requires DynFlags. (yes, I know about pprTrace)
- These instances are not intended to show the internal structure of a
  value, but rather a 'human readable' representation of a value.

My questions for you:

- Is there a reason that there are no derived 'Show' instances for most
  types?
- Would you accept a diff that adds these?

Thank you for your time.

-- 
Tom Sydney Kerckhove


signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs