diff --git a/ShellCheck/Analyzer.hs b/ShellCheck/Analyzer.hs
index 6350a00..fb20f29 100644
--- a/ShellCheck/Analyzer.hs
+++ b/ShellCheck/Analyzer.hs
@@ -32,7 +32,7 @@ import qualified ShellCheck.Checks.ShellSupport
 analyzeScript :: AnalysisSpec -> AnalysisResult
 analyzeScript spec = AnalysisResult {
     arComments =
-        filterByAnnotation (asScript spec) . nub $
+        filterByAnnotation spec params . nub $
             runAnalytics spec
             ++ runChecker params (checkers params)
 }
diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs
index bb8df63..04ac457 100644
--- a/ShellCheck/AnalyzerLib.hs
+++ b/ShellCheck/AnalyzerLib.hs
@@ -109,6 +109,7 @@ data VariableState = Dead Token String | Alive deriving (Show)
 defaultSpec root = AnalysisSpec {
     asScript = root,
     asShellType = Nothing,
+    asCheckSourced = False,
     asExecutionMode = Executed
 }
 
@@ -116,7 +117,8 @@ pScript s =
   let
     pSpec = ParseSpec {
         psFilename = "script",
-        psScript = s
+        psScript = s,
+        psCheckSourced = False
     }
   in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
 
@@ -801,9 +803,10 @@ whenShell l c = do
     when (shell `elem` l ) c
 
 
-filterByAnnotation token =
+filterByAnnotation asSpec params =
     filter (not . shouldIgnore)
   where
+    token = asScript asSpec
     idFor (TokenComment id _) = id
     shouldIgnore note =
         any (shouldIgnoreFor (getCode note)) $
@@ -813,9 +816,9 @@ filterByAnnotation token =
       where
         hasNum (DisableComment ts) = num == ts
         hasNum _ = False
-    shouldIgnoreFor _ T_Include {} = True -- Ignore included files
+    shouldIgnoreFor _ T_Include {} = not $ asCheckSourced asSpec
     shouldIgnoreFor _ _ = False
