[Haskell-cafe] type checking failure curiosity

J. Garrett Morris jgbm at acm.org
Thu Nov 18 03:27:52 UTC 2021


I suspect that if `null` still had type `[t]  -> Bool`, Julian's code would
compile.

 /g

On Tue, Nov 16, 2021 at 10:27 AM Richard Eisenberg <lists at richarde.dev>
wrote:

> 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.
>
> 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.
>
> Richard
>
> > On Nov 16, 2021, at 7:44 AM, Julian Bradfield <
> jcb+hc at julianbradfield.org> wrote:
> >
> >> 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.
> >
> > Hm. I see the MR is off at the command prompt by default, but on in
> > compiled modules. The offending code was in a module starting:
> >
> > module CLTutorial9 where
> > import Prelude hiding (lookup)
> > import Data.Set(Set, insert, empty, member, fromList, toList,
> >                 union,intersection, size, singleton, (\\))
> > import qualified Data.Set as S
> > import Test.QuickCheck
> > import Data.Char
> >
> >
> > I haven't knowingly done any thing to turn off the MR.
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.



-- 
Prosperum ac felix scelus virtus vocatur
 -- Seneca
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20211117/d3b0a21d/attachment.html>


More information about the Haskell-Cafe mailing list