[Haskell-cafe] Fragile GHC rank-2 type inference?

Viktor Dukhovni ietf-dane at dukhovni.org
Sun Jan 20 02:39:10 UTC 2019


> On Jan 19, 2019, at 9:09 PM, 宮里 洸司 <viercc at gmail.com> wrote:
> 
> You enabled TypeFamilies extension, which subsumes MonoLocalBinds.
> MonoLocalBinds disables automatic let-generalization. Unless you
> attach type annotation, the type of locker is not (forall a. IO a -> IO a).

Thanks, that makes sense.  And indeed I only did that while
trying to understand how the use of "withResponse" plays into
the story, but just adding the type annotation is not enough,
so the real problem is elsewhere...

> This is a pure guess, but I think your error in the actual code is
> caused by ApplicativeDo.  The following code fails to compile but
> disabling ApplicativeDo solves the problem.

Nice example, thanks!  Indeed that seems to be much closer to
the heart of the problem.

>  {-# LANGUAGE RankNTypes #-}
>  {-# LANGUAGE ApplicativeDo #-}
>  module Main where
> 
>  import Control.Concurrent.MVar
> 
>  type Locker = forall a. IO a -> IO a
> 
>  main :: IO ()
>  main =
>    do lock1 <- newMVar ()
>       let locker1 :: Locker
>           locker1 = withMVar lock1 . const
>       lock2 <- newMVar ()
>       let locker2 :: Locker
>           locker2 = withMVar lock2 . const
>       f locker1 locker2
> 
>  f :: Locker -> Locker -> IO ()
>  f _ _ = putStrLn "dummy"
> 
> I think this is ApplicativeDo-side bug, not type checking bug.

Yes, removing ApplicativeDo and rewriting the option parser as:

	Env locker <$> f1 <*> f2 <*> ... <*> fN

solves the problem, but results in IMHO harder to maintain code,
because of the required positional correspondence between the
Env constructor fields and the placement of the field parsers.

It is certainly surprising that ApplicativeDo affects the
type inference of "locker" in:

	type Locker = forall a. IO a -> IO a
	data Env = Env { locker :: Locker, f1 :: T1, ... , fN :: TN }

	f locker = do
		f1 <- parser1
		f2 <- parser2
		...
		fN <- parserN
		pure Env{..}

in a way that breaks:

	lock <- newMVar ()
	let locker :: Locker
	    locker = withMVar lock . const
	f locker

but does not break:

	lock <- newMVar ()
	f (mkLocker lock)
      where
	mkLocker :: MVar () -> Locker
	mkLocker lock = withMVar lock . const

Would it be appropriate to file a bug report?  Your
example seems suitably succinct.

-- 
	Viktor.



More information about the Haskell-Cafe mailing list