[Haskell] Typing in haskell and mathematics

Tomasz Zielonka tomasz.zielonka at gmail.com
Fri Jan 28 11:29:09 EST 2005


On Fri, Jan 28, 2005 at 10:01:33AM -0500, Jacques Carette wrote:
> The previous post on record syntax reminded me of some 'problems' I had 
> noticed where Haskell and mathematics have a (deep) usage mismatch.
> 
> First, consider a syntax for other component-wise function application?  
> For example, it would be convenient to have (f,g) @ (x,y)
> be (f x, g y).  In some languages [with dynamic typing], one can even do 
> (f,g) (x,y) :-)  
> Yes, I am aware that this untypeable in Haskell, because polymorphism is 
> straight-jacketed by structural rules.

It's not as bad as you think. You can do this:

    {-# OPTIONS -fglasgow-exts #-}

    module Apply where

    class Apply f a b | f -> a, f -> b where
        apply :: f -> a -> b

    instance Apply (a -> b) a b where
        apply f a = f a

    instance Apply (a1 -> b1, a2 -> b2) (a1, a2) (b1, b2) where
        apply (f1, f2) (a1, a2) = (f1 a1, f2 a2)

    instance Apply (a1 -> b1, a2 -> b2, a3 -> b3) (a1, a2, a3) (b1, b2, b3) where
        apply (f1, f2, f3) (a1, a2, a3) = (f1 a1, f2 a2, f3 a3)

And then:

*Apply> (succ, pred, show) `apply` (1, 2, ())
(2,1,"()")

*Apply> (\x -> 2 * x + 1/2, length) `apply` (10, [1,2,3,4,5])
(20.5,5)

Best regards,
Tomasz


More information about the Haskell mailing list