#1749: forall type gives "not polymorphic enough" error incorrectly
----------------------------------------+-----------------------------------
    Reporter:  guest                    |        Owner:         
        Type:  bug                      |       Status:  new    
    Priority:  normal                   |    Milestone:         
   Component:  Compiler (Type checker)  |      Version:  6.6.1  
    Severity:  normal                   |   Resolution:         
    Keywords:                           |   Difficulty:  Unknown
          Os:  Windows                  |     Testcase:         
Architecture:  x86                      |  
----------------------------------------+-----------------------------------
Old description:

> > type SFST s a b = a -> ST s b
> > newtype SF a b = SF { runSF :: forall s. ST s (SFST s a b) }
>
> When making this into an instance of Arrow, compose works beautifully:
>
> > sfCompose :: SF b c -> SF c d -> SF b d
> > sfCompose bc cd = SF sf where
> >   sf = do
> >     runBc <- runSF bc
> >     runCd <- runSF cd
> >     return $ \b -> runBc b >>= runCd
>
> but pure gives an odd message:
>
> > sfPure :: (b -> c) -> SF b c
> > sfPure f = SF sf where
> >     sf = return $ \b -> return (f b)
>
> frp_typebug.lhs:20:12:
>     Inferred type is less polymorphic than expected
>       Quantified type variable `s' is mentioned in the environment:
>         sf :: ST s (b -> ST s c) (bound at frp_typebug.lhs:21:5)
>     In the first argument of `SF', namely `sf'
>     In the expression: SF sf
>     In the definition of `sfPure':
>         sfPure f = SF sf
>                  where
>                      sf = return $ (\ b -> return (f b))
>
> This can be worked around using scoped type variables:
> > sfPure2 :: (b -> c) -> SF b c
> > sfPure2 (f :: b -> c) = SF sf where
> >     sf :: forall s. ST s (SFST s b c)
> >        = return $ \b -> return (f b)
>
> but it's ugly.

New description:

 {{{
 > type SFST s a b = a -> ST s b
 > newtype SF a b = SF { runSF :: forall s. ST s (SFST s a b) }
 }}}

 When making this into an instance of Arrow, compose works beautifully:

 {{{
 > sfCompose :: SF b c -> SF c d -> SF b d
 > sfCompose bc cd = SF sf where
 >   sf = do
 >     runBc <- runSF bc
 >     runCd <- runSF cd
 >     return $ \b -> runBc b >>= runCd
 }}}

 but pure gives an odd message:

 {{{
 > sfPure :: (b -> c) -> SF b c
 > sfPure f = SF sf where
 >     sf = return $ \b -> return (f b)
 }}}

 {{{
 frp_typebug.lhs:20:12:
     Inferred type is less polymorphic than expected
       Quantified type variable `s' is mentioned in the environment:
         sf :: ST s (b -> ST s c) (bound at frp_typebug.lhs:21:5)
     In the first argument of `SF', namely `sf'
     In the expression: SF sf
     In the definition of `sfPure':
         sfPure f = SF sf
                  where
                      sf = return $ (\ b -> return (f b))
 }}}

 This can be worked around using scoped type variables:

 {{{
 > sfPure2 :: (b -> c) -> SF b c
 > sfPure2 (f :: b -> c) = SF sf where
 >     sf :: forall s. ST s (SFST s b c)
 >        = return $ \b -> return (f b)
 }}}

 but it's ugly.

Comment (by sorear):

 Thanks for the report, but I think I can explain this.

 Firstly, and quite unrelatedly, you can use triple braces to request
 monospace, see my edit to the description.

 'sf' has no arguments, so the monomorphism restriction applies.  The body
 of 'sf' is assigned a typing derivation of the form:

 {{{
 Monad m1, Monad m2, f :: b -> c |- return $ \b -> return (f b) : m1 (a ->
 m2 b)
 }}}

 Because 'm1' and 'm2' are constrained by type classes, the monomorphism
 restriction forces them to be assigned to fully non-polymorphic types;
 unfortunately this means that it is insufficiently polymorphic for SF.

 Possible workarounds include:

 {{{
 {-# LANGUAGE NoMonomorphismRestriction #-}
 -- for older GHC, {-# OPTIONS_GHC -fno-monomorphism-restriction #-}
 }}}

 or:

 {{{
 sfPure :: (b -> c) -> SF b c
 sfPure f = SF sf where
      returnST :: a -> ST s a
      returnST = return

      sf = returnST $ \b -> returnST (f b)  -- no type classes, no MR
 }}}

 or the aforementioned explicit annotation approach (explicit annotations
 disable the MR).

 Unfortunately, the monomorphism restriction is specified by the Haskell 98
 Language Report, so you're more likely to get results from the Haskell-
 prime committee than you are from specific implementors.

 Stefan

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1749#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to