Parse indices of associative arrays properly

This commit is contained in:
Vidar Holen 2016-06-26 14:39:49 -07:00
parent 85e69f86eb
commit 3e5ecaa262
4 changed files with 86 additions and 16 deletions

View file

@ -21,6 +21,7 @@ module ShellCheck.ASTLib where
import ShellCheck.AST
import Control.Monad.Writer
import Control.Monad
import Data.List
import Data.Maybe
@ -251,3 +252,16 @@ getCommandSequences t =
T_IfExpression _ thens elses -> map snd thens ++ [elses]
otherwise -> []
getAssociativeArrays t =
nub . execWriter $ doAnalysis f t
where
f :: Token -> Writer [String] ()
f t@(T_SimpleCommand {}) = fromMaybe (return ()) $ do
name <- getCommandName t
guard $ name == "declare"
let flags = getAllFlags t
guard $ elem "A" $ map snd flags
let args = map fst . filter ((==) "" . snd) $ flags
let names = mapMaybe getLiteralString args
return $ tell names
f _ = return ()