Lazy type-class resolution
Tomasz Zielonka
t.zielonka at students.mimuw.edu.pl
Thu Aug 12 16:49:42 EDT 2004
I forgot to attach the code. Here it is.
Tom
--
.signature: Too many levels of symbolic links
-------------- next part --------------
{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}
module Comp where
newtype F a b = F { runF :: a -> b }
class Fun f a b | f -> a, f -> b where
apply :: f -> a -> b
instance Fun (a -> b) a b where
apply f x = f x
class MatchFun a b f | f -> a, f -> b where
wrapF :: f -> F a b
instance MatchFun a b (a -> b) where
wrapF f = F f
class MkComp a b where
compose :: a -> b
instance MatchFun a b f => MkComp f (F a b) where
compose f = wrapF f
instance ( Compose r f a b
, MkComp (a -> b) t
, Fun r b1 b
, Fun f a b1 ) => MkComp r (f -> t)
where
compose r f = compose (comp r f)
class Compose t f a b | t f -> a, t f -> b where
comp :: t -> f -> a -> b
instance (Fun t b c, Fun f a b) => Compose t f a c where
comp t f x = apply t (apply f x)
More information about the Glasgow-haskell-users
mailing list