[GHC] #9729: GHCi accepts invalid programs when recompiling

GHC ghc-devs at haskell.org
Sun Oct 26 21:34:55 UTC 2014


#9729: GHCi accepts invalid programs when recompiling
-------------------------------------+-------------------------------------
              Reporter:  crockeea    |            Owner:
                  Type:  bug         |           Status:  new
              Priority:  normal      |        Milestone:
             Component:  GHCi        |          Version:  7.8.3
            Resolution:              |         Keywords:
      Operating System:              |     Architecture:  Unknown/Multiple
  Unknown/Multiple                   |       Difficulty:  Unknown
       Type of failure:  GHC         |       Blocked By:
  accepts invalid program            |  Related Tickets:
             Test Case:              |
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Comment (by crockeea):

 By "remove the constraint", I mean comment that single line `Internal (a
 -> b) ~ (Internal a -> Internal b)` in the constraints for `share`. After
 the edit, module B is:

 {{{
 #!haskell
 {-# LANGUAGE GADTs, TypeOperators, FlexibleContexts #-}

 module B where

 import Data.Syntactic

 data Let x where
   Let :: Let (a :-> (a -> b) :-> Full b)

 share :: (Let :<: sup,
           sup ~ Domain b, sup ~ Domain a,
           --Internal (a -> b) ~ (Internal a -> Internal b), -- remove me
           Syntactic a, Syntactic b,
           Syntactic (a -> b),
           SyntacticN (a -> (a -> b) -> b)
             (ASTF sup (Internal a) ->
               ASTF sup (Internal (a -> b)) ->
                ASTF sup (Internal b)))
       => a -> (a -> b) -> b
 share = sugarSym Let
 }}}

 The example is as minimal as I could make it. In particular, GHCi *does*
 detect the change to module B if I do not import BindingT in module A.
 This supports my hypothesis because the instance is never in scope.

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


More information about the ghc-tickets mailing list