Skip to content
This repository has been archived by the owner on Apr 1, 2022. It is now read-only.

dep envs are now sets #380

Merged
merged 2 commits into from
Sep 30, 2021
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 1 addition & 1 deletion src/App/Fossa/VSI/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ toDependency locator =
<*> Right (locatorProject locator)
<*> (Right . Just . CEq $ locatorRevision locator)
<*> Right []
<*> Right []
<*> Right mempty
<*> Right mempty

validateDepType :: Locator -> Either ToDependencyError DepType
Expand Down
6 changes: 4 additions & 2 deletions src/DepTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,8 @@ module DepTypes (
import Data.Aeson
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Data.Set qualified as Set
import Data.Text (Text)
import GHC.Generics (Generic)

Expand All @@ -24,13 +26,13 @@ data Dependency = Dependency
, dependencyName :: Text
, dependencyVersion :: Maybe VerConstraint
, dependencyLocations :: [Text]
, dependencyEnvironments :: [DepEnvironment] -- FIXME: this should be a Set
, dependencyEnvironments :: Set DepEnvironment
, dependencyTags :: Map Text [Text]
}
deriving (Eq, Ord, Show)

insertEnvironment :: DepEnvironment -> Dependency -> Dependency
insertEnvironment env dep = dep{dependencyEnvironments = env : dependencyEnvironments dep}
insertEnvironment env dep = dep{dependencyEnvironments = env `Set.insert` dependencyEnvironments dep}

insertTag :: Text -> Text -> Dependency -> Dependency
insertTag key value dep = dep{dependencyTags = Map.insertWith (++) key [value] (dependencyTags dep)}
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Cargo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -204,12 +204,12 @@ toDependency pkg =
, dependencyName = pkgIdName pkg
, dependencyVersion = Just $ CEq $ pkgIdVersion pkg
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
where
applyLabel :: CargoLabel -> Dependency -> Dependency
applyLabel (CargoDepKind env) dep = dep{dependencyEnvironments = env : dependencyEnvironments dep}
applyLabel (CargoDepKind env) = insertEnvironment env

-- Possible values here are "build", "dev", and null.
-- Null refers to productions, while dev and build refer to development-time dependencies
Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Carthage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -146,7 +146,7 @@ toDependency entry =
, dependencyName = entryToDepName entry
, dependencyVersion = Just (CEq (resolvedVersion entry))
, dependencyTags = Map.empty
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyLocations = [] -- TODO: git location?
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Cocoapods/Podfile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ buildGraph podfile = Graphing.fromList (map toDependency direct)
, dependencyLocations = case Map.lookup SourceProperty properties of
Just repo -> [repo]
_ -> [source podfile]
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Cocoapods/PodfileLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ toDependency externalSrc pkg = foldr applyLabel start
, dependencyName = depName
, dependencyVersion = Nothing
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Composer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -127,10 +127,10 @@ buildGraph lock = run . withLabeling toDependency $ do
, dependencyName = pkgName pkg
, dependencyVersion = Nothing
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

