
I have some lists of integers; e.g., [0,1,2,2,3,3,3,2,1,2,3,3,1] Think of each integer value as representing the indentation level in a hierarchical outline: e.g., 0 1 2 2 3 3 3 2 1 2 3 3 1 I want to convert the list into a structure that better represents the hierarchy. So, I first define a datatype to represent each node of the new structure: data Node = Nd Int [Node] That is, a node consists of an Int representing the value of the node, followed by a list of its immediate child nodes. (In principle, I can deduce the value of a node simply from the nesting level, of course, but in the real problem I'm trying to solve, each node contains other information that I need to preserve as well.) Next, I define some functions to perform the transformation isChild :: Int -> Node -> Bool isChild i (Nd j _) = (j > i) isChild _ _ = False prepend :: Int -> [Node] -> [Node] prepend i [] = [Nd i []] prepend i ns = (Nd i f):s where (f,s) = span (isChild i) ns unflatten :: [Int] -> [Node] unflatten ns = foldr prepend [] ns Finally, I add some code to display the result in an aesthetically pleasing way: showsNodeTail :: [Node] -> String -> String showsNodeTail [] = showChar '}' showsNodeTail (n:ns) = showChar ' '.shows n.showsNodeTail ns showsNodeList :: [Node] -> String -> String showsNodeList [] = showString "" showsNodeList (n:ns) = showChar '{'.shows n.showsNodeTail ns showsNode :: Node -> String -> String showsNode (Nd i ns) = shows i.showsNodeList ns instance Show Node where showsPrec n = showsNode This all works just fine, and when I enter unflatten [0,1,2,2,3,3,3,2,1,2,3,3,1] I get [0{1{2 2{3 3 3} 2} 1{2{3 3}} 1}] as expected. The reason I'm posting this here is that I have a gnawing suspicion that the unflatten/prepend/isChild functions, and possibly the Node data type as well, are not the most elegant way to go about solving the problem, and that I'm missing another more obvious way to do it. Any suggestions? Thanks, Steve Schafer Fenestra Technologies Corp. http://www.fenestra.com/

Perhaps it's cheating, but this is how I did it:
import Data.List
data Tree a = Node a [Tree a]
instance (Show a) => Show (Tree a) where
show (Node x []) = show x
show (Node x xs) = show x ++ "{" ++ concat (intersperse " " (map
show xs)) ++ "}"
treeOf (x:xs) = Node x (map treeOf (groupBy (<) xs))
In ghci, I then get:
*Main> treeOf [0,1,2,2,3,3,3,2,1,2,3,3,1]
0{1{2 2{3 3 3} 2} 1{2{3 3}} 1}
This is an obvious abuse of groupBy, as there's nothing that says what
it should do when the relation is not an equivalence. It just so
happens that it compares the first element with each of the others
until a point at which to split is found (not, as one might also
reasonably expect, by comparing adjacent elements)
- Cale
On 14/02/06, Steve Schafer
I have some lists of integers; e.g.,
[0,1,2,2,3,3,3,2,1,2,3,3,1]
Think of each integer value as representing the indentation level in a hierarchical outline: e.g.,
0 1 2 2 3 3 3 2 1 2 3 3 1
I want to convert the list into a structure that better represents the hierarchy. So, I first define a datatype to represent each node of the new structure:
data Node = Nd Int [Node]
That is, a node consists of an Int representing the value of the node, followed by a list of its immediate child nodes. (In principle, I can deduce the value of a node simply from the nesting level, of course, but in the real problem I'm trying to solve, each node contains other information that I need to preserve as well.)
Next, I define some functions to perform the transformation
isChild :: Int -> Node -> Bool isChild i (Nd j _) = (j > i) isChild _ _ = False
prepend :: Int -> [Node] -> [Node] prepend i [] = [Nd i []] prepend i ns = (Nd i f):s where (f,s) = span (isChild i) ns
unflatten :: [Int] -> [Node] unflatten ns = foldr prepend [] ns
Finally, I add some code to display the result in an aesthetically pleasing way:
showsNodeTail :: [Node] -> String -> String showsNodeTail [] = showChar '}' showsNodeTail (n:ns) = showChar ' '.shows n.showsNodeTail ns
showsNodeList :: [Node] -> String -> String showsNodeList [] = showString "" showsNodeList (n:ns) = showChar '{'.shows n.showsNodeTail ns
showsNode :: Node -> String -> String showsNode (Nd i ns) = shows i.showsNodeList ns
instance Show Node where showsPrec n = showsNode
This all works just fine, and when I enter
unflatten [0,1,2,2,3,3,3,2,1,2,3,3,1]
I get
[0{1{2 2{3 3 3} 2} 1{2{3 3}} 1}]
as expected.
The reason I'm posting this here is that I have a gnawing suspicion that the unflatten/prepend/isChild functions, and possibly the Node data type as well, are not the most elegant way to go about solving the problem, and that I'm missing another more obvious way to do it.
Any suggestions?
Thanks,
Steve Schafer Fenestra Technologies Corp. http://www.fenestra.com/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

process [] = [] process (a:t) = let (kids,sibs) = span (>a) (t) in (Nd a (process kids)):process sibs Ok, modules loaded: Main. *Main> process [0,1,2,2,3,3,3,2,1,2,3,3,1] [0{1{2 2{3 3 3} 2} 1{2{3 3}} 1}] *Main> Steve Schafer wrote:
I have some lists of integers; e.g.,
[0,1,2,2,3,3,3,2,1,2,3,3,1]
Think of each integer value as representing the indentation level in a hierarchical outline: e.g.,
0 1 2 2 3 3 3 2 1 2 3 3 1
I want to convert the list into a structure that better represents the hierarchy. So, I first define a datatype to represent each node of the new structure:
data Node = Nd Int [Node]
That is, a node consists of an Int representing the value of the node, followed by a list of its immediate child nodes. (In principle, I can deduce the value of a node simply from the nesting level, of course, but in the real problem I'm trying to solve, each node contains other information that I need to preserve as well.)
Next, I define some functions to perform the transformation
isChild :: Int -> Node -> Bool isChild i (Nd j _) = (j > i) isChild _ _ = False
prepend :: Int -> [Node] -> [Node] prepend i [] = [Nd i []] prepend i ns = (Nd i f):s where (f,s) = span (isChild i) ns
unflatten :: [Int] -> [Node] unflatten ns = foldr prepend [] ns
Finally, I add some code to display the result in an aesthetically pleasing way:
showsNodeTail :: [Node] -> String -> String showsNodeTail [] = showChar '}' showsNodeTail (n:ns) = showChar ' '.shows n.showsNodeTail ns
showsNodeList :: [Node] -> String -> String showsNodeList [] = showString "" showsNodeList (n:ns) = showChar '{'.shows n.showsNodeTail ns
showsNode :: Node -> String -> String showsNode (Nd i ns) = shows i.showsNodeList ns
instance Show Node where showsPrec n = showsNode
This all works just fine, and when I enter
unflatten [0,1,2,2,3,3,3,2,1,2,3,3,1]
I get
[0{1{2 2{3 3 3} 2} 1{2{3 3}} 1}]
as expected.
The reason I'm posting this here is that I have a gnawing suspicion that the unflatten/prepend/isChild functions, and possibly the Node data type as well, are not the most elegant way to go about solving the problem, and that I'm missing another more obvious way to do it.
Any suggestions?
Thanks,
Steve Schafer Fenestra Technologies Corp. http://www.fenestra.com/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2/14/06, Steve Schafer
isChild :: Int -> Node -> Bool isChild i (Nd j _) = (j > i) isChild _ _ = False
prepend :: Int -> [Node] -> [Node] prepend i [] = [Nd i []] prepend i ns = (Nd i f):s where (f,s) = span (isChild i) ns
unflatten :: [Int] -> [Node] unflatten ns = foldr prepend [] ns
The following seemed a little more natural to me: unflatten [] = [] unflatten (x:xs) = (Node x $ unflatten xh) : unflatten xt where (xh, xt) = span (>x) xs That is, a node containing the first item and the hierarchy of all of its children, followed by the hierarchies of its siblings. Is [0,2,1,2] invalid input? The behavior of both versions puts the first 2 and the 1 as children of the root, but the second 2 is a child of the 1. Colin DeVilbiss
participants (4)
-
Cale Gibbard
-
Chris Kuklewicz
-
Colin DeVilbiss
-
Steve Schafer