
I would like to write a program that can do something like this. ;; lisp syntax * (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5) I end up like this. data Store a = E a | S [Store a] deriving (Show) flat :: [Store a] -> [a] flat [] = [] flat ((E x):xs) = [x] ++ flat xs flat ((S x):xs) = flat x ++ flat xs so *Main> flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5] Compare to a Lisp solution, It 's not looking good. Any suggestion. Thanks, PPhetra -- View this message in context: http://www.nabble.com/flatten-a-nested-list-tf2893713.html#a8084726 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

pphetra:
I would like to write a program that can do something like this.
;; lisp syntax * (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5)
I end up like this.
data Store a = E a | S [Store a] deriving (Show)
flat :: [Store a] -> [a] flat [] = [] flat ((E x):xs) = [x] ++ flat xs flat ((S x):xs) = flat x ++ flat xs
so *Main> flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5]
Compare to a Lisp solution, It 's not looking good. Any suggestion.
Since this data type:
data Store a = E a | S [Store a] deriving (Show)
Is isomorphic to the normal Data.Tree type anyway, so we'll use that:
data Tree a = N a [Tree a] deriving Show
to define a new tree:
tree = N 1 [N 2 [N 3 [], N 4 []], N 5 []]
Now we can flatten by folding:
flatten t = go t [] where go (N x ts) xs = x : foldr go xs ts
So we can flatten our test tree:
list = flatten tree
Even run it:
main = print (flatten tree)
Or in GHCi: *Main> flatten tree [1,2,3,4,5] Based on Data.Tree in the base library. -- Don

On Fri, Dec 29, 2006 at 07:58:54PM +1100, Donald Bruce Stewart wrote:
Since this data type:
data Store a = E a | S [Store a] deriving (Show)
Is isomorphic to the normal Data.Tree type anyway, so we'll use that:
It's a bit different - store has labels only in its leaves. Best regards Tomasz

On Thu, Dec 28, 2006 at 11:56:58PM -0800, pphetra wrote:
data Store a = E a | S [Store a] deriving (Show)
flat :: [Store a] -> [a] flat [] = [] flat ((E x):xs) = [x] ++ flat xs flat ((S x):xs) = flat x ++ flat xs
so *Main> flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5]
Since this problem is fundimentally tied to Lisp's dynamic typing, it is no suprise it can be done very easily using Haskell's support for dynamic typing:
import Data.Typeable
data D = forall a. Typeable a => D a deriving(Typeable)
flat :: D -> [D] flat (D x) = maybe [D x] (>>= flat) (cast x)
To use: map (\ (D x) -> cast x) flat (D [D 1, D [D 2, D 3], D 4]) :: [Maybe Integer] The 'D' defines an existantial type, which can hold a value of any type subject to the Typeable constraint. Typeable allows the typesafe cast function, which returns Nothing if the types were different. maybe and >>= are prelude functions used to make the definition shorter; without them:
flat (D x) = case (cast x) of Just xs -> concatMap flat xs Nothing -> [D x]

Hi pphetra wrote:
Compare to a Lisp solution, It 's not looking good. Any suggestion.
I'm trying to understand what your issue is here. What's not looking good?
I would like to write a program that can do something like this.
;; lisp syntax
I suppose, if it were the implementation of flattening that was the issue, you'd have shown us the Lisp version.
I end up like this.
data Store a = E a | S [Store a] deriving (Show)
flat :: [Store a] -> [a] flat [] = [] flat ((E x):xs) = [x] ++ flat xs flat ((S x):xs) = flat x ++ flat xs
That's a reasonable datatype to pick for finitely-branching trees. You're working a little hard on the function. Here's mine flat1 :: Store a -> [a] flat1 (E a) = return a flat1 (S xs) = xs >>= flat1 Your (flat xs) on a list of stores becomes my (xs >>= flat1), systematically lifting the operation on a single store to lists of them and concatenating the results. The return operation makes a singleton from an element. This way of working with lists by singleton and concatenation is exactly the monadic structure which goes with the list type, so you get it from the library by choosing to work with list types. In Haskell, when you choose a typed representation for data, you are not only choosing a way of containing the data but also a way to structure the computations you can express on that data. Or is your issue more superficial? Is it just that
* (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5)
looks shorter than
so *Main> flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5]
because finitely branching trees of atoms is more-or-less the native data structure of Lisp? Is it the Es and Ss which offend? No big deal, surely. It just makes test input a little more tedious to type. I'm guessing your Lisp implementation of my-flatten is using some sort of atom test to distinguish between elements and sequences, where the Haskell version explicitly codes the result of that test, together with its meaning: pattern matching combines discrimination with selection. The payoff for explicitly separating E from S is that the program becomes abstract with respect to elements. What if you wanted to flatten a nested list of expressions where the expressions did not have an atomic representation? The point, I guess, is that type system carries the structure of the computation. If you start from less structured Lisp data, you need to dig out more of the structure by ad hoc methods. There's more structure hiding in this example, which would make it even neater, hence the exercises at the end... But I hope this helps to make the trade-offs clearer. All the best Conor PS exercises for the over-enthusiastic import Data.Foldable import Data.Traversable import Control.Applicative import Data.Monoid Now consider (or discover!) the 'free monad' construction: data Free sig a = Var a | Op (sig (Free sig a)) (1) Show that if sig is a Functor then Free sig is a Monad, with (>>=) behaving like substitution for terms built over the signature sig. (2) Show that if sig is Traversable then Free sig is Traversable. (3) Replace the above 'Store' with a type synonym by substituting other characters for ? in type Store = Free ?? (4) Replace the ?s with other characters to complete the following definition splat :: (Traversable f, Applicative a, Monoid (a x)) => f x -> a x splat = ???????????? in such a way that the special case splat :: Store a -> [a] behaves like flat1 above.

On 12/29/06, Conor McBride
Or is your issue more superficial? Is it just that
* (my-flatten '(1 (2 (3 4) 5))) (1 2 3 4 5)
looks shorter than
so *Main> flat [E 1, S[E 2, S[E 3, E 4], E 5]] [1,2,3,4,5]
Speaking as a relative newbie to Haskell, the thing that tripped me up was the fact that you can't have nested lists like the Lisp '(1 (2 (3 4) 5)) example in Haskell, because its type is not well-defined. Haskell lists are homogeneous, where Lisp ones aren't. I don't know whether the OP was confused by the same thing as me, but it felt to me that stating the problem was the hard part, rather than implementing a solution. OTOH, it's not entirely clear to me if the issue would come up in "real" code. Slinging about arbitrarily nested lists feels quite natural in Lisp, but isn't really idiomatic Haskell. Cheers, Paul.

On Fri, Dec 29, 2006 at 02:06:32PM +0000, Paul Moore wrote:
Speaking as a relative newbie to Haskell, the thing that tripped me up was the fact that you can't have nested lists like the Lisp '(1 (2 (3 4) 5)) example in Haskell, because its type is not well-defined.
More precisely: You can't ununiformly nest standard [] lists. By ununiformly I mean: with leaves on different depths. You can do it with another list (or rather tree) implementation. You can nest [] lists uniformly, ie. [[1], [2,3,4]] is a nested list.
OTOH, it's not entirely clear to me if the issue would come up in "real" code.
It depends on what you mean by "issue". If syntactical overhead is an issue, then it comes up. For me it's a small issue, if at all.
Slinging about arbitrarily nested lists feels quite natural in Lisp, but isn't really idiomatic Haskell.
Nested lists are trees and using tree-like structures in Haskell is very idiomatic. Perhaps you would want some syntactic sugar for trees. If [] lists didn't have sugar in Haskell, they would be as "cumbersome" to use as trees. Best regards Tomasz
participants (6)
-
Conor McBride
-
dons@cse.unsw.edu.au
-
Paul Moore
-
pphetra
-
Stefan O'Rear
-
Tomasz Zielonka