Type error in GHC-7 but not in GHC-6.12.3

Bas van Dijk v.dijk.bas at gmail.com
Fri Oct 29 10:03:24 EDT 2010


Hello,

I'm updating my usb-safe package for GHC-7:

darcs get http://code.haskell.org/~basvandijk/code/usb-safe

It depends on the HEAD version of regions:
darcs get http://code.haskell.org/~basvandijk/code/regions

I think I'm suffering from the new implied MonoLocalBinds extension
(I'm using GADTs) as described in:

http://hackage.haskell.org/trac/ghc/blog/LetGeneralisationInGhc7

However, I'm not sure this is the problem because I'm not using local
bindings and use explicit type signatures everywhere.

I try to make a small isolated example when I have time but for now
let's use the actual definitions:

The following function type-checked fine in GHC-6.12.3 but fails in
GHC-7.1.20101027:

withDeviceWhich ∷
  ∀ pr α
  . MonadCatchIO pr
  ⇒ USB.Ctx
  → (USB.DeviceDesc → Bool)
  → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
  → pr α
withDeviceWhich ctx p f = do
  devs ← liftIO $ USB.getDevices ctx
  useWhich devs withDevice p f

The error I get is:

Couldn't match expected type `forall s.
                                  RegionalDeviceHandle (RegionT s pr)
                                  -> RegionT s pr α'
                with actual type `RegionalDeviceHandle (RegionT s pr)
                                  -> RegionT s pr α'
    In the fourth argument of `useWhich', namely `f'

These are the types and definitions of the other functions involved:

useWhich ∷
  ∀ k desc e (m ∷ * → *) α
  . (GetDescriptor e desc, MonadIO m)
  ⇒ [e]
  → (e → k → m α)
  → (desc → Bool)
  → k
  → m α
useWhich ds w p f = case find (p ∘ getDesc) ds of
                      Nothing → throw USB.NotFoundException
                      Just d  → w d f

withDevice ∷
    MonadCatchIO pr
  ⇒ USB.Device
  → (∀ s. RegionalDeviceHandle (RegionT s pr) → RegionT s pr α)
  → pr α
withDevice dev f = runRegionT $ openDevice dev >>= f

Note that when I inline the definition of useWhich it type-checks fine:

withDeviceWhich ctx p f = do
  devs ← liftIO $ USB.getDevices ctx
  case find (p ∘ getDesc) devs of
    Nothing → throw USB.NotFoundException
    Just d  → withDevice d f

Since I'm not using local bindings and use explicit type signatures
everywhere, I'm not sure MonoLocalBinds is the problem.

Note that other applications of useWhich which also use RankNTypes
type-check just fine in both GHC-6.12.3 and GHC-7.1.20101027:

-------------------------------------------------------------------------------

setConfigWhich ∷
  ∀ pr cr α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ RegionalDeviceHandle pr
  → (USB.ConfigDesc → Bool)
  → (∀ sCfg. ConfigHandle sCfg → cr α)
  → cr α
setConfigWhich h = useWhich (getConfigs h) setConfig

getConfigs ∷ RegionalDeviceHandle r → [Config r]

setConfig ∷
  ∀ pr cr α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ Config pr
  → (∀ sCfg. ConfigHandle sCfg → cr α)
  → cr α

-------------------------------------------------------------------------------

withInterfaceWhich ∷
  ∀ pr sCfg α
  . MonadCatchIO pr
  ⇒ ConfigHandle sCfg
  → (USB.Interface → Bool)
  → (∀ s. RegionalInterfaceHandle sCfg (RegionT s pr) → RegionT s pr α)
  → pr α
withInterfaceWhich h = useWhich (getInterfaces h) withInterface

getInterfaces ∷ ConfigHandle sCfg → [Interface sCfg]

withInterface ∷
  ∀ pr sCfg α
  . MonadCatchIO pr
  ⇒ Interface sCfg
  → (∀ s. RegionalInterfaceHandle sCfg (RegionT s pr) → RegionT s pr α)
  → pr α


-------------------------------------------------------------------------------

setAlternateWhich ∷
  ∀ pr cr sCfg α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ RegionalInterfaceHandle sCfg pr
  → (USB.InterfaceDesc → Bool)
  → (∀ sAlt. AlternateHandle sAlt pr → cr α)
  → cr α
setAlternateWhich h = useWhich (getAlternates h) setAlternate

getAlternates ∷ RegionalInterfaceHandle sCfg r → [Alternate sCfg r]

setAlternate ∷
  ∀ pr cr sCfg α
  . (pr `AncestorRegion` cr, MonadCatchIO cr)
  ⇒ Alternate sCfg pr
  → (∀ sAlt. AlternateHandle sAlt pr → cr α)
  → cr α


-------------------------------------------------------------------------------

I'm happy to provide more info when needed.

Regards,

Bas


More information about the Glasgow-haskell-users mailing list