Skip to content

Commit

Permalink
Reproduction attempt
Browse files Browse the repository at this point in the history
  • Loading branch information
elldritch committed Jan 11, 2024
1 parent 64c2f20 commit 4988e9d
Show file tree
Hide file tree
Showing 4 changed files with 43 additions and 21 deletions.
25 changes: 14 additions & 11 deletions src/Strategy/Gradle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -262,21 +262,24 @@ analyze ::
Path Abs Dir ->
m (Graphing Dependency)
analyze foundTargets dir = withSystemTempDir "fossa-gradle" $ \tmpDir -> do
let initScriptFilepath = fromAbsDir tmpDir FilePath.</> "jsondeps.gradle"
context "Writing gradle script" $ sendIO (BS.writeFile initScriptFilepath initScript)
-- let initScriptFilepath = fromAbsDir tmpDir FilePath.</> "jsondeps.gradle"
-- context "Writing gradle script" $ sendIO (BS.writeFile initScriptFilepath initScript)

let cmd :: Text -> Command
cmd = case foundTargets of
FoundTargets targets -> gradleJsonDepsCmdTargets initScriptFilepath (toSet targets)
ProjectWithoutTargets -> gradleJsonDepsCmd initScriptFilepath
-- let cmd :: Text -> Command
-- cmd = case foundTargets of
-- FoundTargets targets -> gradleJsonDepsCmdTargets initScriptFilepath (toSet targets)
-- ProjectWithoutTargets -> gradleJsonDepsCmd initScriptFilepath

stdout <- context "running gradle script" $ errCtx FailedToRunGradleAnalysis $ runGradle dir cmd
-- stdout <- context "running gradle script" $ errCtx FailedToRunGradleAnalysis $ runGradle dir cmd

onlyConfigurations <- do
configs <- asks allowedGradleConfigs
pure $ maybe Set.empty (Set.map ConfigName) configs
-- onlyConfigurations <- do
-- configs <- asks allowedGradleConfigs
-- pure $ maybe Set.empty (Set.map ConfigName) configs

let text = decodeUtf8 $ BL.toStrict stdout
let onlyConfigurations = Set.fromList ["compileOnly", "nativeLibsInputZips", "runtimeClasspath", "runtimeOnly"]

-- let text = decodeUtf8 $ BL.toStrict stdout
text <- fmap toText $ sendIO $ readFile "/home/leo/tmp/zd-7543/yubico-search.txt"
let resolvedProjects = ResolutionApi.parseResolutionApiJsonDeps text
let graphFromResolutionApi = ResolutionApi.buildGraph resolvedProjects (onlyConfigurations)

Expand Down
7 changes: 4 additions & 3 deletions src/Strategy/Gradle/Common.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,15 +14,16 @@ module Strategy.Gradle.Common (

import Data.Aeson (FromJSON)
import Data.Maybe (mapMaybe)
import Data.String (IsString)
import Data.Text (Text)
import Data.Text qualified as Text
import DepTypes (DepEnvironment (..))
import Strategy.Android.Util (isDefaultAndroidDevConfig, isDefaultAndroidTestConfig)

newtype ConfigName = ConfigName {unConfigName :: Text} deriving (Eq, Ord, Show, FromJSON)
newtype ConfigName = ConfigName {unConfigName :: Text} deriving (Eq, Ord, Show, FromJSON, IsString)
newtype GradleLabel = Env DepEnvironment deriving (Eq, Ord, Show)
newtype PackageName = PackageName {unPackageName :: Text} deriving (Eq, Ord, Show, FromJSON)
newtype ProjectName = ProjectName {unProjectName :: Text} deriving (Eq, Ord, Show, FromJSON)
newtype PackageName = PackageName {unPackageName :: Text} deriving (Eq, Ord, Show, FromJSON, IsString)
newtype ProjectName = ProjectName {unProjectName :: Text} deriving (Eq, Ord, Show, FromJSON, IsString)

packagePathsWithJson :: [Text] -> [(PackageName, Text)]
packagePathsWithJson = map (\line -> let (x, y) = Text.breakOn "_{" line in (PackageName x, Text.drop 1 y))
Expand Down
7 changes: 4 additions & 3 deletions src/Strategy/Gradle/ResolutionApi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,9 +124,10 @@ buildGraph projects onlyConfigs = run . withLabeling toDependency $ mapM_ addCon
-- Ref: https://docs.gradle.org/current/userguide/java_library_plugin.html#sec:java_library_configurations_graph
toGradleLabel :: ConfigName -> GradleLabel
toGradleLabel conf =
if not $ Set.null onlyConfigs
then Env $ EnvOther (unConfigName conf) -- We only have specified configs, so we mark them all as Other.
else configNameToLabel (unConfigName conf) -- We have no specified configs, so we have to guess the correct Env.
if Set.null onlyConfigs
then configNameToLabel (unConfigName conf) -- We have no specified configs, so we have to guess the correct Env.
else Env $ EnvOther (unConfigName conf) -- We only have specified configs, so we mark them all as Other.

toDependency :: ResolvedDependency -> Set.Set GradleLabel -> Dependency
toDependency dep = foldr applyLabel $ fromResolvedDep dep

Expand Down
25 changes: 21 additions & 4 deletions test/Gradle/ResolutionApiSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,20 +4,22 @@ module Gradle.ResolutionApiSpec (

import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.String.Conversion (toText)
import Data.Text (Text)
import DepTypes
import GraphUtil (expectDeps, expectDirect, expectEdges)
import GraphUtil (expectDep, expectDeps, expectDirect, expectEdges)
import Graphing (Graphing, empty)
import Strategy.Gradle.Common (
ConfigName (ConfigName),
ProjectName (ProjectName),
ConfigName (..),
ProjectName (..),
)
import Strategy.Gradle.ResolutionApi (
ResolvedComponent (ResolvedComponent),
ResolvedComponent (..),
ResolvedConfiguration (..),
ResolvedDependency (..),
ResolvedProject (..),
buildGraph,
parseResolutionApiJsonDeps,
)
import Test.Hspec (Spec, describe, it, shouldBe)

Expand Down Expand Up @@ -184,3 +186,18 @@ spec = do
[ (projectFiveCustomEnv, packageFiveCustomEnv)
]
graph

it "TEST TEST TEST" $ do
exampleInputSingle <- toText <$> readFile "/home/leo/tmp/zd-7543/yubico-search.txt"
let parsed = parseResolutionApiJsonDeps exampleInputSingle
let graph = buildGraph parsed (Set.fromList ["compileOnly", "nativeLibsInputZips", "runtimeClasspath", "runtimeOnly"])
let expected =
Dependency
{ dependencyType = MavenType
, dependencyName = "com.yubico:yubihsm"
, dependencyVersion = Just (CEq "2.3.0.0")
, dependencyLocations = []
, dependencyEnvironments = Set.singleton $ EnvOther "nativeLibsInputZips"
, dependencyTags = Map.empty
}
expectDep expected graph

0 comments on commit 4988e9d

Please sign in to comment.