<div dir="ltr"><div>I suspect that if `null` still had type `[t]  -> Bool`, Julian's code would compile.</div><div><br></div><div> /g<br></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Tue, Nov 16, 2021 at 10:27 AM Richard Eisenberg <<a href="mailto:lists@richarde.dev">lists@richarde.dev</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex">Perhaps you're right -- the monomorphism restriction wouldn't fire there, because there's no constraint to monomorphise. Instead, you just want a monomorphic `new`.... but I see no easy way (other than a type signature) to get this.<br>
<br>
Think of it this way: without the type annotation, you've said `let new = undefined in ...`. Now, replace `new` with `undefined` everywhere you've written `new`. Your code will include `null undefined`, which is indeed irresolvably ambiguous.<br>
<br>
Richard<br>
<br>
> On Nov 16, 2021, at 7:44 AM, Julian Bradfield <<a href="mailto:jcb%2Bhc@julianbradfield.org" target="_blank">jcb+hc@julianbradfield.org</a>> wrote:<br>
> <br>
>> My guess is that you've disabled the monomorphism restriction somehow... but you need the MR to type-check this code. Without the MR, `new` gets a type `forall a. a`, which gets specialized differently in `new`'s two occurrences, meaning that the type information from the second occurrence doesn't affect the first one... which you need it to in order to type-check the `null new` call.<br>
> <br>
> Hm. I see the MR is off at the command prompt by default, but on in<br>
> compiled modules. The offending code was in a module starting:<br>
> <br>
> module CLTutorial9 where<br>
> import Prelude hiding (lookup)<br>
> import Data.Set(Set, insert, empty, member, fromList, toList,<br>
>                 union,intersection, size, singleton, (\\))<br>
> import qualified Data.Set as S<br>
> import Test.QuickCheck<br>
> import Data.Char<br>
> <br>
> <br>
> I haven't knowingly done any thing to turn off the MR.<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
Only members subscribed via the mailman list are allowed to post.</blockquote></div><br clear="all"><br>-- <br><div dir="ltr" class="gmail_signature">Prosperum ac felix scelus virtus vocatur<br> -- Seneca</div>