<div dir="auto">It can't be done in better than O(n) time as you have to look at the whole input.<div dir="auto"><br></div><div dir="auto">I think you must be using O(n) space too. Consider a string of the form "()()()()...()())": You know the output starts with a '(' but you cannot know the second character of the output until you have read all the way to the end of the string and found the final character is unmatched.</div></div><div class="gmail_extra"><br><div class="gmail_quote">On 21 Mar 2017 18:04, "Michael Litchard" <<a href="mailto:litchard.michael@gmail.com">litchard.michael@gmail.com</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><div><div>David,<br></div><div><br></div>Am I mistaken in believing the code I have in both O(1) in time and space?<br></div>I'm certain that my use of Data.Sequence, and therefore finger trees, has this code at O(1) time.<br></div>Doesn't using a lazy list mean I am using O(1) space? Or, would I have to use the conduits or pipes library? <br></div><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Mar 21, 2017 at 10:52 AM, David Turner <span dir="ltr"><<a href="mailto:dct25-561bs@mythic-beasts.com" target="_blank">dct25-561bs@mythic-beasts.com</a><wbr>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="auto"><div>... or it could be a ploy to see how you deal with incomplete or vague specs; how you ask clarifying questions etc.</div><div dir="auto"><br></div><div dir="auto">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.</div><div><div class="m_4004328889744025518h5"><div dir="auto"><div class="gmail_extra" dir="auto"><br><div class="gmail_quote">On 21 Mar 2017 17:44, "Michael Litchard" <<a href="mailto:litchard.michael@gmail.com" target="_blank">litchard.michael@gmail.com</a>> wrote:<br type="attribution"><blockquote class="m_4004328889744025518m_-7407516963408977104quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div><div>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.<br></div>so <br></div>balanceParens ")))" == "()()()" would be incorrect.<br><div><div><div><br><br></div></div></div></div><div class="m_4004328889744025518m_-7407516963408977104elided-text"><div class="gmail_extra"><br><div class="gmail_quote">On Tue, Mar 21, 2017 at 10:20 AM, David Turner <span dir="ltr"><<a href="mailto:dct25-561bs@mythic-beasts.com" target="_blank">dct25-561bs@mythic-beasts.com</a><wbr>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr"><div>My attempt to replicate the OP's strategy but not impl:</div><div><br></div><div><font face="monospace, monospace">balanceParens :: String -> String</font></div><div><font face="monospace, monospace">balanceParens s =  replicate neededOpening '('</font></div><div><font face="monospace, monospace">           ++ s ++ replicate neededClosing ')'</font></div><div><font face="monospace, monospace">  where</font></div><div><font face="monospace, monospace">  depthChange '(' = 1</font></div><div><font face="monospace, monospace">  depthChange ')' = -1</font></div><div><font face="monospace, monospace">  depthChange _   = 0</font></div><div><font face="monospace, monospace"><br></font></div><div><font face="monospace, monospace">  depths = scanl (+) 0 $ map depthChange s</font></div><div><font face="monospace, monospace">  neededOpening = negate $ minimum depths</font></div><div><font face="monospace, monospace">  neededClosing =          last    depths + neededOpening</font></div><div><br></div><div><br></div></div><div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547HOEnZb"><div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547h5"><div class="gmail_extra"><br><div class="gmail_quote">On 21 March 2017 at 17:16, David McBride <span dir="ltr"><<a href="mailto:toad3k@gmail.com" target="_blank">toad3k@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Whether your algorithm is correct depends on how you are supposed to<br>
rebalance them.  My naive attempt gives very different results.<br>
<br>
bal :: String -> String<br>
bal = go 0<br>
  where<br>
    go :: Int -> String -> String<br>
    go 0 "" = ""<br>
    go n "" = replicate n ')'<br>
    go n ('(':xs) = '(' : (go (n + 1) xs)<br>
    go 0 (')':xs) = '(' : ')' : (go 0 xs)<br>
    go n (')':xs) = ')' : (go (n - 1) xs)<br>
<br>
bal "))("<br>
"()()()"<br>
<br>
bal ")))"<br>
"()()()"<br>
<div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547m_-3933083116508655859HOEnZb"><div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547m_-3933083116508655859h5"><br>
On Tue, Mar 21, 2017 at 12:53 PM, Michael Litchard<br>
<<a href="mailto:litchard.michael@gmail.com" target="_blank">litchard.michael@gmail.com</a>> wrote:<br>
> I'm prepping for a coding interview, and am examining the task of correcting<br>
> unbalanced parentheses. The finger tree seems to be the right data<br>
> structure. As a proof of concept I've used Data.Sequence to test my idea. If<br>
> this is the right direction to go, I'll write more specialized finger tree<br>
> code. The code works on the few test cases I have tried. Feedback<br>
> appreciated.<br>
><br>
> {-# LANGUAGE ViewPatterns #-}<br>
> module Parenthesis where<br>
> import BasicPrelude hiding (concat,null,empty)<br>
><br>
> import Data.Sequence hiding (length)<br>
> import Data.Foldable hiding (length,null)<br>
><br>
> balanceParens :: String -> String<br>
> balanceParens str = go str [] empty<br>
>   where<br>
>     go [] [] (null -> True) = []<br>
>     go [] [] parens = Data.Foldable.toList parens<br>
>     go ('(':xs) [] (null -> True) = go xs [RP] (singleton '(')<br>
>     go (')':xs) [] (null -> True) = go xs [] (fromList "()")<br>
>     go ('(':xs) debit parens = go xs (RP:debit) (parens |> '(')<br>
>     go (')':xs) [] parens = go xs [] corrected<br>
>       where corrected = ('(' <| parens) |> ')'<br>
>     go (')':xs) (RP:debit) parens = go xs debit (parens |> ')')<br>
>     go (_:xs) debit parens = go xs debit parens<br>
>     go [] (RP:debit) parens = go [] debit (parens |> ')')<br>
><br>
> example:<br>
><br>
> balanceParens "))("<br>
> "(())()"<br>
> balanceParens ")))"<br>
> "((()))"<br>
><br>
><br>
</div></div><div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547m_-3933083116508655859HOEnZb"><div class="m_4004328889744025518m_-7407516963408977104m_-3708216938673928547m_-3933083116508655859h5">> ______________________________<wbr>_________________<br>
> Haskell-Cafe mailing list<br>
> To (un)subscribe, modify options or view archives go to:<br>
> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
> Only members subscribed via the mailman list are allowed to post.<br>
______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bi<wbr>n/mailman/listinfo/haskell-caf<wbr>e</a><br>
Only members subscribed via the mailman list are allowed to post.</div></div></blockquote></div><br></div>
</div></div></blockquote></div><br></div>
</div></blockquote></div><br></div></div></div></div></div>
</blockquote></div><br></div>
</blockquote></div></div>