-----------------------------------------------------------------------------
-- |
-- Module      :  Control.Search.Local.Tree
-- Copyright   :  (c) Richard Senington & David Duke 2010
-- License     :  GPL-style
-- 
-- Maintainer  :  Richard Senington <sc06r2s@leeds.ac.uk>
-- Stability   :  provisional
-- Portability :  portable
-- 
-- The internal data structure of the library.
----------------------------------------------------------------------------- 

module Control.Search.Local.Tree(
   LSTree(treeNodeName,treeNodeChildren,LSTree),mkTree
)where

{- | A rose tree, but not currently using an optimised data structure, just this little 
  home built one. The accessor functions should be easy enough to understand. -}

data LSTree nme = LSTree {treeNodeName :: nme,
                          treeNodeChildren :: [LSTree nme]}

{- | The construction function, as seen in the paper. Takes a neighbourhood function, that
  is, a function that takes a solution and perterbs it in some way, giving a selection of
   new solutions. It then requires a seed, and gives back an initial tree. -}

mkTree :: (a->[a])->a->LSTree a
mkTree f seed = LSTree seed $ map (mkTree f) (f seed)

{- |  Making a tree part of Ord and Eq, for ease of comparison later.
   Note that how the order is determined depends upon the implementation given for a solution. -}

instance (Ord nme)=>Ord (LSTree nme) where
  compare t1 t2 = compare (treeNodeName t1) (treeNodeName t2)

instance (Eq nme)=>Eq (LSTree nme) where
  (==) t1 t2 = (treeNodeName t1) == (treeNodeName t2)