apfelmus wrote:
Up-pointers won't work in Haskell, you'll need a different approach. Can
you elaborate on what your tree looks like and what it stores?

"pointers" don't exist in Haskell, though they do exist in the Foreign.* interface package.

But Up-values work just fine:

import Data.Tree

-- Build a tree of divisors:
tree :: Tree String
tree = unfoldTree f 12 -- example
  where f 1 = (show 1,[])
        f n = (show n,[ x | x <- [1..n `div` 2], n `mod` x == 0])

-- One possible design, using Maybe:
data UpTree a = UpTree { value :: a
                       , parent :: Maybe (UpTree a)
                       , children :: [UpTree a]
                       }

-- Convert a Tree to an UpTree
treeToUpTree t = helper Nothing t where
  helper p t =
    let p' = UpTree { value = rootLabel t
                    , parent = p
                    , children = map (helper (Just p')) (subForest t)
                    }
    in p'

upTree :: UpTree String
upTree = treeToUpTree tree -- example

-- Pretty print this example UpTree with careful access to parent:

instance Show a => Show (UpTree a) where
  show u@(UpTree {parent=Nothing}) =
      "ROOT_UpTree "++show (value u)++"\n"
               ++(indent 3 $ show (children u))
  show u@(UpTree {parent=Just p,children=[]}) =
      "UpTree "++show (value u)++"\n"
               ++"   parent value is "++show (value p)++"\n"
  show u@(UpTree {parent=Just p}) =
      "UpTree "++show (value u)++"\n"
               ++"   parent value is "++show (value p)++"\n"
               ++(indent 3 $ show (children u))

indent n x = let xs = lines x
             in if null xs then ""
                  else unlines $ map (replicate n ' ' ++) xs


main = print upTree

Gives:

ROOT_UpTree "12"
   [LEAF UpTree "1"
      parent value is "12"
   ,BRANCH UpTree "2"
      parent value is "12"
      [LEAF UpTree "1"
         parent value is "2"
      ]
   ,BRANCH UpTree "3"
      parent value is "12"
      [LEAF UpTree "1"
         parent value is "3"
      ]
   ,BRANCH UpTree "4"
      parent value is "12"
      [LEAF UpTree "1"
         parent value is "4"
      ,BRANCH UpTree "2"
         parent value is "4"
         [LEAF UpTree "1"
            parent value is "2"
         ]
      ]
   ,BRANCH UpTree "6"
      parent value is "12"
      [LEAF UpTree "1"
         parent value is "6"
      ,BRANCH UpTree "2"
         parent value is "6"
         [LEAF UpTree "1"
            parent value is "2"
         ]
      ,BRANCH UpTree "3"
         parent value is "6"
         [LEAF UpTree "1"
            parent value is "3"
         ]
      ]
   ]

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

Reply via email to