diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs
index a8b1fff..b47651f 100644
--- a/src/ShellCheck/AnalyzerLib.hs
+++ b/src/ShellCheck/AnalyzerLib.hs
@@ -118,10 +118,9 @@ defaultSpec root = AnalysisSpec {
 
 pScript s =
   let
-    pSpec = ParseSpec {
+    pSpec = newParseSpec {
         psFilename = "script",
-        psScript = s,
-        psCheckSourced = False
+        psScript = s
     }
   in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
 
diff --git a/src/ShellCheck/Checker.hs b/src/ShellCheck/Checker.hs
index f70a776..1ecf03e 100644
--- a/src/ShellCheck/Checker.hs
+++ b/src/ShellCheck/Checker.hs
@@ -52,10 +52,11 @@ checkScript sys spec = do
     }
   where
     checkScript contents = do
-        result <- parseScript sys ParseSpec {
+        result <- parseScript sys newParseSpec {
             psFilename = csFilename spec,
             psScript = contents,
-            psCheckSourced = csCheckSourced spec
+            psCheckSourced = csCheckSourced spec,
+            psShellTypeOverride = csShellTypeOverride spec
         }
         let parseMessages = prComments result
         let analysisMessages =
@@ -136,6 +137,21 @@ prop_optionDisablesIssue2 =
                     csExcludedWarnings = [2148, 1037]
                 }
 
+prop_wontParseBadShell =
+    [1071] == check "#!/usr/bin/python\ntrue $1\n"
+
+prop_optionDisablesBadShebang =
+    null $ getErrors
+                (mockedSystemInterface [])
+                emptyCheckSpec {
+                    csScript = "#!/usr/bin/python\ntrue\n",
+                    csShellTypeOverride = Just Sh
+                }
+
+prop_annotationDisablesBadShebang =
+    [] == check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n"
+
+
 prop_canParseDevNull =
     [] == check "source /dev/null"
 
@@ -180,7 +196,7 @@ prop_filewideAnnotation1 = null $
 prop_filewideAnnotation2 = null $
     check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1"
 prop_filewideAnnotation3 = null $
-    check "#!/bin/sh\n#unerlated\n# shellcheck disable=2086\ntrue\necho $1"
+    check "#!/bin/sh\n#unrelated\n# shellcheck disable=2086\ntrue\necho $1"
 prop_filewideAnnotation4 = null $
     check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
 prop_filewideAnnotation5 = null $
@@ -197,6 +213,5 @@ prop_filewideAnnotation8 = null $
 prop_sourcePartOfOriginalScript = -- #1181: -x disabled posix warning for 'source'
     2039 `elem` checkWithIncludes [("./saywhat.sh", "echo foo")] "#!/bin/sh\nsource ./saywhat.sh"
 
-
 return []
 runTests = $quickCheckAll
diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs
index 9936653..0d5d7da 100644
--- a/src/ShellCheck/Interface.hs
+++ b/src/ShellCheck/Interface.hs
@@ -52,11 +52,20 @@ emptyCheckSpec = CheckSpec {
     csShellTypeOverride = Nothing
 }
 
+newParseSpec :: ParseSpec
+newParseSpec = ParseSpec {
+    psFilename = "",
+    psScript = "",
+    psCheckSourced = False,
+    psShellTypeOverride = Nothing
+}
+
 -- Parser input and output
 data ParseSpec = ParseSpec {
     psFilename :: String,
     psScript :: String,
-    psCheckSourced :: Bool
+    psCheckSourced :: Bool,
+    psShellTypeOverride :: Maybe Shell
 } deriving (Show, Eq)
 
 data ParseResult = ParseResult {
diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs
index 3b3d8d4..1255d7e 100644
--- a/src/ShellCheck/Parser.hs
+++ b/src/ShellCheck/Parser.hs
@@ -305,7 +305,8 @@ initialSystemState = SystemState {
 
 data Environment m = Environment {
     systemInterface :: SystemInterface m,
-    checkSourced :: Bool
+    checkSourced :: Bool,
+    shellTypeOverride :: Maybe Shell
 }
 
 parseProblem level code msg = do
@@ -2965,17 +2966,24 @@ readScriptFile = do
         parseProblem ErrorC 1082
             "This file has a UTF-8 BOM. Remove it with: LC_CTYPE=C sed '1s/^...//' < yourscript ."
     sb <- option "" readShebang
-    verifyShell pos (getShell sb)
-    if isValidShell (getShell sb) /= Just False
+    allspacing
+    annotationStart <- startSpan
+    annotations <- readAnnotations
+    annotationId <- endSpan annotationStart
+    let shellAnnotationSpecified =
+            any (\x -> case x of ShellOverride {} -> True; _ -> False) annotations
+    shellFlagSpecified <- isJust <$> Mr.asks shellTypeOverride
+    let ignoreShebang = shellAnnotationSpecified || shellFlagSpecified
+
+    unless ignoreShebang $
+        verifyShebang pos (getShell sb)
+    if ignoreShebang || isValidShell (getShell sb) /= Just False
       then do
-            allspacing
-            annotationStart <- startSpan
-            annotations <- readAnnotations
-            annotationId <- endSpan annotationStart
             commands <- withAnnotations annotations readCompoundListOrEmpty
             id <- endSpan start
             verifyEof
-            let script = T_Annotation annotationId annotations $  T_Script id sb commands
+            let script = T_Annotation annotationId annotations $
+                            T_Script id sb commands
             reparseIndices script
         else do
             many anyChar
@@ -2993,7 +3001,7 @@ readScriptFile = do
                     then second
                     else basename first
 
-    verifyShell pos s =
+    verifyShebang pos s = do
         case isValidShell s of
             Just True -> return ()
             Just False -> parseProblemAt pos ErrorC 1071 "ShellCheck only supports sh/bash/dash/ksh scripts. Sorry!"
@@ -3055,16 +3063,16 @@ debugParseScript string =
     }
   where
     result = runIdentity $
-        parseScript (mockedSystemInterface []) $ ParseSpec {
+        parseScript (mockedSystemInterface []) $ newParseSpec {
             psFilename = "debug",
-            psScript = string,
-            psCheckSourced = False
+            psScript = string
         }
 
 testEnvironment =
     Environment {
         systemInterface = (mockedSystemInterface []),
-        checkSourced = False
+        checkSourced = False,
+        shellTypeOverride = Nothing
     }
 
 
@@ -3230,7 +3238,8 @@ parseScript sys spec =
   where
     env = Environment {
         systemInterface = sys,
-        checkSourced = psCheckSourced spec
+        checkSourced = psCheckSourced spec,
+        shellTypeOverride = psShellTypeOverride spec
     }
 
 -- Same as 'try' but emit syntax errors if the parse fails.