Change in rendering of [] in GADTs

Mateusz Kowalczyk fuuzetsu at fuuzetsu.co.uk
Sat Feb 22 23:46:02 UTC 2014


While running Haddock tests today, we noticed that the output for a test
with GADTs changed. See the test file in the bottom.

We used to render ‘Nil :: Pattern '[]’ as ‘Pattern []’ but it now
renders as ‘Pattern `[]`’. The change happened within last 2 days and
I'm guessing it's d3af9807ca8a1db0bc9298ea50895ee9df55edb7 that made the
change.

Should this be something that we fix on Haddock end or should it be left
with the new rendering? I'm unsure whether the previous rendering wasn't
better or not.

The Haddock test suite is not ran as part of GHC validate process so it
the failure slipped by.

The file is:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
module AdvanceTypes where

data Pattern :: [*] -> * where
  Nil :: Pattern '[]
  Cons :: Maybe h -> Pattern t -> Pattern (h ': t)

-- 
Mateusz K.


More information about the ghc-devs mailing list