Add ASSERTs to all calls of nameModule
[ghc-hetmet.git] / compiler / typecheck / TcSplice.lhs
index 27656c9..7139fa8 100644 (file)
@@ -63,13 +63,19 @@ import Maybe
 import BasicTypes
 import Panic
 import FastString
+import Data.Typeable (cast)
+import Exception
 
 import qualified Language.Haskell.TH as TH
 -- THSyntax gives access to internal functions and data types
 import qualified Language.Haskell.TH.Syntax as TH
 
 import GHC.Exts                ( unsafeCoerce#, Int#, Int(..) )
-import qualified Control.Exception  as Exception( userErrors )
+#if __GLASGOW_HASKELL__ < 609
+import qualified Exception ( userErrors )
+#else
+import System.IO.Error
+#endif
 \end{code}
 
 Note [Template Haskell levels]
@@ -157,6 +163,7 @@ The predicate we use is TcEnv.thTopLevelId.
 %************************************************************************
 
 \begin{code}
+tcBracket     :: HsBracket Name -> BoxyRhoType -> TcM (LHsExpr TcId)
 tcSpliceDecls :: LHsExpr Name -> TcM [LHsDecl RdrName]
 tcSpliceExpr  :: HsSplice Name -> BoxyRhoType -> TcM (HsExpr TcId)
 kcSpliceType  :: HsSplice Name -> TcM (HsType Name, TcKind)
@@ -166,8 +173,10 @@ runQuasiQuoteExpr :: HsQuasiQuote Name -> TcM (LHsExpr RdrName)
 runQuasiQuotePat  :: HsQuasiQuote Name -> TcM (LPat RdrName)
 
 #ifndef GHCI
-tcSpliceExpr _ e _ = pprPanic "Cant do tcSpliceExpr without GHCi" (ppr e)
-tcSpliceDecls e    = pprPanic "Cant do tcSpliceDecls without GHCi" (ppr e)
+tcBracket     x _ = pprPanic "Cant do tcBracket without GHCi"     (ppr x)
+tcSpliceExpr  e   = pprPanic "Cant do tcSpliceExpr without GHCi"  (ppr e)
+tcSpliceDecls x   = pprPanic "Cant do tcSpliceDecls without GHCi" (ppr x)
+kcSpliceType  x   = pprPanic "Cant do kcSpliceType without GHCi"  (ppr x)
 
 runQuasiQuoteExpr q = pprPanic "Cant do runQuasiQuoteExpr without GHCi" (ppr q)
 runQuasiQuotePat  q = pprPanic "Cant do runQuasiQuotePat without GHCi" (ppr q)
@@ -193,7 +202,6 @@ Desugared:  f = do { s7 <- g Int 3
                       ; return (ConE "Data.Maybe.Just" s7) }
 
 \begin{code}
-tcBracket :: HsBracket Name -> BoxyRhoType -> TcM (LHsExpr TcId)
 tcBracket brack res_ty = do
    level <- getStage
    case bracketOK level of {
@@ -591,10 +599,24 @@ runMeta convert expr
 
        ; case either_tval of
            Right v -> return v
+#if __GLASGOW_HASKELL__ < 609
            Left exn | Just s <- Exception.userErrors exn
                     , s == "IOEnv failure" 
                     -> failM   -- Error already in Tc monad
                     | otherwise -> failWithTc (mk_msg "run" exn)       -- Exception
+#else
+           Left (SomeException exn) ->
+                    case cast exn of
+                    Just (ErrorCall "IOEnv failure") ->
+                        failM -- Error already in Tc monad
+                    _ ->
+                        case cast exn of
+                        Just ioe
+                         | isUserError ioe &&
+                           (ioeGetErrorString ioe == "IOEnv failure") ->
+                            failM -- Error already in Tc monad
+                        _ -> failWithTc (mk_msg "run" exn)     -- Exception
+#endif
         }}}
   where
     mk_msg s exn = vcat [text "Exception when trying to" <+> text s <+> text "compile-time code:",
@@ -720,25 +742,29 @@ reify th_name
 
 lookupThName :: TH.Name -> TcM Name
 lookupThName th_name@(TH.Name occ flavour)
-  =  do { let rdr_name = thRdrName guessed_ns occ_str flavour
-
-       -- Repeat much of lookupOccRn, becase we want
-       -- to report errors in a TH-relevant way
-       ; rdr_env <- getLocalRdrEnv
-       ; case lookupLocalRdrEnv rdr_env rdr_name of
-           Just name -> return name
-           Nothing | not (isSrcRdrName rdr_name)       -- Exact, Orig
-                   -> lookupImportedName rdr_name
-                   | otherwise                         -- Unqual, Qual
-                   -> do { mb_name <- lookupSrcOcc_maybe rdr_name
-                         ; case mb_name of
-                             Just name -> return name
-                             Nothing   -> failWithTc (notInScope th_name) }
-       }
+  =  do { mb_ns <- mapM lookup [ thRdrName gns occ_str flavour 
+                              | gns <- guessed_nss]
+       ; case catMaybes mb_ns of
+           []    -> failWithTc (notInScope th_name)
+           (n:_) -> return n } -- Pick the first that works
+                               -- E.g. reify (mkName "A") will pick the class A
+                               --      in preference to the data constructor A
   where
-       -- guessed_ns is the name space guessed from looking at the TH name
-    guessed_ns | isLexCon (mkFastString occ_str) = OccName.dataName
-              | otherwise                       = OccName.varName
+    lookup rdr_name
+       = do {  -- Repeat much of lookupOccRn, becase we want
+               -- to report errors in a TH-relevant way
+            ; rdr_env <- getLocalRdrEnv
+            ; case lookupLocalRdrEnv rdr_env rdr_name of
+                Just name -> return (Just name)
+                Nothing | not (isSrcRdrName rdr_name)  -- Exact, Orig
+                        -> do { name <- lookupImportedName rdr_name
+                              ; return (Just name) }
+                        | otherwise                    -- Unqual, Qual
+                        -> lookupSrcOcc_maybe rdr_name }
+
+       -- guessed_ns are the name spaces guessed from looking at the TH name
+    guessed_nss | isLexCon (mkFastString occ_str) = [OccName.tcName,  OccName.dataName]
+               | otherwise                       = [OccName.varName, OccName.tvName]
     occ_str = TH.occString occ
 
 tcLookupTh :: Name -> TcM TcTyThing
@@ -914,7 +940,7 @@ reifyName thing
        -- have free variables, we may need to generate NameL's for them.
   where
     name    = getName thing
-    mod     = nameModule name
+    mod     = ASSERT( isExternalName name ) nameModule name
     pkg_str = packageIdString (modulePackageId mod)
     mod_str = moduleNameString (moduleName mod)
     occ_str = occNameString occ