Skip to content

Commit

Permalink
Add tests
Browse files Browse the repository at this point in the history
  • Loading branch information
9999years committed Nov 18, 2024
1 parent 5181892 commit 9492b41
Show file tree
Hide file tree
Showing 24 changed files with 658 additions and 215 deletions.
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveDataTypeable #-}

module Distribution.Solver.Types.SourcePackage
( PackageDescriptionOverride
, SourcePackage(..)
Expand All @@ -25,7 +27,7 @@ data SourcePackage loc = SourcePackage
, srcpkgSource :: loc
, srcpkgDescrOverride :: PackageDescriptionOverride
}
deriving (Eq, Show, Generic, Typeable)
deriving (Eq, Show, Functor, Generic, Typeable)

instance Binary loc => Binary (SourcePackage loc)
instance Structured loc => Structured (SourcePackage loc)
Expand Down
3 changes: 1 addition & 2 deletions cabal-install/src/Distribution/Client/CmdSdist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -150,7 +150,6 @@ import System.FilePath
, (<.>)
, (</>)
)
import Text.PrettyPrint (text)

-------------------------------------------------------------------------------
-- Command
Expand Down Expand Up @@ -286,7 +285,7 @@ sdistAction (pf@ProjectFlags{..}, SdistFlags{..}) targetStrings globalFlags = do
dieWithException verbosity $
SdistActionException $
map
(prettyShow . fmap (text . renderTargetProblem))
(renderTargetProblem . constraintPackage)
errs
Right pkgs
| length pkgs > 1
Expand Down
10 changes: 5 additions & 5 deletions cabal-install/src/Distribution/Client/ProjectConfig/Legacy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1286,23 +1286,23 @@ legacyProjectConfigFieldDescrs :: ConstraintSource -> [FieldDescr LegacyProjectC
legacyProjectConfigFieldDescrs constraintSrc =
[ newLineListField
"packages"
(pretty . fmap (Disp.text . renderPackageLocationToken))
(Disp.text . renderPackageLocationToken . constraintPackage)
( (\pkg -> WithConstraintSource{constraintPackage = pkg, constraintConstraint = constraintSrc})
`fmap` parsePackageLocationTokenQ
)
legacyPackages
(\v flags -> flags{legacyPackages = v})
, newLineListField
"optional-packages"
(pretty . fmap (Disp.text . renderPackageLocationToken))
(Disp.text . renderPackageLocationToken . constraintPackage)
( (\pkg -> WithConstraintSource{constraintPackage = pkg, constraintConstraint = constraintSrc})
`fmap` parsePackageLocationTokenQ
)
legacyPackagesOptional
(\v flags -> flags{legacyPackagesOptional = v})
, commaNewLineListFieldParsec
"extra-packages"
pretty
(pretty . constraintPackage)
( (\pkg -> WithConstraintSource{constraintPackage = pkg, constraintConstraint = constraintSrc})
`fmap` parsec
)
Expand Down Expand Up @@ -1424,15 +1424,15 @@ legacySharedConfigFieldDescrs constraintSrc =
. addFields
[ commaNewLineListFieldParsec
"constraints"
pretty
(pretty . constraintPackage)
( (\constraint -> WithConstraintSource{constraintPackage = constraint, constraintConstraint = constraintSrc})
`fmap` parsec
)
configExConstraints
(\v conf -> conf{configExConstraints = v})
, commaNewLineListFieldParsec
"preferences"
pretty
(pretty . constraintPackage)
( (\preference -> WithConstraintSource{constraintPackage = preference, constraintConstraint = constraintSrc})
`fmap` parsec
)
Expand Down
Loading

0 comments on commit 9492b41

Please sign in to comment.