How can I apply an arbitrary function in an existential envelope?

I'm trying to write a function (called here hide

) that can enforce a fairly polymorphic function inside an existential wrapper (or hoist functions to work with wrappers with hidden types and therefore "hide"):

{-# LANGUAGE GADTs
           , RankNTypes
  #-}

data Some f
  where Some :: f a -> Some f


hide :: (forall a. f a -> g b) -> Some f -> Some g
hide f (Some x) = Some (f x)


data Phantom a = Phantom

cast :: Phantom a -> Phantom b
cast Phantom = Phantom

works :: Some Phantom -> Some Phantom
works = hide cast


doesn't :: Functor f => Some f -> Some f
doesn't = hide (fmap $ \x -> [x])
{-
foo.hs:23:17:
    Couldn't match type โ€˜b0โ€™ with โ€˜[a]โ€™
      because type variable โ€˜aโ€™ would escape its scope
    This (rigid, skolem) type variable is bound by
      a type expected by the context: f a -> f b0
      at foo.hs:23:11-33
    Expected type: f a -> f b0
      Actual type: f a -> f [a]
    In the first argument of โ€˜hideโ€™, namely โ€˜(fmap $ \ x -> [x])โ€™
    In the expression: hide (fmap $ \ x -> [x])
    In an equation for โ€˜doesn'tโ€™: doesn't = hide (fmap $ \ x -> [x])
Failed, modules loaded: none.
-}


but :: Functor f => Some f -> Some f
but = hide' (fmap $ \x -> [x])
  where hide' :: (forall a. f a -> g [a]) -> Some f -> Some g
        hide' f (Some x) = Some (f x)

      

So, I really understand why this is happening; works

shows what hide

really works when the return type is completely unrelated to the input type, but in doesn't

I call hide

with a type argument a -> [a]

. hide

should get "select" type a

( RankNTypes

), but is b

usually polymorphic. When it b

actually depends a

, it a

can seep.

But in the context where I am actually calling it, a

it doesn't really leak; I end it immediately at Some

. And in fact I can write an alternative hide'

that accepts specifically a -> [a]

functions and works with the same implementation , just a different type of signature.

Is there any way to introduce an implementation hide f (Some x) = Some (f x)

to make it work more broadly? In fact, I'm interested in lifting functions with a type a -> q a

, where q

is some arbitrary function of the type; that is, I expect the return type to depend on a

, but I don't care how it's done. There are probably cases where q a

is a constant (i.e. the return type is independent of a

), but I think they will be much less common.

This example is pretty silly, obviously. In my actual use case, I have a GADT Schema a

that roughly represents types in the external type system; the phantom parameter provides a Haskell type that can be used to represent values โ€‹โ€‹in the external type system. I need this phantom parameter to keep all types safe, but sometimes I build Schema

from runtime data, in which case I don't know what the parameter type is.

I think you need a different type that is type parameter agnostic. Instead of doing (yet) another parallel type, I was hoping to use a simple existential type wrapper Some

to build it from Schema

, and be able to elevate the type's functions forall a. Schema a -> Schema b

to Some Schema -> Some Schema

. So if I have an XY problem and I would be better off using some other ways to pass Schema a

for the unknown a

, that would also solve my problem.

+3


source to share


2 answers


As David Young says, you can write

hide' :: (forall a. f a -> g (q a)) -> Some f -> Some g
hide' f (Some x) = Some (f x)

does :: Functor f => Some f -> Some f
does = hide' (fmap (:[]))

      

but instead of making it hide

fmap-like, you can make it bind-like:

hide'' :: (forall a. f a -> Some g) -> Some f -> Some g
hide'' f (Some x) = f x

does :: Functor f => Some f -> Some f
does = hide'' (Some . fmap (:[]))

      



But this is a bit arbitrary.

Or more generally

elim :: (forall a. f a -> c) -> Some f -> c
elim f (Some x) = f x

      

+4


source


I'm not sure how useful this is for your larger use, as you will have to refactor all existing operations to use the continuation transmission style, but continuations can be used to implement hide

that works for both of your examples and keeps b

completely common.

hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some

cast :: Phantom a -> (forall b. Phantom b -> r Phantom) -> r Phantom
cast Phantom f = f Phantom

works :: Some Phantom -> Some Phantom
works = hide cast

alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide (\a f -> f $ fmap (\x -> [x]) a)

      



You can do this somewhat better by undoing the CPS conversion, which allows you to more easily use existing functions like your original one cast

:

hide :: (forall r a. f a -> (forall b. g b -> r g) -> r g) -> Some f -> Some g
hide f (Some x) = f x Some

cps :: (f a -> g b) -> (f a -> (forall c. g c -> r) -> r)
cps f a c = c (f a)

cast :: Phantom a -> Phantom b
cast Phantom = Phantom

works :: Some Phantom -> Some Phantom
works = hide $ cps cast

alsoWorks :: Functor f => Some f -> Some f
alsoWorks = hide $ cps $ fmap (\x -> [x])

      

+2


source







All Articles