[Haskell-cafe] Instance of Eq on cyclic data structure?
Leonard Siebeneicher
leosieb at arcor.de
Tue May 13 12:29:10 EDT 2008
Hi.
I am testing a winged edge data structure.
> module Main where
>
> type Point3 = (Float, Float, Float)
>
> data Body= Body [Vertex] [Edge] [Face] deriving(Eq)
> data Face= Face Edge deriving(Eq)
> data Edge= Edge (Vertex, Vertex)
> (Face, Face)
> (Edge, Edge)
> (Edge, Edge) deriving(Eq)
> data Vertex= Vertex Point3 Edge deriving(Eq)
...
> --- Face, Edge, Vertex: Conversion
>
> getVertsFromFace :: Face -> [Vertex]
> getVertsFromFace (Face startEdge) = process_wing_clockwise startEdge
> where
> process_wing_clockwise (Edge
> (vp, _)
> _
> (_, eWing1)
> _)
> | startEdge == eWing1 =
> [vp]
> | otherwise =
> vp : (process_wing_clockwise eWing1)
>
>
> --- Misc procedures
> printPointList :: [Vertex] -> IO ()
> printPointList [] = return ()
> printPointList ((Vertex p _ ):vs) = putStr (show p) >>
> printPointList vs
>
> --- main
> main =
> do
> let q = createQuad (0,0,0) (0,1,0) (1,1,0) (1,0,0)
> let f = (\(Body _ _ (face:faces)) -> face) q
> let verts = getVertsFromFace f
> printPointList verts
>
>
Here I get a error message.
> (0.0,0.0,0.0)(0.0,1.0,0.0)(1.0,1.0,0.0)runhugs: Error occurred
>
> ERROR - Control stack overflow
>
I think this come because the derived Eq-Instance "==" get into an
infinite loop
Alternatively I tried following
> --- We want to identify each Body, Face, Edge or Vertex by a number ID
> type ID = Int --- A special number for identifying, used for Eq
>
> data Body = Body ID [Vertex] [Edge] [Face]
> data Face = Face ID (Edge)
> data Edge = Edge ID
> (Vertex , Vertex)
> (Face , Face)
> (Edge , Edge)
> (Edge , Edge)
> data Vertex = Vertex ID Edge
>
> --- Eq Instances
> instance Eq Vertex) where
> (Vertex i1 _) == (Vertex i2 _) = i1 == i2
>
> instance Eq Face where
> (Face i1 _ ) == (Face i2 _) = i1 == i2
>
> instance Eq Edge where
> (Edge i1 _ _ _ _) == (Edge i2 _ _ _ _) = i1 == i2
>
>
> instance Eq (Body) where
> (Body i1 _ _ _) == (Body i2 _ _ _) = i1 == i2
...
This way my code does not hang up. But I have to manage those ugly ID's.
Is there a better way to create instances of class Eq, without something
like ID?
Thanks for reading.
Best regards, Leonard
>
>
> --------------------
> --------------------
> ---- Begin ----
> --------------------
> module Main where
>
> type Point3 = (Float, Float, Float)
>
> data Body= Body [Vertex] [Edge] [Face] deriving(Eq)
> data Face= Face Edge deriving(Eq)
> data Edge= Edge (Vertex, Vertex)
> (Face, Face)
> (Edge, Edge)
> (Edge, Edge) deriving(Eq)
> data Vertex= Vertex Point3 Edge deriving(Eq)
>
> {-
> implementing simple generative modelling
> -}
>
> --- elementar object generation
> createQuad :: Point3 ->
> Point3 ->
> Point3 ->
> Point3 ->
> Body
>
> createQuad p0 p1 p2 p3 =
> let
> {faceFront = Face edge0
> ;faceBack = Face edge2
> ;vert0 = Vertex p0 edge0
> ;edge0 = Edge
> (vert0, vert1)
> (faceFront, faceBack)
> (edge3, edge1)
> (edge1, edge3)
> ;vert1 = Vertex p1 edge1
> ;edge1 = Edge
> (vert1, vert2)
> (faceFront, faceBack)
> (edge0, edge2)
> (edge2, edge0)
> ;vert2 = Vertex p2 edge2
> ;edge2 = Edge
> (vert2, vert3)
> (faceFront, faceBack)
> (edge1, edge3)
> (edge3, edge1)
> ;vert3 = Vertex p3 edge3
> ;edge3 = Edge
> (vert3, vert0)
> (faceFront, faceBack)
> (edge2, edge0)
> (edge0, edge2)
> }
> in
> Body [vert0, vert1, vert2, vert3] [edge0, edge1, edge2, edge3]
> [faceFront, faceBack]
>
> --- Face, Edge, Vertex: Conversion
>
> getVertsFromFace :: Face -> [Vertex]
> getVertsFromFace (Face startEdge) = process_wing_clockwise startEdge
> where
> process_wing_clockwise (Edge
> (vp, _)
> _
> (_, eWing1)
> _)
> | startEdge == eWing1 =
> [vp]
> | otherwise =
> vp : (process_wing_clockwise eWing1)
>
>
> --- Misc procedures
> printPointList :: [Vertex] -> IO ()
> printPointList [] = return ()
> printPointList ((Vertex p _ ):vs) = putStr (show p) >>
> printPointList vs
>
> --- main
> main =
> do
> let q = createQuad (0,0,0) (0,1,0) (1,1,0) (1,0,0)
> let f = (\(Body _ _ (face:faces)) -> face) q
> let verts = getVertsFromFace f
> printPointList verts
> -----------------
> ---- End ----
More information about the Haskell-Cafe
mailing list