[Haskell-cafe] type checking failure curiosity

Richard Eisenberg lists at richarde.dev
Tue Nov 16 02:25:54 UTC 2021


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.

I coincidentally ran into this same issue elsewhere today. I think we need to do a better job around error messages in this case.

Richard

> On Nov 14, 2021, at 11:52 AM, Julian Bradfield <jcb+hc at julianbradfield.org> wrote:
> 
> In the course of updating a tutorial for this year's course, I found
> the provided code didn't compile. This is because a key value is
> "undefined" in order for the students to fill it in, but I'm curious
> why it can't be typechecked nonetheless.
> 
> The code is:
> 
> reachable :: (Ord q) => FSM q ->  Set(Set(q)) -> Set(Set(q))
> reachable fsm@(FSM qs as ts ss fs) supers =
>  let new :: Set(Set(q)) -- typechecking fails without this declaration
>      new = undefined
>  in if null new then supers else reachable fsm (supers \/ new)
> 
> The \/ in the last line is just Set.union.
> 
> On the face of it, the last term directly forces "new" to have type 
> Set(Set(q)), so why doesn't Haskell see that?
> 
> Without the explicit type declaration of "new", we get:
> 
>    • Could not deduce (Foldable t0) arising from a use of ‘null’
>      from the context: Ord q
>        bound by the type signature for:
>                   reachable :: forall q. Ord q => FSM q -> Set (Set q) -> Set (Set q)
>        at CLTutorial9.hs:127:1-60
>      The type variable ‘t0’ is ambiguous
>      These potential instances exist:
>        instance Foldable (Either a) -- Defined in ‘Data.Foldable’
>        instance Foldable Set -- Defined in ‘Data.Set.Internal’
>        instance Foldable Maybe -- Defined in ‘Data.Foldable’
>        ...plus two others
>        ...plus 27 instances involving out-of-scope types
>        (use -fprint-potential-instances to see them all)
>    • In the expression: null new
>      In the expression:
>        if null new then supers else reachable fsm (supers \/ new)
>      In the expression:
>        let new = undefined
>        in if null new then supers else reachable fsm (supers \/ new)
>    |
> 130 |   in if null new then supers else reachable fsm (supers \/ new)
>    |         ^^^^^^^^
> _______________________________________________
> 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.



More information about the Haskell-Cafe mailing list