[Haskell-cafe] Code Review Request - Unbalanced Parenthesis correction

David McBride toad3k at gmail.com
Tue Mar 21 17:16:40 UTC 2017


Whether your algorithm is correct depends on how you are supposed to
rebalance them.  My naive attempt gives very different results.

bal :: String -> String
bal = go 0
  where
    go :: Int -> String -> String
    go 0 "" = ""
    go n "" = replicate n ')'
    go n ('(':xs) = '(' : (go (n + 1) xs)
    go 0 (')':xs) = '(' : ')' : (go 0 xs)
    go n (')':xs) = ')' : (go (n - 1) xs)

bal "))("
"()()()"

bal ")))"
"()()()"

On Tue, Mar 21, 2017 at 12:53 PM, Michael Litchard
<litchard.michael at 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.


More information about the Haskell-Cafe mailing list