Suppose I have a Category C

> import Prelude hiding ((.), id)
> import Control.Category
>
> data C a b
>
> instance Category C where
>        (.) = undefined
>        id = undefined

which has "products" in the sense that there exists a "factors" function
with suitable properties

> factors :: C a (b, c) -> (C a b, C a c)
> factors = undefined

Then I can define this interesting combinator

> (~~) :: (C a b -> r) -> (C a c -> r') -> C a (b, c) -> (r, r')
> (f ~~ g) h = let (l, r) = factors h in (f l, g r)

which allows some form of "pattern matching", for example

> a :: C z a
> b :: C z b 
> c :: C z c
> d :: C z d
> e :: C z e
> ((a, b), (c, (d, e))) = ((id ~~ id) ~~ (id ~~ (id ~~ id))) undefined

and even

> w :: C a w
> x :: C a x
> y :: C a y
> z :: (C a z, C a z')
> ((w, x), (y, z)) = ((id ~~ id) ~~ (id ~~ (id ~~ id))) undefined

Does anyone have anything to say about this?  I'm sure others must have come
across it before.  There's something very lensy going on here too.  There's
nothing special about 'Category's here, but it's an example where the
structure is demonstrated nicely.

It's a shame that the structure of the pattern must be duplicated on the
left and right of the binding.

Tom

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to