Zoey
Zoey

Reputation: 516

Why my balanced brackets stack algorithm fails within nested OPEN brackets?

I know that there're thousands of examples in internet and question here about an algorithm using a Stack to check if a sequence of brackets - "(){}[]" - are balanced.

However all I've found was simple algorithms that stops in the first unbalanced pair and return a boolean or a string saying if the sequence is balanced or not.

My problem go beyond that: I need to group all "parse" errors and then print in screen all those balanced errors!

Example "([}])"

when a common algorithm finds the "}" the program woould return false or "NO"

My algorithm needs to add a "Error: close curly braces does not match" into a list to when the program finish to parse the string all errors would be returned.

That's the complete programs:

module LE2.Stack.Delim
  ( parse
  , erroAbreParen
  , erroAbreCol
  , erroAbreChaves
  , erroFechaParen
  , erroFechaCol
  , erroFechaChaves
  ) where

import           GHC.Exts                       ( sortWith )
import qualified LE2.Stack.TAD                 as Stack

import           Debug.Trace                    ( trace )

tokenize :: String -> [(Char, Int)]
tokenize s = zip (filter ehDelim s) [0 ..]

parse :: String -> [String]
parse lines = go (tokenize lines) Stack.new []
 where
  go x y z | trace ("go: " ++ show x ++ " " ++ show y ++ " " ++ show z) False =
    undefined
  go [] st parsed
    | Stack.isEmpty st = map fst $ sort parsed
    | otherwise        = map fst . sort $ parsed ++ map swap ((Stack.<<>) st)

  go (('(', idx) : xs) st parsed = go xs (Stack.push st (')', idx)) parsed
  go (('[', idx) : xs) st parsed = go xs (Stack.push st (']', idx)) parsed
  go (('{', idx) : xs) st parsed = go xs (Stack.push st ('}', idx)) parsed

  go (pair : xs) st parsed | Stack.isEmpty st = go xs st $ apply pair : parsed

  go ((')', _) : xs) st parsed | Just (')', _) <- Stack.peek st =
    let (Just _, st') = Stack.pop st in go xs st' parsed

  go ((']', _) : xs) st parsed | Just (']', _) <- Stack.peek st =
    let (Just _, st') = Stack.pop st in go xs st' parsed

  go (('}', _) : xs) st parsed | Just ('}', _) <- Stack.peek st =
    let (Just _, st') = Stack.pop st in go xs st' parsed

  go (pair : xs) st parsed = go xs st $ apply pair : parsed

  swap ('(', idx) = apply (')', idx)
  swap (')', idx) = apply ('(', idx)
  swap ('[', idx) = apply (']', idx)
  swap (']', idx) = apply ('[', idx)
  swap ('{', idx) = apply ('}', idx)
  swap ('}', idx) = apply ('{', idx)

  apply ('(', idx) = (erroAbreParen, idx)
  apply (')', idx) = (erroFechaParen, idx)
  apply ('[', idx) = (erroAbreCol, idx)
  apply (']', idx) = (erroFechaCol, idx)
  apply ('{', idx) = (erroAbreChaves, idx)
  apply ('}', idx) = (erroFechaChaves, idx)

  sort = sortWith (abs . snd)

erroFechaParen :: String
erroFechaParen = "Erro: fecha parentêses não casa!"

erroFechaCol :: String
erroFechaCol = "Erro: fecha colchetes não casa!"

erroFechaChaves :: String
erroFechaChaves = "Erro: fecha chaves não casa!"

erroAbreParen :: String
erroAbreParen = "Erro: abre parentêses não casa!"

erroAbreCol :: String
erroAbreCol = "Erro: abre colchetes não casa!"

erroAbreChaves :: String
erroAbreChaves = "Erro: abre chaves não casa!"

ehDelim :: Char -> Bool
ehDelim ch | elem ch "()[]{}" = True
           | otherwise        = False

I know that I maybe overcomplicated the problem but this is one of my first versions!

I also wrote some tests:

module LE2.Stack.DelimSpec where

import           Test.Hspec

import           LE2.Stack.Delim

spec :: Spec
spec = do
  describe "testa o casamento de parênteses, colchetes e chaves!" $ do
    it "deve retornar a quantidade correta de erros" $ do
      let as = "{}[]()"
      let bs = ")]}"
      let cs = "([{"
      let ds = "([]{}"
      let es = "()[{}"
      let fs = "()[]{"
      let xs = "()[]{}"
      let ys = "([{}])"
      let zs = "{[()]}"

      (length $ parse as) `shouldBe` 0
      (length $ parse bs) `shouldBe` 3
      (length $ parse cs) `shouldBe` 3
      (length $ parse ds) `shouldBe` 1
      (length $ parse es) `shouldBe` 1
      (length $ parse fs) `shouldBe` 1
      (length $ parse xs) `shouldBe` 0
      (length $ parse ys) `shouldBe` 0
      (length $ parse zs) `shouldBe` 0

    it "deve retornar os erros corretos" $ do
      let as = "([{"
      let bs = "([]{}"
      let cs = "()[{}"
      let ds = "()[]{"
      let es = "({}])"
      let fs = "([}])"
      let gs = "[{}])"
      let hs = "]]{}}{"
      let is = "(])]{{"
      let js = "{}{[))"
      let ks = "([{})"
      let ls = "([{])"
      let ms = "([{}]"
      let xs = "("
      let ys = "["
      let zs = "{"

      parse as `shouldBe` [erroAbreParen, erroAbreCol, erroAbreChaves]
      parse bs `shouldBe` [erroAbreParen]
      parse cs `shouldBe` [erroAbreCol]
      parse ds `shouldBe` [erroAbreChaves]
      parse es `shouldBe` [erroFechaCol]
      parse fs `shouldBe` [erroFechaChaves]
      parse gs `shouldBe` [erroFechaParen]
      parse hs `shouldBe` [erroFechaCol, erroFechaCol, erroFechaChaves, erroAbreChaves]
      parse is `shouldBe` [erroFechaCol, erroFechaCol, erroAbreChaves, erroAbreChaves]
      parse js `shouldBe` [erroAbreChaves, erroAbreCol, erroFechaParen, erroFechaParen]
      parse ks `shouldBe` [erroAbreCol]
      parse ls `shouldBe` [erroAbreChaves]
      parse ms `shouldBe` [erroAbreParen]
      parse xs `shouldBe` [erroAbreParen]
      parse ys `shouldBe` [erroAbreCol]
      parse zs `shouldBe` [erroAbreChaves]

These tests only breaks in these cases:

let ks = "([{})"
let ls = "([{])"
let ms = "([{}]"

So I got really confused with WHY they break only with nested unbalanced open brackets. I could determine that my logic fails in this clause: go (pair : xs) st parsed = go xs st $ apply pair : parsed

Because the program will push a balanced close bracket but they will remain in the stack.

But why and how I could solve this?

Upvotes: 1

Views: 162

Answers (1)

SergeyKuz1001
SergeyKuz1001

Reputation: 875

You can try change

go (pair : xs) st parsed = go xs st $ apply pair : parsed

to

go (pair : xs) st parsed =
    let (_, st') = Stack.pop st in go (pair : xs) st' $ apply pair : parsed

I really can't ensure that it will work, but in case with ks problem is that you have stack (']', 1) : (')', 0) : [] before ) and stack remains unchanged after ), but if you apply matching ) again with stack (')', 0) : [] it maybe will work.

Upvotes: 1

Related Questions