Circular Typing with Constraints

In the example below, I'm trying to make foo return its "expected" polymorphic output type. The idea is that foo returns a polymorphic value and an existential type, and then bar specifies the type of the tuple to be the hidden type. (Of course this only works if the type in bar is also existential, which is true in my case.) The following example compiles:

{-# LANGUAGE GADTs, ScopedTypeVariables #-}

module Foo where

import Data.Proxy
import Data.Typeable

data HiddenType where
  Hidden :: (Typeable a) => Proxy a -> HiddenType

foo :: (i,HiddenType)
foo = (undefined, Hidden (Proxy::Proxy Int))

data Foo where
  Foo :: i -> Foo

bar :: Foo
bar = 
  let (x,h) = foo
  in case h of 
    (Hidden (p::Proxy i)) -> Foo (x :: i)

I really need a Typeable constraint on foo :

foo :: (Typeable i) => (i,HiddenType)

When I add that constraint (no other changes), I get these errors:

Foo.hs:20:15:
    No instance for (Typeable t0) arising from a use of ‘foo’
    The type variable ‘t0’ is ambiguous
    Relevant bindings include x :: t0 (bound at Foo.hs:20:8)
    Note: there are several potential instances:
      instance [overlap ok] Typeable ()
        -- Defined in ‘Data.Typeable.Internal’
      instance [overlap ok] Typeable Bool
        -- Defined in ‘Data.Typeable.Internal’
      instance [overlap ok] Typeable Char
        -- Defined in ‘Data.Typeable.Internal’
      ...plus 14 others
    In the expression: foo
    In a pattern binding: (x, h) = foo
    In the expression:
      let (x, h) = foo
      in case h of { (Hidden (p :: Proxy i)) -> Foo (x :: i) }

Foo.hs:22:35:
    Couldn't match expected type ‘a’ with actual type ‘t0’
      because type variable ‘a’ would escape its scope
    This (rigid, skolem) type variable is bound by
      a pattern with constructor
        Hidden :: forall a. Typeable a => Proxy a -> HiddenType,
      in a case alternative
      at Foo.hs:22:6-24
    Relevant bindings include
      p :: Proxy a (bound at Foo.hs:22:14)
      x :: t0 (bound at Foo.hs:20:8)
    In the first argument of ‘Foo’, namely ‘(x :: i)’
    In the expression: Foo (x :: i)
Failed, modules loaded: none.

I understand that constraints turn into arguments in core, so it seems to me that the issue here is that GHC can't handle pattern bindings for GADTs. If it could, I could use a recursive let to say something like:

bar :: Foo
bar = 
  let (x :: i,h) = foo
      (Hidden (p::Proxy i)) = h
  in Foo x

That should make the constraint in scope, providing the extra argument to foo . My intent here is that h contains some (hidden) concrete type i , which should be used as the concrete type for the polymorphic function GHC complains:

Foo.hs:19:8:
    You cannot bind scoped type variable ‘i’
      in a pattern binding signature
    In the pattern: x :: i
    In the pattern: (x :: i, h)
    In a pattern binding:
      (x :: i, h) = foo

Foo.hs:20:8:
    My brain just exploded
    I can't handle pattern bindings for existential or GADT data constructors.
    Instead, use a case-expression, or do-notation, to unpack the constructor.
    In the pattern: Hidden (p :: Proxy i)
    In a pattern binding: (Hidden (p :: Proxy i)) = h
    In the expression:
      let
        (x :: i, h) = foo
        (Hidden (p :: Proxy i)) = h
      in Foo x

The assumptions for my use case are that 1. foo computes i and the HiddenType simultaneously 2. The value of the hidden type involves (at least partial) computation of the first tuple element. This means I do not want to call foo twice in bar (once to get the HiddenType , and once to use that type to bind the first tuple element). Is there some way to make the definition of bar possible in the presence of a constraint on foo ?


I suppose the problem is that foo s return value isn't actually polymorphic. foo itself is polymorphic but the returned value must exist at a specific type. Unfortunately, the type you want to use isn't available yet and cannot be brought into scope at foo s call site because of the circular reference. If we write out the definition of foo in pseudo-core, the problem is clear:

foo (@ iType) _ = (undefined @ iType, HiddenType...)

Here @ iType is a type argument. We need to do foo's type application first (and the dictionary application, which is unused) before getting the HiddenType , so there's no way to make this work as-is.

Fortunately, there is a way to convince ghc that foo should return an actual polymorphic value:

{-# LANGUAGE GADTs, ScopedTypeVariables #-}
{-# LANGUAGE ImpredicativeTypes #-}

module Foo where

import Data.Proxy
import Data.Typeable

data HiddenType where
  Hidden :: (Typeable a) => Proxy a -> HiddenType

foo :: (forall i. Typeable i => i,HiddenType)
foo = (undefined, Hidden (Proxy::Proxy Int))

data Foo where
  Foo :: i -> Foo

bar = 
  let (x,h) = foo
  in case h of
    Hidden p -> Foo (x `asProxyTypeOf` p)

If you're familiar with higher-rank types (eg the RankNTypes extension), you can think of ImpredicativeTypes as something similar, except for data structures instead of functions. For example, without ImpredicativeTypes you can write:

list1 :: forall t. Typeable t => [t]

which is the type of a list that contains all values of type t , for some t with a Typeable constraint. Even though it's polymorphic, every element of the list will be of the same type! If instead you wish to move the forall inside the list, so that every element may be a different type t , ImpredicativeTypes will allow this:

list2 :: [forall t. Typeable t => t]

It's not a commonly-enabled extension, but it is occasionally useful.

The core for the impredicative version of foo is a bit different as well:

foo = ((@ iType) _ -> undefined @ iType, HiddenType...)

You can see that this allows for x to be polymorphic as desired if you add an annotation to the let :

bar :: Foo
bar = 
  let (x :: forall i. Typeable i => i,h) = foo
  in case h of
    Hidden p -> Foo (x `asProxyTypeOf` p)

This allows you to delay the instantiation of x at the hidden type until later, when it's available. You still need to box it up inside Foo or another Hidden though, as ghc won't allow the type to escape from under the first Hidden pattern match.

链接地址: http://www.djcxy.com/p/7456.html

上一篇: 如何在这个例子中得到更好的Haskell中的多态类型推断?

下一篇: 循环键入约束