On Wed, Aug 23, 2006 at 11:55:06PM -0000, GHC wrote:
> 
>  [EMAIL PROTECTED] should_run]$ cat dsrun014.hs
>  module Main where
> 
>  import Control.Exception ( assert )
> 
>  main = assert "Hello" True $ print "World"
> 
>  [EMAIL PROTECTED] should_run]$ $GHC66 dsrun014.hs
> 
>  dsrun014.hs:5:7:
>      Couldn't match expected type `GHC.Prim.Addr#'
>             against inferred type `[Char]'
>      In the first argument of `GHC.Err.assertError', namely
>          `"dsrun014.hs:5:7-12"'
>      In the call (GHC.Err.assertError "dsrun014.hs:5:7-12" "Hello" True)
>      In the first argument of `($)', namely
>          `GHC.Err.assertError "dsrun014.hs:5:7-12" "Hello" True'

I think

hunk ./compiler/rename/RnExpr.lhs 974
+
+srcSpanPrimLit :: SrcSpan -> HsExpr Name
+srcSpanPrimLit span = HsLit (HsStringPrim (mkFastString (showSDoc (ppr span))))
hunk ./compiler/rename/RnExpr.lhs 992
-                    (L sloc (srcSpanLit sloc))
+                    (L sloc (srcSpanPrimLit sloc))

should fix this, but I haven't been able to test it yet.


Thanks
Ian

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to