[Haskell-cafe] Code Review Request - Unbalanced Parenthesis correction
MarLinn
monkleyon at gmail.com
Tue Mar 21 17:49:30 UTC 2017
Hi Michael,
I think you're making your own task harder than necessary. For one
thing, -XViewPatterns is nice, but in this case they hide some of the
structure. Most importantly, they hide that all the special null-cases
are actually unnecessary because the normal cases already cover them. I
would further advise to use layout to reveal even more structure. That's
especially useful when you later convert the explicit recursion into a fold.
But even then, on a different level you're still working too hard:
You're parsing the string and building/correcting the tree in one step.
Why not create the tree, convert the tree, and then read out the tree in
three steps? It's still the same complexity class but much easier to
write and read. And once you are free to think of the tree manipulations
on their own it might help recognize optimizations like those the
solutions of other commenters use.
That's not to say your modifications are useless. But the exploratory
phase seems too early to apply them.
Cheers,
MarLinn
On 2017-03-21 17:53, Michael Litchard wrote:
>
> I'm prepping for a coding interview, and am examining the task of
> correcting unbalanced parentheses. The finger tree seems to be the
> right data structure. As a proof of concept I've used |Data.Sequence|
> to test my idea. If this is the right direction to go, I'll write more
> specialized finger tree code. The code works on the few test cases I
> have tried. Feedback appreciated.
>
> |{-# LANGUAGE ViewPatterns #-}moduleParenthesis whereimportBasicPrelude
> hiding (concat,null,empty)importData.Sequence hiding
> (length)importData.Foldable hiding (length,null)balanceParens ::String
> ->String balanceParens str =go str []empty wherego [][](null
> ->True)=[]go [][]parens =Data.Foldable.toList parens go
> ('(':xs)[](null ->True)=go xs [RP](singleton '(')go (')':xs)[](null
> ->True)=go xs [](fromList "()")go ('(':xs)debit parens =go xs
> (RP:debit)(parens |>'(')go (')':xs)[]parens =go xs []corrected
> wherecorrected =('('<|parens)|>')'go (')':xs)(RP:debit)parens =go xs
> debit (parens |>')')go (_:xs)debit parens =go xs debit parens go
> [](RP:debit)parens =go []debit (parens |>')')|
>
> example:
>
> |balanceParens "))(""(())()"balanceParens ")))""((()))"|
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170321/43ef8f5d/attachment.html>
More information about the Haskell-Cafe
mailing list