No subject


Sun Oct 23 10:51:38 CEST 2011


to understand it....
Anyway, thank you.

On Thu, Nov 17, 2011 at 4:02 PM,  <oleg at okmij.org> wrote:
>
> Multi-parameter type classes are more flexible. Here is how you can
> write your old code:
>
>> {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
>>
>> class (ClassA a, ClassB b) =3D> ClassC a b where
>> =C2=A0 from :: a -> [b]
>> =C2=A0 to =C2=A0 :: a -> [b]
>>
>> data H =3D H
>>
>> class ClassA a where toInt :: a -> Int
>> class ClassB b where fromInt :: Int -> b
>>
>> instance ClassB H where fromInt _ =3D H
>>
>> data Test =3D Test { m :: H }
>> instance ClassA Test where toInt _ =3D 0
>>
>> instance ClassC Test H where
>> =C2=A0 from =3D (:[]) . m
>> =C2=A0 to =C2=A0 =3D (:[]) . m
>
>
> The constraints in the ClassC a b declaration specify that in all
> instances of ClassC, the type a must be in ClassA and the type b must
> be in ClassB. This is the case for the "ClassC Test H" instance.
>
> You can also specify that for some particular 'a' the function 'from'
> can produce the value of the type [b] for any b in ClassB. The caller
> will determine which b it wants. This is similar to your original
> intention, as I understand.
>
>> instance ClassA Int where toInt =3D id
>>
>> instance ClassB b =3D> ClassC Int b where
>> =C2=A0 from x =3D [fromInt x]
>>
>> t1:: [H]
>> t1 =3D from (5::Int)
>
>
>



--=20
=E7=AB=B9=E5=AF=86=E5=B2=82=E5=A6=A8=E6=B5=81=E6=B0=B4=E8=BF=87
=E5=B1=B1=E9=AB=98=E5=93=AA=E9=98=BB=E9=87=8E=E4=BA=91=E9=A3=9E



More information about the Haskell-Cafe mailing list