[Haskell] Type of y f = f . f

Keean Schupke k.schupke at imperial.ac.uk
Tue Mar 1 13:49:20 EST 2005


Here's a type that fits:

    d :: forall b a t c. (F t c b, F t a c) => t -> a -> b

from the following code:

 >-# OPTIONS -fglasgow-exts #-}
 >module Main where
 >
 >main :: IO ()
 >main = putStrLn "OK"
 >
 >data ID = ID
 >data HEAD = HEAD
 >data FST = FST
 >
 >class F t a b | t a -> b where
 >        f :: t -> a -> b
 >instance F ID a a where
 >        f _ a = a
 >instance F HEAD [a] a where
 >        f _ a = head a
 >instance F FST (a,b) a where
 >        f _ a = fst a
 >
 >d :: (F t a c, F t c b) => t -> a -> b
 >d t = f t . f t
 >
 >t0 a = d ID a
 >t1 a = d HEAD a
 >t2 a = d FST a

Keean.

Jim Apple wrote:

> Is there a type we can give to
>
> y f = f . f
>
> y id
> y head
> y fst
>
> are all typeable?
>
> Jim Apple
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell




More information about the Haskell mailing list