[GHC] #16183: GHC HEAD regression: -ddump-splices incorrectly parenthesizes HsKindSig applications
GHC
ghc-devs at haskell.org
Tue Jan 15 02:15:58 UTC 2019
#16183: GHC HEAD regression: -ddump-splices incorrectly parenthesizes HsKindSig
applications
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.8.1
Component: Template Haskell | Version: 8.7
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Debugging | Unknown/Multiple
information is incorrect | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by RyanGlScott):
So are type family equations:
{{{#!hs
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -ddump-splices #-}
module Bug where
import Data.Kind
$([d| type family F a where
F (a :: Type) = Int |])
}}}
{{{
$ ~/Software/ghc4/inplace/bin/ghc-stage2 --interactive Bug.hs
GHCi, version 8.7.20190114: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Bug ( Bug.hs, interpreted )
Bug.hs:(8,3)-(9,30): Splicing declarations
[d| type family F_a1B4 a_a1B5 where
F_a1B4 (a_a1B6 :: Type) = Int |]
======>
type family F_a4tB a_a4tC where
F_a4tB a_a4tD :: Type = Int
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16183#comment:3>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list