[GHC] #14983: Have custom type errors imply Void
GHC
ghc-devs at haskell.org
Thu Mar 29 12:45:27 UTC 2018
#14983: Have custom type errors imply Void
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: task | Status: new
Priority: lowest | Milestone:
Component: Compiler | Version: 8.5
Resolution: | Keywords:
| CustomTypeErrors
| QuantifiedConstraints wipT2893
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):
* keywords: CustomTypeErrors => CustomTypeErrors QuantifiedConstraints
wipT2893
Comment:
Can't you just do this?
{{{#!hs
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE UndecidableSuperClasses #-}
module Foo where
import Data.Void
import GHC.TypeLits
class (forall x. x) => No where
no :: Void
class (TypeError a, forall x. x) => MyTypeError a
instance MyTypeError (Text "Can't show functions") => Show (a -> b) where
show = absurd no
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14983#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list