[GHC] #9580: Possible excessive leniency in interaction between coerce and data families?

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: 7.8.3 checker) | Operating System: Keywords: | Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: Difficulty: Unknown | None/Unknown Blocked By: | Test Case: Related Tickets: | Blocking: | Differential Revisions: -------------------------------------+------------------------------------- Per goldfire's request at #8177, I am promoting this issue into it's own ticket. I am entirely not confident that it represents a bug; I raise the issue because, while it happens to do exactly what I want, I cannot understand *why* it does what I want, and it seems like it might possibly also do related undesirable things. I have the following situation, which I have distilled from a real use case, retaining its identifiers but eliding a whole bunch of irrelevant detail. The real thing is on GitHub if it helps anyone to see why I want to do this, but it's really a side issue AFAICT. It's split into two modules, because goldfire had suggested that it might have arisen because the newtype constructor `Quantity'` was in scope at the site of the `coerce`, this test shows that it arises even when `Quantity'` is not in scope. {{{ {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleInstances #-} module Test ( Quantity, Unit, Dimension(..), Variant(..), Mass, KnownVariant(Dimensional) ) where data Variant = DQuantity | DUnit data Dimension = DMass | DLength | DTime -- ... this isn't the real way, it's simplified data UnitName = UnitName String class KnownVariant (var :: Variant) where data Dimensional var :: Dimension -> * -> * instance KnownVariant DQuantity where newtype Dimensional DQuantity d v = Quantity' v instance KnownVariant DUnit where data Dimensional DUnit d v = Unit' UnitName v instance (Show v) => Show (Dimensional DQuantity d v) where show (Quantity' x) = "As A Quantity " ++ show x type Quantity = Dimensional DQuantity type Unit = Dimensional DUnit type Mass v = Quantity DMass v }}} And the main module: {{{ module Main where import Test import Data.Coerce main = do let x = 3.7 :: Double putStrLn . show $ x let y = (coerce x) :: Mass Double putStrLn . show $ y let z = (coerce y) :: Double putStrLn . show $ z }}} My question is in two parts: 1) Why are these coercions allowed if the role signature of `Dimensional` is, as GHCi's :i tells me, nominal nominal nominal? 2) Is this the intended behavior? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): I tried a bunch of variations to see if I could get this to not compile to see what might be causing it. It still works if you move the type synonym definitions of `Mass` and `Quantity` out of `Test` and into `Main` (as long as you move the language extensions too). It still works even if the last type parameter is held polymorphic, as {{{ f :: Num v => v -> Mass v f x = coerce $ 3 * x }}} even when `f` is defined in `Main`. It even still works if the last two parameters are held polymorphic, as {{{ g :: Num v => v -> Quantity d v g x = coerce $ 3 * x }}} even when `g` is defined in `Main`. It also works if you do the same thing but expand the type synonyms manually. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Oh yes, this is a real bug. Here is a cut-down test case {{{ {-# LANGUAGE KindSignatures, TypeFamilies #-} module T9580a( Dimensional ) where data family Dimensional var :: * -> * newtype instance Dimensional Int v = Quantity' v ------------------ module T9680 where import T9580a import Data.Coerce foo :: Dimensional Int Double -> Double foo x = coerce x }}} Obviously, the latter module should fail to type check, since `Quantity'` is not in scope. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: new Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * owner: => simonpj Comment: I'm on this (refactoring...), but am now out of action till Tues. SImon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data
families?
-------------------------------------+-------------------------------------
Reporter: dmcclean | Owner: simonpj
Type: bug | Status: new
Priority: low | Milestone:
Component: Compiler | Version: 7.8.3
(Type checker) | Keywords:
Resolution: | Architecture: Unknown/Multiple
Operating System: | Difficulty: Unknown
Unknown/Multiple | Blocked By:
Type of failure: | Related Tickets:
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => indexed-types/should_fail/T9580 * resolution: => fixed Comment: Thank you for identifying this. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): Thanks for fixing it! I just have one followup question. One reason the coercion shouldn't have worked is because the newtype constructor wasn't in scope. But, with the newtype constructor in scope, should it be coercible or not? I thought that it should still not be, because the data family's role signature has all nominal arguments. The newtype instance happens to use its argument in a representational way, but should that property of the definition be visible when "looking through" the data family? (It may be the case that one of your refactoring changes addresses this, I don't understand most of those comments.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by simonpj): Cam you give a concrete example? And compare with whatever [http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/ the paper] says? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): I think I may have been confused for 2 different reasons. First, I forgot that we are coercing in your example from Dimensional Int Double -> Double, which should work according to rule 2 in figure 2. I had it mixed up with converting from Dimensional Int Double -> Dimensional Int x (where there is a coercion from Double to x). Second, it doesn't appear to actually be possible to export the Quantity' constructor from the defining module at all. (If I put it in the export list, GHCi tells me that it isn't in scope even though it is and I checked the spelling three times.) So the scenario I was thinking of isn't possible for that reason too; I hadn't realized that this was a rule. I now think that with the change you made everything is correct, sorry for the confusion. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

I think I may have been confused for 2 different reasons.
First, I forgot that we are coercing in your example from Dimensional Int Double -> Double, which should work according to rule 2 in figure 2. I had it mixed up with converting from Dimensional Int Double -> Dimensional Int x (where there is a coercion from Double to x).
Second, it doesn't appear to actually be possible to export the Quantity' constructor from the defining module at all. (If I put it in the export list, GHCi tells me that it isn't in scope even though it is and I checked the spelling three times.) So the scenario I was thinking of isn't
#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dfeuer): Replying to [comment:8 dmcclean]: possible for that reason too; I hadn't realized that this was a rule.
I now think that with the change you made everything is correct, sorry
for the confusion. Did you use the proper export syntax, `Dimensional (Quantity')`? That's supposed to work. If you didn't get an unknown whatever error when exporting `Quantity'` from the defining module, I'm ''guessing'' that it exported the `Quantity'` ''type'' (produced by `DataKinds`) rather than the data constructor. I don't really know how that extension is supposed to work with module exports though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#9580: Possible excessive leniency in interaction between coerce and data families? -------------------------------------+------------------------------------- Reporter: dmcclean | Owner: simonpj Type: bug | Status: closed Priority: low | Milestone: Component: Compiler | Version: 7.8.3 (Type checker) | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: indexed- | types/should_fail/T9580 | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by dmcclean): No, I did not use the proper export syntax. I'm sorry, I wasn't aware of it. With the proper syntax it does work. Thank you both again. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/9580#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC