[Haskell-cafe] handling rank 2 types

Andrew Pimlott andrew at pimlott.net
Fri Nov 4 18:02:56 EST 2005


On Thu, Nov 03, 2005 at 08:35:26PM -0800, Andrew Pimlott wrote:
> I want a function
> 
> > newtype Empty = Empty (forall a. [a])
> > listToEmpty :: [v] -> IO Empty
> > listToEmpty l = liftM Empty (mapM no l) where
> >   no :: a -> IO a'
> >   no x = fail "element found"
...
> I could probably define a generic family of wrappers
> 
> > newtype Forall = Forall (forall a. a)
> > newtype Forall1 c1 = Forall1 (forall a. c1 a)

This worked out ok for me:

    newtype Forall        = Forall  { unForall  :: forall a. a }
    newtype Forall1 c1    = Forall1 { unForall1 :: forall a. c1 a }

    liftForall :: Functor f => f Forall -> Forall1 f
    liftForall f = Forall1 (fmap unForall f) 

    type Empty = Forall1 []
    listToEmptyForall :: [v] -> IO Empty
    listToEmptyForall l = liftM liftForall (mapM no l) where
      no :: a -> IO Forall
      no x = fail "element found"

I can live with that.  Hmm... it occurs to me I could instead write

    type Empty = [Forall]
    listToEmptyForall :: [v] -> IO Empty
    listToEmptyForall l = mapM no l where
      no :: a -> IO Forall
      no x = fail "element found"

Followup question:  unForall and unForall1 are no-ops at run-time.  Is
"map unForall" also a no-op?  That seems too much to ask for; I assume
the spine of the list would be copied, right?

Essentially, I'm thinking about how expensive a "cast" "[Forall] ->
[Int]" is, compared to "Forall1 [] -> [Int]", which should be free.

Andrew


More information about the Haskell-Cafe mailing list