Circular Data Types - a directory tree abstraction
Tom Moertel
tom-list-haskell@moertel.com
Sun, 04 Mar 2001 14:28:26 -0500
Shlomi Fish wrote:
>
> 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.
Here's one way that uses Haskell's Either type to differentiate between
directory entries that represent documents and those the represent
directories.
module URITree
where
-- some type synonynms to make things easier to remember
type URI = String
type MimeType = String
type Title = String
-- here is the type the represents a directory entry
newtype DirectoryEntry = DE (URI, Title, (Either [DirectoryEntry] {- Directory -}
MimeType)) {- Document -}
deriving (Show, Read, Eq)
-- a few helper functions to create entries
mkDirectory :: URI -> Title -> [DirectoryEntry] -> DirectoryEntry
mkDirectory uri title subs = DE (uri, title, (Left subs))
mkDocument :: URI -> Title -> MimeType -> DirectoryEntry
mkDocument uri title mtype = DE (uri, title, (Right mtype))
mkHTMLDocument :: URI -> Title -> DirectoryEntry
mkHTMLDocument uri title = DE (uri, title, (Right "text/html"))
-- here is a sample directory entry for a small hierarchy of documents
contents = mkDirectory "" "Contents" $
[ mkHTMLDocument "intro.html" "Introduction"
, mkHTMLDocument "properties.html" "Properties"
, mkDirectory "recursion/" "Recursion" $
[ mkHTMLDocument "fib1.html" "Fibonnaci (Take 1)"
, mkHTMLDocument "qsort.html" "Quick Sort"
]
, mkDirectory "lazy_eval/" "Lazy Evaluation" $
[ mkHTMLDocument "primes1.html" "Primes (Take 1)"
, mkHTMLDocument "fib2.html" "Fibonnaci (Take 2)"
]
, mkDocument "style.css" "Style sheet" "text/css"
]
-- traverse a directory entry, generating an indented set of titles
-- that represents its contents
traverse :: DirectoryEntry -> String
traverse d = tr 0 d
where tr n (DE (uri,title,ent)) = (indent n)++title++"\n"++(content (n+1) ent)
content n (Left subs) = foldr (++) "" (map (tr n) subs)
content n (Right _) = ""
indent n = foldr (++) "" (replicate n " ")
Hugs98 session using the above:
> :load uri-tree.hs
Reading file "uri-tree.hs":
Hugs session for:
C:\hugs98\lib\Prelude.hs
uri-tree.hs
URITree> putStr (traverse contents)
Contents
Introduction
Properties
Recursion
Fibonnaci (Take 1)
Quick Sort
Lazy Evaluation
Primes (Take 1)
Fibonnaci (Take 2)
Style sheet