[GHC] #12760: Assertion failed with BuildFlavour = devel2 (yet another)

GHC ghc-devs at haskell.org
Mon Oct 24 05:28:40 UTC 2016


#12760: Assertion failed with BuildFlavour = devel2 (yet another)
-------------------------------------+-------------------------------------
           Reporter:  pacak          |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.0.1
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  Compile-time
  Unknown/Multiple                   |  crash or panic
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Still trying to debug compilation failures in our codebase, still can't
 build prerequisites yet.


 ghc needs to be compiled with BuildVlavour = devel2 and compilation with
 -O2 is required:


 {{{#!hs
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}

 module A where

 import Data.List(minimumBy)
 import Data.Ord (comparing)

 data A a = A Int

 newtype B = B Double deriving
 (Eq,Ord,Num,Real,Fractional,RealFrac,Floating,RealFloat)

 class C a where
     _c :: [a] -> D a

 instance C B where
     _c = f2 u


 data D x = D [(x,Double)] [ x ]


 u = undefined

 f1 :: RealFloat a => A a -> a -> [a] -> D a
 f1 (A a1) m ps0 = D (zip tickvs []) labelvs
   where

     range _ | m == m = if m==0 then (-1,1) else (m, m)
     labelvs   = map fromRational $ f3 (fromIntegral a1) (range ps0)
     tickvs    = map fromRational $ f3 (fromIntegral a1) (head labelvs,
 head labelvs)

 f2 :: RealFloat a => A a -> [a] -> D a
 f2 lap ps = f1 u (minimum ps) ps

 f3 :: RealFloat a => a -> (a,a) -> [Rational]
 f3 k rs@(m,_ ) = map ((s*) . fromIntegral) [floor m .. ]
   where
     s = minimumBy (comparing ((+ k) . realToFrac)) [0]

 }}}

 {{{
 % ghc -O2 A.hs
 [1 of 1] Compiling A                ( A.hs, A.o )
 ghc: panic! (the 'impossible' happened)
   (GHC version 8.0.1 for x86_64-unknown-linux):
         ASSERT failed!
   CallStack (from HasCallStack):
   assertPprPanic, called at compiler/types/TyCoRep.hs:1978:56 in
 ghc:TyCoRep
   checkValidSubst, called at compiler/types/TyCoRep.hs:2014:17 in
 ghc:TyCoRep
   substTy, called at compiler/types/Coercion.hs:1454:33 in ghc:Coercion
   in_scope InScope [00 :-> wild_00, X1o :-> wild_X1o,
                     X1p :-> wild_X1p, a4z5 :-> $c==_a4z5, a4zs :->
 $c/=_a4zs,
                     a4zV :-> $ccompare_a4zV, a4Ai :-> $c<_a4Ai, a4AF :->
 $c<=_a4AF,
                     a4B2 :-> $c>_a4B2, a4Bp :-> $c>=_a4Bp, a4BM :->
 $cmax_a4BM,
                     a4C9 :-> $cmin_a4C9, a4Cy :-> $c+_a4Cy, a4CV :->
 $c-_a4CV,
                     a4Di :-> $c*_a4Di, a4DF :-> $cnegate_a4DF, a4DY :->
 $cabs_a4DY,
                     a4Eh :-> $csignum_a4Eh, a4EA :-> $cfromInteger_a4EA,
                     a4F3 :-> $ctoRational_a4F3, a4Fs :-> $c/_a4Fs,
                     a4FP :-> $crecip_a4FP, a4G8 :-> $cfromRational_a4G8,
                     a4GB :-> $cproperFraction_a4GB, a4Hg :->
 $ctruncate_a4Hg,
                     a4HV :-> $cround_a4HV, a4IA :-> $cceiling_a4IA,
                     a4Jf :-> $cfloor_a4Jf, a4K0 :-> $cpi_a4K0, a4Kf :->
 $cexp_a4Kf,
                     a4Ky :-> $clog_a4Ky, a4KR :-> $csqrt_a4KR, a4La :->
 $c**_a4La,
                     a4Lx :-> $clogBase_a4Lx, a4LU :-> $csin_a4LU, a4Md :->
 $ccos_a4Md,
                     a4Mw :-> $ctan_a4Mw, a4MP :-> $casin_a4MP, a4N8 :->
 $cacos_a4N8,
                     a4Nr :-> $catan_a4Nr, a4NK :-> $csinh_a4NK, a4O3 :->
 $ccosh_a4O3,
                     a4Om :-> $ctanh_a4Om, a4OF :-> $casinh_a4OF, a4OY :->
 $cacosh_a4OY,
                     a4Ph :-> $catanh_a4Ph, a4PA :-> $clog1p_a4PA,
                     a4PT :-> $cexpm1_a4PT, a4Qc :-> $clog1pexp_a4Qc,
                     a4Qv :-> $clog1mexp_a4Qv, a4QY :-> $cfloatRadix_a4QY,
                     a4Rh :-> $cfloatDigits_a4Rh, a4RA :->
 $cfloatRange_a4RA,
                     a4RT :-> $cdecodeFloat_a4RT, a4Sc :->
 $cencodeFloat_a4Sc,
                     a4Sz :-> $cexponent_a4Sz, a4SS :-> $csignificand_a4SS,
                     a4Tb :-> $cscaleFloat_a4Tb, a4Ty :-> $cisNaN_a4Ty,
                     a4TR :-> $cisInfinite_a4TR, a4Ua :->
 $cisDenormalized_a4Ua,
                     a4Ut :-> $cisNegativeZero_a4Ut, a4UM :->
 $cisIEEE_a4UM,
                     a4V5 :-> $catan2_a4V5, a4Vu :-> $c_c_a4Vu, a5eH :->
 wild_a5eH,
                     a5eJ :-> x_a5eJ, ruN :-> u, ruO :-> f1, ruP :-> f2,
 ruQ :-> f3,
                     r24E :-> $tc'A, r25L :-> $tcA, r25N :-> $tc'B, r25Z
 :-> $tcB,
                     r2dl :-> $tc'D, r2ds :-> $tcD, r2dF :-> $tcC, r2dG :->
 $tc'C:C,
                     r2dL :-> $fCB, r2dZ :-> $fEqB, r2ec :-> $fOrdB, r2nC
 :-> $fNumB,
                     r2nK :-> $fRealB, r2nT :-> $fFractionalB, r2oa :->
 $fRealFracB,
                     r2oC :-> $fFloatingB, r2oX :-> $fRealFloatB, r4yJ :->
 $trModule,
                     s5iM :-> $trModule_s5iM, s5iN :-> $trModule_s5iN,
                     s5iO :-> $tc'A_s5iO, s5iQ :-> $tc'B_s5iQ, s5iR :->
 $tcB_s5iR,
                     s5iS :-> $tc'D_s5iS, s5iT :-> $tcD_s5iT, s5iU :->
 $tc'C:C_s5iU,
                     s5iV :-> $tcC_s5iV, s5jw :-> $sf2_s5jw, s5jM :->
 $sf1_s5jM,
                     s5jU :-> labelvs_s5jU, s5k8 :-> $sf3_s5k8,
                     s5ki :-> $sfromIntegral_s5ki, s5kD :-> $sminimum_s5kD,
                     s5kE :-> $scomparing_s5kE, s5kF :-> $srealToFrac_s5kF,
                     s5kG :-> $sfromIntegral_s5kG, s5kN :-> lvl_s5kN, s5kX
 :-> lvl_s5kX,
                     s5lc :-> lvl_s5lc, s5ln :-> lvl_s5ln, s5pu :->
 lvl_s5pu,
                     s5pv :-> lvl_s5pv, s5ra :-> lvl_s5ra, s5rb :->
 lvl_s5rb,
                     s5Bi :-> $w$sf3_s5Bi, s5Bt :-> $wf3_s5Bt, s5Bx :->
 w_s5Bx,
                     s5BB :-> ww_s5BB, s5BF :-> $w$sf1_s5BF, s5BS :->
 $wf1_s5BS,
                     s5BW :-> $wf2_s5BW, s5D0 :-> $j_s5D0, s5FJ :->
 lvl_s5FJ,
                     s5FL :-> $wgo_s5FL, s5FM :-> lvl_s5FM, s5FN :->
 lvl_s5FN,
                     s5FP :-> karg_s5FP, s5FW :-> go_s5FW, s5FX :->
 lvl_s5FX,
                     s5FY :-> lvl_s5FY, s5FZ :-> lvl_s5FZ, s5G0 :->
 lvl_s5G0,
                     s5G1 :-> lvl_s5G1, s5G2 :-> lvl_s5G2, s5G4 :->
 lvl_s5G4,
                     s5G5 :-> lvl_s5G5, s5G6 :-> lvl_s5G6, s5G7 :->
 lvl_s5G7,
                     s5Io :-> $s$j_s5Io, s5Ip :-> $s$j_s5Ip, s5Ir :->
 $sgo_s5Ir]
   tenv []
   tenvFVs []
   cenv [s5Ij :-> sg_s5Ij, s5Ik :-> sg_s5Ik]
   cenvFVs [s5Ij :-> sg_s5Ij, s5Ik :-> sg_s5Ik]
   tys [Ratio Integer]
   cos []

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
 }}}

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12760>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list