Mine is somewhat more elegant...


data (CatList a)       =  CatNil
                       |  Wrap a
                       |  Cat (CatList a) (CatList a) deriving Show


instance (Eq a) => Eq (CatList a) where
   CatNil      == CatNil = True
   Wrap x      == Wrap y = x==y
 
   a@(Cat x y) == b      = case (adjust a) of
                              CatNil  -> b==CatNil
                              Wrap x  -> (adjust b)==Wrap x
                              Cat x y ->
                                 case (adjust b) of
                                   Cat z w   -> (x==z) && (y==w)
                                   otherwise -> False
  
   b == a@(Cat x y) = a==b
   _ == _ = False
 
adjust                           :: CatList a -> CatList a
adjust (Cat CatNil x) = x
adjust (Cat x CatNil) = x
adjust (Cat (Cat x y) z) = adjust (Cat x (Cat y z))
adjust (Cat x y) = Cat (adjust x) (adjust y)
adjust x = x


You don't have to evaluate everything. Just do a recursion fixing the associative rule.



2009/3/4 R J <rj248842@hotmail.com>
Could someone provide an elegant solution to Bird problem 4.2.13?

Here are the problem and my inelegant solution:

Problem
-------

Since concatenation seems such a basic operation on lists, we can try to construct a data type that captures
concatenation as a primitive.

For example,

data (CatList a)       =  CatNil
                       |  Wrap a
                       |  Cat (CatList a) (CatList a)

The intention is that CatNil represents [], Wrap x represents [x], and Cat x y represents
x ++ y.

However, since "++" is associative, the expressions "Cat xs (Cat ys zs)" and "Cat (Cat xs ys) zs" should be regarded as equal.

Define appropriate instances of "Eq" and "Ord" for "CatList".

Inelegant Solution
------------------

The following solution works:

instance (Eq a) => Eq (CatList a) where
    CatNil      ==  CatNil       =    True
    CatNil      ==  Wrap   z     =    False
    CatNil      ==  Cat    z w   =  ( z == CatNil  && w == CatNil )

    Wrap   x    ==  CatNil       =    False
    Wrap   x    ==  Wrap   z     =    x == z
    Wrap   x    ==  Cat    z w   =  ( Wrap x == z  && w == CatNil ) ||
                                    ( Wrap x == w  && z == CatNil )


    Cat    x y  ==  CatNil       =    x == CatNil  && y == CatNil
    Cat    x y  ==  Wrap   z     =  ( x == Wrap z  && y == CatNil ) ||
                                    ( x == CatNil  && y == Wrap z )

    Cat    x y  ==  Cat    z w   =  unwrap (Cat x y) == unwrap (Cat z w)

unwrap                           :: CatList a -> [a]
unwrap CatNil                    =  []
unwrap (Wrap x)                  =  [x]
unwrap (Cat x y)                 =  unwrap x ++ unwrap y

instance (Eq a, Ord a) => Ord (CatList a) where
    x < y = unwrap x < unwrap y

This solution correctly recognizes the equality of the following, including nested lists(represented, for example, by Wrap (Wrap 1), which corresponds to [[1]]):

Wrap 1                               == Cat (Wrap 1) CatNil
Cat (Wrap 1) (Cat (Wrap 2) (Wrap 3)) == Cat (Wrap 1) (Cat (Wrap 2) (Wrap 3))
Wrap (Wrap 1)                        == Wrap (Cat (Wrap 1) CatNil)

Although this solution works, it's a hack, because unwrap converts CatLists to lists.  The question clearly seeks a pure solution that does not rely on Haskell's built-in lists.

What's the pure solution that uses cases and recursion on
CatList, not Haskell's built-in lists, to capture the equality of nested CatLists?



Windows Live™ Contacts: Organize your contact list. Check it out.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




--
Rafael Gustavo da Cunha Pereira Pinto
Electronic Engineer, MSc.