How to express existential types using higher rank (rank-N) type polymorphism?

后端 未结 2 777
余生分开走
余生分开走 2020-12-13 10:24

We\'re used to having universally quantified types for polymorphic functions. Existentially quantified types are used much less often. How can we express existentially quant

相关标签:
2条回答
  • 2020-12-13 10:53

    I found an anwer in Proofs and Types by Jean-Yves Girard, Yves Lafont and Paul Taylor.

    Imagine we have some one-argument type t :: * -> * and construct an existential type that holds t a for some a: exists a. t a. What can we do with such a type? In order to compute something out of it we need a function that can accept t a for arbitrary a, that means a function of type forall a. t a -> b. Knowing this, we can encode an existential type simply as a function that takes functions of type forall a. t a -> b, supplies the existential value to them and returns the result b:

    {-# LANGUAGE RankNTypes #-}
    
    newtype Exists t = Exists (forall b. (forall a. t a -> b) -> b)
    

    Creating an existential value is now easy:

    exists :: t a -> Exists t
    exists x = Exists (\f -> f x)
    

    And if we want to unpack the existential value, we just apply its content to a function that produces the result:

    unexists :: (forall a. t a -> b) -> Exists t -> b
    unexists f (Exists e) = e f
    

    However, purely existential types are of very little use. We cannot do anything reasonable with a value we know nothing about. More often we need an existential type with a type class constraint. The procedure is just the same, we just add a type class constraint for a. For example:

    newtype ExistsShow t = ExistsShow (forall b. (forall a. Show a => t a -> b) -> b)
    
    existsShow :: Show a => t a -> ExistsShow t
    existsShow x = ExistsShow (\f -> f x)
    
    unexistsShow :: (forall a. Show a => t a -> b) -> ExistsShow t -> b
    unexistsShow f (ExistsShow e) = e f
    

    Note: Using existential quantification in functional programs is often considered a code-smell. It can indicate that we haven't liberated ourselves from OO thinking.

    0 讨论(0)
  • 2020-12-13 10:56

    It turns out that existential types are just a special case of Σ-types (sigma types). What are they?

    Sigma types

    Just as Π-types (pi types) generalise our ordinary function types, allowing the resulting type to depend on the value of its argument, Σ-types generalise pairs, allowing the type of second component to depend on the value of the first one.

    In a made-up Haskell-like syntax, Σ-type would look like this:

    data Sigma (a :: *) (b :: a -> *)
        = SigmaIntro
            { fst :: a
            , snd :: b fst
            }
    
    -- special case is a non-dependent pair
    type Pair a b = Sigma a (\_ -> b)
    

    Assuming * :: * (i.e. the inconsistent Set : Set), we can define exists a. a as:

    Sigma * (\a -> a)
    

    The first component is a type and the second one is a value of that type. Some examples:

    foo, bar :: Sigma * (\a -> a)
    foo = SigmaIntro Int  4
    bar = SigmaIntro Char 'a'
    

    exists a. a is fairly useless - we have no idea what type is inside, so the only operations that can work with it are type-agnostic functions such as id or const. Let's extend it to exists a. F a or even exists a. Show a => F a. Given F :: * -> *, the first case is:

    Sigma * F   -- or Sigma * (\a -> F a)
    

    The second one is a bit trickier. We cannot just take a Show a type class instance and put it somewhere inside. However, if we are given a Show a dictionary (of type ShowDictionary a), we can pack it with the actual value:

    Sigma * (\a -> (ShowDictionary a, F a))
    -- inside is a pair of "F a" and "Show a" dictionary
    

    This is a bit inconvenient to work with and assumes that we have a Show dictionary around, but it works. Packing the dictionary along is actually what GHC does when compiling existential types, so we could define a shortcut to have it more convenient, but that's another story. As we will learn soon enough, the encoding doesn't actually suffer from this problem.


    Digression: thanks to constraint kinds, it's possible to reify the type class into concrete data type. First, we need some language pragmas and one import:

    {-# LANGUAGE ConstraintKinds, GADTs, KindSignatures  #-}
    import GHC.Exts -- for Constraint
    

    GADTs already give us the option to pack a type class along with the constructor, for example:

    data BST a where
        Nil  :: BST a
        Node :: Ord a => a -> BST a -> BST a -> BST a
    

    However, we can go one step further:

    data Dict :: Constraint -> * where
        D :: ctx => Dict ctx
    

    It works much like the BST example above: pattern matching on D :: Dict ctx gives us access to the whole context ctx:

    show' :: Dict (Show a) -> a -> String
    show' D = show
    
    (.+) :: Dict (Num a) -> a -> a -> a
    (.+) D = (+)
    

    We also get quite natural generalisation for existential types that quantify over more type variables, such as exists a b. F a b.

    Sigma * (\a -> Sigma * (\b -> F a b))
    -- or we could use Sigma just once
    Sigma (*, *) (\(a, b) -> F a b)
    -- though this looks a bit strange
    

    The encoding

    Now, the question is: can we encode Σ-types with just Π-types? If yes, then the existential type encoding is just a special case. In all glory, I present you the actual encoding:

    newtype SigmaEncoded (a :: *) (b :: a -> *)
        = SigmaEncoded (forall r. ((x :: a) -> b x -> r) -> r)
    

    There are some interesting parallels. Since dependent pairs represent existential quantification and from classical logic we know that:

    (∃x)R(x) ⇔ ¬(∀x)¬R(x) ⇔ (∀x)(R(x) → ⊥) → ⊥
    

    forall r. r is almost , so with a bit of rewriting we get:

    (∀x)(R(x) → r) → r
    

    And finally, representing universal quantification as a dependent function:

    forall r. ((x :: a) -> R x -> r) -> r
    

    Also, let's take a look at the type of Church-encoded pairs. We get a very similar looking type:

    Pair a b  ~  forall r. (a -> b -> r) -> r
    

    We just have to express the fact that b may depend on the value of a, which we can do by using dependent function. And again, we get the same type.

    The corresponding encoding/decoding functions are:

    encode :: Sigma a b -> SigmaEncoded a b
    encode (SigmaIntro a b) = SigmaEncoded (\f -> f a b)
    
    decode :: SigmaEncoded a b -> Sigma a b
    decode (SigmaEncoded f) = f SigmaIntro
    -- recall that SigmaIntro is a constructor
    

    The special case actually simplifies things enough that it becomes expressible in Haskell, let's take a look:

    newtype ExistsEncoded (F :: * -> *)
        = ExistsEncoded (forall r. ((x :: *) -> (ShowDictionary x, F x) -> r) -> r)
        -- simplify a bit
        = ExistsEncoded (forall r. (forall x. (ShowDictionary x, F x) -> r) -> r)
        -- curry (ShowDictionary x, F x) -> r
        = ExistsEncoded (forall r. (forall x. ShowDictionary x -> F x -> r) -> r)
        -- and use the actual type class
        = ExistsEncoded (forall r. (forall x. Show x => F x -> r) -> r)
    

    Note that we can view f :: (x :: *) -> x -> x as f :: forall x. x -> x. That is, a function with extra * argument behaves as a polymorphic function.

    And some examples:

    showEx :: ExistsEncoded [] -> String
    showEx (ExistsEncoded f) = f show
    
    someList :: ExistsEncoded []
    someList = ExistsEncoded $ \f -> f [1]
    
    showEx someList == "[1]"
    

    Notice that someList is actually constructed via encode, but we dropped the a argument. That's because Haskell will infer what x in the forall x. part you actually mean.

    From Π to Σ?

    Strangely enough (although out of the scope of this question), you can encode Π-types via Σ-types and regular function types:

    newtype PiEncoded (a :: *) (b :: a -> *)
        = PiEncoded (forall r. Sigma a (\x -> b x -> r) -> r)
    -- \x -> is lambda introduction, b x -> r is a function type
    -- a bit confusing, I know
    
    encode :: ((x :: a) -> b x) -> PiEncoded a b
    encode f = PiEncoded $ \sigma -> case sigma of
        SigmaIntro a bToR -> bToR (f a)
    
    decode :: PiEncoded a b -> (x :: a) -> b x
    decode (PiEncoded f) x = f (SigmaIntro x (\b -> b))
    
    0 讨论(0)
提交回复
热议问题