Inferred generic function typechecks as a return type but not an argument type

*爱你&永不变心* 提交于 2019-12-24 01:59:30

问题


I'm learning about SYB and rank n types, and came across a confusing case of what seems like the monomorphism restriction.

I wrote a function to find the shallowest entry that matches a predicate. Instead of a reducing function, I wanted to accept a more predicate-like function using Alternative, and transform it into a generic function myself. I decided to omit the type annotation in the let block to see how the monomorphism reduction would affect the type in this implementation:

shallowest :: (Alternative f, Typeable b) => (b -> f a) -> GenericQ (f a)
shallowest p z =
  let op = (empty `mkQ` p) in
    op z <|> foldl (<|>) empty (gmapQ op z)

This produces an error that suggests that the ambiguity in the let binding prevents the typechecker from solving the constraint Data a1.

Error: • Couldn't match type ‘d’ with ‘a1’
  ‘d’ is a rigid type variable bound by
    a type expected by the context:
      forall d. Data d => d -> m a
  ‘a1’ is a rigid type variable bound by
    the type signature for:
      shallowest :: (b -> m a) -> GenericQ (m a)

(Other bodies like head (gmapQ op z) cause an explicit error about ambiguity for the let binding along the lines of "Could not deduce (Typeable a0) arising from a use of ‘mkQ’"; I also haven't figured out why the above form doesn't).

The type error goes away when we add an annotation in the let block for op :: GenericQ (f a) (requiring ScopedTypeVariables).

However, I'm confused that it seems the Data constraint on op can be inferred: the follow typechecks when it's the return type:

shallowest p = let { op = (empty `mkQ` p) } in op

What's the difference? Both cases require op to be forall d. Data d => d -> f a; the only difference I see is that the first is in an argument position and the second is in a return position.


回答1:


In your second snippet, op is actually not polymorphic.

shallowest p = let { op = (empty `mkQ` p) } in op

It is a subtle difference: op is in fact monomorphic, but in an open context. With the usual notation for typing judgements, the typing of op to the right of in looks as follows:

 types         values
 ↓             ↓
 x, a, f, ...; op :: x -> f a, ... |- op :: x -> f a
                                            ↑
                                            monotype (no "forall")

 In English: "op has type (x -> f a) in the context consisting of type variables (x, a, f, ...) and values (op :: x -> f a, ...)"

shallowest is made polymorphic by a generalization step that happens at the toplevel. If, in a context with type variables x, a, f, ..., the body of shallowest has type x -> f a, then we can "close the context" and move the type variables into the type of shallowest :: forall x a f. x -> f a. The type derivation looks like this:

     x, a, f |- (let op = ... in op) :: x -> f a
 ⸻⸻⸻⸻⸻⸻⸻⸻⸻⸻⸻⸻⸻ (generalization)
   |- (let op = .... in op) :: forall x a f. x -> f a

(Things are complicated further by type classes and unification algorithms, but that's beside the point of this answer.)

The main problem for typechecking with polymorphism is to decide when generalization should happen. There is no general solution, by lack of principal types and by undecidability. So a typechecker implementation has to make some choices.

In Haskell, generalization happens at the following locations (the list might not be exhaustive), which are fairly natural choices:

  • function definitions, i.e., let and toplevel bindings with at least one explicit argument (here is the monomorphism restriction);

  • polymorphic arguments of higher-rank functions: if you have a function f :: (forall a. w a) -> r, then f x is going to generalize a when typechecking x;

  • and of course, when instructed by an explicit annotation _ :: forall a. t a.




回答2:


Preliminary notes: Given the evidence presented here, I will assume you are using:

  • type GenericQ r = forall a . Data a => a -> r from syb, and
  • gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] from Data.Data.

Please let me know me if I'm mistaken about that. Also, any foralls in what follows will be written explicitly.


There is more than meets the eye here. As Li-yao Xia suggests, it is a matter of generalisation involving the type of op. There are three relevant facts about your first definition of shallowest:

  1. Before generalisation, the inferred type of op is Data d => d -> f a. Given the Data d constraint, Rule 1 of the monomorphism restriction (see subsection 4.5.5 of the Report) means d in this type cannot be generalised.

  2. In the body of shallowest, op shows up in two places. The first one is op z, with z :: a1 being bound and constrained at top level by the signature of shallowest. The upshot is that this occurrence of op does not require generalisation of the argument type: as far as it is concerned, the type of op could be forall f a. a1 -> f a, monomorphic in the type variable a1 (I took this terminology from subsection 4.5.4 of the Report).

  3. The other occurrence, though, is gmapQ op z. gmapQ has a rank-2 type, requiring a polymorphic argument. That being so, this occurrence requires generalisation of the argument type of op, as noted at the end of Li-yao Xia's answer.

#1 and #3 are contradictory requirements, and so you get a type error, which can be avoided either by disabling the monomorphism restriction or by demanding op to be polymorphic on the argument type with a signature. Thanks to the other occurrence of op described in #2, the situation is reported as a mismatch involving the two occurrences.


Here follows a more minimal extended example, which might help to see what is going on. (If you are going to plop the following snippets into GHCi, besides -XRankNTypes you should also set -XMonomorphismRestriction and -XNoExtendedDefaultRules in order to see the same results.)

This is a function with a rank-2 type, which will play the role of gmapQ:

glub :: (forall x. Show x => x -> String) -> String
glub f = f 7

Now let's try a scenario similar to that involving shallowest...

