[GHC] #12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on Travis

GHC ghc-devs at haskell.org
Tue May 17 07:28:22 UTC 2016


#12077: T8761 (Make pattern synonyms work with Template Haskell) is failing on
Travis
-------------------------------------+-------------------------------------
           Reporter:  thomie         |             Owner:
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Template       |           Version:  8.0.1
  Haskell                            |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:  #8761
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Note that Travis uses `DYNAMIC_GHC_PROGRAMS=NO`.

 First failure: https://travis-ci.org/ghc/ghc/builds/129738012

 {{{
 Actual stderr output differs from expected:
 --- ./th/T8761.stderr.normalised        2016-05-12 15:08:16.512921981
 +0000
 +++ ./th/T8761.comp.stderr.normalised   2016-05-12 15:08:16.512921981
 +0000
 @@ -1,7 +1,3 @@
 -pattern Q1 x1_0 x2_1 x3_2 <- ((x1_0, x2_1), [x3_2], _, _)
 -pattern x1_0 Q2 x2_1 = ((x1_0, x2_1))
 -pattern Q3 {qx3, qy3, qz3} <- ((qx3, qy3), [qz3]) where
 -                                  Q3 qx3 qy3 qz3 = ((qx3, qy3), [qz3])
  T8761.hs:(15,1)-(38,13): Splicing declarations
      do { [qx1, qy1, qz1] <- mapM
                                (/ i -> newName $ "x" ++ show i) [1, 2, 3];
 @@ -123,30 +119,6 @@
      pattern Pup x <- MkUnivProv x
      pattern Puep :: forall a. forall b. Show b => a -> b -> (ExProv, a)
      pattern Puep x y <- (MkExProv y, x)
 -pattern T8761.P :: GHC.Types.Bool
 -pattern T8761.Pe :: () => forall (a0_0 :: *) . a0_0 -> T8761.Ex
 -pattern T8761.Pu :: forall (a0_0 :: *) . a0_0 -> a0_0
 -pattern T8761.Pue :: forall (a0_0 :: *) . () => forall (b0_1 :: *) .
 -                                                a0_0 -> b0_1 -> (a0_0,
 T8761.Ex)
 -pattern T8761.Pur :: forall (a0_0 :: *) . (GHC.Num.Num a0_0,
 -                                           GHC.Classes.Eq a0_0) =>
 -                     a0_0 -> [a0_0]
 -pattern T8761.Purp :: forall (a0_0 :: *) (b0_1 :: *) . (GHC.Num.Num a0_0,
 -                                                        GHC.Classes.Eq
 a0_0) =>
 -                      GHC.Show.Show b0_1 => a0_0 -> b0_1 -> ([a0_0],
 T8761.UnivProv b0_1)
 -pattern T8761.Pure :: forall (a0_0 :: *) . (GHC.Num.Num a0_0,
 -                                            GHC.Classes.Eq a0_0) =>
 -                      forall (b0_1 :: *) . a0_0 -> b0_1 -> ([a0_0],
 T8761.Ex)
 -pattern T8761.Purep :: forall (a0_0 :: *) . (GHC.Num.Num a0_0,
 -                                             GHC.Classes.Eq a0_0) =>
 -                       forall (b0_1 :: *) . GHC.Show.Show b0_1 =>
 -                       a0_0 -> b0_1 -> ([a0_0], T8761.ExProv)
 -pattern T8761.Pep :: () => forall (a0_0 :: *) . GHC.Show.Show a0_0 =>
 -                           a0_0 -> T8761.ExProv
 -pattern T8761.Pup :: forall (a0_0 :: *) . () => GHC.Show.Show a0_0 =>
 -                                                a0_0 -> T8761.UnivProv
 a0_0
 -pattern T8761.Puep :: forall (a0_0 :: *) . () => forall (b0_1 :: *) .
 GHC.Show.Show b0_1 =>
 -                                                 a0_0 -> b0_1 ->
 (T8761.ExProv, a0_0)
  T8761.hs:(107,1)-(111,25): Splicing declarations
      do { infos <- mapM
                      reify
 *** unexpected failure for T8761(normal)
 }}}

 @bollmann added the test in c079de3c43704ea88f592e441389e520313e30ad.

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


More information about the ghc-tickets mailing list