
On 14 October 2010 08:56, Max Bolingbroke
But if the only operation you ever do on this pair is (.), you may as well skolemise and just store (fnA1 . fnA2) directly. What is the advantage of doing otherwise?
I forgot to mention that if you *really really* want to program with the type [exists b. (b -> a, b)] directly you can do it without defining a new data type to hold the existential package by using CPS style and making use of the logical law that not(exists a. P[a]) <==> forall a. not(P[a]): """ {-# LANGUAGE Rank2Types, ImpredicativeTypes #-} foo :: [forall res. (forall b. (b -> Bool, b) -> res) -> res] foo = [\k -> k (not, True), \k -> k ((<10), 5), \k -> k (uncurry (==), ("Hi", "Hi"))] main :: IO () main = print $ [k (\(f, x) -> f x) | k <- foo] """ I pass to each "k" in the "foo" list a continuation that consumes that item in the list (in this case, a function and its arguments) and returns a result of uniform type (in this case, Bool). Cheers, Max