[Haskell-cafe] Re: Type constrain in instance?

Louis Zhuang louis.zhuang at acm.org
Fri Apr 9 14:40:32 EDT 2010


Casey McCann <syntaxglitch <at> gmail.com> writes:

> {-# LANGUAGE MultiParamTypeClasses, GADTs #-}
> import qualified Control.Category as Cat
> 
> data ChainableFunction a b where
>     CF :: (Num a, Num b) => (a->b) -> (a->b) -> ChainableFunction a b
>     CFId :: ChainableFunction a a
> 
> instance Cat.Category ChainableFunction where
>     id = CFId
>     CF g g' . CF f f' = CF (g.f) (\a -> f' a *> g' (f a))
>     CFId . f = f
>     g . CFId = g
> 
> You've probably noticed that I've been ignoring the Module class.
> Unfortunately, the solution thus far is insufficient; a Module
> constraint on the CF constructor does work as expected, providing a
> context with (Module a b, Module b c), but the result requires an
> instance for Module a c, which neither available, nor easily obtained.
> I'm not sure how best to handle that issue; if you find the rest of
> this useful, hopefully it will have given you enough of a start to
> build a complete solution.
> 
> - C.
> 


Thanks for the comment. If we try to use GADT to construct Cat.id, actually
(Numa) constraint is redundant because I just want "1" for first derivative
of x.

However instance (Module a b, Module b c) => Module a c is a must for
chain rule... I'm looking at Data.Category suggested by Jason, because it
allows subset of Hask object to be applied into parameters



More information about the Haskell-Cafe mailing list