[Haskell-cafe] Code Review Request - Unbalanced Parenthesis correction
Michael Litchard
litchard.michael at gmail.com
Tue Mar 21 16:53:43 UTC 2017
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 whereimport
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 ")))""((()))"
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20170321/caa25358/attachment.html>
More information about the Haskell-Cafe
mailing list