diff --git a/spectrometer.cabal b/spectrometer.cabal index 8e887bdc1b..c6f4f4cc9d 100644 --- a/spectrometer.cabal +++ b/spectrometer.cabal @@ -161,7 +161,7 @@ common deps , yarn-lock ^>=0.6.5 , zip ^>=2.0.0 , zlib ^>=0.6.2.1 - + , validation-selective >= 0.1.0 && < 0.3 if !os(windows) -- included with GHC, consider upgrading this as part of a ghc upgrade build-depends: unix ^>=2.7.2.2 @@ -259,6 +259,7 @@ library App.Fossa.Report App.Fossa.Report.Attribution App.Fossa.RunThemis + Data.Toml.Extra App.Fossa.Snippets App.Fossa.Snippets.Analyze App.Fossa.Snippets.Commit diff --git a/src/Data/Toml/Extra.hs b/src/Data/Toml/Extra.hs new file mode 100644 index 0000000000..4c92ecd9a0 --- /dev/null +++ b/src/Data/Toml/Extra.hs @@ -0,0 +1,201 @@ +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Redundant lambda" #-} +{-# HLINT ignore "Use for_" #-} +module Data.Toml.Extra ( + tableMap' +) where + +import Toml.Codec.BiMap (BiMap (..), TomlBiMap) +import Toml.Codec.Code (execTomlCodec) +import Toml.Codec.Combinator.Common (whenLeftBiMapError) +import Toml.Codec.Types (Codec (..), TomlCodec, TomlEnv, TomlState (..)) +import Toml.Type.Key +import Toml.Type.TOML (TOML (..), insertTable, insertTableArrays) +import qualified Toml.Type.PrefixTree as Prefix +import Control.Applicative (empty) +import Control.Monad (forM_) +import Control.Monad.State (gets, modify) +import qualified Data.Map.Strict as Map +import Data.Maybe (fromMaybe) +import Data.Traversable (for) +import Data.HashMap.Strict (HashMap) +import Data.Hashable (Hashable) +import qualified Data.HashMap.Strict as HashMap +import Validation (Validation (..)) +import Data.Map.Strict (Map) +import Prelude hiding (lookup) +import Debug.Trace (trace) +import qualified Data.List.NonEmpty as NE +import Toml.Codec (TomlDecodeError) +-- import qualified Strategy.Python.Poetry.PyProject as group.group.dev.dev + +-- tables :: + +applicableKey :: Show a => Key -> Prefix.PrefixMap a -> [Key] +applicableKey key prefMap = map simplify $ filter (compareKey' key) allKeys + where + listed = trace ("input.simplify.listed': " ++ show (Prefix.toList prefMap)) $ Prefix.toList prefMap + + allKeys :: [Key] + allKeys = trace ("input.simplify.allKeys': " ++ show (map (simplify . fst) $ Prefix.toList prefMap)) $ map (simplify . fst) $ listed + + simplify :: Key -> Key + simplify key' = trace ("input.simplify': " ++ show key') $ Key . removeConsecutiveDuplicates . unKey $ key' + +removeConsecutiveDuplicates :: Eq a => NE.NonEmpty a -> NE.NonEmpty a +removeConsecutiveDuplicates (x NE.:| []) = x NE.:| [] +removeConsecutiveDuplicates (x NE.:| (y:ys)) + | x == y = removeConsecutiveDuplicates (x NE.:| ys) + | otherwise = case NE.nonEmpty (y:ys) of + Just ne -> NE.singleton x <> (removeConsecutiveDuplicates ne) + _ -> x NE.:| [] + +tableMap' + :: forall k v + . (Ord k, Show k, Show v) + => TomlBiMap Key k + -- ^ Bidirectional converter between TOML 'Key's and 'Map' keys + -> (Key -> TomlCodec v) + -- ^ Codec for 'Map' values for the corresponding 'Key' + -> Key + -- ^ Table name for 'Map' + -> TomlCodec (Map k v) +tableMap' = internalTableMap Map.empty Map.toList Map.fromList Map.unions + +-- type TomlEnv a = TOML -> Validation [TomlDecodeError] a + +internalTableMap + :: forall map k v + . Show map => map -- ^ empty map + -> (map -> [(k, v)]) -- ^ toList function + -> ([(k, v)] -> map) -- ^ fromList function + -> ([map] -> map) -- ^ union function + -> TomlBiMap Key k + -- ^ Bidirectional converter between TOML 'Key's and Map keys + -> (Key -> TomlCodec v) + -- ^ Codec for Map values for the corresponding 'Key' + -> Key + -- ^ Table name for Map + -> TomlCodec map +internalTableMap emptyMap toListMap fromListMap unionsMap keyBiMap valCodec tableName = + Codec input output + where + -- tableNames :: TOML -> [Key] + -- tableNames t = applicableKey "group.*.dependencies" (tomlTables t) + + getTable :: Key -> TomlEnv map + getTable lookupKey = \t -> case Prefix.lookup lookupKey $ tomlTables t of + Nothing -> Success emptyMap + Just toml' -> + let valKeys = HashMap.keys $ tomlPairs toml' + tableKeys = fmap (:|| []) $ HashMap.keys $ tomlTables toml' + tableArrayKey = HashMap.keys $ tomlTableArrays toml' + in fmap fromListMap $ for (valKeys <> tableKeys <> tableArrayKey) $ \key -> + whenLeftBiMapError key (forward keyBiMap key) $ \k -> + (k,) <$> codecRead (valCodec key) toml' + + merge :: [Validation [TomlDecodeError] map] -> Validation [TomlDecodeError] map + merge validations = + case sequenceA validations of + Failure errors -> Failure errors + Success values -> Success $ unionsMap values + + input :: TomlEnv map + input = \t -> do + let viableKeys = trace ("input.viableKeys:" ++ show (applicableKey "group.*.dependencies" (tomlTables t))) $ applicableKey "group.*.dependencies" (tomlTables t) + let maps = merge $ map (`getTable` t) viableKeys + maps + + input' :: TomlEnv map + input' = \t -> case Prefix.lookup tableName $ tomlTables t of + Nothing -> Success emptyMap + Just toml -> + let valKeys = HashMap.keys $ tomlPairs toml + tableKeys = fmap (:|| []) $ HashMap.keys $ tomlTables toml + tableArrayKey = HashMap.keys $ tomlTableArrays toml + in fmap fromListMap $ for (valKeys <> tableKeys <> tableArrayKey) $ \key -> + whenLeftBiMapError key (forward keyBiMap key) $ \k -> + (k,) <$> codecRead (valCodec key) toml + + -- for tableNames $ \tableName' -> + -- case lookup tableName' tables of + -- Nothing -> pure Nothing + -- Just toml -> Just toml + + -- maps :: [Maybe (Key, TOML)] <- for tableNames $ \tableName' -> + -- case lookup tableName' tables of + -- Nothing -> pure Nothing + -- Just toml -> pure . Just $ (tableName', toml) + + -- Just toml -> trace ("input.toml: " ++ show toml) $ do + -- let valKeys = trace ("input.valKeys: " ++ show (HashMap.keys $ tomlPairs toml)) $ HashMap.keys $ tomlPairs toml + -- let tableKeys = trace ("input.tableKeys: " ++ show (HashMap.keys $ tomlTables toml)) $ fmap (:|| []) $ HashMap.keys $ tomlTables toml + + -- for (valKeys <> tableKeys) $ \key -> do + -- whenLeftBiMapError key (forward keyBiMap key) $ \k -> trace ("input.whenLeftBiMapError.key: " ++ show key) $ + -- (k,) <$> codecRead (valCodec key) toml + + -- Success emptyMap + + output :: map -> TomlState map + output m = do + mTable <- gets $ lookup tableName . tomlTables + let toml = fromMaybe mempty mTable + let (_, newToml) = unTomlState updateMapTable toml + m <$ modify (insertTable tableName newToml) + where + updateMapTable :: TomlState () + updateMapTable = forM_ (toListMap m) $ \(k, v) -> case backward keyBiMap k of + Left _ -> empty + Right key -> codecWrite (valCodec key) v + + +lookupT :: Key -> Prefix.PrefixTree a -> Maybe a +lookupT lk (Prefix.Leaf k v) = trace ("input.lookupT.Prefix.Leaf => k:" ++ show k ++ " lk:" ++ show lk) $ if compareKey lk k then Just v else Nothing +lookupT lk (Prefix.Branch pref mv prefMap) = trace ("input.lookupT.Prefix.Branch => pref:" ++ show pref ++ " lk:" ++ show lk) $ + case keysDiff' pref lk of + Equal -> trace ("input.lookupT.Prefix.Branch.Equal:") $ mv + NoPrefix -> trace ("input.lookupT.Prefix.Branch.NoPrefix:") $ Nothing + Diff _ _ _ -> trace ("input.lookupT.Prefix.Branch.Diff:") $ Nothing + SndIsPref _ -> trace ("input.lookupT.Prefix.Branch.SndIsPref:") $ Nothing + -- The first key is the prefix of the second one. + FstIsPref k -> trace ("input.lookupT.Prefix.Branch.FstIsPref: k:" ++ show k) $ lookup k prefMap + +lookup :: Key -> Prefix.PrefixMap a -> Maybe a +lookup k@(p :|| _) prefMap = HashMap.lookup p prefMap >>= lookupT k + + + +compareKey :: Key -> Key -> Bool +compareKey lhs rhs = lhs == rhs + +keysDiff' :: Key -> Key -> KeysDiff +keysDiff' (x :|| xs) (y :|| ys) + | x == y = trace ("x <> y:" ++ show x ++ ".." ++ show y) $ listSame xs ys [] + | x == "*" = trace ("x <> y:" ++ show x ++ ".." ++ show y) $ listSame xs ys [] + | otherwise = trace ("x <> y:" ++ show x ++ ".." ++ show y) $ NoPrefix + where + listSame :: [Piece] -> [Piece] -> [Piece] -> KeysDiff + listSame [] [] _ = Equal + listSame [] (s:ss) _ = FstIsPref $ s :|| ss + listSame (f:fs) [] _ = SndIsPref $ f :|| fs + listSame (f:fs) (s:ss) pr = + if f == s + then listSame fs ss (pr ++ [f]) + else Diff (x :|| pr) (f :|| fs) (s :|| ss) + +compareKey' :: Key -> Key -> Bool +compareKey' (x :|| xs) (y :|| ys) = trace ("input.compareKey' => lhs:" ++ show x ++ " rhs:" ++ show y) $ + if (x == "*" || x == y) + then do + case (mkKey xs, mkKey ys) of + (Just lhs', Just rhs') -> trace ("input.compareKey' => lhs':" ++ show lhs' ++ " rhs':" ++ show rhs') $ compareKey' lhs' rhs' + (Nothing, Nothing) -> True + _ -> False + else False + +mkKey :: [Piece] -> Maybe Key +mkKey xs = Key <$> NE.nonEmpty xs + + + diff --git a/src/Strategy/Python/Poetry.hs b/src/Strategy/Python/Poetry.hs index e7a7cb688b..277f591f11 100644 --- a/src/Strategy/Python/Poetry.hs +++ b/src/Strategy/Python/Poetry.hs @@ -2,9 +2,14 @@ module Strategy.Python.Poetry ( discover, -- * for testing only - graphFromLockFile, + findProjects, + analyze, + graphFromPyProjectAndLockFile, setGraphDirectsFromPyproject, PoetryProject (..), + PyProjectTomlFile (..), + PoetryLockFile (..), + ProjectDir (..), ) where import App.Fossa.Analyze.Types (AnalyzeProject (analyzeProjectStaticOnly), analyzeProject) @@ -18,7 +23,7 @@ import Data.Map (Map) import Data.Map.Strict qualified as Map import Data.Maybe (fromMaybe) import Data.Text (Text) -import DepTypes (DepType (..), Dependency (..)) +import DepTypes (DepType (..), Dependency (..), hydrateDepEnvs) import Diag.Common ( MissingDeepDeps (MissingDeepDeps), MissingEdges (MissingEdges), @@ -30,7 +35,7 @@ import Discovery.Walk ( findFileNamed, walkWithFilters', ) -import Effect.Logger (Logger, Pretty (pretty), logDebug) +import Effect.Logger (Logger, Pretty (pretty), logDebug, logStdout, logInfo) import Effect.ReadFS (ReadFS, readContentsToml) import GHC.Generics (Generic) import Graphing (Graphing) @@ -42,8 +47,10 @@ import Strategy.Python.Errors ( ) import Strategy.Python.Poetry.Common (getPoetryBuildBackend, logIgnoredDeps, pyProjectDeps, toCanonicalName, toMap) import Strategy.Python.Poetry.PoetryLock (PackageName (..), PoetryLock (..), PoetryLockPackage (..), poetryLockCodec) -import Strategy.Python.Poetry.PyProject (PyProject (..), pyProjectCodec) +import Strategy.Python.Poetry.PyProject (PyProject (..), pyProjectCodec, allPoetryProductionDeps, allPoetryNonProductionDeps) import Types (DependencyResults (..), DiscoveredProject (..), DiscoveredProjectType (PoetryProjectType), GraphBreadth (..)) +import Text.Pretty.Simple (pShow) +import Data.Text.Lazy (toStrict) newtype PyProjectTomlFile = PyProjectTomlFile {pyProjectTomlPath :: Path Abs File} deriving (Eq, Ord, Show, Generic) newtype PoetryLockFile = PoetryLockFile {poetryLockPath :: Path Abs File} deriving (Eq, Ord, Show, Generic) @@ -154,7 +161,8 @@ analyze PoetryProject{pyProjectToml, poetryLock} = do Just lockPath -> do poetryLockProject <- readContentsToml poetryLockCodec (poetryLockPath lockPath) _ <- logIgnoredDeps pyproject (Just poetryLockProject) - graph <- context "Building dependency graph from pyproject.toml and poetry.lock" $ pure $ setGraphDirectsFromPyproject (graphFromLockFile poetryLockProject) pyproject + logInfo $ pretty $ pShow pyproject + graph <- context "Building dependency graph from pyproject.toml and poetry.lock" $ setGraphDirectsFromPyproject (graphFromPyProjectAndLockFile pyproject poetryLockProject) pyproject pure $ DependencyResults { dependencyGraph = graph @@ -179,22 +187,43 @@ analyze PoetryProject{pyProjectToml, poetryLock} = do } -- | Use a `pyproject.toml` to set the direct dependencies of a graph created from `poetry.lock`. -setGraphDirectsFromPyproject :: Graphing Dependency -> PyProject -> Graphing Dependency -setGraphDirectsFromPyproject graph pyproject = Graphing.promoteToDirect isDirect graph +setGraphDirectsFromPyproject :: (Has Logger sig m) => Graphing Dependency -> PyProject -> m (Graphing Dependency) +setGraphDirectsFromPyproject graph pyproject = do + -- let graph = hydrateDepEnvs graph' + logInfo $ pretty $ pShow directDeps + logInfo $ pretty $ pShow prodPkgNames + logInfo $ pretty $ pShow devPkgNames + logInfo $ pretty $ pShow graph' + pure graph' where + graph' :: Graphing Dependency + graph' = hydrateDepEnvs $ Graphing.promoteToDirect isDirect graph + + prodPkgNames :: [Text] + prodPkgNames = Map.keys $ allPoetryProductionDeps pyproject + + devPkgNames :: [Text] + devPkgNames = Map.keys $ allPoetryNonProductionDeps pyproject + + directDeps :: [Dependency] + directDeps = pyProjectDeps pyproject + -- Dependencies in `poetry.lock` are direct if they're specified in `pyproject.toml`. -- `pyproject.toml` may use non canonical naming, when naming dependencies. isDirect :: Dependency -> Bool isDirect dep = case pyprojectPoetry pyproject of Nothing -> False - Just _ -> any (\n -> toCanonicalName (dependencyName n) == toCanonicalName (dependencyName dep)) $ pyProjectDeps pyproject + Just _ -> any (\n -> toCanonicalName (dependencyName n) == toCanonicalName (dependencyName dep)) directDeps -- | Using a Poetry lockfile, build the graph of packages. -- The resulting graph contains edges, but does not distinguish between direct and deep dependencies, -- since `poetry.lock` does not indicate which dependencies are direct. -graphFromLockFile :: PoetryLock -> Graphing Dependency -graphFromLockFile poetryLock = Graphing.gmap pkgNameToDependency (edges <> Graphing.deeps pkgsNoDeps) +graphFromPyProjectAndLockFile :: PyProject -> PoetryLock -> Graphing Dependency +graphFromPyProjectAndLockFile pyProject poetryLock = graph where + graph :: Graphing Dependency + graph = Graphing.gmap pkgNameToDependency (edges <> Graphing.deeps pkgsNoDeps) + pkgs :: [PoetryLockPackage] pkgs = poetryLockPackages poetryLock @@ -217,7 +246,13 @@ graphFromLockFile poetryLock = Graphing.gmap pkgNameToDependency (edges <> Graph canonicalPkgName name = PackageName . toCanonicalName $ unPackageName name mapOfDependency :: Map PackageName Dependency - mapOfDependency = toMap pkgs + mapOfDependency = toMap prodPkgNames devPkgNames pkgs + + prodPkgNames :: [PackageName] + prodPkgNames = PackageName <$> Map.keys (allPoetryProductionDeps pyProject) + + devPkgNames :: [PackageName] + devPkgNames = PackageName <$> Map.keys (allPoetryNonProductionDeps pyProject) -- Pip packages are [case insensitive](https://www.python.org/dev/peps/pep-0508/#id21), but poetry.lock may use -- non-canonical name for reference. Try to lookup with provided name, otherwise fallback to canonical naming. diff --git a/src/Strategy/Python/Poetry/Common.hs b/src/Strategy/Python/Poetry/Common.hs index cf842a9ef2..a77bd0ef16 100644 --- a/src/Strategy/Python/Poetry/Common.hs +++ b/src/Strategy/Python/Poetry/Common.hs @@ -35,7 +35,7 @@ import Strategy.Python.Poetry.PyProject ( PyProjectPoetryGitDependency (..), PyProjectPoetryPathDependency (..), PyProjectPoetryUrlDependency (..), - allPoetryDevDeps, + allPoetryNonProductionDeps, toDependencyVersion, ) @@ -64,7 +64,7 @@ logIgnoredDeps pyproject poetryLock = for_ notSupportedDepsMsgs (logDebug . pret notSupportedPyProjectDevDeps = Map.keys $ Map.filter (not . supportedPyProjectDep) $ - maybe Map.empty allPoetryDevDeps (pyprojectPoetry pyproject) + allPoetryNonProductionDeps pyproject notSupportedPyProjectDeps :: [Text] notSupportedPyProjectDeps = @@ -84,9 +84,12 @@ pyProjectDeps project = filter notNamedPython $ map snd allDeps notNamedPython = (/= "python") . dependencyName supportedDevDeps :: Map Text PoetryDependency - supportedDevDeps = - Map.filter supportedPyProjectDep $ - maybe Map.empty allPoetryDevDeps (pyprojectPoetry project) + supportedDevDeps = Map.filter supportedPyProjectDep devDeps + where + devDeps = Map.unions [devDep] + devDep = maybe Map.empty devDependencies (pyprojectPoetry project) + -- devGroupDep = maybe Map.empty groupDevDependencies (pyprojectPoetry project) + -- devTestDep = maybe Map.empty groupTestDependencies (pyprojectPoetry project) supportedProdDeps :: Map Text PoetryDependency supportedProdDeps = Map.filter supportedPyProjectDep $ maybe Map.empty dependencies (pyprojectPoetry project) @@ -157,12 +160,27 @@ toCanonicalName :: Text -> Text toCanonicalName t = toLower $ replace "_" "-" (replace "." "-" t) -- | Maps poetry lock package to map of package name and associated dependency. -toMap :: [PoetryLockPackage] -> Map.Map PackageName Dependency -toMap pkgs = Map.fromList $ (\x -> (canonicalPkgName x, toDependency x)) <$> (filter supportedPoetryLockDep pkgs) +toMap :: [PackageName] -> [PackageName] -> [PoetryLockPackage] -> Map.Map PackageName Dependency +toMap prodPkgs devPkgs pkgs = Map.fromList $ (\x -> (canonicalPkgName x, toDependency x)) <$> (filter supportedPoetryLockDep pkgs) where canonicalPkgName :: PoetryLockPackage -> PackageName canonicalPkgName pkg = PackageName $ toCanonicalName $ unPackageName $ poetryLockPackageName pkg + canonicalPkgName' :: PackageName -> PackageName + canonicalPkgName' = PackageName . toCanonicalName . unPackageName + + canonicalProdPkgNames :: [PackageName] + canonicalProdPkgNames = map canonicalPkgName' prodPkgs + + canonicalDevPkgNames :: [PackageName] + canonicalDevPkgNames = map canonicalPkgName' devPkgs + + isProductionDirectDep :: PoetryLockPackage -> Bool + isProductionDirectDep pkg = canonicalPkgName pkg `elem` canonicalProdPkgNames + + isDevelopmentDirectDep :: PoetryLockPackage -> Bool + isDevelopmentDirectDep pkg = canonicalPkgName pkg `elem` canonicalDevPkgNames + toDependency :: PoetryLockPackage -> Dependency toDependency pkg = Dependency @@ -170,7 +188,7 @@ toMap pkgs = Map.fromList $ (\x -> (canonicalPkgName x, toDependency x)) <$> (fi , dependencyName = toDepName pkg , dependencyVersion = toDepVersion pkg , dependencyLocations = toDepLocs pkg - , dependencyEnvironments = Set.singleton $ toDepEnvironment pkg + , dependencyEnvironments = toDepEnvironment pkg , dependencyTags = Map.empty } @@ -203,16 +221,22 @@ toMap pkgs = Map.fromList $ (\x -> (canonicalPkgName x, toDependency x)) <$> (fi ref <- poetryLockPackageSourceReference lockPkgSrc if poetryLockPackageSourceType lockPkgSrc /= "legacy" then Just ref else Nothing - toDepEnvironment :: PoetryLockPackage -> DepEnvironment + toDepEnvironment :: PoetryLockPackage -> Set.Set DepEnvironment toDepEnvironment pkg = case poetryLockPackageCategory pkg of + -- If category is provided, use category to infer if dependency's environment Just category -> case category of - "dev" -> EnvDevelopment - "main" -> EnvProduction - "test" -> EnvTesting - other -> EnvOther other - Nothing -> defaultDepEnvironment - - defaultDepEnvironment :: DepEnvironment - -- Poetry made this field optional. When not present, it defaults to `main`, which maps to `EnvProduction`. - -- https://github.com/python-poetry/poetry/pull/7637 - defaultDepEnvironment = EnvProduction + "dev" -> Set.singleton EnvDevelopment + "main" -> Set.singleton EnvProduction + "test" -> Set.singleton EnvTesting + other -> Set.singleton $ EnvOther other + -- If category is not provided, lockfile is likely greater than __. + -- In this case, if the package name exists in the dependencies + -- list, mark as production dependency, otherwise, mark it as development dependency + -- - + -- Refer to: + -- * https://github.com/python-poetry/poetry/pull/7637 + Nothing -> + case (isProductionDirectDep pkg, isDevelopmentDirectDep pkg) of + (True, _) -> Set.singleton EnvProduction + (_, True) -> Set.singleton EnvDevelopment + _ -> mempty diff --git a/src/Strategy/Python/Poetry/PyProject.hs b/src/Strategy/Python/Poetry/PyProject.hs index ed1f0a655e..34bfa8f8c3 100644 --- a/src/Strategy/Python/Poetry/PyProject.hs +++ b/src/Strategy/Python/Poetry/PyProject.hs @@ -1,3 +1,5 @@ +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use newtype instead of data" #-} module Strategy.Python.Poetry.PyProject ( PyProject (..), PyProjectMetadata (..), @@ -9,17 +11,18 @@ module Strategy.Python.Poetry.PyProject ( PyProjectPoetryGitDependency (..), PyProjectPoetryUrlDependency (..), PyProjectPoetryDetailedVersionDependency (..), + allPoetryProductionDeps, -- * for testing only parseConstraintExpr, toDependencyVersion, - allPoetryDevDeps, + allPoetryNonProductionDeps, ) where import Control.Monad.Combinators.Expr (Operator (..), makeExprParser) import Data.Foldable (asum) import Data.Functor (void) -import Data.Map (Map) +import Data.Map (Map, keys) import Data.Maybe (fromMaybe) import Data.String.Conversion (toString, toText) import Data.Text (Text) @@ -53,6 +56,11 @@ import Text.Megaparsec.Char (char) import Text.Megaparsec.Char.Lexer qualified as Lexer import Toml (TomlCodec, (.=)) import Toml qualified +import qualified Data.Text.IO as TIO +import Text.Pretty.Simple (pShow, pPrint) +import Debug.Trace (trace) +import Data.Toml.Extra (tableMap') +import Toml.Codec (mkAnyValueBiMap) type Parser = Parsec Void Text @@ -115,12 +123,27 @@ data PyProjectPoetry = PyProjectPoetry , description :: Maybe Text , dependencies :: Map Text PoetryDependency , devDependencies :: Map Text PoetryDependency + -- , groupDevDependencies :: [PyProjectGroup] , groupDevDependencies :: Map Text PoetryDependency } deriving (Show, Eq, Ord) -allPoetryDevDeps :: PyProjectPoetry -> Map Text PoetryDependency -allPoetryDevDeps PyProjectPoetry{devDependencies, groupDevDependencies} = devDependencies <> groupDevDependencies +allPoetryProductionDeps :: PyProject -> Map Text PoetryDependency +allPoetryProductionDeps project = case pyprojectPoetry project of + Just (PyProjectPoetry{dependencies}) -> dependencies + _ -> mempty + +allPoetryNonProductionDeps :: PyProject -> Map Text PoetryDependency +allPoetryNonProductionDeps project = case pyprojectPoetry project of + _ -> mempty + -- Just (PyProjectPoetry{devDependencies, groupDevDependencies, groupTestDependencies}) -> + -- devDependencies <> groupDevDependencies <> groupTestDependencies + -- _ -> mempty + +data PoetryDependencyGroup = PoetryDependencyGroup { + poetryDependencyGroupOptional :: Maybe Bool + -- , poetryDependencyGroupDependencies :: Map Text PoetryDependency +} deriving (Show, Eq, Ord) data PoetryDependency = PoetryTextVersion Text @@ -138,7 +161,12 @@ pyProjectPoetryCodec = <*> Toml.dioptional (Toml.text "description") .= description <*> Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec "dependencies" .= dependencies <*> Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec "dev-dependencies" .= devDependencies - <*> Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec "group.dev.dependencies" .= groupDevDependencies + <*> Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec "group.dev.dependencies" .= devDependencies + -- <*> Toml.arrayOf pyProjectGroupCodec "group" .= groupDevDependencies + +data PyProjectGroup = PyProjectGroup { + pyProjectGroupName :: Text +} deriving (Show, Eq, Ord) pyProjectPoetryDependencyCodec :: Toml.Key -> TomlCodec PoetryDependency pyProjectPoetryDependencyCodec key = @@ -299,3 +327,18 @@ parseConstraintExpr = makeExprParser parseVerConstraint operatorTable where binary :: Text -> (VerConstraint -> VerConstraint -> VerConstraint) -> Operator Parser VerConstraint binary name f = InfixL (f <$ symbol name) + +-- rgbCodec :: TomlCodec (Map Text SomeThing) +-- rgbCodec = trace ("rgbCodec ") $ tableMap' Toml._KeyText rgbCodec' "group.dev" + +-- rgbCodec' :: Toml.Key -> TomlCodec SomeThing +-- rgbCodec' key = trace ("calling rgbCodec' with x = " ++ show key) $ SomeThing <$> Toml.tableMap Toml._KeyText (\k -> Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec "dependencies") key .= something + +rgbCodec :: TomlCodec (Map Text (Map Text PoetryDependency)) +rgbCodec = tableMap' Toml._KeyText (Toml.tableMap Toml._KeyText pyProjectPoetryDependencyCodec) "" + +debugIO :: IO () +debugIO = do + content <- TIO.readFile "test/Python/Poetry/testdata/no-category/pyproject.test.toml" + pPrint $ Toml.parse content + pPrint $ Toml.decode rgbCodec content \ No newline at end of file diff --git a/test/Python/Poetry/CommonSpec.hs b/test/Python/Poetry/CommonSpec.hs index fb586c3f02..b25e1a788a 100644 --- a/test/Python/Poetry/CommonSpec.hs +++ b/test/Python/Poetry/CommonSpec.hs @@ -100,7 +100,8 @@ expectedPyProject = , devDependencies = Map.fromList [("pytest", PoetryTextVersion "*")] - , groupDevDependencies = Map.empty -- TODO: Fill in for real. + , groupDevDependencies = Map.empty + , groupTestDependencies = Map.empty } } @@ -181,7 +182,7 @@ spec = do describe "toMap" $ do it "should map poetry lock package to dependency" $ - toMap + toMap mempty mempty [ PoetryLockPackage { poetryLockPackageName = PackageName "pkgOne" , poetryLockPackageVersion = "1.21.0" @@ -213,7 +214,7 @@ spec = do describe "when poetry lock dependency is from git source" $ it "should replace poetry lock package name to git url" $ - toMap + toMap mempty mempty [ PoetryLockPackage { poetryLockPackageName = PackageName "pkgWithGitSource" , poetryLockPackageVersion = "5.22.0.post0" @@ -240,7 +241,7 @@ spec = do describe "when poetry lock dependency is from url source" $ it "should replace poetry lock package name to url" $ - toMap + toMap mempty mempty [ PoetryLockPackage { poetryLockPackageName = PackageName "pkgSourcedFromUrl" , poetryLockPackageVersion = "3.92.1" @@ -267,7 +268,7 @@ spec = do describe "when poetry lock dependency is from file source" $ it "should replace poetry lock package name to filepath" $ - toMap + toMap mempty mempty [ PoetryLockPackage { poetryLockPackageName = PackageName "pkgSourcedFromFile" , poetryLockPackageVersion = "1.21.0" @@ -282,7 +283,7 @@ spec = do describe "when poetry lock dependency is from secondary sources" $ it "should include url into dependency location" $ - toMap + toMap mempty mempty [ PoetryLockPackage { poetryLockPackageName = PackageName "myprivatepkg" , poetryLockPackageVersion = "0.0.1" diff --git a/test/Python/Poetry/PyProjectSpec.hs b/test/Python/Poetry/PyProjectSpec.hs index 4cd69dd277..fd21c05ea5 100644 --- a/test/Python/Poetry/PyProjectSpec.hs +++ b/test/Python/Poetry/PyProjectSpec.hs @@ -77,18 +77,48 @@ expectedPyProject = , devDependencies = Map.fromList [("pytest", PoetryTextVersion "*")] - , groupDevDependencies = Map.empty -- TODO: Fill this in for realsies. + , groupDevDependencies = Map.empty + , groupTestDependencies = Map.empty + } + } + +expectedPyProject3 :: PyProject +expectedPyProject3 = + PyProject + { pyprojectBuildSystem = Just $ PyProjectBuildSystem{buildBackend = "poetry.core.masonry.api"} + , pyprojectProject = Nothing + , pyprojectPdmDevDependencies = Just mempty + , pyprojectPoetry = + Just $ + PyProjectPoetry + { name = Just "test_name" + , version = Just "test_version" + , description = Just "test_description" + , dependencies = + Map.fromList + [ ("python", PoetryTextVersion "^3.12") + , ("rich", PoetryTextVersion "*") + ] + , devDependencies = Map.empty + , groupDevDependencies = Map.fromList + [ ("click", PoetryTextVersion "*") + ] + , groupTestDependencies = Map.fromList + [ ("pytest", PoetryTextVersion "^6.0.0") + ] } } spec :: Spec spec = do nominalContents <- runIO (TIO.readFile "test/Python/Poetry/testdata/pyproject1.toml") + groupDevContents <- runIO (TIO.readFile "test/Python/Poetry/testdata/no-category/pyproject.toml") describe "pyProjectCodec" $ describe "when provided with all possible types of dependency sources" $ - it "should parse pyrproject file with all source types" $ + it "should parse pyrproject file with all source types" $ do Toml.decode pyProjectCodec nominalContents `shouldBe` Right expectedPyProject + Toml.decode pyProjectCodec groupDevContents `shouldBe` Right expectedPyProject3 describe "parseConstraintExpr" $ do it "should parse equality constraint" $ do diff --git a/test/Python/Poetry/testdata/no-category/poetry.lock b/test/Python/Poetry/testdata/no-category/poetry.lock new file mode 100644 index 0000000000..8fe05484e1 --- /dev/null +++ b/test/Python/Poetry/testdata/no-category/poetry.lock @@ -0,0 +1,570 @@ +# This file is automatically @generated by Poetry 1.8.2 and should not be changed by hand. + +[[package]] +name = "atomicwrites" +version = "1.4.1" +description = "Atomic file writes." +optional = false +python-versions = ">=2.7, !=3.0.*, !=3.1.*, !=3.2.*, !=3.3.*" +files = [ + {file = "atomicwrites-1.4.1.tar.gz", hash = "sha256:81b2c9071a49367a7f770170e5eec8cb66567cfbbc8c73d20ce5ca4a8d71cf11"}, +] + +[[package]] +name = "attrs" +version = "23.2.0" +description = "Classes Without Boilerplate" +optional = false +python-versions = ">=3.7" +files = [ + {file = "attrs-23.2.0-py3-none-any.whl", hash = "sha256:99b87a485a5820b23b879f04c2305b44b951b502fd64be915879d77a7e8fc6f1"}, + {file = "attrs-23.2.0.tar.gz", hash = "sha256:935dc3b529c262f6cf76e50877d35a4bd3c1de194fd41f47a2b7ae8f19971f30"}, +] + +[package.extras] +cov = ["attrs[tests]", "coverage[toml] (>=5.3)"] +dev = ["attrs[tests]", "pre-commit"] +docs = ["furo", "myst-parser", "sphinx", "sphinx-notfound-page", "sphinxcontrib-towncrier", "towncrier", "zope-interface"] +tests = ["attrs[tests-no-zope]", "zope-interface"] +tests-mypy = ["mypy (>=1.6)", "pytest-mypy-plugins"] +tests-no-zope = ["attrs[tests-mypy]", "cloudpickle", "hypothesis", "pympler", "pytest (>=4.3.0)", "pytest-xdist[psutil]"] + +[[package]] +name = "click" +version = "8.1.7" +description = "Composable command line interface toolkit" +optional = false +python-versions = ">=3.7" +files = [ + {file = "click-8.1.7-py3-none-any.whl", hash = "sha256:ae74fb96c20a0277a1d615f1e4d73c8414f5a98db8b799a7931d1582f3390c28"}, + {file = "click-8.1.7.tar.gz", hash = "sha256:ca9853ad459e787e2192211578cc907e7594e294c7ccc834310722b41b9ca6de"}, +] + +[package.dependencies] +colorama = {version = "*", markers = "platform_system == \"Windows\""} + +[[package]] +name = "colorama" +version = "0.4.6" +description = "Cross-platform colored terminal text." +optional = false +python-versions = "!=3.0.*,!=3.1.*,!=3.2.*,!=3.3.*,!=3.4.*,!=3.5.*,!=3.6.*,>=2.7" +files = [ + {file = "colorama-0.4.6-py2.py3-none-any.whl", hash = "sha256:4f1d9991f5acc0ca119f9d443620b77f9d6b33703e51011c16baf57afb285fc6"}, + {file = "colorama-0.4.6.tar.gz", hash = "sha256:08695f5cb7ed6e0531a20572697297273c47b8cae5a63ffc6d6ed5c201be6e44"}, +] + +[[package]] +name = "ghp-import" +version = "2.1.0" +description = "Copy your docs directly to the gh-pages branch." +optional = false +python-versions = "*" +files = [ + {file = "ghp-import-2.1.0.tar.gz", hash = "sha256:9c535c4c61193c2df8871222567d7fd7e5014d835f97dc7b7439069e2413d343"}, + {file = "ghp_import-2.1.0-py3-none-any.whl", hash = "sha256:8337dd7b50877f163d4c0289bc1f1c7f127550241988d568c1db512c4324a619"}, +] + +[package.dependencies] +python-dateutil = ">=2.8.1" + +[package.extras] +dev = ["flake8", "markdown", "twine", "wheel"] + +[[package]] +name = "iniconfig" +version = "2.0.0" +description = "brain-dead simple config-ini parsing" +optional = false +python-versions = ">=3.7" +files = [ + {file = "iniconfig-2.0.0-py3-none-any.whl", hash = "sha256:b6a85871a79d2e3b22d2d1b94ac2824226a63c6b741c88f7ae975f18b6778374"}, + {file = "iniconfig-2.0.0.tar.gz", hash = "sha256:2d91e135bf72d31a410b17c16da610a82cb55f6b0477d1a902134b24a455b8b3"}, +] + +[[package]] +name = "jinja2" +version = "3.1.3" +description = "A very fast and expressive template engine." +optional = false +python-versions = ">=3.7" +files = [ + {file = "Jinja2-3.1.3-py3-none-any.whl", hash = "sha256:7d6d50dd97d52cbc355597bd845fabfbac3f551e1f99619e39a35ce8c370b5fa"}, + {file = "Jinja2-3.1.3.tar.gz", hash = "sha256:ac8bd6544d4bb2c9792bf3a159e80bba8fda7f07e81bc3aed565432d5925ba90"}, +] + +[package.dependencies] +MarkupSafe = ">=2.0" + +[package.extras] +i18n = ["Babel (>=2.7)"] + +[[package]] +name = "markdown" +version = "3.6" +description = "Python implementation of John Gruber's Markdown." +optional = false +python-versions = ">=3.8" +files = [ + {file = "Markdown-3.6-py3-none-any.whl", hash = "sha256:48f276f4d8cfb8ce6527c8f79e2ee29708508bf4d40aa410fbc3b4ee832c850f"}, + {file = "Markdown-3.6.tar.gz", hash = "sha256:ed4f41f6daecbeeb96e576ce414c41d2d876daa9a16cb35fa8ed8c2ddfad0224"}, +] + +[package.extras] +docs = ["mdx-gh-links (>=0.2)", "mkdocs (>=1.5)", "mkdocs-gen-files", "mkdocs-literate-nav", "mkdocs-nature (>=0.6)", "mkdocs-section-index", "mkdocstrings[python]"] +testing = ["coverage", "pyyaml"] + +[[package]] +name = "markdown-it-py" +version = "3.0.0" +description = "Python port of markdown-it. Markdown parsing, done right!" +optional = false +python-versions = ">=3.8" +files = [ + {file = "markdown-it-py-3.0.0.tar.gz", hash = "sha256:e3f60a94fa066dc52ec76661e37c851cb232d92f9886b15cb560aaada2df8feb"}, + {file = "markdown_it_py-3.0.0-py3-none-any.whl", hash = "sha256:355216845c60bd96232cd8d8c40e8f9765cc86f46880e43a8fd22dc1a1a8cab1"}, +] + +[package.dependencies] +mdurl = ">=0.1,<1.0" + +[package.extras] +benchmarking = ["psutil", "pytest", "pytest-benchmark"] +code-style = ["pre-commit (>=3.0,<4.0)"] +compare = ["commonmark (>=0.9,<1.0)", "markdown (>=3.4,<4.0)", "mistletoe (>=1.0,<2.0)", "mistune (>=2.0,<3.0)", "panflute (>=2.3,<3.0)"] +linkify = ["linkify-it-py (>=1,<3)"] +plugins = ["mdit-py-plugins"] +profiling = ["gprof2dot"] +rtd = ["jupyter_sphinx", "mdit-py-plugins", "myst-parser", "pyyaml", "sphinx", "sphinx-copybutton", "sphinx-design", "sphinx_book_theme"] +testing = ["coverage", "pytest", "pytest-cov", "pytest-regressions"] + +[[package]] +name = "markupsafe" +version = "2.1.5" +description = "Safely add untrusted strings to HTML/XML markup." +optional = false +python-versions = ">=3.7" +files = [ + {file = "MarkupSafe-2.1.5-cp310-cp310-macosx_10_9_universal2.whl", hash = "sha256:a17a92de5231666cfbe003f0e4b9b3a7ae3afb1ec2845aadc2bacc93ff85febc"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-macosx_10_9_x86_64.whl", hash = "sha256:72b6be590cc35924b02c78ef34b467da4ba07e4e0f0454a2c5907f473fc50ce5"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:e61659ba32cf2cf1481e575d0462554625196a1f2fc06a1c777d3f48e8865d46"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:2174c595a0d73a3080ca3257b40096db99799265e1c27cc5a610743acd86d62f"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:ae2ad8ae6ebee9d2d94b17fb62763125f3f374c25618198f40cbb8b525411900"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-musllinux_1_1_aarch64.whl", hash = "sha256:075202fa5b72c86ad32dc7d0b56024ebdbcf2048c0ba09f1cde31bfdd57bcfff"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-musllinux_1_1_i686.whl", hash = "sha256:598e3276b64aff0e7b3451b72e94fa3c238d452e7ddcd893c3ab324717456bad"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-musllinux_1_1_x86_64.whl", hash = "sha256:fce659a462a1be54d2ffcacea5e3ba2d74daa74f30f5f143fe0c58636e355fdd"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-win32.whl", hash = "sha256:d9fad5155d72433c921b782e58892377c44bd6252b5af2f67f16b194987338a4"}, + {file = "MarkupSafe-2.1.5-cp310-cp310-win_amd64.whl", hash = "sha256:bf50cd79a75d181c9181df03572cdce0fbb75cc353bc350712073108cba98de5"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-macosx_10_9_universal2.whl", hash = "sha256:629ddd2ca402ae6dbedfceeba9c46d5f7b2a61d9749597d4307f943ef198fc1f"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-macosx_10_9_x86_64.whl", hash = "sha256:5b7b716f97b52c5a14bffdf688f971b2d5ef4029127f1ad7a513973cfd818df2"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:6ec585f69cec0aa07d945b20805be741395e28ac1627333b1c5b0105962ffced"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:b91c037585eba9095565a3556f611e3cbfaa42ca1e865f7b8015fe5c7336d5a5"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:7502934a33b54030eaf1194c21c692a534196063db72176b0c4028e140f8f32c"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-musllinux_1_1_aarch64.whl", hash = "sha256:0e397ac966fdf721b2c528cf028494e86172b4feba51d65f81ffd65c63798f3f"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-musllinux_1_1_i686.whl", hash = "sha256:c061bb86a71b42465156a3ee7bd58c8c2ceacdbeb95d05a99893e08b8467359a"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-musllinux_1_1_x86_64.whl", hash = "sha256:3a57fdd7ce31c7ff06cdfbf31dafa96cc533c21e443d57f5b1ecc6cdc668ec7f"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-win32.whl", hash = "sha256:397081c1a0bfb5124355710fe79478cdbeb39626492b15d399526ae53422b906"}, + {file = "MarkupSafe-2.1.5-cp311-cp311-win_amd64.whl", hash = "sha256:2b7c57a4dfc4f16f7142221afe5ba4e093e09e728ca65c51f5620c9aaeb9a617"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-macosx_10_9_universal2.whl", hash = "sha256:8dec4936e9c3100156f8a2dc89c4b88d5c435175ff03413b443469c7c8c5f4d1"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-macosx_10_9_x86_64.whl", hash = "sha256:3c6b973f22eb18a789b1460b4b91bf04ae3f0c4234a0a6aa6b0a92f6f7b951d4"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:ac07bad82163452a6884fe8fa0963fb98c2346ba78d779ec06bd7a6262132aee"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:f5dfb42c4604dddc8e4305050aa6deb084540643ed5804d7455b5df8fe16f5e5"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:ea3d8a3d18833cf4304cd2fc9cbb1efe188ca9b5efef2bdac7adc20594a0e46b"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-musllinux_1_1_aarch64.whl", hash = "sha256:d050b3361367a06d752db6ead6e7edeb0009be66bc3bae0ee9d97fb326badc2a"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-musllinux_1_1_i686.whl", hash = "sha256:bec0a414d016ac1a18862a519e54b2fd0fc8bbfd6890376898a6c0891dd82e9f"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-musllinux_1_1_x86_64.whl", hash = "sha256:58c98fee265677f63a4385256a6d7683ab1832f3ddd1e66fe948d5880c21a169"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-win32.whl", hash = "sha256:8590b4ae07a35970728874632fed7bd57b26b0102df2d2b233b6d9d82f6c62ad"}, + {file = "MarkupSafe-2.1.5-cp312-cp312-win_amd64.whl", hash = "sha256:823b65d8706e32ad2df51ed89496147a42a2a6e01c13cfb6ffb8b1e92bc910bb"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-macosx_10_9_x86_64.whl", hash = "sha256:c8b29db45f8fe46ad280a7294f5c3ec36dbac9491f2d1c17345be8e69cc5928f"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:ec6a563cff360b50eed26f13adc43e61bc0c04d94b8be985e6fb24b81f6dcfdf"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:a549b9c31bec33820e885335b451286e2969a2d9e24879f83fe904a5ce59d70a"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:4f11aa001c540f62c6166c7726f71f7573b52c68c31f014c25cc7901deea0b52"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-musllinux_1_1_aarch64.whl", hash = "sha256:7b2e5a267c855eea6b4283940daa6e88a285f5f2a67f2220203786dfa59b37e9"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-musllinux_1_1_i686.whl", hash = "sha256:2d2d793e36e230fd32babe143b04cec8a8b3eb8a3122d2aceb4a371e6b09b8df"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-musllinux_1_1_x86_64.whl", hash = "sha256:ce409136744f6521e39fd8e2a24c53fa18ad67aa5bc7c2cf83645cce5b5c4e50"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-win32.whl", hash = "sha256:4096e9de5c6fdf43fb4f04c26fb114f61ef0bf2e5604b6ee3019d51b69e8c371"}, + {file = "MarkupSafe-2.1.5-cp37-cp37m-win_amd64.whl", hash = "sha256:4275d846e41ecefa46e2015117a9f491e57a71ddd59bbead77e904dc02b1bed2"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-macosx_10_9_universal2.whl", hash = "sha256:656f7526c69fac7f600bd1f400991cc282b417d17539a1b228617081106feb4a"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-macosx_10_9_x86_64.whl", hash = "sha256:97cafb1f3cbcd3fd2b6fbfb99ae11cdb14deea0736fc2b0952ee177f2b813a46"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:1f3fbcb7ef1f16e48246f704ab79d79da8a46891e2da03f8783a5b6fa41a9532"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:fa9db3f79de01457b03d4f01b34cf91bc0048eb2c3846ff26f66687c2f6d16ab"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:ffee1f21e5ef0d712f9033568f8344d5da8cc2869dbd08d87c84656e6a2d2f68"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-musllinux_1_1_aarch64.whl", hash = "sha256:5dedb4db619ba5a2787a94d877bc8ffc0566f92a01c0ef214865e54ecc9ee5e0"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-musllinux_1_1_i686.whl", hash = "sha256:30b600cf0a7ac9234b2638fbc0fb6158ba5bdcdf46aeb631ead21248b9affbc4"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-musllinux_1_1_x86_64.whl", hash = "sha256:8dd717634f5a044f860435c1d8c16a270ddf0ef8588d4887037c5028b859b0c3"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-win32.whl", hash = "sha256:daa4ee5a243f0f20d528d939d06670a298dd39b1ad5f8a72a4275124a7819eff"}, + {file = "MarkupSafe-2.1.5-cp38-cp38-win_amd64.whl", hash = "sha256:619bc166c4f2de5caa5a633b8b7326fbe98e0ccbfacabd87268a2b15ff73a029"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-macosx_10_9_universal2.whl", hash = "sha256:7a68b554d356a91cce1236aa7682dc01df0edba8d043fd1ce607c49dd3c1edcf"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-macosx_10_9_x86_64.whl", hash = "sha256:db0b55e0f3cc0be60c1f19efdde9a637c32740486004f20d1cff53c3c0ece4d2"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:3e53af139f8579a6d5f7b76549125f0d94d7e630761a2111bc431fd820e163b8"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:17b950fccb810b3293638215058e432159d2b71005c74371d784862b7e4683f3"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-manylinux_2_5_i686.manylinux1_i686.manylinux_2_17_i686.manylinux2014_i686.whl", hash = "sha256:4c31f53cdae6ecfa91a77820e8b151dba54ab528ba65dfd235c80b086d68a465"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-musllinux_1_1_aarch64.whl", hash = "sha256:bff1b4290a66b490a2f4719358c0cdcd9bafb6b8f061e45c7a2460866bf50c2e"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-musllinux_1_1_i686.whl", hash = "sha256:bc1667f8b83f48511b94671e0e441401371dfd0f0a795c7daa4a3cd1dde55bea"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-musllinux_1_1_x86_64.whl", hash = "sha256:5049256f536511ee3f7e1b3f87d1d1209d327e818e6ae1365e8653d7e3abb6a6"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-win32.whl", hash = "sha256:00e046b6dd71aa03a41079792f8473dc494d564611a8f89bbbd7cb93295ebdcf"}, + {file = "MarkupSafe-2.1.5-cp39-cp39-win_amd64.whl", hash = "sha256:fa173ec60341d6bb97a89f5ea19c85c5643c1e7dedebc22f5181eb73573142c5"}, + {file = "MarkupSafe-2.1.5.tar.gz", hash = "sha256:d283d37a890ba4c1ae73ffadf8046435c76e7bc2247bbb63c00bd1a709c6544b"}, +] + +[[package]] +name = "mdurl" +version = "0.1.2" +description = "Markdown URL utilities" +optional = false +python-versions = ">=3.7" +files = [ + {file = "mdurl-0.1.2-py3-none-any.whl", hash = "sha256:84008a41e51615a49fc9966191ff91509e3c40b939176e643fd50a5c2196b8f8"}, + {file = "mdurl-0.1.2.tar.gz", hash = "sha256:bb413d29f5eea38f31dd4754dd7377d4465116fb207585f97bf925588687c1ba"}, +] + +[[package]] +name = "mergedeep" +version = "1.3.4" +description = "A deep merge function for 🐍." +optional = false +python-versions = ">=3.6" +files = [ + {file = "mergedeep-1.3.4-py3-none-any.whl", hash = "sha256:70775750742b25c0d8f36c55aed03d24c3384d17c951b3175d898bd778ef0307"}, + {file = "mergedeep-1.3.4.tar.gz", hash = "sha256:0096d52e9dad9939c3d975a774666af186eda617e6ca84df4c94dec30004f2a8"}, +] + +[[package]] +name = "mkdocs" +version = "1.6.0" +description = "Project documentation with Markdown." +optional = false +python-versions = ">=3.8" +files = [ + {file = "mkdocs-1.6.0-py3-none-any.whl", hash = "sha256:1eb5cb7676b7d89323e62b56235010216319217d4af5ddc543a91beb8d125ea7"}, + {file = "mkdocs-1.6.0.tar.gz", hash = "sha256:a73f735824ef83a4f3bcb7a231dcab23f5a838f88b7efc54a0eef5fbdbc3c512"}, +] + +[package.dependencies] +click = ">=7.0" +colorama = {version = ">=0.4", markers = "platform_system == \"Windows\""} +ghp-import = ">=1.0" +jinja2 = ">=2.11.1" +markdown = ">=3.3.6" +markupsafe = ">=2.0.1" +mergedeep = ">=1.3.4" +mkdocs-get-deps = ">=0.2.0" +packaging = ">=20.5" +pathspec = ">=0.11.1" +pyyaml = ">=5.1" +pyyaml-env-tag = ">=0.1" +watchdog = ">=2.0" + +[package.extras] +i18n = ["babel (>=2.9.0)"] +min-versions = ["babel (==2.9.0)", "click (==7.0)", "colorama (==0.4)", "ghp-import (==1.0)", "importlib-metadata (==4.4)", "jinja2 (==2.11.1)", "markdown (==3.3.6)", "markupsafe (==2.0.1)", "mergedeep (==1.3.4)", "mkdocs-get-deps (==0.2.0)", "packaging (==20.5)", "pathspec (==0.11.1)", "pyyaml (==5.1)", "pyyaml-env-tag (==0.1)", "watchdog (==2.0)"] + +[[package]] +name = "mkdocs-get-deps" +version = "0.2.0" +description = "MkDocs extension that lists all dependencies according to a mkdocs.yml file" +optional = false +python-versions = ">=3.8" +files = [ + {file = "mkdocs_get_deps-0.2.0-py3-none-any.whl", hash = "sha256:2bf11d0b133e77a0dd036abeeb06dec8775e46efa526dc70667d8863eefc6134"}, + {file = "mkdocs_get_deps-0.2.0.tar.gz", hash = "sha256:162b3d129c7fad9b19abfdcb9c1458a651628e4b1dea628ac68790fb3061c60c"}, +] + +[package.dependencies] +mergedeep = ">=1.3.4" +platformdirs = ">=2.2.0" +pyyaml = ">=5.1" + +[[package]] +name = "packaging" +version = "24.0" +description = "Core utilities for Python packages" +optional = false +python-versions = ">=3.7" +files = [ + {file = "packaging-24.0-py3-none-any.whl", hash = "sha256:2ddfb553fdf02fb784c234c7ba6ccc288296ceabec964ad2eae3777778130bc5"}, + {file = "packaging-24.0.tar.gz", hash = "sha256:eb82c5e3e56209074766e6885bb04b8c38a0c015d0a30036ebe7ece34c9989e9"}, +] + +[[package]] +name = "pathspec" +version = "0.12.1" +description = "Utility library for gitignore style pattern matching of file paths." +optional = false +python-versions = ">=3.8" +files = [ + {file = "pathspec-0.12.1-py3-none-any.whl", hash = "sha256:a0d503e138a4c123b27490a4f7beda6a01c6f288df0e4a8b79c7eb0dc7b4cc08"}, + {file = "pathspec-0.12.1.tar.gz", hash = "sha256:a482d51503a1ab33b1c67a6c3813a26953dbdc71c31dacaef9a838c4e29f5712"}, +] + +[[package]] +name = "platformdirs" +version = "4.2.1" +description = "A small Python package for determining appropriate platform-specific dirs, e.g. a `user data dir`." +optional = false +python-versions = ">=3.8" +files = [ + {file = "platformdirs-4.2.1-py3-none-any.whl", hash = "sha256:17d5a1161b3fd67b390023cb2d3b026bbd40abde6fdb052dfbd3a29c3ba22ee1"}, + {file = "platformdirs-4.2.1.tar.gz", hash = "sha256:031cd18d4ec63ec53e82dceaac0417d218a6863f7745dfcc9efe7793b7039bdf"}, +] + +[package.extras] +docs = ["furo (>=2023.9.10)", "proselint (>=0.13)", "sphinx (>=7.2.6)", "sphinx-autodoc-typehints (>=1.25.2)"] +test = ["appdirs (==1.4.4)", "covdefaults (>=2.3)", "pytest (>=7.4.3)", "pytest-cov (>=4.1)", "pytest-mock (>=3.12)"] +type = ["mypy (>=1.8)"] + +[[package]] +name = "pluggy" +version = "1.5.0" +description = "plugin and hook calling mechanisms for python" +optional = false +python-versions = ">=3.8" +files = [ + {file = "pluggy-1.5.0-py3-none-any.whl", hash = "sha256:44e1ad92c8ca002de6377e165f3e0f1be63266ab4d554740532335b9d75ea669"}, + {file = "pluggy-1.5.0.tar.gz", hash = "sha256:2cffa88e94fdc978c4c574f15f9e59b7f4201d439195c3715ca9e2486f1d0cf1"}, +] + +[package.extras] +dev = ["pre-commit", "tox"] +testing = ["pytest", "pytest-benchmark"] + +[[package]] +name = "py" +version = "1.11.0" +description = "library with cross-python path, ini-parsing, io, code, log facilities" +optional = false +python-versions = ">=2.7, !=3.0.*, !=3.1.*, !=3.2.*, !=3.3.*, !=3.4.*" +files = [ + {file = "py-1.11.0-py2.py3-none-any.whl", hash = "sha256:607c53218732647dff4acdfcd50cb62615cedf612e72d1724fb1a0cc6405b378"}, + {file = "py-1.11.0.tar.gz", hash = "sha256:51c75c4126074b472f746a24399ad32f6053d1b34b68d2fa41e558e6f4a98719"}, +] + +[[package]] +name = "pygments" +version = "2.17.2" +description = "Pygments is a syntax highlighting package written in Python." +optional = false +python-versions = ">=3.7" +files = [ + {file = "pygments-2.17.2-py3-none-any.whl", hash = "sha256:b27c2826c47d0f3219f29554824c30c5e8945175d888647acd804ddd04af846c"}, + {file = "pygments-2.17.2.tar.gz", hash = "sha256:da46cec9fd2de5be3a8a784f434e4c4ab670b4ff54d605c4c2717e9d49c4c367"}, +] + +[package.extras] +plugins = ["importlib-metadata"] +windows-terminal = ["colorama (>=0.4.6)"] + +[[package]] +name = "pytest" +version = "6.2.5" +description = "pytest: simple powerful testing with Python" +optional = false +python-versions = ">=3.6" +files = [ + {file = "pytest-6.2.5-py3-none-any.whl", hash = "sha256:7310f8d27bc79ced999e760ca304d69f6ba6c6649c0b60fb0e04a4a77cacc134"}, + {file = "pytest-6.2.5.tar.gz", hash = "sha256:131b36680866a76e6781d13f101efb86cf674ebb9762eb70d3082b6f29889e89"}, +] + +[package.dependencies] +atomicwrites = {version = ">=1.0", markers = "sys_platform == \"win32\""} +attrs = ">=19.2.0" +colorama = {version = "*", markers = "sys_platform == \"win32\""} +iniconfig = "*" +packaging = "*" +pluggy = ">=0.12,<2.0" +py = ">=1.8.2" +toml = "*" + +[package.extras] +testing = ["argcomplete", "hypothesis (>=3.56)", "mock", "nose", "requests", "xmlschema"] + +[[package]] +name = "pytest-mock" +version = "3.14.0" +description = "Thin-wrapper around the mock package for easier use with pytest" +optional = false +python-versions = ">=3.8" +files = [ + {file = "pytest-mock-3.14.0.tar.gz", hash = "sha256:2719255a1efeceadbc056d6bf3df3d1c5015530fb40cf347c0f9afac88410bd0"}, + {file = "pytest_mock-3.14.0-py3-none-any.whl", hash = "sha256:0b72c38033392a5f4621342fe11e9219ac11ec9d375f8e2a0c164539e0d70f6f"}, +] + +[package.dependencies] +pytest = ">=6.2.5" + +[package.extras] +dev = ["pre-commit", "pytest-asyncio", "tox"] + +[[package]] +name = "python-dateutil" +version = "2.9.0.post0" +description = "Extensions to the standard Python datetime module" +optional = false +python-versions = "!=3.0.*,!=3.1.*,!=3.2.*,>=2.7" +files = [ + {file = "python-dateutil-2.9.0.post0.tar.gz", hash = "sha256:37dd54208da7e1cd875388217d5e00ebd4179249f90fb72437e91a35459a0ad3"}, + {file = "python_dateutil-2.9.0.post0-py2.py3-none-any.whl", hash = "sha256:a8b2bc7bffae282281c8140a97d3aa9c14da0b136dfe83f850eea9a5f7470427"}, +] + +[package.dependencies] +six = ">=1.5" + +[[package]] +name = "pyyaml" +version = "6.0.1" +description = "YAML parser and emitter for Python" +optional = false +python-versions = ">=3.6" +files = [ + {file = "PyYAML-6.0.1-cp310-cp310-macosx_10_9_x86_64.whl", hash = "sha256:d858aa552c999bc8a8d57426ed01e40bef403cd8ccdd0fc5f6f04a00414cac2a"}, + {file = "PyYAML-6.0.1-cp310-cp310-macosx_11_0_arm64.whl", hash = "sha256:fd66fc5d0da6d9815ba2cebeb4205f95818ff4b79c3ebe268e75d961704af52f"}, + {file = "PyYAML-6.0.1-cp310-cp310-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:69b023b2b4daa7548bcfbd4aa3da05b3a74b772db9e23b982788168117739938"}, + {file = "PyYAML-6.0.1-cp310-cp310-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:81e0b275a9ecc9c0c0c07b4b90ba548307583c125f54d5b6946cfee6360c733d"}, + {file = "PyYAML-6.0.1-cp310-cp310-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:ba336e390cd8e4d1739f42dfe9bb83a3cc2e80f567d8805e11b46f4a943f5515"}, + {file = "PyYAML-6.0.1-cp310-cp310-musllinux_1_1_x86_64.whl", hash = "sha256:326c013efe8048858a6d312ddd31d56e468118ad4cdeda36c719bf5bb6192290"}, + {file = "PyYAML-6.0.1-cp310-cp310-win32.whl", hash = "sha256:bd4af7373a854424dabd882decdc5579653d7868b8fb26dc7d0e99f823aa5924"}, + {file = "PyYAML-6.0.1-cp310-cp310-win_amd64.whl", hash = "sha256:fd1592b3fdf65fff2ad0004b5e363300ef59ced41c2e6b3a99d4089fa8c5435d"}, + {file = "PyYAML-6.0.1-cp311-cp311-macosx_10_9_x86_64.whl", hash = "sha256:6965a7bc3cf88e5a1c3bd2e0b5c22f8d677dc88a455344035f03399034eb3007"}, + {file = "PyYAML-6.0.1-cp311-cp311-macosx_11_0_arm64.whl", hash = "sha256:f003ed9ad21d6a4713f0a9b5a7a0a79e08dd0f221aff4525a2be4c346ee60aab"}, + {file = "PyYAML-6.0.1-cp311-cp311-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:42f8152b8dbc4fe7d96729ec2b99c7097d656dc1213a3229ca5383f973a5ed6d"}, + {file = "PyYAML-6.0.1-cp311-cp311-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:062582fca9fabdd2c8b54a3ef1c978d786e0f6b3a1510e0ac93ef59e0ddae2bc"}, + {file = "PyYAML-6.0.1-cp311-cp311-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:d2b04aac4d386b172d5b9692e2d2da8de7bfb6c387fa4f801fbf6fb2e6ba4673"}, + {file = "PyYAML-6.0.1-cp311-cp311-musllinux_1_1_x86_64.whl", hash = "sha256:e7d73685e87afe9f3b36c799222440d6cf362062f78be1013661b00c5c6f678b"}, + {file = "PyYAML-6.0.1-cp311-cp311-win32.whl", hash = "sha256:1635fd110e8d85d55237ab316b5b011de701ea0f29d07611174a1b42f1444741"}, + {file = "PyYAML-6.0.1-cp311-cp311-win_amd64.whl", hash = "sha256:bf07ee2fef7014951eeb99f56f39c9bb4af143d8aa3c21b1677805985307da34"}, + {file = "PyYAML-6.0.1-cp312-cp312-macosx_10_9_x86_64.whl", hash = "sha256:855fb52b0dc35af121542a76b9a84f8d1cd886ea97c84703eaa6d88e37a2ad28"}, + {file = "PyYAML-6.0.1-cp312-cp312-macosx_11_0_arm64.whl", hash = "sha256:40df9b996c2b73138957fe23a16a4f0ba614f4c0efce1e9406a184b6d07fa3a9"}, + {file = "PyYAML-6.0.1-cp312-cp312-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:a08c6f0fe150303c1c6b71ebcd7213c2858041a7e01975da3a99aed1e7a378ef"}, + {file = "PyYAML-6.0.1-cp312-cp312-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:6c22bec3fbe2524cde73d7ada88f6566758a8f7227bfbf93a408a9d86bcc12a0"}, + {file = "PyYAML-6.0.1-cp312-cp312-musllinux_1_1_x86_64.whl", hash = "sha256:8d4e9c88387b0f5c7d5f281e55304de64cf7f9c0021a3525bd3b1c542da3b0e4"}, + {file = "PyYAML-6.0.1-cp312-cp312-win32.whl", hash = "sha256:d483d2cdf104e7c9fa60c544d92981f12ad66a457afae824d146093b8c294c54"}, + {file = "PyYAML-6.0.1-cp312-cp312-win_amd64.whl", hash = "sha256:0d3304d8c0adc42be59c5f8a4d9e3d7379e6955ad754aa9d6ab7a398b59dd1df"}, + {file = "PyYAML-6.0.1-cp36-cp36m-macosx_10_9_x86_64.whl", hash = "sha256:50550eb667afee136e9a77d6dc71ae76a44df8b3e51e41b77f6de2932bfe0f47"}, + {file = "PyYAML-6.0.1-cp36-cp36m-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:1fe35611261b29bd1de0070f0b2f47cb6ff71fa6595c077e42bd0c419fa27b98"}, + {file = "PyYAML-6.0.1-cp36-cp36m-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:704219a11b772aea0d8ecd7058d0082713c3562b4e271b849ad7dc4a5c90c13c"}, + {file = "PyYAML-6.0.1-cp36-cp36m-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:afd7e57eddb1a54f0f1a974bc4391af8bcce0b444685d936840f125cf046d5bd"}, + {file = "PyYAML-6.0.1-cp36-cp36m-win32.whl", hash = "sha256:fca0e3a251908a499833aa292323f32437106001d436eca0e6e7833256674585"}, + {file = "PyYAML-6.0.1-cp36-cp36m-win_amd64.whl", hash = "sha256:f22ac1c3cac4dbc50079e965eba2c1058622631e526bd9afd45fedd49ba781fa"}, + {file = "PyYAML-6.0.1-cp37-cp37m-macosx_10_9_x86_64.whl", hash = "sha256:b1275ad35a5d18c62a7220633c913e1b42d44b46ee12554e5fd39c70a243d6a3"}, + {file = "PyYAML-6.0.1-cp37-cp37m-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:18aeb1bf9a78867dc38b259769503436b7c72f7a1f1f4c93ff9a17de54319b27"}, + {file = "PyYAML-6.0.1-cp37-cp37m-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:596106435fa6ad000c2991a98fa58eeb8656ef2325d7e158344fb33864ed87e3"}, + {file = "PyYAML-6.0.1-cp37-cp37m-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:baa90d3f661d43131ca170712d903e6295d1f7a0f595074f151c0aed377c9b9c"}, + {file = "PyYAML-6.0.1-cp37-cp37m-win32.whl", hash = "sha256:9046c58c4395dff28dd494285c82ba00b546adfc7ef001486fbf0324bc174fba"}, + {file = "PyYAML-6.0.1-cp37-cp37m-win_amd64.whl", hash = "sha256:4fb147e7a67ef577a588a0e2c17b6db51dda102c71de36f8549b6816a96e1867"}, + {file = "PyYAML-6.0.1-cp38-cp38-macosx_10_9_x86_64.whl", hash = "sha256:1d4c7e777c441b20e32f52bd377e0c409713e8bb1386e1099c2415f26e479595"}, + {file = "PyYAML-6.0.1-cp38-cp38-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:a0cd17c15d3bb3fa06978b4e8958dcdc6e0174ccea823003a106c7d4d7899ac5"}, + {file = "PyYAML-6.0.1-cp38-cp38-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:28c119d996beec18c05208a8bd78cbe4007878c6dd15091efb73a30e90539696"}, + {file = "PyYAML-6.0.1-cp38-cp38-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:7e07cbde391ba96ab58e532ff4803f79c4129397514e1413a7dc761ccd755735"}, + {file = "PyYAML-6.0.1-cp38-cp38-musllinux_1_1_x86_64.whl", hash = "sha256:49a183be227561de579b4a36efbb21b3eab9651dd81b1858589f796549873dd6"}, + {file = "PyYAML-6.0.1-cp38-cp38-win32.whl", hash = "sha256:184c5108a2aca3c5b3d3bf9395d50893a7ab82a38004c8f61c258d4428e80206"}, + {file = "PyYAML-6.0.1-cp38-cp38-win_amd64.whl", hash = "sha256:1e2722cc9fbb45d9b87631ac70924c11d3a401b2d7f410cc0e3bbf249f2dca62"}, + {file = "PyYAML-6.0.1-cp39-cp39-macosx_10_9_x86_64.whl", hash = "sha256:9eb6caa9a297fc2c2fb8862bc5370d0303ddba53ba97e71f08023b6cd73d16a8"}, + {file = "PyYAML-6.0.1-cp39-cp39-macosx_11_0_arm64.whl", hash = "sha256:c8098ddcc2a85b61647b2590f825f3db38891662cfc2fc776415143f599bb859"}, + {file = "PyYAML-6.0.1-cp39-cp39-manylinux_2_17_aarch64.manylinux2014_aarch64.whl", hash = "sha256:5773183b6446b2c99bb77e77595dd486303b4faab2b086e7b17bc6bef28865f6"}, + {file = "PyYAML-6.0.1-cp39-cp39-manylinux_2_17_s390x.manylinux2014_s390x.whl", hash = "sha256:b786eecbdf8499b9ca1d697215862083bd6d2a99965554781d0d8d1ad31e13a0"}, + {file = "PyYAML-6.0.1-cp39-cp39-manylinux_2_17_x86_64.manylinux2014_x86_64.whl", hash = "sha256:bc1bf2925a1ecd43da378f4db9e4f799775d6367bdb94671027b73b393a7c42c"}, + {file = "PyYAML-6.0.1-cp39-cp39-musllinux_1_1_x86_64.whl", hash = "sha256:04ac92ad1925b2cff1db0cfebffb6ffc43457495c9b3c39d3fcae417d7125dc5"}, + {file = "PyYAML-6.0.1-cp39-cp39-win32.whl", hash = "sha256:faca3bdcf85b2fc05d06ff3fbc1f83e1391b3e724afa3feba7d13eeab355484c"}, + {file = "PyYAML-6.0.1-cp39-cp39-win_amd64.whl", hash = "sha256:510c9deebc5c0225e8c96813043e62b680ba2f9c50a08d3724c7f28a747d1486"}, + {file = "PyYAML-6.0.1.tar.gz", hash = "sha256:bfdf460b1736c775f2ba9f6a92bca30bc2095067b8a9d77876d1fad6cc3b4a43"}, +] + +[[package]] +name = "pyyaml-env-tag" +version = "0.1" +description = "A custom YAML tag for referencing environment variables in YAML files. " +optional = false +python-versions = ">=3.6" +files = [ + {file = "pyyaml_env_tag-0.1-py3-none-any.whl", hash = "sha256:af31106dec8a4d68c60207c1886031cbf839b68aa7abccdb19868200532c2069"}, + {file = "pyyaml_env_tag-0.1.tar.gz", hash = "sha256:70092675bda14fdec33b31ba77e7543de9ddc88f2e5b99160396572d11525bdb"}, +] + +[package.dependencies] +pyyaml = "*" + +[[package]] +name = "rich" +version = "13.7.1" +description = "Render rich text, tables, progress bars, syntax highlighting, markdown and more to the terminal" +optional = false +python-versions = ">=3.7.0" +files = [ + {file = "rich-13.7.1-py3-none-any.whl", hash = "sha256:4edbae314f59eb482f54e9e30bf00d33350aaa94f4bfcd4e9e3110e64d0d7222"}, + {file = "rich-13.7.1.tar.gz", hash = "sha256:9be308cb1fe2f1f57d67ce99e95af38a1e2bc71ad9813b0e247cf7ffbcc3a432"}, +] + +[package.dependencies] +markdown-it-py = ">=2.2.0" +pygments = ">=2.13.0,<3.0.0" + +[package.extras] +jupyter = ["ipywidgets (>=7.5.1,<9)"] + +[[package]] +name = "six" +version = "1.16.0" +description = "Python 2 and 3 compatibility utilities" +optional = false +python-versions = ">=2.7, !=3.0.*, !=3.1.*, !=3.2.*" +files = [ + {file = "six-1.16.0-py2.py3-none-any.whl", hash = "sha256:8abb2f1d86890a2dfb989f9a77cfcfd3e47c2a354b01111771326f8aa26e0254"}, + {file = "six-1.16.0.tar.gz", hash = "sha256:1e61c37477a1626458e36f7b1d82aa5c9b094fa4802892072e49de9c60c4c926"}, +] + +[[package]] +name = "toml" +version = "0.10.2" +description = "Python Library for Tom's Obvious, Minimal Language" +optional = false +python-versions = ">=2.6, !=3.0.*, !=3.1.*, !=3.2.*" +files = [ + {file = "toml-0.10.2-py2.py3-none-any.whl", hash = "sha256:806143ae5bfb6a3c6e736a764057db0e6a0e05e338b5630894a5f779cabb4f9b"}, + {file = "toml-0.10.2.tar.gz", hash = "sha256:b3bda1d108d5dd99f4a20d24d9c348e91c4db7ab1b749200bded2f839ccbe68f"}, +] + +[[package]] +name = "watchdog" +version = "4.0.0" +description = "Filesystem events monitoring" +optional = false +python-versions = ">=3.8" +files = [ + {file = "watchdog-4.0.0-cp310-cp310-macosx_10_9_universal2.whl", hash = "sha256:39cb34b1f1afbf23e9562501673e7146777efe95da24fab5707b88f7fb11649b"}, + {file = "watchdog-4.0.0-cp310-cp310-macosx_10_9_x86_64.whl", hash = "sha256:c522392acc5e962bcac3b22b9592493ffd06d1fc5d755954e6be9f4990de932b"}, + {file = "watchdog-4.0.0-cp310-cp310-macosx_11_0_arm64.whl", hash = "sha256:6c47bdd680009b11c9ac382163e05ca43baf4127954c5f6d0250e7d772d2b80c"}, + {file = "watchdog-4.0.0-cp311-cp311-macosx_10_9_universal2.whl", hash = "sha256:8350d4055505412a426b6ad8c521bc7d367d1637a762c70fdd93a3a0d595990b"}, + {file = "watchdog-4.0.0-cp311-cp311-macosx_10_9_x86_64.whl", hash = "sha256:c17d98799f32e3f55f181f19dd2021d762eb38fdd381b4a748b9f5a36738e935"}, + {file = "watchdog-4.0.0-cp311-cp311-macosx_11_0_arm64.whl", hash = "sha256:4986db5e8880b0e6b7cd52ba36255d4793bf5cdc95bd6264806c233173b1ec0b"}, + {file = "watchdog-4.0.0-cp312-cp312-macosx_10_9_universal2.whl", hash = "sha256:11e12fafb13372e18ca1bbf12d50f593e7280646687463dd47730fd4f4d5d257"}, + {file = "watchdog-4.0.0-cp312-cp312-macosx_10_9_x86_64.whl", hash = "sha256:5369136a6474678e02426bd984466343924d1df8e2fd94a9b443cb7e3aa20d19"}, + {file = "watchdog-4.0.0-cp312-cp312-macosx_11_0_arm64.whl", hash = "sha256:76ad8484379695f3fe46228962017a7e1337e9acadafed67eb20aabb175df98b"}, + {file = "watchdog-4.0.0-cp38-cp38-macosx_10_9_universal2.whl", hash = "sha256:45cc09cc4c3b43fb10b59ef4d07318d9a3ecdbff03abd2e36e77b6dd9f9a5c85"}, + {file = "watchdog-4.0.0-cp38-cp38-macosx_10_9_x86_64.whl", hash = "sha256:eed82cdf79cd7f0232e2fdc1ad05b06a5e102a43e331f7d041e5f0e0a34a51c4"}, + {file = "watchdog-4.0.0-cp38-cp38-macosx_11_0_arm64.whl", hash = "sha256:ba30a896166f0fee83183cec913298151b73164160d965af2e93a20bbd2ab605"}, + {file = "watchdog-4.0.0-cp39-cp39-macosx_10_9_universal2.whl", hash = "sha256:d18d7f18a47de6863cd480734613502904611730f8def45fc52a5d97503e5101"}, + {file = "watchdog-4.0.0-cp39-cp39-macosx_10_9_x86_64.whl", hash = "sha256:2895bf0518361a9728773083908801a376743bcc37dfa252b801af8fd281b1ca"}, + {file = "watchdog-4.0.0-cp39-cp39-macosx_11_0_arm64.whl", hash = "sha256:87e9df830022488e235dd601478c15ad73a0389628588ba0b028cb74eb72fed8"}, + {file = "watchdog-4.0.0-pp310-pypy310_pp73-macosx_10_9_x86_64.whl", hash = "sha256:6e949a8a94186bced05b6508faa61b7adacc911115664ccb1923b9ad1f1ccf7b"}, + {file = "watchdog-4.0.0-pp38-pypy38_pp73-macosx_10_9_x86_64.whl", hash = "sha256:6a4db54edea37d1058b08947c789a2354ee02972ed5d1e0dca9b0b820f4c7f92"}, + {file = "watchdog-4.0.0-pp39-pypy39_pp73-macosx_10_9_x86_64.whl", hash = "sha256:d31481ccf4694a8416b681544c23bd271f5a123162ab603c7d7d2dd7dd901a07"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_aarch64.whl", hash = "sha256:8fec441f5adcf81dd240a5fe78e3d83767999771630b5ddfc5867827a34fa3d3"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_armv7l.whl", hash = "sha256:6a9c71a0b02985b4b0b6d14b875a6c86ddea2fdbebd0c9a720a806a8bbffc69f"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_i686.whl", hash = "sha256:557ba04c816d23ce98a06e70af6abaa0485f6d94994ec78a42b05d1c03dcbd50"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_ppc64.whl", hash = "sha256:d0f9bd1fd919134d459d8abf954f63886745f4660ef66480b9d753a7c9d40927"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_ppc64le.whl", hash = "sha256:f9b2fdca47dc855516b2d66eef3c39f2672cbf7e7a42e7e67ad2cbfcd6ba107d"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_s390x.whl", hash = "sha256:73c7a935e62033bd5e8f0da33a4dcb763da2361921a69a5a95aaf6c93aa03a87"}, + {file = "watchdog-4.0.0-py3-none-manylinux2014_x86_64.whl", hash = "sha256:6a80d5cae8c265842c7419c560b9961561556c4361b297b4c431903f8c33b269"}, + {file = "watchdog-4.0.0-py3-none-win32.whl", hash = "sha256:8f9a542c979df62098ae9c58b19e03ad3df1c9d8c6895d96c0d51da17b243b1c"}, + {file = "watchdog-4.0.0-py3-none-win_amd64.whl", hash = "sha256:f970663fa4f7e80401a7b0cbeec00fa801bf0287d93d48368fc3e6fa32716245"}, + {file = "watchdog-4.0.0-py3-none-win_ia64.whl", hash = "sha256:9a03e16e55465177d416699331b0f3564138f1807ecc5f2de9d55d8f188d08c7"}, + {file = "watchdog-4.0.0.tar.gz", hash = "sha256:e3e7065cbdabe6183ab82199d7a4f6b3ba0a438c5a512a68559846ccb76a78ec"}, +] + +[package.extras] +watchmedo = ["PyYAML (>=3.10)"] + +[metadata] +lock-version = "2.0" +python-versions = "^3.12" +content-hash = "f1373e68b3910dac104fa0f849c71df5179eefbb936a3bb9f9f8f5d443786194" diff --git a/test/Python/Poetry/testdata/no-category/pyproject.test.toml b/test/Python/Poetry/testdata/no-category/pyproject.test.toml new file mode 100644 index 0000000000..01120193c4 --- /dev/null +++ b/test/Python/Poetry/testdata/no-category/pyproject.test.toml @@ -0,0 +1,8 @@ +[group.dev.dependencies] +a = "1.0.0" + +[group.docs] +optional = false + +[group.docs.dependencies] +b = "1.0.0" diff --git a/test/Python/Poetry/testdata/no-category/pyproject.toml b/test/Python/Poetry/testdata/no-category/pyproject.toml new file mode 100644 index 0000000000..2b219d92a4 --- /dev/null +++ b/test/Python/Poetry/testdata/no-category/pyproject.toml @@ -0,0 +1,27 @@ +[tool.poetry] +name = "hippo" +version = "0.1.0" +description = "" +authors = ["meghfossa "] +readme = "README.md" + +[tool.poetry.dependencies] +python = "^3.12" +rich = "*" + +[tool.poetry.group.dev.dependencies] +click = "*" + +[tool.poetry.group.test.dependencies] +pytest = "^6.0.0" +pytest-mock = "*" + +[tool.poetry.group.docs] +optional = true + +[tool.poetry.group.docs.dependencies] +mkdocs = "*" + +[build-system] +requires = ["poetry-core"] +build-backend = "poetry.core.masonry.api" diff --git a/test/Python/PoetrySpec.hs b/test/Python/PoetrySpec.hs index bf91376e02..c7858eb613 100644 --- a/test/Python/PoetrySpec.hs +++ b/test/Python/PoetrySpec.hs @@ -1,23 +1,44 @@ -module Python.PoetrySpec ( - spec, -) where +{-# LANGUAGE TemplateHaskell #-} + +module Python.PoetrySpec + ( spec, + ) +where import Data.Map qualified as Map +import Data.Set qualified as Set import DepTypes (DepEnvironment (..), DepType (..), Dependency (..), VerConstraint (..)) import Graphing (Graphing) import Graphing qualified -import Strategy.Python.Poetry (graphFromLockFile, setGraphDirectsFromPyproject) -import Strategy.Python.Poetry.PoetryLock ( - PackageName (..), - PoetryLock (..), - PoetryLockDependencySpec (..), - PoetryLockPackage (..), - PoetryMetadata (..), - ) - -import Data.Set qualified as Set +import Path (mkRelDir, mkRelFile, ()) +import Path.IO (getCurrentDir) +import Strategy.Python.Poetry + ( PoetryLockFile (PoetryLockFile), + PoetryProject (PoetryProject), + ProjectDir (ProjectDir), + PyProjectTomlFile (PyProjectTomlFile), + analyze, + graphFromPyProjectAndLockFile, + setGraphDirectsFromPyproject, + ) +import Strategy.Python.Poetry.PoetryLock + ( PackageName (..), + PoetryLock (..), + PoetryLockDependencySpec (..), + PoetryLockPackage (..), + PoetryMetadata (..), + ) import Strategy.Python.Poetry.PyProject (PoetryDependency (..), PyProject (..), PyProjectBuildSystem (..), PyProjectPoetry (..)) -import Test.Hspec +import Test.Effect (it', shouldBe') +import Test.Hspec (Spec, describe, it, runIO, shouldBe) +import Types (DependencyResults (dependencyGraph)) +import Data.Text (Text, splitOn) +import GraphUtil ( expectDeps', expectEdges', expectDirect' ) +import Text.Pretty.Simple (pShow, pShowNoColor) +import Control.Carrier.Lift (sendIO) +import Effect.Logger (logInfo) +import Effect.Logger (Pretty(..), logStdout) +import Data.Text.Lazy (toStrict) newPoetryLock :: [PoetryLockPackage] -> PoetryLock newPoetryLock pkgs = PoetryLock pkgs $ PoetryMetadata "some-version" "some-hash" "some-poetry-version" @@ -26,7 +47,7 @@ candidatePyProject :: PyProject candidatePyProject = PyProject (Just $ PyProjectBuildSystem "poetry.core.masonry.api") - (Just $ PyProjectPoetry Nothing Nothing Nothing (Map.fromList ([("flow_pipes", PoetryTextVersion "^1.21")])) Map.empty Map.empty) + (Just $ PyProjectPoetry Nothing Nothing Nothing (Map.fromList ([("flow_pipes", PoetryTextVersion "^1.21")])) Map.empty Map.empty Map.empty) Nothing Nothing @@ -34,22 +55,22 @@ candidatePoetryLock :: PoetryLock candidatePoetryLock = newPoetryLock [ PoetryLockPackage - { poetryLockPackageName = PackageName "flow_pipes" - , poetryLockPackageVersion = "1.21.0" - , poetryLockPackageCategory = Just "main" - , poetryLockPackageOptional = False - , poetryLockPackageDependencies = Map.fromList [("flow_pipes_gravity", TextVersion "^1.1")] - , poetryLockPackagePythonVersions = "*" - , poetryLockPackageSource = Nothing - } - , PoetryLockPackage - { poetryLockPackageName = PackageName "flow_pipes_gravity" - , poetryLockPackageVersion = "1.1.1" - , poetryLockPackageCategory = Just "main" - , poetryLockPackageOptional = False - , poetryLockPackageDependencies = Map.empty - , poetryLockPackagePythonVersions = "*" - , poetryLockPackageSource = Nothing + { poetryLockPackageName = PackageName "flow_pipes", + poetryLockPackageVersion = "1.21.0", + poetryLockPackageCategory = Just "main", + poetryLockPackageOptional = False, + poetryLockPackageDependencies = Map.fromList [("flow_pipes_gravity", TextVersion "^1.1")], + poetryLockPackagePythonVersions = "*", + poetryLockPackageSource = Nothing + }, + PoetryLockPackage + { poetryLockPackageName = PackageName "flow_pipes_gravity", + poetryLockPackageVersion = "1.1.1", + poetryLockPackageCategory = Just "main", + poetryLockPackageOptional = False, + poetryLockPackageDependencies = Map.empty, + poetryLockPackagePythonVersions = "*", + poetryLockPackageSource = Nothing } ] @@ -71,48 +92,118 @@ expectedGraphWithDeps = spec :: Spec spec = do + poetryV1_5OrGtSpec + describe "setGraphDirectsFromPyproject" $ it "should should promote direct dependencies and create valid graph" $ - setGraphDirectsFromPyproject (graphFromLockFile candidatePoetryLock) candidatePyProject `shouldBe` expectedGraph - + (setGraphDirectsFromPyproject (graphFromPyProjectAndLockFile candidatePyProject candidatePoetryLock) candidatePyProject) `shouldBe` expectedGraph describe "graphFromLockFile" $ do describe "when package has no transitive dependencies" $ do it "should produce graph with no edges" $ do let poetryLock = newPoetryLock [ PoetryLockPackage - { poetryLockPackageName = PackageName "somePkg" - , poetryLockPackageVersion = "1.21.0" - , poetryLockPackageCategory = Just "main" - , poetryLockPackageOptional = False - , poetryLockPackageDependencies = Map.empty - , poetryLockPackagePythonVersions = "*" - , poetryLockPackageSource = Nothing + { poetryLockPackageName = PackageName "somePkg", + poetryLockPackageVersion = "1.21.0", + poetryLockPackageCategory = Just "main", + poetryLockPackageOptional = False, + poetryLockPackageDependencies = Map.empty, + poetryLockPackagePythonVersions = "*", + poetryLockPackageSource = Nothing } ] - graphFromLockFile poetryLock `shouldBe` expectedGraphWithNoDeps + graphFromPyProjectAndLockFile candidatePyProject poetryLock `shouldBe` expectedGraphWithNoDeps describe "when package has deep dependencies" $ do it "should produce graph with edges" $ do - let peortyLockDeps = + let poetryLockDeps = newPoetryLock [ PoetryLockPackage - { poetryLockPackageName = PackageName "somePkg" - , poetryLockPackageVersion = "1.21.0" - , poetryLockPackageCategory = Just "main" - , poetryLockPackageOptional = False - , poetryLockPackageDependencies = Map.fromList [("pkgOneChildOne", TextVersion "*")] - , poetryLockPackagePythonVersions = "*" - , poetryLockPackageSource = Nothing - } - , PoetryLockPackage - { poetryLockPackageName = PackageName "pkgOneChildOne" - , poetryLockPackageVersion = "1.22.0" - , poetryLockPackageCategory = Just "main" - , poetryLockPackageOptional = False - , poetryLockPackageDependencies = Map.empty - , poetryLockPackagePythonVersions = "*" - , poetryLockPackageSource = Nothing + { poetryLockPackageName = PackageName "somePkg", + poetryLockPackageVersion = "1.21.0", + poetryLockPackageCategory = Just "main", + poetryLockPackageOptional = False, + poetryLockPackageDependencies = Map.fromList [("pkgOneChildOne", TextVersion "*")], + poetryLockPackagePythonVersions = "*", + poetryLockPackageSource = Nothing + }, + PoetryLockPackage + { poetryLockPackageName = PackageName "pkgOneChildOne", + poetryLockPackageVersion = "1.22.0", + poetryLockPackageCategory = Just "main", + poetryLockPackageOptional = False, + poetryLockPackageDependencies = Map.empty, + poetryLockPackagePythonVersions = "*", + poetryLockPackageSource = Nothing } ] - graphFromLockFile peortyLockDeps `shouldBe` expectedGraphWithDeps + graphFromPyProjectAndLockFile candidatePyProject poetryLockDeps `shouldBe` expectedGraphWithDeps + +poetryV1_5OrGtSpec :: Spec +poetryV1_5OrGtSpec = do + currDir <- runIO getCurrentDir + describe "Poetry graph" $ do + let absSpecDir = currDir $(mkRelDir "test/Python/Poetry/testdata/no-category") + let pyprojectFile = absSpecDir $(mkRelFile "pyproject.toml") + let lockfile = absSpecDir $(mkRelFile "poetry.lock") + + let poetryProject = PoetryProject (ProjectDir absSpecDir) (PyProjectTomlFile pyprojectFile) (Just $ PoetryLockFile lockfile) + it' "create expected graph" $ do + -- - + -- >> poetry show -t + -- + -- click 8.1.7 Composable command line interface toolkit + -- └── colorama * + -- pytest 6.2.5 pytest: simple powerful testing with Python + -- ├── atomicwrites >=1.0 + -- ├── attrs >=19.2.0 + -- ├── colorama * + -- ├── iniconfig * + -- ├── packaging * + -- ├── pluggy >=0.12,<2.0 + -- ├── py >=1.8.2 + -- └── toml * + -- pytest-mock 3.14.0 Thin-wrapper around the mock package for easier use with pytest + -- └── pytest >=6.2.5 + -- ├── atomicwrites >=1.0 + -- ├── attrs >=19.2.0 + -- ├── colorama * + -- ├── iniconfig * + -- ├── packaging * + -- ├── pluggy >=0.12,<2.0 + -- ├── py >=1.8.2 + -- └── toml * + -- rich 13.7.1 Render rich text, tables, progress bars, syntax highlighting, markdown and more to the terminal + -- ├── markdown-it-py >=2.2.0 + -- │ └── mdurl >=0.1,<1.0 + -- └── pygments >=2.13.0,<3.0.0 + graph <- dependencyGraph <$> analyze poetryProject + logStdout $ toStrict $ pShow graph + expectDeps' deps graph + expectDirect' deps graph + expectEdges' [] graph + +deps :: [Dependency] +deps = [click] + +click :: Dependency +click = mkPipProdDep "click@8.1.7" + +mkDep :: DepType -> Text -> Maybe DepEnvironment -> Dependency +mkDep dt nameAtVersion env = do + let nameAndVersionSplit = splitOn "@" nameAtVersion + name = head nameAndVersionSplit + version = last nameAndVersionSplit + Dependency + dt + name + (CEq <$> (Just version)) + mempty + (maybe mempty Set.singleton env) + mempty + +mkPipProdDep :: Text -> Dependency +mkPipProdDep nameAtVersion = mkDep PipType nameAtVersion (Just EnvProduction) + +mkPipDevDep :: Text -> Dependency +mkPipDevDep nameAtVersion = mkDep PipType nameAtVersion (Just EnvDevelopment)