[Haskell-cafe] Fragile GHC rank-2 type inference?
Viktor Dukhovni
ietf-dane at dukhovni.org
Sun Jan 20 07:24:39 UTC 2019
> On Jan 20, 2019, at 2:09 AM, 宮里 洸司 <viercc at gmail.com> wrote:
>
>> Would it be appropriate to file a bug report?
>
> Found that there's a related bug report:
> https://ghc.haskell.org/trac/ghc/ticket/11982
Yes, that looks close. I think that your example could be added
to the bug report, making a more compelling case for fixing it.
I've tidied it up a bit more below my signature. Would you like
to add this to that ticket, or should I?
--
Viktor.
{-# 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
More information about the Haskell-Cafe
mailing list