type class problem
Dean Herington
heringto at cs.unc.edu
Mon Sep 29 14:57:07 EDT 2003
Can someone explain why the following doesn't work? Is there some other
way to achieve the same effect (declaring a set of instances for pair-like
types in one go)?
Thanks.
Dean
swan(108)% cat Test1.hs
{-# OPTIONS -fglasgow-exts #-}
class R r where
rId :: r -> String
class (R r) => RT r t where
rtId :: r -> t -> String
data (R r1, R r2) => RPair r1 r2 = RPair r1 r2
instance (R r1, R r2) => R (RPair r1 r2) where
rId (RPair r1 r2) = "RPair " ++ rId r1 ++ " " ++ rId r2
class TPair t t1 t2 where
prj :: t -> (t1,t2)
inj :: (t1,t2) -> t
instance (RT r1 t1, RT r2 t2, TPair t t1 t2) => RT (RPair r1 r2) t where
rtId (RPair r1 r2) t = "RT (RPair " ++ rtId r1 t1 ++ " " ++ rtId r2 t2 ++ ")"
where (t1,t2) = prj t
main = return ()
swan(109)% ghci Test1.hs
___ ___ _
/ _ \ /\ /\/ __(_)
/ /_\// /_/ / / | | GHC Interactive, version 5.04.3, for Haskell 98.
/ /_\\/ __ / /___| | http://www.haskell.org/ghc/
\____/\/ /_/\____/|_| Type :? for help.
Loading package base ... linking ... done.
Loading package haskell98 ... linking ... done.
Compiling Main ( Test1.hs, interpreted )
Test1.hs:19:
Could not deduce (RT r2 t21, RT r1 t11)
from the context (RT (RPair r1 r2) t,
RT r1 t1,
RT r2 t2,
TPair t t1 t2,
R (RPair r1 r2))
Probable fix:
Add (RT r2 t21, RT r1 t11) to the class or instance method `rtId'
arising from use of `rtId' at Test1.hs:19
In the first argument of `(++)', namely `rtId r2 t2'
In the second argument of `(++)', namely `(rtId r2 t2) ++ ")"'
Test1.hs:20:
Could not deduce (TPair t t11 t21)
from the context (RT (RPair r1 r2) t,
RT r1 t1,
RT r2 t2,
TPair t t1 t2,
R (RPair r1 r2))
Probable fix:
Add (TPair t t11 t21) to the class or instance method `rtId'
arising from use of `prj' at Test1.hs:20
In a pattern binding: prj t
Failed, modules loaded: none.
Prelude>
More information about the Haskell
mailing list