addLabel :: CompLabel -> Dependency -> Dependency
addLabel (DepVersion ver) dep = dep{dependencyVersion = Just (CEq ver)}
addLabel (CompEnv env) dep = dep{dependencyEnvironments = env : dependencyEnvironments dep}
addLabel (CompEnv env) dep = insertEnvironment env dep
2 changes: 1 addition & 1 deletion src/Strategy/Conda/CondaList.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ buildGraph deps = Graphing.fromList (map toDependency deps)
, dependencyName = listName
, dependencyVersion = CEq <$> listVersion
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Conda/EnvironmentYml.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ buildGraph envYmlFile = Graphing.fromList (map toDependency allDeps)
, dependencyName = depName
, dependencyVersion = CEq <$> depVersion -- todo - properly handle version constraints
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
5 changes: 3 additions & 2 deletions src/Strategy/Dart/PubSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ import Data.Foldable (asum, for_)
import Data.Map (Map, toList)
import Data.Map.Strict qualified as Map
import Data.Maybe (fromMaybe, maybeToList)
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Yaml (FromJSON (parseJSON), (.:), (.:?))
import Data.Yaml qualified as Yaml
Expand Down Expand Up @@ -116,7 +117,7 @@ toDependency environment name (HostedSource (PubSpecDepHostedSource version _ ur
, dependencyName = unPackageName name
, dependencyVersion = CEq <$> version
, dependencyLocations = maybeToList url
, dependencyEnvironments = [environment]
, dependencyEnvironments = Set.singleton environment
, dependencyTags = Map.empty
}
toDependency environment _ (GitSource (PubSpecDepGitSource gitRef gitUrl)) =
Expand All @@ -126,7 +127,7 @@ toDependency environment _ (GitSource (PubSpecDepGitSource gitRef gitUrl)) =
, dependencyName = gitUrl
, dependencyVersion = CEq <$> gitRef
, dependencyLocations = []
, dependencyEnvironments = [environment]
, dependencyEnvironments = Set.singleton environment
, dependencyTags = Map.empty
}
toDependency _ _ (SdkSource _) = Nothing
Expand Down
3 changes: 2 additions & 1 deletion src/Strategy/Dart/PubSpecLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Data.Aeson.Types qualified as AesonTypes
import Data.Foldable (asum, for_)
import Data.Map (Map)
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Yaml (FromJSON (parseJSON), (.:), (.:?))
Expand Down Expand Up @@ -128,7 +129,7 @@ toDependency pkg meta =
, dependencyName = depName
, dependencyVersion = depVersion
, dependencyLocations = depLocation
, dependencyEnvironments = pubLockPackageEnvironment meta
, dependencyEnvironments = Set.fromList $ pubLockPackageEnvironment meta
, dependencyTags = Map.empty
}
where
Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Elixir/MixTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -305,7 +305,7 @@ buildGraph deps depsResolved = unfold deps subDeps toDependency
, dependencyName = dName md depsResolved
, dependencyVersion = dVersion md depsResolved
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Erlang/Rebar3Tree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,7 +79,7 @@ buildGraph deps = unfold deps subDeps toDependency
, dependencyName = if Text.isInfixOf "github.com" depLocation then depLocation else depName
, dependencyVersion = Just (CEq depVersion)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Go/GlideLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ buildGraph lockfile = Graphing.fromList (map toDependency direct)
, dependencyName = depName
, dependencyVersion = Just (CEq depVersion)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Go/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ golangPackageToDependency pkg = foldr applyLabel start
, dependencyName = goImportPath pkg
, dependencyVersion = Nothing
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
3 changes: 2 additions & 1 deletion src/Strategy/Googlesource/RepoManifest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ import Control.Monad (unless)
import Data.Foldable (find)
import Data.HashMap.Strict qualified as HM
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Data.String.Conversion (toString, toText)
import Data.Text (Text)
import Data.Text.Prettyprint.Doc (pretty)
Expand Down Expand Up @@ -279,7 +280,7 @@ buildGraph projects = unfold projects (const []) toDependency
, dependencyVersion = Just (CEq validatedProjectRevision)
, dependencyLocations = [render validatedProjectUrl]
, dependencyTags = Map.empty
, dependencyEnvironments = [EnvProduction]
, dependencyEnvironments = Set.singleton EnvProduction
}

data ManifestGitConfigError
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Gradle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -346,7 +346,7 @@ buildGraph projectsAndDeps = run . withLabeling toDependency $ Map.traverseWithK
, dependencyName = name
, dependencyVersion = Just (CEq version)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand All @@ -356,7 +356,7 @@ buildGraph projectsAndDeps = run . withLabeling toDependency $ Map.traverseWithK
, dependencyName = name
, dependencyVersion = Nothing
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Haskell/Cabal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ toDependency plan =
, dependencyName = planName plan
, dependencyVersion = Just $ CEq $ planVersion plan
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Haskell/Stack.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,7 +120,7 @@ toDependency dep =
, dependencyName = unPackageName $ stackName dep
, dependencyVersion = Just $ CEq $ stackVersion dep
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Leiningen.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,7 @@ toDependency node = foldr applyLabel start
, dependencyName = nodeName node
, dependencyVersion = Just (CEq (nodeVersion node))
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
applyLabel (ScopeLabel "test") dep = insertEnvironment EnvTesting dep
Expand Down
4 changes: 3 additions & 1 deletion src/Strategy/Maven/DepTree.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ import Control.Effect.Exception (finally)
import Control.Effect.Lift (Lift, sendIO)
import Data.Char (isSpace)
import Data.Foldable (for_)
import Data.Set qualified as Set
import Data.String.Conversion (toString, toText)
import Data.Text (Text)
import Data.Text qualified as Text
Expand Down Expand Up @@ -154,7 +155,8 @@ toDependency PackageId{groupName, artifactName, artifactVersion, buildTag} =
, dependencyName = groupName <> ":" <> artifactName
, dependencyVersion = Just $ CEq artifactVersion
, dependencyLocations = []
, dependencyEnvironments = maybe [EnvProduction] ((: []) . toBuildTag) buildTag
, -- TODO: cleanup logic, no need to use list
dependencyEnvironments = Set.fromList $ maybe [EnvProduction] ((: []) . toBuildTag) buildTag
, dependencyTags = mempty
}