foo1 :: forall a. Show a => a -> String
foo1 x = bar x ++ glub bar
  where
  bar = show

... and there is your error:

<interactive>:506:23: error:
    • Couldn't match type ‘x’ with ‘a’
      ‘x’ is a rigid type variable bound by
        a type expected by the context:
          forall x. Show x => x -> String
        at <interactive>:506:18-25
      ‘a’ is a rigid type variable bound by
        the type signature for:
          foo1 :: forall a. Show a => a -> String
        at <interactive>:505:1-38
      Expected type: x -> String
        Actual type: a -> String
    • In the first argument of ‘glub’, namely ‘bar’
      In the second argument of ‘(++)’, namely ‘glub bar’
      In the expression: bar x ++ glub bar
    • Relevant bindings include
        bar :: a -> String (bound at <interactive>:508:3)
        x :: a (bound at <interactive>:506:5)
        foo1 :: a -> String (bound at <interactive>:506:1)

Adding a wildcard where the signature of bar should go gives an additional error which is slightly more suggestive:

foo2 :: forall a. Show a => a -> String
foo2 x = bar x ++ glub bar
  where
  bar :: _
  bar = show
• Found type wildcard ‘_’ standing for ‘a -> String’
  Where: ‘a’ is a rigid type variable bound by
           the type signature for:
             foo2 :: forall a. Show a => a -> String
           at <interactive>:511:1-38
  To use the inferred type, enable PartialTypeSignatures
• In the type signature: bar :: _
  In an equation for ‘foo2’:
      foo2 x
        = bar x ++ glub bar
        where
            bar :: _
            bar = show
• Relevant bindings include
    x :: a (bound at <interactive>:512:5)
    foo2 :: a -> String (bound at <interactive>:512:1)

Note how the wildcard "standing for a -> String" is stated as a separate fact from a being bound by the type signature of foo2. I believe that corresponds to the distinction bewteen monomorphic in a type variable and polymorphic that I alluded to in point #2 above.

Giving bar a polymorphic type signature makes it work:

foo3 :: forall a. Show a => a -> String
foo3 x = bar x ++ glub bar
  where
  bar :: forall b. Show b => b -> String
  bar = show

And so does making the definition of bar pointful, which evades the monomorphism restriction by making it a "function binding" rather than a "simple pattern binding":

foo4 :: forall a. Show a => a -> String
foo4 x = bar x ++ glub bar
  where
  bar x = show x

For the sake of completeness, it is worth noting that no constraint on the type means no monomorphism restriction:

foo5 :: forall a. Show a => a -> String
foo5 x = bar x ++ glub bar
  where
  bar = const "bar"

A related situation involves using bar twice, but without a rank-2 function:

foo6 x y = bar x ++ bar y
  where
  bar = show

Which type will GHC infer for foo6?

GHCi> :t foo6
foo6 :: Show a => a -> a -> [Char]

The arguments get the same type, as doing otherwise would require generalisation of bar, which requires a type signature (or pointfullness, etc.):

foo7 x y = bar x ++ bar y
  where
  bar :: forall a. Show a => a -> String
  bar = show
GHCi> :t foo7
foo7 :: (Show a1, Show a2) => a1 -> a2 -> [Char]

Since I didn't mention it yet, here is an analogue to your second shallowest:

foo8 :: forall a. Show a => a -> String 
foo8 x = bar x
  where
  bar = show

It is worth emphasising that bar is not actually being generalised here: it is monomorphic in the type variable a. We can still break this example, by messing with foo7 rather than with bar:

foo9 = bar
  where
  bar :: _
  bar = show

In this case, bar is not generalised, and neither is foo (now pointfree and without a signature). That means the monomorphic type variable is never resolved. In terms of Rule 2 of the monomorphism restriction, it becomes an ambiguous type variable:

    <interactive>:718:14: error:
        • Found type wildcard ‘_’ standing for ‘a0 -> String’
          Where: ‘a0’ is an ambiguous type variable
          To use the inferred type, enable PartialTypeSignatures
        • In the type signature: bar :: _
          In an equation for ‘foo9’:
              foo9
                = bar
                where
                    bar :: _
                    bar = show
        • Relevant bindings include
            foo9 :: a0 -> String (bound at <interactive>:716:5)

<interactive>:719:13: error:
    • Ambiguous type variable ‘a0’ arising from a use of ‘show’
      prevents the constraint ‘(Show a0)’ from being solved.
      Relevant bindings include
        bar :: a0 -> String (bound at <interactive>:719:7)
        foo9 :: a0 -> String (bound at <interactive>:716:5)
      Probable fix: use a type annotation to specify what ‘a0’ should be.
      These potential instances exist:
        instance Show a => Show (ZipList a)
          -- Defined in ‘Control.Applicative’
        instance Show Constr -- Defined in ‘Data.Data’
        instance Show ConstrRep -- Defined in ‘Data.Data’
        ...plus 64 others
        ...plus 250 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
    • In the expression: show
      In an equation for ‘bar’: bar = show
      In an equation for ‘foo9’:
          foo9
            = bar
            where
                bar :: _
                bar = show

Adding a type signature to bar in the definition of foo9 won't help -- it just changes the point from which the error is reported. Changing bar to something without a constraint does eliminate the error, as it makes it possible to generalise both bar and foo.



来源:https://stackoverflow.com/questions/56315140/inferred-generic-function-typechecks-as-a-return-type-but-not-an-argument-type

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!