
27 Jan
2010
27 Jan
'10
1:08 a.m.
Ivan Miljenovic wrote:
2010/1/27 Tony Morris
: It might be more obvious by giving:
fromMaybe :: a -> (a -> x, x) -> x
I actually found this more confusing, and am not sure of its validity: should that be "Maybe a" there at the beginning?
Sorry a mistake. Correction: fromMaybe :: a -> ((a -> x, x) -> x) -> x {-# LANGUAGE RankNTypes #-} data Maybe' a = M (forall x. (a -> x, x) -> x) to :: Maybe' t -> Maybe t to (M f) = f (Just, Nothing) from :: Maybe a -> Maybe' a from (Just a) = M (flip fst a) from Nothing = M snd -- Tony Morris http://tmorris.net/