Skip to content

Commit

Permalink
Satisfy build and lint
Browse files Browse the repository at this point in the history
  • Loading branch information
alt-romes committed Feb 27, 2024
1 parent 6c19b98 commit d4d94ac
Show file tree
Hide file tree
Showing 15 changed files with 30 additions and 34 deletions.
7 changes: 5 additions & 2 deletions Cabal-described/src/Distribution/Described.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,7 @@ import Distribution.Types.AbiDependency (AbiDependency)
import Distribution.Types.AbiHash (AbiHash)
import Distribution.Types.BenchmarkType (BenchmarkType)
import Distribution.Types.BuildType (BuildType)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.Dependency (Dependency, PrivateAlias(..))
import Distribution.Types.ExecutableScope (ExecutableScope)
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.ExposedModule (ExposedModule)
Expand Down Expand Up @@ -446,6 +446,9 @@ instance Described ModuleName where
describe _ = REMunch1 (reChar '.') component where
component = RECharSet csUpper <> REMunch reEps (REUnion [RECharSet csAlphaNum, RECharSet (fromString "_'")])

instance Described PrivateAlias where
describe _ = describe (Proxy :: Proxy ModuleName)

instance Described ModuleReexport where
describe _ = RETodo

Expand Down Expand Up @@ -591,4 +594,4 @@ instance Described CompatLicenseFile where
describe _ = describe ([] :: [Token])

instance Described CompatFilePath where
describe _ = describe ([] :: [Token])
describe _ = describe ([] :: [Token])
1 change: 0 additions & 1 deletion Cabal-tests/tests/CheckTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,6 @@ module Main
) where

import Test.Tasty
import Test.Tasty.ExpectedFailure
import Test.Tasty.Golden.Advanced (goldenTest)

import Data.Algorithm.Diff (PolyDiff (..), getGroupedDiff)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module UnitTests.Distribution.PackageDescription.Check (tests) where

import Distribution.Compat.Prelude.Internal
import Distribution.Compat.Prelude
import Prelude ()

import Distribution.PackageDescription.Check
Expand Down
4 changes: 2 additions & 2 deletions Cabal-tests/tests/UnitTests/Distribution/Utils/Structured.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,15 +33,15 @@ md5Check proxy md5Int = structureHash proxy @?= md5FromInteger md5Int
md5CheckGenericPackageDescription :: Proxy GenericPackageDescription -> Assertion
md5CheckGenericPackageDescription proxy = md5Check proxy
#if MIN_VERSION_base(4,19,0)
0x4136daf844669c3c272845160cb5a908
0x3836b3b3818f20e4705b6b49a17cb254
#else
0x196b441722dfe556ed5b5d1d874741b3
#endif

md5CheckLocalBuildInfo :: Proxy LocalBuildInfo -> Assertion
md5CheckLocalBuildInfo proxy = md5Check proxy
#if MIN_VERSION_base(4,19,0)
0x8a30fa23374160aac9cdd1996dc5112b
0x1f8991209aaf600f8b70c852f11f5e1e
#else
0x2e959a7f1da8f0d11f6923831ab6ab55
#endif
4 changes: 2 additions & 2 deletions Cabal/src/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -696,9 +696,9 @@ computeLocalBuildConfig cfg comp programDb = do

data PackageInfo = PackageInfo
{ internalPackageSet :: Set LibraryName
, promisedDepsSet :: Map (PackageName, ComponentName) ComponentId
, promisedDepsSet :: Map (PackageName, ComponentName, Maybe PrivateAlias) ComponentId
, installedPackageSet :: InstalledPackageIndex
, requiredDepsMap :: Map (PackageName, ComponentName) InstalledPackageInfo
, requiredDepsMap :: Map (PackageName, ComponentName, Maybe PrivateAlias) InstalledPackageInfo
}

configurePackage
Expand Down
2 changes: 1 addition & 1 deletion Cabal/src/Distribution/Types/LocalBuildInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -151,7 +151,7 @@ pattern LocalBuildInfo
-> Maybe FilePath
-> Graph ComponentLocalBuildInfo
-> Map ComponentName [ComponentLocalBuildInfo]
-> Map (PackageName, ComponentName) ComponentId
-> Map (PackageName, ComponentName, Maybe PrivateAlias) ComponentId
-> InstalledPackageIndex
-> PackageDescription
-> ProgramDb
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -561,8 +561,6 @@ convLibDepsAs :: DependencyReason PN -> PrivateDependency -> [LDep PN]
convLibDepsAs dr (PrivateDependency alias deps) =
[ LDep dr $ Dep (PkgComponent pn (ExposedLib lib)) (Private alias) (Constrained vr)
| Dependency pn vr libs <- deps, lib <- NonEmptySet.toList libs ]
where


-- | Convert a Cabal dependency on an executable (build-tools) to a solver-specific dependency.
convExeDep :: DependencyReason PN -> ExeDependency -> LDep PN
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -176,7 +176,7 @@ instance IsNode NonSetupLibDepSolverPlanPackage where
nodeKey spkg

nodeNeighbors (NonSetupLibDepSolverPlanPackage spkg) =
ordNub $ (map fst $ CD.nonSetupDeps (resolverPackageLibDeps spkg))
ordNub $ map fst (CD.nonSetupDeps (resolverPackageLibDeps spkg))