Expand Down
3 changes: 2 additions & 1 deletion src/Strategy/Maven/PluginStrategy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@ import Control.Effect.Lift (Lift)
import Data.Foldable (traverse_)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import DepTypes (
DepEnvironment (..),
DepType (MavenType),
Expand Down Expand Up @@ -67,7 +68,7 @@ buildGraph PluginOutput{..} = run $
, dependencyName = artifactGroupId <> ":" <> artifactArtifactId
, dependencyVersion = Just (CEq artifactVersion)
, dependencyLocations = []
, dependencyEnvironments = [EnvTesting | "test" `elem` artifactScopes]
, dependencyEnvironments = Set.fromList $ [EnvTesting | "test" `elem` artifactScopes]
, dependencyTags =
Map.fromList $
("scopes", artifactScopes) :
Expand Down
4 changes: 2 additions & 2 deletions src/Strategy/Maven/Pom.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,15 +74,15 @@ toDependency (MavenPackage group artifact version) = foldr applyLabel start
, dependencyName = group <> ":" <> artifact
, dependencyVersion = CEq <$> version
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

applyLabel :: MavenLabel -> Dependency -> Dependency
applyLabel lbl dep = case lbl of
MavenLabelScope scope ->
if scope == "test"
then dep{dependencyEnvironments = EnvTesting : dependencyEnvironments dep}
then insertEnvironment EnvTesting dep
else addTag "scope" scope dep
MavenLabelOptional opt -> addTag "optional" opt dep

Expand Down
2 changes: 1 addition & 1 deletion src/Strategy/Node/NpmList.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ buildGraph top = unfold direct getDeps toDependency
, dependencyName = nodeName
, dependencyVersion = CEq <$> outputVersion nodeOutput
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}

Expand Down
6 changes: 3 additions & 3 deletions src/Strategy/Node/NpmLock.hs
Original file line number Diff line number Diff line change
Expand Up @@ -103,8 +103,8 @@ buildGraph packageJson = run . withLabeling toDependency $ do
toDependency pkg = foldr addLabel (start pkg)

addLabel :: NpmPackageLabel -> Dependency -> Dependency
addLabel (NpmPackageEnv env) dep = dep{dependencyEnvironments = env : dependencyEnvironments dep}
addLabel (NpmPackageLocation loc) dep = dep{dependencyLocations = loc : dependencyLocations dep}
addLabel (NpmPackageEnv env) = insertEnvironment env
addLabel (NpmPackageLocation loc) = insertLocation loc

start :: NpmPackage -> Dependency
start NpmPackage{..} =
Expand All @@ -113,6 +113,6 @@ buildGraph packageJson = run . withLabeling toDependency $ do
, dependencyName = pkgName
, dependencyVersion = Just $ CEq pkgVersion
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
20 changes: 15 additions & 5 deletions src/Strategy/Node/PackageJson.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,19 @@ import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Data.Text (Text)
import DepTypes
import Effect.Grapher
import DepTypes (
DepEnvironment (..),
DepType (NodeJSType),
Dependency (..),
VerConstraint (CCompatible),
insertEnvironment,
)
import Effect.Grapher (
LabeledGrapher,
direct,
label,
withLabeling,
)
import Effect.ReadFS
import Graphing (Graphing)
import Path
Expand Down Expand Up @@ -62,8 +73,7 @@ buildGraph PackageJson{..} = run . withLabeling toDependency $ do
toDependency dep = foldr addLabel (start dep)

addLabel :: NodePackageLabel -> Dependency -> Dependency
addLabel (NodePackageEnv env) dep =
dep{dependencyEnvironments = env : dependencyEnvironments dep}
addLabel (NodePackageEnv env) = insertEnvironment env

start :: NodePackage -> Dependency
start NodePackage{..} =
Expand All @@ -72,6 +82,6 @@ buildGraph PackageJson{..} = run . withLabeling toDependency $ do
, dependencyName = pkgName
, dependencyVersion = Just (CCompatible pkgConstraint)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
2 changes: 1 addition & 1 deletion src/Strategy/NuGet/Nuspec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,6 +148,6 @@ buildGraph project = Graphing.fromList (map toDependency direct)
, dependencyName = depID
, dependencyVersion = Just (CEq depVersion)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
2 changes: 1 addition & 1 deletion src/Strategy/NuGet/PackageReference.hs
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,6 @@ buildGraph project = Graphing.fromList (map toDependency direct)
, dependencyName = depID
, dependencyVersion = fmap CEq depVersion
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
2 changes: 1 addition & 1 deletion src/Strategy/NuGet/PackagesConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,6 @@ buildGraph = Graphing.fromList . map toDependency . deps
, dependencyName = depID
, dependencyVersion = Just (CEq depVersion)
, dependencyLocations = []
, dependencyEnvironments = []
, dependencyEnvironments = mempty
, dependencyTags = Map.empty
}
Loading