Re: Question on rank-N polymorphism

Ryan Ingram discussed a question of writing
fs f g = (f fst, g snd)
so that fs ($ (1, "2")) type checks. This is not that difficult:
{-# LANGUAGE RankNTypes, MultiParamTypeClasses -#} {-# LANGUAGE FunctionalDependencies, FlexibleInstances #-}
class Apply f x y | f x -> y where apply :: f -> x -> y
instance Apply (x->y) x y where apply = ($)
data Fst = Fst data Snd = Snd
instance Apply Fst (x,y) x where apply _ = fst
instance Apply Snd (x,y) y where apply _ = snd
The function in question:
fs3 f = (apply f Fst, apply f Snd)
-- One of Wouter Swierstra's examples -- examples = (fs id, fs repeat, fs (\x -> [x]), fs ((,)id))
data Id a = Id
instance Apply (Id a) Fst ((a,a) -> a) where apply _ _ = fst
instance Apply (Id a) Snd ((a,a) -> a) where apply _ _ = snd
ex1 = fs3 Id
Now, Ryan's main example
newtype Pair a b = Pair (forall w. (((a,b) -> w) -> w))
instance Apply (Pair a b) Fst a where apply (Pair f) _ = f fst
instance Apply (Pair a b) Snd b where apply (Pair f) _ = f snd
ex4 = fs3 (Pair ($ (1, "2"))) -- (1,"2")
Incidentally, a different variation of this example is discussed in http://okmij.org/ftp/Computation/extra-polymorphism.html Indeed, such a selection from a pair occurs quite often...
participants (1)
-
oleg@okmij.org