-- | Work out which version of the Cabal we will be using to talk to the
-- Setup.hs interface for this package.
Expand Down
11 changes: 5 additions & 6 deletions cabal-install/tests/UnitTests/Distribution/Client/ScriptUtils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,9 +29,8 @@ testScriptPath (ShortPath p) = withMaxSuccess 10000 $ ioProperty $ do
hashed_path <- getScriptCacheDirectory p
script_build_dir <- defaultScriptBuildsDir
return $
and
-- 1. Is it a valid path at all
[ isValid hashed_path
, -- 2. Is the computed hashed path in the expected directory?
(script_build_dir </> takeFileName hashed_path) `equalFilePath` hashed_path
]
-- 1. Is it a valid path at all
isValid hashed_path
&&
-- 2. Is the computed hashed path in the expected directory?
(script_build_dir </> takeFileName hashed_path) `equalFilePath` hashed_path
Original file line number Diff line number Diff line change
Expand Up @@ -97,7 +97,6 @@ import Distribution.Solver.Types.Settings
import Distribution.Solver.Types.SolverPackage
import Distribution.Solver.Types.SourcePackage
import Distribution.Solver.Types.Variable
import Distribution.Types.Dependency (PrivateAlias)

{-------------------------------------------------------------------------------
Example package database DSL
Expand Down Expand Up @@ -293,13 +292,12 @@ data ExampleQualifier
= QualNone
| QualIndep ExamplePkgName
| QualSetup ExamplePkgName
| -- The two package names are the build target and the package containing the
-- setup script.
QualIndepSetup ExamplePkgName ExamplePkgName
| -- The two package names are the package depending on the exe and the
-- package containing the exe.
QualExe ExamplePkgName ExamplePkgName

-- ROMES:TODO: Add QualPrivateAlias?

-- | Whether to enable tests in all packages in a test case.
newtype EnableAllTests = EnableAllTests Bool
deriving (BooleanFlag)
Expand Down Expand Up @@ -680,6 +678,7 @@ exAvSrcPkg ex =

mkDirectD :: (ExamplePkgName, C.LibraryName, C.VersionRange, Maybe ExamplePrivateAlias) -> C.PrivateDependency
mkDirectD (dep, name, vr, Just alias) = C.PrivateDependency (C.PrivateAlias (fromString alias)) [C.Dependency (C.mkPackageName dep) vr (NonEmptySet.singleton name)]
mkDirectD (_, _, _, Nothing) = error "mkDirectD: private deps are never Nothing since we partition them by 'isJust' above"

mkFlagged
:: (C.LibraryVisibility -> C.BuildInfo -> a)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -321,12 +321,6 @@ runTest SolverTest{..} = askOption $ \(OptionShowSolverLog showSolverLog) ->
P.PackagePath
(P.IndependentComponent (C.mkPackageName s) C.ComponentSetup)
(P.QualToplevel)
{-
QualIndepSetup p s ->
P.PackagePath
(P.Independent $ C.mkPackageName p)
(P.QualSetup (C.mkPackageName s))
-}
QualExe p1 p2 ->
P.PackagePath
(P.IndependentBuildTool (C.mkPackageName p1) (C.mkPackageName p2))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,8 @@ import Distribution.Utils.ShortText (ShortText)

import Distribution.Client.Setup (defaultMaxBackjumps)

import Distribution.ModuleName
import Distribution.Types.Dependency (PrivateAlias (..))
import Distribution.Types.LibraryVisibility
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName
Expand Down Expand Up @@ -626,6 +628,8 @@ instance Hashable OptionalStanza
instance Hashable FlagName
instance Hashable PackageName
instance Hashable ShortText
instance Hashable ModuleName
instance Hashable PrivateAlias

deriving instance Generic (Variable pn)
deriving instance Generic (P.Qualified a)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,11 +25,11 @@ main = do
"show" -> do
s <- getContents
let a1 :: A = decode s
res <- return $ show a1
res = show a1
putStr (encode res)
"inc" -> do
s <- getContents
let a1 :: A = decode s
res <- return $ inc a1
res = inc a1
putStr (encode res)
_ -> error "Hook not yet implemented"
Original file line number Diff line number Diff line change
Expand Up @@ -68,14 +68,14 @@ revertA2 L2.B = L.B

hooks_show :: L.A -> HooksM String
hooks_show a = do
ver <- hooksVersion <$> ask
ver <- asks hooksVersion
case ver of
V01 -> readHooksExe "show" (convertA1 a)
V02 -> readHooksExe "show" (convertA2 a)

hooks_inc :: L.A -> HooksM L.A
hooks_inc a = do
ver <- hooksVersion <$> ask
ver <- asks hooksVersion
case ver of
V01 -> revertA1 <$> (readHooksExe "inc" (convertA1 a))
V02 -> revertA2 <$> (readHooksExe "inc" (convertA2 a))
Expand All @@ -88,7 +88,7 @@ hooks_inc a = do

readHooksExe :: (Binary a, Binary b) => String -> a -> HooksM b
readHooksExe hook args = do
exe <- hooksExe <$> ask
exe <- asks hooksExe
liftIO $ readHooksExe_ exe hook args

withForkWait :: IO () -> (IO () -> IO a) -> IO a
Expand Down
2 changes: 1 addition & 1 deletion cabal-testsuite/src/Test/Cabal/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1174,7 +1174,7 @@ findDependencyInStore :: String -- ^package name prefix
findDependencyInStore pkgName = do
storeDir <- testStoreDir <$> getTestEnv
liftIO $ do
storeDirForGhcVersion <- head <$> listDirectory storeDir
(storeDirForGhcVersion:_) <- listDirectory storeDir
packageDirs <- listDirectory (storeDir </> storeDirForGhcVersion)
-- Ideally, we should call 'hashedInstalledPackageId' from 'Distribution.Client.PackageHash'.
-- But 'PackageHashInputs', especially 'PackageHashConfigInputs', is too hard to construct.
Expand Down

0 comments on commit d4d94ac

Please sign in to comment.