The monomorphism restriction and monomorphic pattern bindings

Simon Marlow marlowsd at gmail.com
Thu Apr 24 13:12:27 EDT 2008


Iavor Diatchki wrote:

> I should also point out that if we were to adopt the MBP rule, we
> would have to adjust the definition of what pattern bindings mean.
> For example, I think that this is how things are desugared at the
> moment:
> (x,y)  = e
> becomes
> new_var = e
> x = case new_var of (v,_) -> v
> y = case new_var of (_,v) -> v

The report doesn't actually mention this translation although it is 
widely used to implement pattern bindings, and in some compilers (not 
GHC) the translation is done before type checking.

What's interesting to me is that perhaps this gives us a way to 
understand what the static semantics of pattern bindings should be, 
absent MPB. e.g.

(x,y) = (negate,show)

(Simon's example) translates to

z = (negate,show)
x = fst z
y = snd z

and we can see why both x and y end up generalised over both 
constraints, because

z :: (Num a, Show b) => (a -> a, b -> String)

and this also explains why the pattern-bound variables don't have to be 
generalised over all the type variables.  e.g. in

z = (id,id)
x = fst z
y = snd z

we'd get

  z :: forall a b . (a->a, b->b)
  x :: forall a . a -> a

not

  x :: forall a b . a -> a

because the generalisation step for x only generalises over the type 
variables in the type arising from its right-hand side.

Cheers,
	Simon

> It seems that under MBP the second program is not equivalent to the
> first because it is more polymorphic.
> 
> -Iavor
> 
> 
> 
> On Wed, Apr 23, 2008 at 10:32 AM, Simon Marlow <marlowsd at gmail.com> wrote:
>> Folks,
>>
>>  The current proposal on the table for what to do about the monomorphism
>> restriction (henceforth MR) is
>>
>>   * remove the MR entirely
>>   * adopt Monomorphic Pattern Bindings (MPB)
>>
>>  Right now, the committee is almost uniformly in favour of dropping the MR,
>> and most of us are coming round to the idea of MPB.  Since this area has
>> historically been difficult to achieve a concensus on, I'm excited that we
>> appear to be close to making a decision, and a good one at that!
>>
>>  The arguments for removing the MR are pretty well summarised on the wiki:
>>
>>  http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphismRestriction
>>
>>  You can read about MPB here:
>>
>>
>> http://hackage.haskell.org/trac/haskell-prime/wiki/MonomorphicPatternBindings
>>
>>  GHC has implemented MPB by default (i.e. we deviate slightly from Haskell
>> 98) since 6.8.1.
>>
>>  The nice thing about the combination of removing MR and adopting MPB is
>> that we retain a way to explicitly declare monomorphic bindings.  These are
>> monomorphic bindings:
>>
>>   ~x = e
>>   x at _ = e
>>
>>  or if you don't mind a strict binding: !x = e.  The wiki points out that
>>
>>   (x) = e
>>
>>  would also be monomorphic, but arguably this is in poor taste since we
>> expect (x) to mean the same as x everywhere.
>>
>>  Cheers,
>>         Simon
>>  _______________________________________________
>>  Haskell-prime mailing list
>>  Haskell-prime at haskell.org
>>  http://www.haskell.org/mailman/listinfo/haskell-prime
>>



More information about the Haskell-prime mailing list