2008/12/15 Mario Blazevic <mblaze...@stilo.com> > Alexander Dunlap wrote: > >> The problem is that y is not mentioned in the signature of wrapper. >> When you call wrapper x, there could be many different instances of >> Container x y with the same x, so GHC doesn't know which version to >> call. >> > > > I guess I see it now. However, if the explicit 'Container x y =>' > context couldn't fix the y to use for instantiation of Container x y, I > don't see any way to fix it. And if there is no way to call wrapper in any > context, the class declaration itself is illegal and GHC should have > reported the error much sooner. Should I create a ticket? >
Please do not create a ticket. Such a typeclass is legitimate, but not useful alone or with functional dependencies. It is useful with Type Families though, so celebrate! Thomas ----- START CODE ---- {-# LANGUAGE TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-} import Data.Maybe class Container x where type Contains x wrapper :: x -> Bool unwrap :: x -> Contains x rewrap :: Contains x -> x liftWrap :: Container x => (Contains x -> Contains x) -> x -> x liftWrap f x = (if wrapper x then rewrap . f . unwrap else id) x instance Container (Maybe x) where type Contains (Maybe x) = x wrapper = isJust unwrap = fromJust rewrap = Just main = print (liftWrap (succ :: Int -> Int) (Just 1 :: Maybe Int)) -----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe