On Wednesday 10 April 2002 11:07 am, Hal Daume III wrote: > Does this have a name: > > data S s a = Nil | S a (s (S s a)) > > it seems to capture the essense of many recursive data structures. With: > > newtype Id a = Id a > > newtype Pair a = Pair (a,a) > probably more...
It seems to me that this is very similar to the "Mu" datatype from Mark Jones' paper "Functional Programming with Overloading and Higher-Order Polymorphism" (http://www.cse.ogi.edu/~mpj/pubs.html) He has examples of isomorphisms with lists and rose trees, etc. Here is an example: data Mu f = In (f (Mu f)) type IntList = Mu IntListF data IntListF a = Nil | Cons Int a nil = In Nil cons x xs = In (Cons x xs) > Is there any theory about what types of recursive data structures can be > captured with "S" and what types cannot? It seems that those The paper also mentions some stuff about anamorphisms and catamorphisms, which are apparently like generalized folds and unfolds, which you might be interested in. (I don't pretend to be an expert as I have just found out about them myself.) > Also, if we want to write a show instance for S s, this seems to be > impossible. Is it? If so, is this a weakness in Haskell (cyclic instance > declarations) or is it theoretically not possible? > > - Hal Here is my attempt at a Show instance for S s (It works, but I'm not sure how to get rid of all the escaped quote marks): data S s a = Nil | S a (s (S s a)) newtype Id a = Id a instance Functor Id where fmap f (Id i) = Id (f i) instance Show a => Show (Id a) where show (Id a) = show a instance Functor s => Functor (S s) where fmap f Nil = Nil fmap f (S a ss) = S (f a) (fmap (fmap f) ss) instance (Functor s, Show a, Show (s String)) => Show (S s a) where show Nil = "Nil" show (S a ss) = show a ++ show (fmap show ss) infixr 5 `cons` cons x xs = S x (Id xs) test :: S Id Int test = 1 `cons` 2 `cons` 3 `cons` Nil main = print test -- 1"2\"3\\\"Nil\\\"\"" _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell