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.


_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to