Refactor to not generate Parameters twice

This commit is contained in:
Vidar Holen 2022-07-27 19:47:37 -07:00
parent 3ce310e939
commit f440912279
4 changed files with 25 additions and 27 deletions

View file

@ -20,9 +20,10 @@
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where
import ShellCheck.Analyzer
import ShellCheck.ASTLib
import ShellCheck.Interface
import ShellCheck.Parser
import ShellCheck.Analyzer
import Data.Either
import Data.Functor
@ -85,7 +86,7 @@ checkScript sys spec = do
asCheckSourced = csCheckSourced spec,
asExecutionMode = Executed,
asTokenPositions = tokenPositions,
asOptionalChecks = csOptionalChecks spec
asOptionalChecks = getEnableDirectives root ++ csOptionalChecks spec
} where as = newAnalysisSpec root
let analysisMessages =
maybe []