
#12102: “Constraints in kinds” illegal family application in instance (+ documentation issues?) -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: TypeInType Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #13780 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I'm confused then on what this ticket is about. Is the plan to keep this feature and fix the bugs reported in the original comment? FWIW, I noticed that even after commit c2417b87ff59c92fbfa8eceeff2a0d6152b11a47, which fixed several ugly pretty- printer bugs that caused things like `'GHC.Types.Eq#` to be printed, a similar pretty-printer bug in this ticket is still //not// fixed on GHC HEAD. For instance, this program: {{{#!hs {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeOperators #-} import Data.Kind import GHC.TypeLits hiding (type (*)) type family IsTypeLit a where IsTypeLit Nat = 'True IsTypeLit Symbol = 'True IsTypeLit a = 'False data T :: forall a. (IsTypeLit a ~ 'True) => a -> * where MkNat :: T 42 MkSymbol :: T "Don't panic!" instance Show (T 42) where }}} Still spits out `'GHC.Types.Eq#`: {{{ $ ghc5/inplace/bin/ghc-stage2 --interactive Bug.hs GHCi, version 8.3.20170725: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Main ( Bug.hs, interpreted ) Bug.hs:21:10: error: • Illegal type synonym family application in instance: T ('Data.Type.Equality.C:~ ('GHC.Types.Eq# <>)) 42 • In the instance declaration for ‘Show (T 42)’ | 21 | instance Show (T 42) where | ^^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12102#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler