
Hi, I cannot build GHC head on Linux and Mac (Mavericks) today: compiler/typecheck/TcEvidence.lhs:152:16: Not in scope: data constructor `ASSERT2' compiler/typecheck/TcEvidence.lhs:174:5: Not in scope: data constructor `ASSERT2' compiler/typecheck/TcEvidence.lhs:489:15: Not in scope: data constructor `ASSERT2' compiler/typecheck/TcEvidence.lhs:712:5: Not in scope: data constructor `ASSERT2' make[1]: *** [compiler/stage1/build/TcEvidence.o] Error 1 make[1]: *** Waiting for unfinished jobs.... make: *** [all] Error 2 --Kazu

Hi, Am Donnerstag, den 28.11.2013, 12:43 +0900 schrieb Kazu Yamamoto:
I cannot build GHC head on Linux and Mac (Mavericks) today:
compiler/typecheck/TcEvidence.lhs:152:16: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:174:5: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:489:15: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:712:5: Not in scope: data constructor `ASSERT2' make[1]: *** [compiler/stage1/build/TcEvidence.o] Error 1 make[1]: *** Waiting for unfinished jobs.... make: *** [all] Error 2
these were added by me, but these are CPP macros that should be always defined (in HsVersions.h). Also, the problem is not a general one, as you can see on https://travis-ci.org/nomeata/ghc-complete/builds) Do you have any idea what might be unusual about your CPP setup? Greetings, Joachim -- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0x4743206C Debian Developer: nomeata@debian.org

