Circular Data Types - a directory tree abstraction

Shlomi Fish shlomif@vipe.technion.ac.il
Sun, 4 Mar 2001 17:48:35 +0200 (IST)


I want to implement a directory data type where each directory may contain
other directories, as well as end documents. I declared the following
file for managing it:

------------------------------
module Contents_Abs where

data Contents_Image url mime = MakeContents_Image url mime

get_image_url (MakeContents_Image url mime) = url
get_image_mime_type (MakeContents_Image url mime) = mime

make_image url mime = (MakeContents_Image url mime)

data Contents_Node url title subs images is_dir = 
    MakeContents_Node url title subs images is_dir

get_url (MakeContents_Node url title subs images is_dir) = url
get_title (MakeContents_Node url title subs images is_dir) = title
get_subs (MakeContents_Node url title subs images is_dir) = subs
get_is_dir (MakeContents_Node url title subs images is_dir) = is_dir

make_contents_doc url title = (MakeContents_Node url title [] [] False)

make_contents_dir url title subs = (MakeContents_Node url title subs []
True)

make_contents_dir_with_images url title subs images = (MakeContents_Node
url title subs images True)

--------------------------------------------

Now, I have the following example file:

--------------------------------------------

module Contents where

import Contents_Abs

contents = (make_contents_dir_with_images "" "Contents"
            [
                (make_contents_doc "intro.html" "Introduction"),
                (make_contents_doc "properties.html" "Properties"),
                (make_contents_dir "recursion" "Recursion"
                [
                    (make_contents_doc "fib1.html" "Fibonnaci (Take 1)"),
                    (make_contents_doc "qsort.html" "Quick Sort")
                ]
                ),
                (make_contents_dir "lazy_eval" "Lazy Evaluation"
                [
                    (make_contents_doc "primes1.html" "Primes (Take 1)"),
                    (make_contents_doc "fib2.html" "Fibonnaci (Take 2)")
                ]
                )
            ]
            [
                (make_image "style.css" "text/css")
            ]
            )
-------------------------------------------

I would like to be able to traverse this tree, so I defined the following
script:


---------------------
import Contents_Abs
import Contents

mytraverse contents = trav contents where
    trav branch = 
        (get_url branch) ++ (trav_subs (get_subs branch)) where            
            trav_subs [] = ""
            trav_subs (a:as) = (trav a) ++ (trav_subs as) 
        
        
result = mytraverse contents
        
    
-----------------------

However, when trying to load it hugs reports the following error:

Reading file "Z:\Download\unpack\hugs98\lib\Prelude.hs":
Reading file "print_cont.hs":
Reading file "Contents_Abs.hs":
Reading file "Contents.hs":
Reading file "print_cont.hs":
Type checking
ERROR "print_cont.hs" (line 5): Type error in function binding
*** Term           : trav
*** Type           : Contents_Node [Char] b [a] c d -> [Char]
*** Does not match : a -> [Char]
*** Because        : unification would give infinite type

Contents>


I would like to know how I can define a data structure that will contain a
list of references to its own types (I don't need circular data
structures). I would also like to know how I can define such an
abstraction inside a type.

Regards,

	Shlomi Fish



----------------------------------------------------------------------
Shlomi Fish        shlomif@vipe.technion.ac.il 
Home Page:         http://t2.technion.ac.il/~shlomif/
Home E-mail:       shlomif@techie.com

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.