T8761 failing for ext-interp
Erik de Castro Lopo
mle+hs at mega-nerd.com
Sun Jun 26 06:29:19 UTC 2016
Erik de Castro Lopo wrote:
> > Erik, could it be the same symptom as Edward is seeing here?
> > https://ghc.haskell.org/trac/ghc/ticket/12230
>
> Yes it is.
Just to provide a little more info, the tests I'm seeing fail (perf-llvm)
are:
TEST="TH_repUnboxedTuples T10828 T10596 TH_reifyMkName T9064 T8628
T11797 T10796b TH_reifyDecl2 TH_repPrim2 T10891 ClosedFam1TH
ghci006 TH_reifyInstances TH_repPrim T9692 prog001 TH_Roles3
T10796a T8639_api TH_reifyDecl1 T5362 T2222 T5037 T8884 TH_TyInstWhere2
T11341 TH_foreignCallingConventions T3920 T7477 T9738 process009 T8953
T4135 T2700 TH_Roles4 T9262 TH_RichKinds2 TH_repGuard T8761 ghci004 T4188
TH_RichKinds"
Some examples of the failue are:
T10596.hs:1:1: error:
Exception when trying to run compile-time code:
ghc-stage2: ghc-iserv terminated (-11)
Code: do { putQ (100 :: Int);
x <- (getQ :: Q (Maybe Int));
($) runIO print x;
.... }
T9064.hs:1:1: error:
Exception when trying to run compile-time code:
ghc-stage2: ghc-iserv terminated (-11)
Code: do { info <- reify ''C;
($)
runIO
do { ($) putStrLn pprint info;
.... };
return [] }
TH_RichKinds2.hs:1:1: error:
Exception when trying to run compile-time code:
ghc-stage2: ghc-iserv terminated (-11)
Code: let
fixKs :: String -> String
fixKs s = ...
in
do { decls <- [d| data SMaybe :: (k -> *) -> (Maybe k) -> *
where
SNothing :: SMaybe s Nothing
SJust :: s a -> SMaybe s (Just a)
type instance Map f (h : t) = (f h) : (Map f t)
type instance Map f '[] = '[] |];
reportWarning (fixKs (pprint decls));
.... }
So yes, very similar to #12230.
Erik
--
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/
More information about the ghc-devs
mailing list