[GHC] #13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler | Version: 8.2.1-rc2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I encountered this problem when trying to compile the `ivory-bsp-stm32` library (unsuccessfully) with GHC 8.2. Here's a somewhat minimized example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} -- Not enabling MonoLocalBinds makes it compile again {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE RankNTypes #-} module Bug where import GHC.TypeLits i2cPeripheralDriver :: I2CPeriph -> ChanOutput ('Stored ITime) -> Monitor e () i2cPeripheralDriver periph watchdog_per = do let sendresult' :: Ivory eff () sendresult' = do -- Commenting out the line below makes it compile again clearSR1 periph return undefined sendresult = sendresult' handler watchdog_per undefined $ do callback $ \_ -> do sendresult return undefined clearSR1 :: I2CPeriph -> Ivory eff () clearSR1 = undefined ----- -- Auxiliary definitions ----- data ITime data I2CPeriph = I2CPeriph data Ivory (eff :: Effects) a instance Functor (Ivory eff) instance Applicative (Ivory eff) instance Monad (Ivory eff) data Monitor e a instance Functor (Monitor e) instance Applicative (Monitor e) instance Monad (Monitor e) data ChanOutput (a :: Area *) data RefScope = Global | forall s. Stack s type ConstRef = Pointer 'Valid 'Const -- :: RefScope -> Area * -> * data Nullability = Nullable | Valid data Constancy = Const | Mutable data Pointer (n :: Nullability) (c :: Constancy) (s :: RefScope) (a :: Area *) type AllocEffects s = 'Effects 'NoReturn 'NoBreak ('Scope s) -- :: Effects data Effects = Effects ReturnEff BreakEff AllocEff data ReturnEff = forall t. Returns t | NoReturn data BreakEff = Break | NoBreak data AllocEff = forall s. Scope s | NoAlloc callback :: (IvoryArea a, IvoryZero a) => (forall (s :: RefScope) s'. ConstRef s a -> Ivory (AllocEffects s') ()) -> Handler a e () callback _ = undefined handler :: (IvoryArea a, IvoryZero a) => ChanOutput a -> String -> Handler a e () -> Monitor e () data Handler (area :: Area *) e a handler = undefined data Area k = Struct Symbol | Array Nat (Area k) | CArray (Area k) | Stored k data Time class IvoryArea (a :: Area *) class IvoryZero (area :: Area *) where class IvoryType t instance IvoryType ITime instance IvoryType a => IvoryArea ('Stored a) class IvoryZeroVal a instance IvoryZeroVal ITime instance IvoryZeroVal a => IvoryZero ('Stored a) }}} In GHC 7.10 and 8.0, this compiles. With GHC 8.2, however, it errors: {{{#!hs GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:25:7: error: • Couldn't match type ‘eff0’ with ‘AllocEffects s'’ because type variable ‘s'’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall (s :: RefScope) s'. ConstRef s ('Stored ITime) -> Ivory (AllocEffects s') () at Bug.hs:(24,5)-(25,16) Expected type: Ivory (AllocEffects s') () Actual type: Ivory eff0 () • In a stmt of a 'do' block: sendresult In the expression: do sendresult In the second argument of ‘($)’, namely ‘\ _ -> do sendresult’ • Relevant bindings include sendresult :: Ivory eff0 () (bound at Bug.hs:21:7) | 25 | sendresult | ^^^^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: @@ -122,1 +122,1 @@ - {{{#!hs + {{{ New description: I encountered this problem when trying to compile the `ivory-bsp-stm32` library (unsuccessfully) with GHC 8.2. Here's a somewhat minimized example: {{{#!hs {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE KindSignatures #-} -- Not enabling MonoLocalBinds makes it compile again {-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE RankNTypes #-} module Bug where import GHC.TypeLits i2cPeripheralDriver :: I2CPeriph -> ChanOutput ('Stored ITime) -> Monitor e () i2cPeripheralDriver periph watchdog_per = do let sendresult' :: Ivory eff () sendresult' = do -- Commenting out the line below makes it compile again clearSR1 periph return undefined sendresult = sendresult' handler watchdog_per undefined $ do callback $ \_ -> do sendresult return undefined clearSR1 :: I2CPeriph -> Ivory eff () clearSR1 = undefined ----- -- Auxiliary definitions ----- data ITime data I2CPeriph = I2CPeriph data Ivory (eff :: Effects) a instance Functor (Ivory eff) instance Applicative (Ivory eff) instance Monad (Ivory eff) data Monitor e a instance Functor (Monitor e) instance Applicative (Monitor e) instance Monad (Monitor e) data ChanOutput (a :: Area *) data RefScope = Global | forall s. Stack s type ConstRef = Pointer 'Valid 'Const -- :: RefScope -> Area * -> * data Nullability = Nullable | Valid data Constancy = Const | Mutable data Pointer (n :: Nullability) (c :: Constancy) (s :: RefScope) (a :: Area *) type AllocEffects s = 'Effects 'NoReturn 'NoBreak ('Scope s) -- :: Effects data Effects = Effects ReturnEff BreakEff AllocEff data ReturnEff = forall t. Returns t | NoReturn data BreakEff = Break | NoBreak data AllocEff = forall s. Scope s | NoAlloc callback :: (IvoryArea a, IvoryZero a) => (forall (s :: RefScope) s'. ConstRef s a -> Ivory (AllocEffects s') ()) -> Handler a e () callback _ = undefined handler :: (IvoryArea a, IvoryZero a) => ChanOutput a -> String -> Handler a e () -> Monitor e () data Handler (area :: Area *) e a handler = undefined data Area k = Struct Symbol | Array Nat (Area k) | CArray (Area k) | Stored k data Time class IvoryArea (a :: Area *) class IvoryZero (area :: Area *) where class IvoryType t instance IvoryType ITime instance IvoryType a => IvoryArea ('Stored a) class IvoryZeroVal a instance IvoryZeroVal ITime instance IvoryZeroVal a => IvoryZero ('Stored a) }}} In GHC 7.10 and 8.0, this compiles. With GHC 8.2, however, it errors: {{{ GHCi, version 8.2.0.20170522: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:25:7: error: • Couldn't match type ‘eff0’ with ‘AllocEffects s'’ because type variable ‘s'’ would escape its scope This (rigid, skolem) type variable is bound by a type expected by the context: forall (s :: RefScope) s'. ConstRef s ('Stored ITime) -> Ivory (AllocEffects s') () at Bug.hs:(24,5)-(25,16) Expected type: Ivory (AllocEffects s') () Actual type: Ivory eff0 () • In a stmt of a 'do' block: sendresult In the expression: do sendresult In the second argument of ‘($)’, namely ‘\ _ -> do sendresult’ • Relevant bindings include sendresult :: Ivory eff0 () (bound at Bug.hs:21:7) | 25 | sendresult | ^^^^^^^^^^ }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: facundo.dominguez (added) * related: => #11698 Comment: This behavior was introduced in commit c9e8f801170b213b85735ed403f24b2842aedf1b (Set tct_closed to TopLevel for closed bindings). Facundo, is this expected? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by facundo.dominguez): Something odd is going on. Adding the type signature {{{sendresult :: Ivory eff ()}}} also makes the program compile. {{{tct_closed}}} is affected by the use of {{{periph}}} in {{{sendresult'}}}. This makes {{{sendresult}}} not closed. But I do not understand how this relates to the error message that GHC produces. It might be that some use of {{{tct_closed}}} in the type-checker is assuming its old meaning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I see what is happening here. We have {{{ f periph = let sr :: forall a. [a] -> [a] sr = ... periph ... sr' = sr in ... }}} Can we do type inference for `sr'`? Of course! Its only free var is `sr` which has a closed type. But from the point of view of static pointers, `sr'` mentions `sr` and `sr` mentions `periph`, so they could not be floated out. So they aren't closed in that sense. We were mixing the two up. Fix incoming. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * Attachment "T13804.patch" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The attached patch does the job, but regresses `perf/compiler/T12227`. I'm tied up this week; would anyone like to investigate? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: highest | Milestone:
Component: Compiler (Type | Version: 8.2.1-rc2
checker) |
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: #11698 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: merge Priority: highest | Milestone: Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => merge Comment: It took me a surprisingly long time to really understand what's going on here, but I hope that the new documentation will help for next time! Probably merge. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13804: MonoLocalBinds/RankNTypes type inference regression in GHC 8.2 -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: highest | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.2.1-rc2 checker) | Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11698 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed * resolution: => fixed * milestone: => 8.2.1 Comment: Merged with 15af7156087dec6b1031406bcbe4508b71cc3470. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13804#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC