Re-entrant TcRnIf

p.k.f.holzenspies at utwente.nl p.k.f.holzenspies at utwente.nl
Thu Jun 13 14:13:03 CEST 2013


Dear Thomas,

Thanks for your reply. If all else fails, this could be the way to go, but if at all possible, I would like to get rid of the file-idea ;)

Maybe it helps if I make things slightly more concrete. Like I said, I'm building an interactive user interface. In this interface, users manipulate terms. There is a bootstrapping problem here; how do they get "terms" to begin with? The answer (quite unsatisfactory at the moment): They type them in. For the sake of the argument, lets say users give these terms names of type UIName. Part of the UI's state is a "Map UIName (LHsExpr Id)" which can be manipulated with, e.g. this function:


addExpr :: UIName -> String -> UI (Maybe ErrorMessage)


which parses its String argument, akin to how exprType works. The problem, now, is that if I simply restart the TcRnMonad, I'm worried uniques in one expression may not be unique in the entire map of expressions. Also, I will be looking for ways to combine these expression, e.g.


mkApplication :: UIName -> UIName -> UIName -> UI ()
mkApplication new func arg = do
  m <- gets exprMap
  f <- maybe (fail ...) return (lookup func m)
  a <- maybe (fail ...) return (lookup arg m)
  let n = L (combineLocs f a) (HsApp f a)
  checkType n
  modify (\s -> s { exprMap = insert new n m })


Again, it seems that restarting the TcRnMonad for everything breaks stuff. Then again, it probably doesn't help that the AST (f and a in the function above) contain IORefs with type-state. I was thinking that if that is problematic, I would always "lower" the type of 'n' from "LHsExpr Id" to "LHsExpr Name" such that all type information is reconstructed, but it is quite vital that the renaming is preserved (i.e. I can't go all the way down to "LHsExpr RdrName").

Thoughts?

Regards,
Philip


  

-----Original Message-----
From: Thomas Schilling [mailto:nominolo at googlemail.com] 
Sent: dinsdag 11 juni 2013 13:46
To: Holzenspies, P.K.F. (EWI)
Cc: glasgow-haskell-users at haskell.org
Subject: Re: Re-entrant TcRnIf

There are quite a lot of dependencies between different parts of the AST.

The renamer takes the whole parser output and then discovers its dependencies.  After that you can split things into smaller units based on this dependency graph.

The renamer and type checker do not necessarily need to be interleaved.  Every Haskell file is de-facto split apart after each top-level TH splice.

If I understand you correctly you want to build some IDE functionality that only recompiles the parts that changed.  You can do that currently (crudely) by splitting the file into three parts based on the dependency graph that the renamer discovered:

 1. Everything upstream of the focused definition, i.e., everything that does not depend on the focused definition.
 2. The focused definition and everything that is in its recursive group.
 3. Everything downstream of the focused, i.e., everything that directly or indirectly depends on the focused definition.

You can put each part into a separate file and only recompile part 2.
Of course you also need to detect when new (renamer) dependencies are formed as that will change the split between parts 1, 2, and 3.

Let me know if you need more details on this approach.

 / Thomas

On 11 June 2013 11:55,  <p.k.f.holzenspies at utwente.nl> wrote:
> Dear GHC-ers,
>
> The current API *seems* to assume that all different stages of the compiler pipeline are always passed successively (with the exception of the interleaving of the renamer and the type checker for the sake of Template Haskell), in other words, it is assumed all parsing has been done once we start renaming and that when we desugar the AST, we can through out all type checker state. I'm working on an interactive environment (different in many ways from ghci), in which I would like to incrementally parse a statement, rename it and type check it, after which I may chose to wash, rinse and repeat.
>
> This is somewhat problematic in the renamer (at least; this is how far I have come), at the very least with regards to the unique source and the provenance of things. What I'm hoping to do is to generalize the monads in the GHC API to some class, along these lines:
>
> class Generalizes m n where
>   glift :: n a -> m a
> class (GhcMonad m, Generalizes m TcRnIf, Generalizes m CoreM, ...) => 
> GHCAPI m
>
> What such a monad needs is to be able to evaluate some function in (for example) the renamer monad, extract the part of the renamer state that needs to persist and store that for whenever another renamer function is evaluated. One such thing would be the supply of unique names.
>
> I tried simply carrying over everything in the Env, except the env_top (HscEnv), but this broke things. Upon inspection of the TcGblEnv and TcLclEnv, this seems logical, considering they are dependent on the HscEnv (at least in terms of tcg_type_env_var, but there may be other dependencies I've not spotted). The thing that seems to bite me is the assumption that the top-level environment is assumed to be fixed [1]. In my scenario, this assumption does not hold.
>
> Concretely:
>
> 1) Do ways exist to carry over the part of the TcRnMonad state that is required to restart the renamer / type checker / etc later on?
> 2) If not, what parts of the Env, TcGblEnv and TcLclEnv should I copy over to the new state, assuming the HscEnv changed between consecutive runs?
> 3) Is there a particular reason why the front-end (of the front-end) is defined in an overloaded monad (GhcMonad) and the later bits all take concrete monads (TcRnIf etc.)?
>
> Regards,
> Philip
>
>
> [1] 
> http://hackage.haskell.org/trac/ghc/wiki/Commentary/Compiler/TcRnMonad
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



More information about the Glasgow-haskell-users mailing list