[GHC] #11982: Typechecking fails for parallel monad comprehensions with polymorphic let

GHC ghc-devs at haskell.org
Sun Jan 20 09:03:04 UTC 2019


#11982: Typechecking fails for parallel monad comprehensions with polymorphic let
-------------------------------------+-------------------------------------
        Reporter:  simonpj           |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  7.10.3
      Resolution:                    |             Keywords:  ApplicativeDo
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by vdukhovni):

 [ Help to pin down the cause by 宮里 洸司 (Koji Miyazato) much appreciated
 ]

 Probably the same underlying cause, where a let-bound universally
 quantified function that transforms IO actions to run under a lock, leads
 to type errors when ApplicativeDo is in use (sometimes for unrelated code
 in the same module). Removing ApplicativeDo allows the code to compile, as
 does inlining the let-bound polymorphic value into the call site.
 {{{
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ApplicativeDo #-}
 module Main where
 import Control.Concurrent.MVar

 type Locker = forall a. IO a -> IO a

 main :: IO ()
 main = do
     line <- getLine
     lock <- newMVar ()
     let locker :: Locker
         locker = withMVar lock . const
     f line locker

 f :: String -> Locker -> IO ()
 f line locker = locker $ putStrLn line
 }}}
 This fails with:
 {{{
 appdobug.hs:14:13: error:
     • Couldn't match type ‘a’ with ‘a0’
       ‘a’ is a rigid type variable bound by
         a type expected by the context:
           Locker
         at appdobug.hs:14:6-18
       Expected type: IO a -> IO a
         Actual type: IO a0 -> IO a0
     • In the second argument of ‘f’, namely ‘locker’
       In a stmt of a 'do' block: f line locker
       In the expression:
         do line <- getLine
            lock <- newMVar ()
            let locker :: Locker
                locker = withMVar lock . const
            f line locker
     • Relevant bindings include
         locker :: IO a0 -> IO a0 (bound at appdobug.hs:13:10)
 }}}
 With the value of 'locker' inlined as below, what one would expect to be
 the "same" code now compiles. The behaviour is sufficiently surprising to
 perhaps merit another look at this issue.
 {{{
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ApplicativeDo #-}
 module Main where
 import Control.Concurrent.MVar

 type Locker = forall a. IO a -> IO a

 main :: IO ()
 main = do
     line <- getLine
     lock <- newMVar ()
     f line $ withMVar lock . const

 f :: String -> Locker -> IO ()
 f line locker = locker $ putStrLn line
 }}}

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


More information about the ghc-tickets mailing list