Hi guys,
This is more clang CPP funniness — I've patched this kind of thing before
(e.g.
https://ghc.haskell.org/trac/ghc/attachment/ticket/8445/fix-xcode5-cpp-error...).
Basically clang CPP can't handle the space before the open-paren, so it
needs to be removed to be recognized and processed as a macro.
Cheers
Luke
On Thu, Nov 28, 2013 at 1:23 AM, Joachim Breitner
Hi,
Am Donnerstag, den 28.11.2013, 12:43 +0900 schrieb Kazu Yamamoto:
I cannot build GHC head on Linux and Mac (Mavericks) today:
compiler/typecheck/TcEvidence.lhs:152:16: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:174:5: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:489:15: Not in scope: data constructor `ASSERT2'
compiler/typecheck/TcEvidence.lhs:712:5: Not in scope: data constructor `ASSERT2' make[1]: *** [compiler/stage1/build/TcEvidence.o] Error 1 make[1]: *** Waiting for unfinished jobs.... make: *** [all] Error 2
these were added by me, but these are CPP macros that should be always defined (in HsVersions.h). Also, the problem is not a general one, as you can see on https://travis-ci.org/nomeata/ghc-complete/builds)
Do you have any idea what might be unusual about your CPP setup?
Greetings, Joachim
-- Joachim “nomeata” Breitner mail@joachim-breitner.de • http://www.joachim-breitner.de/ Jabber: nomeata@joachim-breitner.de • GPG-Key: 0x4743206C Debian Developer: nomeata@debian.org
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

Hi,
I cannot build GHC head on Linux and Mac (Mavericks) today:
compiler/typecheck/TcEvidence.lhs:152:16: Not in scope: data constructor `ASSERT2'
The attached patches are necessary to build GHC head on Mavericks. --Kazu diff --git a/compiler/coreSyn/CoreUtils.lhs b/compiler/coreSyn/CoreUtils.lhs index 91f68a2..9e23348 100644 --- a/compiler/coreSyn/CoreUtils.lhs +++ b/compiler/coreSyn/CoreUtils.lhs @@ -190,7 +190,7 @@ applyTypeToArgs e op_ty args -- | Wrap the given expression in the coercion safely, dropping -- identity coercions and coalescing nested coercions mkCast :: CoreExpr -> Coercion -> CoreExpr -mkCast e co | ASSERT2 ( coercionRole co == Representational +mkCast e co | ASSERT2( coercionRole co == Representational , ptext (sLit "coercion") <+> ppr co <+> ptext (sLit "passed to mkCast") <+> ppr e <+> ptext (sLit "has wrong role") <+> ppr (coercionRole co) ) isReflCo co = e diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs index 9866453..5764d11 100644 --- a/compiler/deSugar/DsBinds.lhs +++ b/compiler/deSugar/DsBinds.lhs @@ -705,7 +705,7 @@ dsHsWrapper (WpTyApp ty) e = return $ App e (Type ty) dsHsWrapper (WpLet ev_binds) e = do bs <- dsTcEvBinds ev_binds return (mkCoreLets bs e) dsHsWrapper (WpCompose c1 c2) e = dsHsWrapper c1 =<< dsHsWrapper c2 e -dsHsWrapper (WpCast co) e = ASSERT (tcCoercionRole co == Representational) +dsHsWrapper (WpCast co) e = ASSERT(tcCoercionRole co == Representational) dsTcCoercion co (mkCast e) dsHsWrapper (WpEvLam ev) e = return $ Lam ev e dsHsWrapper (WpTyLam tv) e = return $ Lam tv e diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index d51fbf6..8f60bc5 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -1132,7 +1132,7 @@ canEqLeafTyVar ev tv s2 -- ev :: tv ~ s2 (Just tv1, Just tv2) | tv1 == tv2 -> do { when (isWanted ev) $ - ASSERT ( tcCoercionRole co == Nominal ) + ASSERT( tcCoercionRole co == Nominal ) setEvBind (ctev_evar ev) (mkEvCast (EvCoercion (mkTcReflCo Nominal xi1)) (mkTcSubCo co)) ; return Stop } diff --git a/compiler/typecheck/TcEvidence.lhs b/compiler/typecheck/TcEvidence.lhs index 6b1ee3e..c233d71 100644 --- a/compiler/typecheck/TcEvidence.lhs +++ b/compiler/typecheck/TcEvidence.lhs @@ -149,7 +149,7 @@ mkTcTyConAppCo role tc cos -- No need to expand type synonyms -- mkSubCo will do some normalisation. We do not do it for TcCoercions, but -- defer that to desugaring; just to reduce the code duplication a little bit mkTcSubCo :: TcCoercion -> TcCoercion -mkTcSubCo co = ASSERT2 ( tcCoercionRole co == Nominal, ppr co) +mkTcSubCo co = ASSERT2( tcCoercionRole co == Nominal, ppr co) TcSubCo co maybeTcSubCo2_maybe :: Role -- desired role @@ -171,7 +171,7 @@ maybeTcSubCo2 r1 r2 co mkTcAxInstCo :: Role -> CoAxiom br -> Int -> [TcType] -> TcCoercion mkTcAxInstCo role ax index tys - | ASSERT2 ( not (role == Nominal && ax_role == Representational) , ppr (ax, tys) ) + | ASSERT2( not (role == Nominal && ax_role == Representational) , ppr (ax, tys) ) arity == n_tys = maybeTcSubCo2 role ax_role $ TcAxiomInstCo ax_br index rtys | otherwise = ASSERT( arity < n_tys ) maybeTcSubCo2 role ax_role $ @@ -486,7 +486,7 @@ c <.> WpHole = c c1 <.> c2 = c1 `WpCompose` c2 mkWpCast :: TcCoercion -> HsWrapper -mkWpCast co = ASSERT2 (tcCoercionRole co == Representational, ppr co) +mkWpCast co = ASSERT2(tcCoercionRole co == Representational, ppr co) WpCast co mkWpTyApps :: [Type] -> HsWrapper @@ -709,7 +709,7 @@ The story for kind `Symbol` is analogous: \begin{code} mkEvCast :: EvTerm -> TcCoercion -> EvTerm mkEvCast ev lco - | ASSERT2 (tcCoercionRole lco == Representational, (vcat [ptext (sLit "Coercion of wrong role passed to mkEvCast:"), ppr ev, ppr lco])) + | ASSERT2(tcCoercionRole lco == Representational, (vcat [ptext (sLit "Coercion of wrong role passed to mkEvCast:"), ppr ev, ppr lco])) isTcReflCo lco = ev | otherwise = EvCast ev lco diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 90fe446..06856d7 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1708,7 +1708,7 @@ rewriteCtFlavor (CtGiven { ctev_evtm = old_tm , ctev_loc = loc }) new_pred co rewriteCtFlavor (CtWanted { ctev_evar = evar, ctev_loc = loc }) new_pred co = do { new_evar <- newWantedEvVar loc new_pred - ; MASSERT ( tcCoercionRole co == Nominal ) + ; MASSERT( tcCoercionRole co == Nominal ) ; setEvBind evar (mkEvCast (getEvTerm new_evar) (mkTcSubCo co)) ; case new_evar of Fresh ctev -> return (Just ctev)

On 2013-11-29 at 03:30:56 +0100, Kazu Yamamoto (山本和彦) wrote:
I cannot build GHC head on Linux and Mac (Mavericks) today:
compiler/typecheck/TcEvidence.lhs:152:16: Not in scope: data constructor `ASSERT2'
The attached patches are necessary to build GHC head on Mavericks.
thanks, applied per http://git.haskell.org/ghc.git/commitdiff/96416412cc8100bd1c1625e10c09df17c8... btw, curiously, Clang seems happy to compile "ASSERT (...)" occurences in C files such as rts/STM.c which have several of those... Cheers, hvr
participants (4)
-
Herbert Valerio Riedel
-
Joachim Breitner
-
Kazu Yamamoto
-
Luke Iannini