Hi Michael,

Are there any strange constraints on the problem, such as the input string being 10s of GB long, or any particular correction strategy being required? Your code seems to add some parens to the start/end of the entire string to balance it, whereas I think I might have balanced "))(" to "()()()" given free reign. Is the goal efficiency or clarity or something else?

From personal taste, I would recommend including a suite of automated tests alongside your implementation even if it is not explicitly requested. A quickcheck test asserting that the output is always balanced and that the input string is a substring of the output might be appropriate.




On 21 March 2017 at 16:53, Michael Litchard <litchard.michael@gmail.com> 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 #-}
module Parenthesis where
import BasicPrelude hiding (concat,null,empty)

import Data.Sequence hiding (length)
import Data.Foldable hiding (length,null)

balanceParens :: String -> String
balanceParens str = go str [] empty
  where
    go [] [] (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
      where corrected = ('(' <| 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.