Safe Haskell | None |
---|---|
Language | Haskell98 |
- class Symbolic a => GhcLookup a where
- lookupGhcThing :: (MonadIO m, MonadError (TError t) m, MonadState BareEnv m, GhcLookup a) => [Char] -> (TyThing -> Maybe b) -> a -> m b
- lookupGhcVar :: GhcLookup a => a -> BareM Var
- lookupGhcTyCon :: GhcLookup a => a -> BareM TyCon
- lookupGhcDataCon :: (MonadIO m, MonadError (TError t) m, MonadState BareEnv m) => Located Symbol -> m DataCon
Documentation
lookupGhcThing :: (MonadIO m, MonadError (TError t) m, MonadState BareEnv m, GhcLookup a) => [Char] -> (TyThing -> Maybe b) -> a -> m b Source
lookupGhcVar :: GhcLookup a => a -> BareM Var Source
It's possible that we have already resolved the Name
we are looking for,
but have had to turn it back into a String
, e.g. to be used in an Expr
,
as in {v:Ordering | v = EQ}
. In this case, the fully-qualified Name
(GHC.Types.EQ
) will likely not be in scope, so we store our own mapping of
fully-qualified Name
s to Var
s and prefer pulling Var
s from it.
lookupGhcTyCon :: GhcLookup a => a -> BareM TyCon Source
lookupGhcDataCon :: (MonadIO m, MonadError (TError t) m, MonadState BareEnv m) => Located Symbol -> m DataCon Source