
{- Hi, I am trying to get some Haskell code to run from a research paper[1] The relevant fragment is shown below. The issue is that I cannot get the code to run using the original Eq instance. I have replaced the Eq instance with a set of deriving statements on the data types and this works fine. But I am anxious to know why I get the error when using the original code. Also, it seems reasonable to be able to define equality based on names. With the original Eq Instance I get the following error: Context reduction stack overflow;... In the expression: elem car cars In an equation for `element': element car cars = elem car cars In the instance declaration for `Collection Cars Car' I am not too sure how to interpret this message. Any clarification of the error and possible fix would be appreciated. Thanks, Pat [1] ifgi.uni-muenster.de/~sumitsen/sen_Font05.pdf -} {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances,FunctionalDependencies, TypeSynonymInstances,UndecidableInstances,TypeSynonymInstances ,OverlappingInstances #-} import Data.List class Collection collection single where empty :: collection addOne :: single -> collection -> collection remove :: single -> collection -> collection element :: single -> collection -> Bool doToAll :: (single -> single) -> collection -> collection class Named object name | object -> name where name :: object -> name -- **** in original code **** -- All named objects can be compared for equality if names can instance (Eq name, Named object name) => Eq object where object1 == object2 = (name object1) == (name object2) -- could add (Eq, Show) here data Edge = Edge Node Node deriving Show -- (Eq, Show) type Name = [Char] data Node = Node Name deriving Show -- (Eq, Show) data Car = Car Node deriving Show -- (Eq, Show) type Cars = [Car] instance Named Car Name where name c = "a" instance Collection Cars Car where empty = [] -- ::Cars addOne car cars = car:cars remove car cars = delete car cars element car cars = elem car cars doToAll f cars = map f cars -- addOne (Car (Node "a")) [Car (Node "a")] -- addOne (Car (Node "a")) []::Cars -- addOne (Car (Node "b")) [(Car (Node "a"))] -- remove (Car (Node "a")) (addOne (Car (Node "b")) [(Car (Node "a"))]) -- This email originated from DIT. If you received this email in error, please delete it from your system. Please note that if you are not the named addressee, disclosing, copying, distributing or taking any action based on the contents of this email or attachments is prohibited. www.dit.ie Is ó ITBÁC a tháinig an ríomhphost seo. Má fuair tú an ríomhphost seo trí earráid, scrios de do chóras é le do thoil. Tabhair ar aird, mura tú an seolaí ainmnithe, go bhfuil dianchosc ar aon nochtadh, aon chóipeáil, aon dáileadh nó ar aon ghníomh a dhéanfar bunaithe ar an ábhar atá sa ríomhphost nó sna hiatáin seo. www.dit.ie Tá ITBÁC ag aistriú go Gráinseach Ghormáin – DIT is on the move to Grangegorman http://www.dit.ie/grangegorman
participants (1)
-
PATRICK BROWNE