[GHC] #16249: no runtime error for -fdefer-type-errors with TypeError constraint

GHC ghc-devs at haskell.org
Mon Jan 28 16:44:00 UTC 2019


#16249: no runtime error for -fdefer-type-errors with TypeError constraint
-------------------------------------+-------------------------------------
           Reporter:  guibou         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.6.3
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):                 |         Wiki Page:
-------------------------------------+-------------------------------------
 Part of a testsuite, I'm using `-fdefer-type-errors` to check if haskell
 expression raises type error. However the haskell expression may be
 perfectly valid except for a `TypeError` constraint on a typeclass.

 The following code:

 {{{#!haskell
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE DataKinds #-}

 import GHC.TypeLits

 class Foo t where
   foo :: t -> t
   foo = id

 instance Foo Int
 instance (TypeError (Text "String does not work")) => Foo String

 main :: IO ()
 main = do
   putStrLn (show (foo 10 :: Int))
   putStrLn (foo "hello")
 }}}

 Correctly generates errors when compiled:

 {{{
 $ ghc ./DeferTypes.hs
 [1 of 1] Compiling Main             ( DeferTypes.hs, DeferTypes.o ) [flags
 changed]

 DeferTypes.hs:17:13: error:
     • String does not work
     • In the first argument of ‘putStrLn’, namely ‘(foo "hello")’
       In a stmt of a 'do' block: putStrLn (foo "hello")
       In the expression:
         do putStrLn (show (foo 10 :: Int))
            putStrLn (foo "hello")
    |
 17 |   putStrLn (foo "hello")
    |
 }}}

 And also with `-fdefer-type-erros`, the error is transformed into a
 warning:

 {{{
 $ ghc -fdefer-type-errors ./DeferTypes.hs
 [1 of 1] Compiling Main             ( DeferTypes.hs, DeferTypes.o ) [flags
 changed]

 DeferTypes.hs:17:13: warning: [-Wdeferred-type-errors]
     • String does not work
     • In the first argument of ‘putStrLn’, namely ‘(foo "hello")’
       In a stmt of a 'do' block: putStrLn (foo "hello")
       In the expression:
         do putStrLn (show (foo 10 :: Int))
            putStrLn (foo "hello")
    |
 17 |   putStrLn (foo "hello")
    |             ^^^^^^^^^^^
 Linking DeferTypes ...
 }}}

 However, executing the program gives no runtime error:
 {{{
 $ ./DeferTypes
 10
 hello
 }}}

 I was expecting something such as:

 {{{
 $ ./DeferTypes
 10
 [a defered type error exception]
 }}}

 With ghc 8.6.3 from nix.

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


More information about the ghc-tickets mailing list