mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-10-03 19:29:44 +08:00
Enable syntax highlighting
20
DevGuide.md
20
DevGuide.md
@@ -24,13 +24,17 @@ Parser warnings come in two flavors: problems and notes.
|
|||||||
|
|
||||||
Notes are only emitted when parsing succeeds (they are stored in the Parsec user state). For example, a note is emitted when adding spaces around `=` in assignments, because if the parser later fails (i.e. it's not actually an assignment), we want to discard the suggestion:
|
Notes are only emitted when parsing succeeds (they are stored in the Parsec user state). For example, a note is emitted when adding spaces around `=` in assignments, because if the parser later fails (i.e. it's not actually an assignment), we want to discard the suggestion:
|
||||||
|
|
||||||
|
```haskell
|
||||||
when (hasLeftSpace || hasRightSpace) $
|
when (hasLeftSpace || hasRightSpace) $
|
||||||
parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments."
|
parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments."
|
||||||
|
```
|
||||||
|
|
||||||
On the other hand, problems are always emitted, even when parsing fails (they are stored in a StateT higher than Parsec in the transformer stack). For example, a problem is emitted for unicode quotes, because this issue is likely to cause parsing to fail:
|
On the other hand, problems are always emitted, even when parsing fails (they are stored in a StateT higher than Parsec in the transformer stack). For example, a problem is emitted for unicode quotes, because this issue is likely to cause parsing to fail:
|
||||||
|
|
||||||
|
```haskell
|
||||||
when (single && '\n' `elem` space) $
|
when (single && '\n' `elem` space) $
|
||||||
parseProblemAt pos ErrorC 1080 "When breaking lines in [ ], you need \\ before the linefeed."
|
parseProblemAt pos ErrorC 1080 "When breaking lines in [ ], you need \\ before the linefeed."
|
||||||
|
```
|
||||||
|
|
||||||
So basically, notes are emitted for non-fatal warnings while problems are emitted for fatal ones.
|
So basically, notes are emitted for non-fatal warnings while problems are emitted for fatal ones.
|
||||||
|
|
||||||
@@ -50,17 +54,21 @@ AST analysis comes in two primary flavors: checks that run on the root node (som
|
|||||||
|
|
||||||
Here's a simple check designed to run on each node, using pattern matching to find backticks:
|
Here's a simple check designed to run on each node, using pattern matching to find backticks:
|
||||||
|
|
||||||
|
```haskell
|
||||||
checkBackticks _ (T_Backticked id list) | not (null list) =
|
checkBackticks _ (T_Backticked id list) | not (null list) =
|
||||||
style id 2006 "Use $(..) instead of legacy `..`."
|
style id 2006 "Use $(..) instead of legacy `..`."
|
||||||
checkBackticks _ _ = return ()
|
checkBackticks _ _ = return ()
|
||||||
|
````
|
||||||
|
|
||||||
A lot of checks are just like this, though usually with a bit more matching logic.
|
A lot of checks are just like this, though usually with a bit more matching logic.
|
||||||
|
|
||||||
Each check is preceded by some mostly self-explanatory unit tests:
|
Each check is preceded by some mostly self-explanatory unit tests:
|
||||||
|
|
||||||
|
```haskell
|
||||||
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
|
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
|
||||||
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
|
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
|
||||||
prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
||||||
|
```
|
||||||
|
|
||||||
There are a few specialized test types for efficiency reasons.
|
There are a few specialized test types for efficiency reasons.
|
||||||
|
|
||||||
@@ -95,7 +103,7 @@ Ok, modules loaded: ShellCheck.Parser, ShellCheck.AST, ShellCheck.ASTLib, ShellC
|
|||||||
|
|
||||||
This has given us a REPL where we can call parsing functions. There's a convenient `debugParse` function that will take a parser and a string, and give the result. The main parser function is `readScript`:
|
This has given us a REPL where we can call parsing functions. There's a convenient `debugParse` function that will take a parser and a string, and give the result. The main parser function is `readScript`:
|
||||||
|
|
||||||
```
|
```haskell
|
||||||
*ShellCheck.Parser> debugParse readScript "sort file > tmp"
|
*ShellCheck.Parser> debugParse readScript "sort file > tmp"
|
||||||
Right (T_Annotation (Id 1) [] (T_Script (Id 0) "" [T_Pipeline (Id 3) [] [T_Redirecting (Id 4) [T_FdRedirect (Id 10) "" (T_IoFile (Id 11) (T_Greater (Id 12)) (T_NormalWord (Id 13) [T_Literal (Id 14) "tmp"]))] (T_SimpleCommand (Id 5) [] [T_NormalWord (Id 6) [T_Literal (Id 7) "sort"],T_NormalWord (Id 8) [T_Literal (Id 9) "file"]])]]))
|
Right (T_Annotation (Id 1) [] (T_Script (Id 0) "" [T_Pipeline (Id 3) [] [T_Redirecting (Id 4) [T_FdRedirect (Id 10) "" (T_IoFile (Id 11) (T_Greater (Id 12)) (T_NormalWord (Id 13) [T_Literal (Id 14) "tmp"]))] (T_SimpleCommand (Id 5) [] [T_NormalWord (Id 6) [T_Literal (Id 7) "sort"],T_NormalWord (Id 8) [T_Literal (Id 9) "file"]])]]))
|
||||||
*ShellCheck.Parser>
|
*ShellCheck.Parser>
|
||||||
@@ -103,7 +111,7 @@ Right (T_Annotation (Id 1) [] (T_Script (Id 0) "" [T_Pipeline (Id 3) [] [T_Redir
|
|||||||
|
|
||||||
Not very pretty, but we can see the part we're interested in:
|
Not very pretty, but we can see the part we're interested in:
|
||||||
|
|
||||||
```
|
```haskell
|
||||||
(T_IoFile (Id 11) (T_Greater (Id 12)) (T_NormalWord (Id 13) [T_Literal (Id 14) "tmp"]))
|
(T_IoFile (Id 11) (T_Greater (Id 12)) (T_NormalWord (Id 13) [T_Literal (Id 14) "tmp"]))
|
||||||
```
|
```
|
||||||
|
|
||||||
@@ -114,7 +122,7 @@ We can compare this with the definition in `AST.hs`:
|
|||||||
^-- Filename (T_NormalWord)
|
^-- Filename (T_NormalWord)
|
||||||
|
|
||||||
Let's just add a check to `Analytics.hs`:
|
Let's just add a check to `Analytics.hs`:
|
||||||
```
|
```haskell
|
||||||
checkTmpFilename _ token =
|
checkTmpFilename _ token =
|
||||||
case token of
|
case token of
|
||||||
T_IoFile id operator filename ->
|
T_IoFile id operator filename ->
|
||||||
@@ -124,7 +132,7 @@ Let's just add a check to `Analytics.hs`:
|
|||||||
|
|
||||||
and then append `checkTmpFilename` to the list of node checks at the top of the file:
|
and then append `checkTmpFilename` to the list of node checks at the top of the file:
|
||||||
|
|
||||||
```
|
```haskell
|
||||||
nodeChecks :: [Parameters -> Token -> Writer [TokenComment] ()]
|
nodeChecks :: [Parameters -> Token -> Writer [TokenComment] ()]
|
||||||
nodeChecks = [
|
nodeChecks = [
|
||||||
checkUuoc
|
checkUuoc
|
||||||
@@ -155,7 +163,7 @@ sort file > tmp
|
|||||||
Now we can flesh out the check. See `ASTLib.hs` and `AnalyzerLib.hs` for convenient functions to work with AST nodes, such as getting the name of an invoked command, getting a list of flags using canonical flag parsing rules, or in this case, getting the literal string of a T_NormalWord so that it doesn't matter if we use `> 'tmp'`, `> "tmp"` or `> "t"'m'p`:
|
Now we can flesh out the check. See `ASTLib.hs` and `AnalyzerLib.hs` for convenient functions to work with AST nodes, such as getting the name of an invoked command, getting a list of flags using canonical flag parsing rules, or in this case, getting the literal string of a T_NormalWord so that it doesn't matter if we use `> 'tmp'`, `> "tmp"` or `> "t"'m'p`:
|
||||||
|
|
||||||
|
|
||||||
```
|
```haskell
|
||||||
checkTmpFilename _ token =
|
checkTmpFilename _ token =
|
||||||
case token of
|
case token of
|
||||||
T_IoFile id operator filename ->
|
T_IoFile id operator filename ->
|
||||||
@@ -166,7 +174,7 @@ Now we can flesh out the check. See `ASTLib.hs` and `AnalyzerLib.hs` for conveni
|
|||||||
|
|
||||||
We can also prepend a few unit tests that will automatically be picked up if they start with `prop_`:
|
We can also prepend a few unit tests that will automatically be picked up if they start with `prop_`:
|
||||||
|
|
||||||
```
|
```haskell
|
||||||
prop_checkTmpFilename1 = verify checkTmpFilename "sort file > tmp"
|
prop_checkTmpFilename1 = verify checkTmpFilename "sort file > tmp"
|
||||||
prop_checkTmpFilename2 = verifyNot checkTmpFilename "sort file > $tmp"
|
prop_checkTmpFilename2 = verifyNot checkTmpFilename "sort file > $tmp"
|
||||||
```
|
```
|
||||||
|
Reference in New Issue
Block a user