
David, Am I mistaken in believing the code I have in both O(1) in time and space? I'm certain that my use of Data.Sequence, and therefore finger trees, has this code at O(1) time. Doesn't using a lazy list mean I am using O(1) space? Or, would I have to use the conduits or pipes library? On Tue, Mar 21, 2017 at 10:52 AM, David Turner < dct25-561bs@mythic-beasts.com> wrote:
... or it could be a ploy to see how you deal with incomplete or vague specs; how you ask clarifying questions etc.
Adding sufficiently many opening parens at the start can't obviously be done without traversing the whole input first, whereas adding them as you discover excesses of closing parens is possible to implement in a streaming fashion, i.e. with O(1) memory usage and only traversing the input once.
On 21 Mar 2017 17:44, "Michael Litchard"
wrote: I got this idea from looking at glassdoor comments of previous interviewees. The spec was vague, but I imagined that the requirement would need to be efficient and keep contiguous parenthesis unaltered. so balanceParens ")))" == "()()()" would be incorrect.
On Tue, Mar 21, 2017 at 10:20 AM, David Turner < dct25-561bs@mythic-beasts.com> wrote:
My attempt to replicate the OP's strategy but not impl:
balanceParens :: String -> String balanceParens s = replicate neededOpening '(' ++ s ++ replicate neededClosing ')' where depthChange '(' = 1 depthChange ')' = -1 depthChange _ = 0
depths = scanl (+) 0 $ map depthChange s neededOpening = negate $ minimum depths neededClosing = last depths + neededOpening
On 21 March 2017 at 17:16, David McBride
wrote: 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 ")))" "()()()"
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
On Tue, Mar 21, 2017 at 12:53 PM, Michael Litchard
wrote: 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.
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.