-    parents = getParentTree token
+    parents = parentMap params
     getCode (TokenComment _ (Comment _ c _)) = c
 
 -- Is this a ${#anything}, to get string length or array count?
diff --git a/ShellCheck/Checker.hs b/ShellCheck/Checker.hs
index 3a7cd2e..297a2cd 100644
--- a/ShellCheck/Checker.hs
+++ b/ShellCheck/Checker.hs
@@ -54,7 +54,8 @@ checkScript sys spec = do
     checkScript contents = do
         result <- parseScript sys ParseSpec {
             psFilename = csFilename spec,
-            psScript = contents
+            psScript = contents,
+            psCheckSourced = csCheckSourced spec
         }
         let parseMessages = prComments result
         let analysisMessages =
@@ -77,6 +78,7 @@ checkScript sys spec = do
         AnalysisSpec {
             asScript = root,
             asShellType = csShellTypeOverride spec,
+            asCheckSourced = csCheckSourced spec,
             asExecutionMode = Executed
          }
 
@@ -88,13 +90,21 @@ getErrors sys spec =
 
 check = checkWithIncludes []
 
+checkWithSpec includes =
+    getErrors (mockedSystemInterface includes)
+
 checkWithIncludes includes src =
-    getErrors
-        (mockedSystemInterface includes)
-        emptyCheckSpec {
-            csScript = src,
-            csExcludedWarnings = [2148]
-        }
+    checkWithSpec includes emptyCheckSpec {
+        csScript = src,
+        csExcludedWarnings = [2148]
+    }
+
+checkRecursive includes src =
+    checkWithSpec includes emptyCheckSpec {
+        csScript = src,
+        csExcludedWarnings = [2148],
+        csCheckSourced = True
+    }
 
 prop_findsParseIssue = check "echo \"$12\"" == [1037]
 
@@ -153,6 +163,12 @@ prop_cantSourceDynamic2 =
 prop_canSourceDynamicWhenRedirected =
     null $ checkWithIncludes [("lib", "")] "#shellcheck source=lib\n. \"$1\""
 
+prop_recursiveAnalysis =
+    [2086] == checkRecursive [("lib", "echo $1")] "source lib"
+
+prop_recursiveParsing =
+    [1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib"
+
 prop_sourceDirectiveDoesntFollowFile =
     null $ checkWithIncludes
                 [("foo", "source bar"), ("bar", "baz=3")]
diff --git a/ShellCheck/Formatter/CheckStyle.hs b/ShellCheck/Formatter/CheckStyle.hs
index 9bd7166..2be073c 100644
--- a/ShellCheck/Formatter/CheckStyle.hs
+++ b/ShellCheck/Formatter/CheckStyle.hs
@@ -34,14 +34,27 @@ format = return Formatter {
         putStrLn "<checkstyle version='4.3'>",
 
     onFailure = outputError,
-    onResult = outputResult,
+    onResult = outputResults,
 
     footer = putStrLn "</checkstyle>"
 }
 
-outputResult result contents = do
-    let comments = makeNonVirtual (crComments result) contents
-    putStrLn . formatFile (crFilename result) $ comments
+outputResults cr sys =
+    if null comments
+    then outputFile (crFilename cr) "" []
+    else mapM_ outputGroup fileGroups
+  where
+    comments = crComments cr
+    fileGroups = groupWith sourceFile comments
+    outputGroup group = do
+        let filename = sourceFile (head group)
+        result <- (siReadFile sys) filename
+        let contents = either (const "") id result
+        outputFile filename contents group
+
+outputFile filename contents warnings = do
+    let comments = makeNonVirtual warnings contents
+    putStrLn . formatFile filename $ comments
 
 formatFile name comments = concat [
     "<file ", attr "name" name, ">\n",
diff --git a/ShellCheck/Formatter/Format.hs b/ShellCheck/Formatter/Format.hs
index 143de8d..c49b65e 100644
--- a/ShellCheck/Formatter/Format.hs
+++ b/ShellCheck/Formatter/Format.hs
@@ -25,11 +25,12 @@ import ShellCheck.Interface
 -- A formatter that carries along an arbitrary piece of data
 data Formatter = Formatter {
     header ::  IO (),
-    onResult :: CheckResult -> String -> IO (),
+    onResult :: CheckResult -> SystemInterface IO -> IO (),
     onFailure :: FilePath -> ErrorMessage -> IO (),
     footer :: IO ()
 }
 
+sourceFile (PositionedComment pos _ _) = posFile pos
 lineNo (PositionedComment pos _ _) = posLine pos
 endLineNo (PositionedComment _ end _) = posLine end
 colNo  (PositionedComment pos _ _) = posColumn pos
diff --git a/ShellCheck/Formatter/GCC.hs b/ShellCheck/Formatter/GCC.hs
index ae542bf..52fe04e 100644
--- a/ShellCheck/Formatter/GCC.hs
+++ b/ShellCheck/Formatter/GCC.hs
@@ -31,14 +31,25 @@ format = return Formatter {
     header = return (),
     footer = return (),
     onFailure = outputError,
-    onResult = outputResult
+    onResult = outputAll
 }
 
 outputError file error = hPutStrLn stderr $ file ++ ": " ++ error
 
-outputResult result contents = do
-    let comments = makeNonVirtual (crComments result) contents
-    mapM_ (putStrLn . formatComment (crFilename result)) comments
+outputAll cr sys = mapM_ f groups
+  where
+    comments = crComments cr
+    groups = groupWith sourceFile comments
+    f :: [PositionedComment] -> IO ()
+    f group = do
+        let filename = sourceFile (head group)
+        result <- (siReadFile sys) filename
+        let contents = either (const "") id result
+        outputResult filename contents group
+
+outputResult filename contents warnings = do
+    let comments = makeNonVirtual warnings contents
+    mapM_ (putStrLn . formatComment filename) comments
 
 formatComment filename c = concat [
     filename, ":",
diff --git a/ShellCheck/Formatter/TTY.hs b/ShellCheck/Formatter/TTY.hs
index 444c28b..27ecdc7 100644
--- a/ShellCheck/Formatter/TTY.hs
+++ b/ShellCheck/Formatter/TTY.hs
@@ -43,15 +43,22 @@ colorForLevel level =
         "style"   -> 32 -- green
         "message" -> 1 -- bold
         "source"  -> 0 -- none
-        otherwise -> 0 -- none
+        _ -> 0         -- none
 
 outputError options file error = do
     color <- getColorFunc $ foColorOption options
     hPutStrLn stderr $ color "error" $ file ++ ": " ++ error
 
-outputResult options result contents = do
+outputResult options result sys = do
     color <- getColorFunc $ foColorOption options
     let comments = crComments result
+    let fileGroups = groupWith sourceFile comments
+    mapM_ (outputForFile color sys) fileGroups
+
+outputForFile color sys comments = do
+    let fileName = sourceFile (head comments)
+    result <- (siReadFile sys) fileName
+    let contents = either (const "") id result
     let fileLines = lines contents
     let lineCount = fromIntegral $ length fileLines
     let groups = groupWith lineNo comments
@@ -62,7 +69,7 @@ outputResult options result contents = do
                         else fileLines !! fromIntegral (lineNum - 1)
         putStrLn ""
         putStrLn $ color "message" $
-           "In " ++ crFilename result ++" line " ++ show lineNum ++ ":"
+           "In " ++ fileName ++" line " ++ show lineNum ++ ":"
         putStrLn (color "source" line)
         mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) x
         putStrLn ""
diff --git a/ShellCheck/Interface.hs b/ShellCheck/Interface.hs
index 861be12..3b77d94 100644
--- a/ShellCheck/Interface.hs
+++ b/ShellCheck/Interface.hs
@@ -33,6 +33,7 @@ newtype SystemInterface m = SystemInterface {
 data CheckSpec = CheckSpec {
     csFilename :: String,
     csScript :: String,
+    csCheckSourced :: Bool,
     csExcludedWarnings :: [Integer],
     csShellTypeOverride :: Maybe Shell
 } deriving (Show, Eq)
@@ -46,6 +47,7 @@ emptyCheckSpec :: CheckSpec
 emptyCheckSpec = CheckSpec {
     csFilename = "",
     csScript = "",
+    csCheckSourced = False,
     csExcludedWarnings = [],
     csShellTypeOverride = Nothing
 }
@@ -53,7 +55,8 @@ emptyCheckSpec = CheckSpec {
 -- Parser input and output
 data ParseSpec = ParseSpec {
     psFilename :: String,
-    psScript :: String
+    psScript :: String,
+    psCheckSourced :: Bool
 } deriving (Show, Eq)
 
 data ParseResult = ParseResult {
@@ -66,7 +69,8 @@ data ParseResult = ParseResult {
 data AnalysisSpec = AnalysisSpec {
     asScript :: Token,
     asShellType :: Maybe Shell,
-    asExecutionMode :: ExecutionMode
+    asExecutionMode :: ExecutionMode,
+    asCheckSourced :: Bool
 }
 
 newtype AnalysisResult = AnalysisResult {
diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs
index f75130c..1732b56 100644
--- a/ShellCheck/Parser.hs
+++ b/ShellCheck/Parser.hs
@@ -47,7 +47,7 @@ import qualified Data.Map as Map
 
 import Test.QuickCheck.All (quickCheckAll)
 
-type SCBase m = Mr.ReaderT (SystemInterface m) (Ms.StateT SystemState m)
+type SCBase m = Mr.ReaderT (Environment m) (Ms.StateT SystemState m)
 type SCParser m v = ParsecT String UserState (SCBase m) v
 
 backslash :: Monad m => SCParser m Char
@@ -248,12 +248,14 @@ addParseNote n = do
 
 shouldIgnoreCode code = do
     context <- getCurrentContexts
-    return $ any disabling context
+    checkSourced <- Mr.asks checkSourced
+    return $ any (disabling checkSourced) context
   where
-    disabling (ContextAnnotation list) =
-        any disabling' list
-    disabling (ContextSource _) = True -- Don't add messages for sourced files
-    disabling _ = False
+    disabling checkSourced item =
+        case item of
+            ContextAnnotation list -> any disabling' list
+            ContextSource _ -> not $ checkSourced
+            _ -> False
     disabling' (DisableComment n) = code == n
     disabling' _ = False
 
@@ -297,6 +299,11 @@ initialSystemState = SystemState {
     parseProblems = []
 }
 
+data Environment m = Environment {
+    systemInterface :: SystemInterface m,
+    checkSourced :: Bool
+}
+
 parseProblem level code msg = do
     pos <- getPosition
     parseProblemAt pos level code msg
@@ -1879,7 +1886,7 @@ readSource pos t@(T_Redirecting _ _ (T_SimpleCommand _ _ (cmd:file:_))) = do
                     "This file appears to be recursively sourced. Ignoring."
                 return t
               else do
-                sys <- Mr.ask
+                sys <- Mr.asks systemInterface
                 input <-
                     if filename == "/dev/null" -- always allow /dev/null
                     then return (Right "")
@@ -2788,16 +2795,22 @@ readScript = do
 -- Interactively run a parser in ghci:
 -- debugParse readScript "echo 'hello world'"
 debugParse p string = runIdentity $ do
-    (res, _) <- runParser (mockedSystemInterface []) p "-" string
+    (res, _) <- runParser testEnvironment p "-" string
     return res
 
+testEnvironment =
+    Environment {
+        systemInterface = (mockedSystemInterface []),
+        checkSourced = False
+    }
+
 
 isOk p s =      parsesCleanly p s == Just True   -- The string parses with no warnings
 isWarning p s = parsesCleanly p s == Just False  -- The string parses with warnings
 isNotOk p s =   parsesCleanly p s == Nothing     -- The string does not parse
 
 parsesCleanly parser string = runIdentity $ do
-    (res, sys) <- runParser (mockedSystemInterface [])
+    (res, sys) <- runParser testEnvironment
                     (parser >> eof >> getState) "-" string
     case (res, sys) of
         (Right userState, systemState) ->
@@ -2842,22 +2855,22 @@ getStringFromParsec errors =
                 Message s     ->  if null s then Nothing else return $ s ++ "."
 
 runParser :: Monad m =>
-    SystemInterface m ->
+    Environment m ->
     SCParser m v ->
     String ->
     String ->
     m (Either ParseError v, SystemState)
 
-runParser sys p filename contents =
+runParser env p filename contents =
     Ms.runStateT
         (Mr.runReaderT
             (runParserT p initialUserState filename contents)
-            sys)
+            env)
         initialSystemState
 system = lift . lift . lift
 
-parseShell sys name contents = do
-    (result, state) <- runParser sys (parseWithNotes readScript) name contents
+parseShell env name contents = do
+    (result, state) <- runParser env (parseWithNotes readScript) name contents
     case result of
         Right (script, userstate) ->
             return ParseResult {
@@ -2943,7 +2956,12 @@ posToPos sp = Position {
 parseScript :: Monad m =>
         SystemInterface m -> ParseSpec -> m ParseResult
 parseScript sys spec =
-    parseShell sys (psFilename spec) (psScript spec)
+    parseShell env (psFilename spec) (psScript spec)
+  where
+    env = Environment {
+        systemInterface = sys,
+        checkSourced = psCheckSourced spec
+    }
 
 
 return []
diff --git a/shellcheck.1.md b/shellcheck.1.md
index c957896..eb5c171 100644
--- a/shellcheck.1.md
+++ b/shellcheck.1.md
@@ -32,6 +32,12 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
 
 # OPTIONS
 
+**-a**,\ **--check-sourced**
+
+:   Emit warnings in sourced files. Normally, `shellcheck` will only warn
+    about issues in the specified files. With this option, any issues in
+    sourced files files will also be reported.
+
 **-C**[*WHEN*],\ **--color**[=*WHEN*]
 
 :   For TTY output, enable colors *always*, *never* or *auto*. The default
@@ -67,6 +73,7 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
     line (plus `/dev/null`). This option allows following any file the script
     may `source`.
 
+
 # FORMATS
 
 **tty**
diff --git a/shellcheck.hs b/shellcheck.hs
index 09055d9..9b41525 100644
--- a/shellcheck.hs
+++ b/shellcheck.hs
@@ -33,8 +33,9 @@ import Control.Monad
 import Control.Monad.Except
 import Data.Bits
 import Data.Char
-import Data.Functor
 import Data.Either
+import Data.Functor
+import Data.IORef
 import Data.List
 import qualified Data.Map as Map
 import Data.Maybe
@@ -75,21 +76,23 @@ defaultOptions = Options {
 
 usageHeader = "Usage: shellcheck [OPTIONS...] FILES..."
 options = [
-    Option "e" ["exclude"]
-        (ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings",
-    Option "f" ["format"]
-        (ReqArg (Flag "format") "FORMAT") $
-        "output format (" ++ formatList ++ ")",
+    Option "a" ["check-sourced"]
+        (NoArg $ Flag "sourced" "false") "Include warnings from sourced files",
     Option "C" ["color"]
         (OptArg (maybe (Flag "color" "always") (Flag "color")) "WHEN")
         "Use color (auto, always, never)",
+    Option "e" ["exclude"]
+        (ReqArg (Flag "exclude") "CODE1,CODE2..") "Exclude types of warnings",
+    Option "f" ["format"]
+        (ReqArg (Flag "format") "FORMAT") $
+        "Output format (" ++ formatList ++ ")",
     Option "s" ["shell"]
         (ReqArg (Flag "shell") "SHELLNAME")
         "Specify dialect (sh, bash, dash, ksh)",
-    Option "x" ["external-sources"]
-        (NoArg $ Flag "externals" "true") "Allow 'source' outside of FILES.",
     Option "V" ["version"]
-        (NoArg $ Flag "version" "true") "Print version information"
+        (NoArg $ Flag "version" "true") "Print version information",
+    Option "x" ["external-sources"]
+        (NoArg $ Flag "externals" "true") "Allow 'source' outside of FILES"
     ]
 
 printErr = lift . hPutStrLn stderr
@@ -136,7 +139,7 @@ getExclusions options =
     in
         map (Prelude.read . clean) elements :: [Int]
 
-toStatus = liftM (either id id) . runExceptT
+toStatus = fmap (either id id) . runExceptT
 
 getEnvArgs = do
     opts <- getEnv "SHELLCHECK_OPTS" `catch` cantWaitForLookupEnv
@@ -193,23 +196,27 @@ runFormatter sys format options files = do
         newStatus <- process file `catch` handler file
         return $ status `mappend` newStatus
     handler :: FilePath -> IOException -> IO Status
-    handler file e = do
-        onFailure format file (show e)
+    handler file e = reportFailure file (show e)
+    reportFailure file str = do
+        onFailure format file str
         return RuntimeException
 
     process :: FilePath -> IO Status
     process filename = do
-        contents <- inputFile filename
-        let checkspec = (checkSpec options) {
-            csFilename = filename,
-            csScript = contents
-        }
-        result <- checkScript sys checkspec
-        onResult format result contents
-        return $
-            if null (crComments result)
-            then NoProblems
-            else SomeProblems
+        input <- (siReadFile sys) filename
+        either (reportFailure filename) check input
+      where
+        check contents = do
+            let checkspec = (checkSpec options) {
+                csFilename = filename,
+                csScript = contents
+            }
+            result <- checkScript sys checkspec
+            onResult format result sys
+            return $
+                if null (crComments result)
+                then NoProblems
+                else SomeProblems
 
 parseColorOption colorOption =
     case colorOption of
@@ -254,6 +261,13 @@ parseOption flag options =
                 }
             }
 
+        Flag "sourced" _ ->
+            return options {
+                checkSpec = (checkSpec options) {
+                    csCheckSourced = True
+                }
+            }
+
         _ -> return options
   where
     die s = do
@@ -268,14 +282,28 @@ parseOption flag options =
 
 ioInterface options files = do
     inputs <- mapM normalize files
+    cache <- newIORef emptyCache
     return SystemInterface {
-        siReadFile = get inputs
+        siReadFile = get cache inputs
     }
   where
-    get inputs file = do
+    emptyCache :: Map.Map FilePath String
+    emptyCache = Map.empty
+    get cache inputs file = do
+        map <- readIORef cache
+        case Map.lookup file map of
+            Just x -> return $ Right x
+            Nothing -> fetch cache inputs file
+
+    fetch cache inputs file = do
         ok <- allowable inputs file
         if ok
-          then (Right <$> inputFile file) `catch` handler
+          then (do
+            (contents, shouldCache) <- inputFile file
+            when shouldCache $
+                modifyIORef cache $ Map.insert file contents
+            return $ Right contents
+            ) `catch` handler
           else return $ Left (file ++ " was not specified as input (see shellcheck -x).")
 
       where
@@ -296,16 +324,19 @@ ioInterface options files = do
         fallback path _ = return path
 
 inputFile file = do
-    handle <-
+    (handle, shouldCache) <-
             if file == "-"
-            then return stdin
-            else openBinaryFile file ReadMode
+            then return (stdin, True)
+            else do
+                h <- openBinaryFile file ReadMode
+                reopenable <- hIsSeekable h
+                return (h, not reopenable)
 
     hSetBinaryMode handle True
     contents <- decodeString <$> hGetContents handle -- closes handle
 
     seq (length contents) $
-        return contents
+        return (contents, shouldCache)
 
 -- Decode a char8 string into a utf8 string, with fallback on
 -- ISO-8859-1. This avoids depending on additional libraries.