GHC API: monad and error handling

Henning Thielemann lemming at henning-thielemann.de
Mon Jul 14 10:58:07 EDT 2008


On Mon, 14 Jul 2008, Thomas Schilling wrote:

> Hello librarians,
>
> as some may know, I am currently working on improvements to the GHC API. 
> Many of the exported functions of the GHC module have a type of the form
>
> Session -> ... -> IO (Maybe X)
>
> where 'Session' is mutable and 'X' is the actual result type of the function. 
> In order to enforce (the implicitly assumed) single-threaded use of a session 
> and to provide richer error information I am restructuring all exported 
> functions of the GHC API to return a computation in the 'Ghc' monad.  This 
> currently looks like this(*)
>
> newtype Ghc a = Ghc { unGhc :: Session -> IO (Either GhcError a }
>
> newtype Session = Session (IORef HscEnv)

Good idea.

> Functions that modify a session are now in this monad but behave mostly the 
> same.  A more difficult decision is how to deal with errors.  The GhcError 
> type currently looks like this:
>
> -- | An error annotated with the phase it happened in.
> data GhcError
>     = GhcError HscPhase Messages
>       -- ^ A "normal" compilation error.
>     | ApiError HscPhase String
>       -- ^ An error that violated some pre-condition/invariant of the API.
>     | GhcIOException Exception
>       -- some IO exception
>       -- XXX: would (forall e. Typeable e => e) be better?


Another instance of mixing errors (ApiError) and exceptions (GhcError, 
GhcIOException)? How should I handle errors that I made myself by calling 
the GHC API the wrong way? Of course, I must correct those calls to GHC 
instead. The clean design would be to drop the ApiError constructor and 
indicate wrong uses of the GHC library with simple 'error'.


> Note that we have to wrap IO exceptions and propagate them separately in the 
> Ghc monad.(**)

That's a good thing. All (IO) exceptions should be handled this way.
  (See the extensible exception thread on this list.)


>  For the latter It is, however, not always clear what is a compile error 
> and what is not.  Consider, for example, the following function:
>
> -- | Takes a 'ModuleName' and possibly a 'PackageId', and consults the
> -- filesystem and package database to find the corresponding 'Module',-- 
> using the algorithm that is used for an @import@ declaration.
> findModule :: ModuleName -> Maybe PackageId -> Ghc Module
> findModule mod_name maybe_pkg = withSession $ \hsc_env ->
> let
>       dflags = hsc_dflags hsc_env
>       hpt    = hsc_HPT hsc_env
>       this_pkg = thisPackage dflags
> in
> case lookupUFM hpt mod_name of
>   Just mod_info -> return (mi_module (hm_iface mod_info))
>   _not_a_home_module -> do
>         -- XXX: should we really throw IO exceptions here?
> 	  res <- io $ findImportedModule hsc_env mod_name maybe_pkg
> 	  case res of
> 	    Found _ m | modulePackageId m /= this_pkg -> return m
> 		      | otherwise -> throwDyn (CmdLineError (showSDoc $
> 					text "module" <+> pprModule m <+>
> 					text "is not loaded"))
> 	    err -> let msg = cannotFindModule dflags mod_name err in
> 		   throwDyn (CmdLineError (showSDoc msg))

> This either returns a Module or throw an exception by looking it up in the 
> home package table.  Otherwise, it throws a CmdLineError exception, which is 
> intended for reporting failure inside GHCi.  I guess the proper way for this 
> function would be to throw an 'ApiError', i.e., we expect the looked-up 
> module to be existing in the home package table and to be loaded.

Can you please explain, what you are doing here?

If a module cannot be found on disk, this is certainly an (IO) exception, 
since you cannot enforce the existence of a file. If a module cannot be 
found in an internal table, although it should be there, this is an 
'error'. However one should try to minimize such situations, may by 
organizing the lookup in another way.


> My questions thus are:
>
> - Does this sound like a reasonable strategy?
> - Is such a monad a good or a bad idea?

Good idea!

> - Does anyone have an idea of a classification of errors, or 
> guidelines/principles for one?

Yes! Read my articles on the Wiki
   http://www.haskell.org/haskellwiki/Exception
   http://www.haskell.org/haskellwiki/Error
  and my posts to the "extensible exception" thread:
   http://www.haskell.org/pipermail/libraries/2008-July/010120.html
  and share my opinion! :-)


> - Any other comments?

Thank you for the practical example of exceptions!


> (*) an alternative implementation that would probably be a bit more efficient 
> in case of errors could use continuation-passing style:
>
> newtype Ghc a
>    = Ghc { unGhc :: forall ans.
>                     Session
>                  -> (GhcError -> IO ans)  -- failure continuation
>                  -> (a -> IO ans)         -- success continuation
>                  -> IO ans

Why do you think it would be more efficient?



More information about the Libraries mailing list