Skip to content

Commit

Permalink
[ANE-2123] A fix around listing excluded dirs (#1493)
Browse files Browse the repository at this point in the history
* [ANE-2123] Get Walk.Discovery.walkWithFilters to avoid listDir calls on excluded dirs

* [ANE-2123] Add a spec for walkWithFilters' to check that it does not touch excluded dirs

* Update src/Discovery/Walk.hs

Co-authored-by: Christopher Sasarak <csasarak@users.noreply.github.com>

* [ANE-2123] Address PR comments

* [ANE-2123] Fix formatting

* [ANE-2123] Update changelog to match our standard format and reflect our readers' expectations

---------

Co-authored-by: James Clemer <clemer19@gmail.com>
Co-authored-by: Christopher Sasarak <csasarak@users.noreply.github.com>
  • Loading branch information
3 people authored Jan 15, 2025
1 parent 9a86016 commit 847addf
Show file tree
Hide file tree
Showing 11 changed files with 181 additions and 34 deletions.
3 changes: 3 additions & 0 deletions Changelog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,8 @@
# FOSSA CLI Changelog

## 3.9.43
- Discovery: Fix a bug where directories in paths.exclude may still be accessed during discovery which causes an error when users don't have permission to read those directories.

## 3.9.42
- Licensing: Adds support for the Text-Tabs+Wrap License

Expand Down
6 changes: 5 additions & 1 deletion src/App/Fossa/Analyze.hs
Original file line number Diff line number Diff line change
Expand Up @@ -413,7 +413,11 @@ analyze cfg = Diag.context "fossa-analyze" $ do
reachabilityUnitsResult <-
case orgInfo of
(Just (Organization{orgSupportsReachability = False})) -> pure []
_ -> Diag.context "reachability analysis" . runReader (Config.reachabilityConfig cfg) $ analyzeForReachability projectScans
_ ->
Diag.context "reachability analysis"
. runReader (Config.reachabilityConfig cfg)
. runReader filters
$ analyzeForReachability projectScans
let reachabilityUnits = onlyFoundUnits reachabilityUnitsResult

let analysisResult = AnalysisScanResult projectScans vsiResults binarySearchResults manualSrcUnits dynamicLinkedResults maybeLernieResults reachabilityUnitsResult
Expand Down
4 changes: 4 additions & 0 deletions src/App/Fossa/Reachability/Maven.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,11 +7,13 @@ import App.Fossa.Reachability.Jar (callGraphFromJars, isValidJar)
import App.Fossa.Reachability.Types (CallGraphAnalysis (..))
import Control.Carrier.Lift (Lift)
import Control.Effect.Diagnostics (Diagnostics, context, fromEither, recover)
import Control.Effect.Reader (Reader)
import Control.Monad (filterM, join)
import Data.Map qualified as Map
import Data.Maybe (catMaybes, fromMaybe)
import Data.String.Conversion (ToText (toText))
import Data.Text (Text, replace)
import Discovery.Filters (AllFilters)
import Effect.Exec (Exec)
import Effect.Logger (Logger, logDebug, pretty)
import Effect.ReadFS (Has, ReadFS, resolveDir', resolveFile)
Expand All @@ -32,6 +34,7 @@ mavenJarCallGraph ::
, Has Diagnostics sig m
, Has Exec sig m
, Has (Lift IO) sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m CallGraphAnalysis
Expand All @@ -44,6 +47,7 @@ getJarsByBuild ::
( Has Logger sig m
, Has ReadFS sig m
, Has Diagnostics sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m [Path Abs File]
Expand Down
3 changes: 3 additions & 0 deletions src/App/Fossa/Reachability/Upload.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ import Data.List (nub)
import Data.Map qualified as Map
import Data.Maybe (mapMaybe)
import Diag.Result (Result (..))
import Discovery.Filters (AllFilters)
import Effect.Exec (Exec)
import Effect.Logger (Logger, logDebug, logInfo, pretty)
import Effect.ReadFS (ReadFS)
Expand All @@ -57,6 +58,7 @@ analyzeForReachability ::
, Has (Lift IO) sig m
, Has Debug sig m
, Has (Reader ReachabilityConfig) sig m
, Has (Reader AllFilters) sig m
) =>
[DiscoveredProjectScan] ->
m [SourceUnitReachabilityAttempt]
Expand Down Expand Up @@ -107,6 +109,7 @@ callGraphOf ::
, Has (Lift IO) sig m
, Has Debug sig m
, Has (Reader ReachabilityConfig) sig m
, Has (Reader AllFilters) sig m
) =>
DiscoveredProjectScan ->
m SourceUnitReachabilityAttempt
Expand Down
36 changes: 31 additions & 5 deletions src/Discovery/Walk.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,10 +14,11 @@ module Discovery.Walk (
) where

import Control.Carrier.Writer.Church
import Control.Effect.Diagnostics
import Control.Effect.Diagnostics (Diagnostics, context, fatal)
import Control.Effect.Reader (Reader, ask)
import Control.Monad.Trans
import Control.Monad.Trans.Maybe
import Data.Bifunctor (second)
import Data.Foldable (find)
import Data.Functor (void)
import Data.Glob qualified as Glob
Expand Down Expand Up @@ -73,17 +74,41 @@ pathFilterIntercept ::
AllFilters ->
Path Abs Dir ->
Path Abs Dir ->
[Path Abs Dir] ->
m (o, WalkStep) ->
m (o, WalkStep)
pathFilterIntercept filters base path act = do
pathFilterIntercept filters base dir subdirs act = do
-- We know that the two have the same base, but if that invariant is broken,
-- we just allow the path during discovery. It's better than crashing.
case stripProperPrefix base path of
case stripProperPrefix base dir of
Nothing -> act
Just relative ->
if pathAllowed filters relative
then act
then (fmap . second) skipDisallowed act
else pure (mempty, WalkSkipAll)
where
disallowedSubdirs :: [Text]
disallowedSubdirs = do
subdir <- subdirs
stripped <- stripProperPrefix base subdir
let isAllowed = pathAllowed filters stripped
if isAllowed
then mempty
else pure $ (toText . toFilePath . dirname) subdir

-- skipDisallowed needs to look at either:
-- * WalkStep.WalkContinue
-- * WalkStep.WalkSkipSome [Text]
-- and add on any missing disallowed subdirs
skipDisallowed :: WalkStep -> WalkStep
skipDisallowed action =
if null disallowedSubdirs
then
action
else case action of
WalkContinue -> WalkSkipSome disallowedSubdirs
WalkSkipSome dirs -> WalkSkipSome $ disallowedSubdirs ++ dirs
_ -> action

-- | Like @walk@, but collects the output of @f@ in a monoid.
walk' ::
Expand Down Expand Up @@ -117,7 +142,7 @@ walkWithFilters' ::
m o
walkWithFilters' f root = do
filters <- ask
let f' dir subdirs files = pathFilterIntercept filters root dir $ f dir subdirs files
let f' dir subdirs files = pathFilterIntercept filters root dir subdirs $ f dir subdirs files
walk' f' root

-- | Search upwards in the directory tree for the existence of the supplied file.
Expand Down Expand Up @@ -169,6 +194,7 @@ walkDir ::
walkDir handler topdir =
context "Walking the filetree" $
void $
-- makeAbsolute topdir >>= walkAvoidLoop Set.empty
-- makeAbsolute topdir >>= walkAvoidLoop Set.empty
walkAvoidLoop Set.empty topdir
where
Expand Down
17 changes: 10 additions & 7 deletions src/Strategy/Maven/Pom/Closure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,21 +27,24 @@ import Path.IO qualified as PIO
import Strategy.Maven.Pom.PomFile
import Strategy.Maven.Pom.Resolver

import Control.Effect.Reader (Reader)
import Data.Text (Text)
import Discovery.Filters (AllFilters)

findProjects :: (Has ReadFS sig m, Has Diagnostics sig m) => Path Abs Dir -> m [MavenProjectClosure]
findProjects :: (Has ReadFS sig m, Has Diagnostics sig m, Has (Reader AllFilters) sig m) => Path Abs Dir -> m [MavenProjectClosure]
findProjects basedir = do
pomFiles <- context "Finding pom files" $ findPomFiles basedir
globalClosure <- context "Building global closure" $ buildGlobalClosure pomFiles
context "Building project closures" $ pure (buildProjectClosures basedir globalClosure)

findPomFiles :: (Has ReadFS sig m, Has Diagnostics sig m) => Path Abs Dir -> m [Path Abs File]
findPomFiles dir = execState @[Path Abs File] [] $
flip walk dir $ \_ _ files -> do
let poms = filter (\file -> "pom.xml" `isSuffixOf` fileName file || ".pom" `isSuffixOf` fileName file) files
traverse_ (modify . (:)) poms
findPomFiles :: (Has ReadFS sig m, Has Diagnostics sig m, Has (Reader AllFilters) sig m) => Path Abs Dir -> m [Path Abs File]
findPomFiles dir =
execState @[Path Abs File] [] $
flip walkWithFilters' dir $ \_ _ files -> do
let poms = filter (\file -> "pom.xml" `isSuffixOf` fileName file || ".pom" `isSuffixOf` fileName file) files
traverse_ (modify . (:)) poms

pure (WalkSkipSome ["target"])
pure ((), WalkSkipSome ["target"])

buildProjectClosures :: Path Abs Dir -> GlobalClosure -> [MavenProjectClosure]
buildProjectClosures basedir global = closures
Expand Down
6 changes: 3 additions & 3 deletions src/Strategy/Node.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,7 @@ import Discovery.Filters (AllFilters, withMultiToolFilter)
import Discovery.Walk (
WalkStep (WalkSkipSome),
findFileNamed,
walk',
walkWithFilters',
)
import Effect.Logger (
Logger,
Expand Down Expand Up @@ -129,8 +129,8 @@ discover dir = withMultiToolFilter [YarnProjectType, NpmProjectType, PnpmProject
graphs <- context "Splitting global graph into chunks" $ fromMaybe CyclicPackageJson $ splitGraph globalGraph
context "Converting graphs to analysis targets" $ traverse (mkProject <=< identifyProjectType) graphs

collectManifests :: (Has ReadFS sig m, Has Diagnostics sig m) => Path Abs Dir -> m [Manifest]
collectManifests = walk' $ \_ _ files ->
collectManifests :: (Has ReadFS sig m, Has Diagnostics sig m, Has (Reader AllFilters) sig m) => Path Abs Dir -> m [Manifest]
collectManifests = walkWithFilters' $ \_ _ files ->
case findFileNamed "package.json" files of
Nothing -> pure ([], skipJsFolders)
Just jsonFile -> pure ([Manifest jsonFile], skipJsFolders)
Expand Down
44 changes: 34 additions & 10 deletions src/Strategy/SwiftPM.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ import Discovery.Simple (simpleDiscover)
import Discovery.Walk (
WalkStep (WalkContinue, WalkSkipSome),
findFileNamed,
walk',
walkWithFilters',
)
import Effect.Logger (Logger, Pretty (pretty), logDebug)
import Effect.ReadFS (ReadFS)
Expand Down Expand Up @@ -54,15 +54,27 @@ instance ToJSON SwiftProject
discover :: (Has ReadFS sig m, Has Diagnostics sig m, Has Logger sig m, Has (Reader AllFilters) sig m) => Path Abs Dir -> m [DiscoveredProject SwiftProject]
discover = simpleDiscover findProjects mkProject SwiftProjectType

findProjects :: (Has ReadFS sig m, Has Diagnostics sig m, Has Logger sig m) => Path Abs Dir -> m [SwiftProject]
findProjects ::
( Has ReadFS sig m
, Has Diagnostics sig m
, Has Logger sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m [SwiftProject]
findProjects dir = do
swiftPackageProjects <- context "Finding swift package projects" $ findSwiftPackageProjects dir
xCodeProjects <- context "Finding xcode projects using swift package manager" $ findXcodeProjects dir
pure (swiftPackageProjects <> xCodeProjects)

-- TODO: determine if walkWithFilters' is safe here
findSwiftPackageProjects :: (Has ReadFS sig m, Has Diagnostics sig m) => Path Abs Dir -> m [SwiftProject]
findSwiftPackageProjects = walk' $ \dir _ files -> do
findSwiftPackageProjects ::
( Has ReadFS sig m
, Has Diagnostics sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m [SwiftProject]
findSwiftPackageProjects = walkWithFilters' $ \dir _ files -> do
let packageManifestFile = findFileNamed "Package.swift" files
let packageResolvedFile = findFileNamed "Package.resolved" files
case (packageManifestFile, packageResolvedFile) of
Expand All @@ -72,9 +84,15 @@ findSwiftPackageProjects = walk' $ \dir _ files -> do
-- Package.resolved without Package.swift or Xcode project file is not a valid swift project.
(Nothing, _) -> pure ([], WalkContinue)

-- TODO: determine if walkWithFilters' is safe here
findXcodeProjects :: (Has ReadFS sig m, Has Diagnostics sig m, Has Logger sig m) => Path Abs Dir -> m [SwiftProject]
findXcodeProjects = walk' $ \dir _ files -> do
findXcodeProjects ::
( Has ReadFS sig m
, Has Diagnostics sig m
, Has Logger sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m [SwiftProject]
findXcodeProjects = walkWithFilters' $ \dir _ files -> do
let xcodeProjectFile = findFileNamed "project.pbxproj" files
case xcodeProjectFile of
Nothing -> pure ([], WalkContinue)
Expand All @@ -89,8 +107,14 @@ findXcodeProjects = walk' $ \dir _ files -> do
-- XCode projects using swift package manager retain Package.resolved,
-- not in the same directory as project file, but rather in workspace's xcshareddata/swiftpm directory.
-- Reference: https://developer.apple.com/documentation/swift_packages/adding_package_dependencies_to_your_app.
findFirstResolvedFileRecursively :: (Has ReadFS sig m, Has Diagnostics sig m) => Path Abs Dir -> m (Maybe (Path Abs File))
findFirstResolvedFileRecursively baseDir = listToMaybe <$> walk' findFile baseDir
findFirstResolvedFileRecursively ::
( Has ReadFS sig m
, Has Diagnostics sig m
, Has (Reader AllFilters) sig m
) =>
Path Abs Dir ->
m (Maybe (Path Abs File))
findFirstResolvedFileRecursively baseDir = listToMaybe <$> walkWithFilters' findFile baseDir
where
isParentDirSwiftPm :: Path Abs Dir -> Bool
isParentDirSwiftPm d = (dirname d) == [reldir|swiftpm|]
Expand Down
4 changes: 1 addition & 3 deletions test/Discovery/FiltersSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Discovery.Filters (
withToolFilter,
)
import Path (Dir, Path, Rel, mkRelDir)
import Test.Fixtures (excludePath)
import Test.Hspec (
Expectation,
Spec,
Expand Down Expand Up @@ -284,9 +285,6 @@ testHarness include exclude = traverse_ testSingle
where
testSingle ((buildtool, dir), targets, expected) = applyFilters (AllFilters include exclude) buildtool dir targets `shouldBe` expected

excludePath :: Path Rel Dir -> AllFilters
excludePath path = AllFilters mempty $ comboExclude mempty [path]

excludeTool :: DiscoveredProjectType -> AllFilters
excludeTool tool = AllFilters mempty $ comboExclude [TypeTarget $ toText tool] mempty

Expand Down
Loading

0 comments on commit 847addf

Please sign in to comment.