Trying to abstract away typeclass, but a type variable escapes

核能气质少年 提交于 2020-07-09 05:55:11

问题


I have some classes and their instances. The example shows some nonsensical classes. Their exact nature is not important.

{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}


class Foo a where
   foo :: a -> Int
class Bar a where
   bar :: a -> String

instance Foo Int where
   foo x = x
instance Foo String where
   foo x = length x

instance Bar Int where
   bar x = show x
instance Bar String where
   bar x = x

OK, now I want to create some existential types that hide these classes behind some datatype façade, so I don't have to deal with constraints. (I know existential types are considered an anti-pattern, please don't explain this to me).

data TFoo = forall a. Foo a => TFoo a
instance Foo TFoo where
  foo (TFoo x) = foo x
data TBar = forall a. Bar a => TBar a
instance Bar TBar where
  bar (TBar x) = bar x

Obviously there's some boilerplate in there. I want to abstract it away.

{-# LANGUAGE ConstraintKinds #-}
data Obj cls = forall o. (cls o) => Obj o

So instead of several existential types I have just one, parametrised by a typeclass. So far so good.

Now how do I perform operations on Obj a? The obvious attempt

op f (Obj a) = f a

fails because the type variable could escape.

existential.hs:31:18: error:
    • Couldn't match expected type ‘o -> p1’ with actual type ‘p’
        because type variable ‘o’ would escape its scope
      This (rigid, skolem) type variable is bound by
        a pattern with constructor:
          Obj :: forall (cls :: * -> Constraint) o. cls o => o -> Obj cls,
        in an equation for ‘call’
        at existential.hs:31:9-13
    • In the expression: f k
      In an equation for ‘call’: call f (Obj k) = f k
    • Relevant bindings include
        k :: o (bound at existential.hs:31:13)
        f :: p (bound at existential.hs:31:6)
        call :: p -> Obj cls -> p1 (bound at existential.hs:31:1)
   |
31 | call f (Obj k) = f k
   |                  ^^^
Failed, no modules loaded.

I kinda understand why this happens. But with real invocations like call foo and call bar the type variable wouldn't escape. Can I convince the compiler of it? Perhaps I somehow can express the type u -> v where v does not mention u (which really should be the type of f)? If not, what other ways to deal with the situation are there? I guess I could generate something with TemplateHaskell but I still cannot wrap my head around it.


回答1:


Your code works fine; the compiler just needs some help with its type.

Obj hides the type of its contents, which means that op's argument f must be polymorphic (that is, it can't scrutinise its argument). Turn on RankNTypes:

op :: (forall a. cls a => a -> r) -> Obj cls -> r
op f (Obj x) = f x

You have to give the type signature in full because GHC can't infer higher-rank types.

Existentially quantifying over a class like this is usually not the best way to design a given program.



来源:https://stackoverflow.com/questions/62667612/trying-to-abstract-away-typeclass-but-a-type-variable-escapes

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