parsing types
Ranjit Jhala
jhala at cs.ucsd.edu
Wed Apr 27 01:42:03 CEST 2011
Dear Simon, Daniel and Thomas,
thanks for your help with this! I managed to get what I
want by writing something like so:
tcExpr :: FilePath -> String -> IO Type
tcExpr f s =
defaultErrorHandler defaultDynFlags $
runGhc (Just libdir) $ do
df <- getSessionDynFlags
setSessionDynFlags df
cm <- compileToCoreModule f
setContext [(cm_module cm)] []
env <- getSession
r <- hscTcExpr env s
return r
In short, I take the filepath, compile it to a module, then
add that to the context and then extract the env and typecheck.
If there's a shorter route, I'm all ears, but this seems to
get the job done...
Thanks again!,
Ranjit.
On Apr 26, 2011, at 3:13 AM, Simon Peyton-Jones wrote:
> Ranjit
>
> [NB: all of this is based on a quick look at the source code; I'm not that familiar with the GHC API, so others may correct me.]
>
> A good entry point to the GHC API is InteractiveEval.hs. You'll see that all its functions are parameterised over a simple state monad (GhcMonad m), which is any monad supporting
> getSession :: m HscEnv
> setSession :: HscEnv -> m ()
>
> The HscEnv encapsulates all the persistent state of the session, including the "ambient modules"; in a GHCi session these are the ones you have "imported" to the command line prompt.
>
> You can augment these ambient modules with InteractiveEval.setContext. (Its API is a bit confusing and it's on my list of things to change.) So just call that to augment the context.
>
> Then you can call hscTcExpr. [Maybe there should be a GhcMonad version of this function, with the type sig you give. The one in HscMain isn't.]
>
> Does that help?
>
> Simon
>
> | -----Original Message-----
> | From: glasgow-haskell-users-bounces at haskell.org [mailto:glasgow-haskell-
> | users-bounces at haskell.org] On Behalf Of Ranjit Jhala
> | Sent: 24 April 2011 02:27
> | To: Daniel Peebles
> | Cc: ghc-users
> | Subject: Re: parsing types
> |
> | Hi Daniel --
> |
> | that was a good lead, with a little digging around, I found
> |
> | hscTcExpr :: GhcMonad m => HscEnv -> String -> m Type
> |
> | which almost gets the job done, if only I could call it with
> | the appropriate HscEnv. The one I get using
> |
> | getSession :: GhcMonad m => m HscEnv
> |
> | appears rather impoverished, as it fails to find the usual
> | prelude names like
> |
> | Not in scope: `undefined'
> | Not in scope: `error'
> |
> | (though it does succeed on the expression "5" yielding the type)
> |
> | "forall t_a4eW. (GHC.Num.Num t_a4eW) => t_a4eW"
> |
> | Does anyone have a clue as to how to get a hold on an appropriate
> | environment? (I would have thought that the HscEnv obtained _after_
> | compiling some file "f" would populated with at least the names
> | needed to compile "f") that is, if I do:
> |
> | cm0 <- compileToCoreSimplified f
> | env <- getSession
> |
> | then the resulting "env" would suffice, but unfortunately thats not
> | the case...
> |
> | Thanks!,
> |
> | Ranjit.
> |
> |
> |
> |
> |
> |
> |
> |
> | On Apr 23, 2011, at 11:54 AM, Daniel Peebles wrote:
> |
> | > I don't have an answer for you, but you might want to look at what :k does
> | in ghci, since that needs to parse a type.
> | >
> | > On Sat, Apr 23, 2011 at 2:06 PM, Ranjit Jhala <jhala at cs.ucsd.edu> wrote:
> | > Hi all,
> | >
> | > can someone give me a hint as to the best way to parse a type from a
> | string.
> | > Ideally, I'd like a function
> | >
> | > stringType :: String -> Maybe Type
> | >
> | > or possibly,
> | >
> | > stringType :: (GhcMonad m) => String -> m (Maybe Type)
> | >
> | > such that,
> | >
> | > stringType s == Just t
> | >
> | > if in the current GHC context the string s is the name of the type t. For
> | > example, I'd like:
> | >
> | > stringType "Int"
> | >
> | > to return a value equal to intTy (from TysWiredIn). My investigations have
> | > led me to
> | >
> | > parseType :: P (LHsType RdrName)
> | >
> | > and I suspect that with some work (mainly creating an appropriate PState,
> | > and mapping the name back, I can extract what I want, but I was wondering
> | > if there is some simpler route that I've overlooked.
> | >
> | > Thanks!
> | >
> | > Ranjit.
> | >
> | > _______________________________________________
> | > Glasgow-haskell-users mailing list
> | > Glasgow-haskell-users at haskell.org
> | > http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
> | >
> |
> |
> | _______________________________________________
> | 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