Skip to content

Commit

Permalink
Represent dependencies as a Map from names to versions
Browse files Browse the repository at this point in the history
  • Loading branch information
sol committed Sep 23, 2017
1 parent 61d5bc2 commit 4bd0f7b
Show file tree
Hide file tree
Showing 4 changed files with 74 additions and 45 deletions.
41 changes: 25 additions & 16 deletions src/Hpack/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,7 @@ module Hpack.Config (
, package
, section
, Package(..)
, Dependencies
, Dependency(..)
, DependencyVersion(..)
, SourceDependency(..)
Expand Down Expand Up @@ -54,6 +55,7 @@ import qualified Data.Map.Lazy as Map
import qualified Data.HashMap.Lazy as HashMap
import Data.List.Compat (nub, (\\), sortBy, isPrefixOf)
import Data.Maybe
import Data.Monoid
import Data.Ord
import Data.String
import Data.Text (Text)
Expand Down Expand Up @@ -106,24 +108,26 @@ renamePackage name p@Package{..} = p {
}

renameDependencies :: String -> String -> Section a -> Section a
renameDependencies old new sect@Section{..} = sect {sectionDependencies = map rename sectionDependencies, sectionConditionals = map renameConditional sectionConditionals}
renameDependencies old new sect@Section{..} = sect {sectionDependencies = (Map.fromList . map rename . Map.toList) sectionDependencies, sectionConditionals = map renameConditional sectionConditionals}
where
rename dep
| dependencyName dep == old = dep {dependencyName = new}
rename dep@(name, version)
| name == old = (new, version)
| otherwise = dep

renameConditional :: Conditional -> Conditional
renameConditional (Conditional condition then_ else_) = Conditional condition (renameDependencies old new then_) (renameDependencies old new <$> else_)

packageDependencies :: Package -> [Dependency]
packageDependencies Package{..} = nub . sortBy (comparing (lexicographically . dependencyName)) $
(concatMap sectionDependencies packageExecutables)
++ (concatMap sectionDependencies packageTests)
++ (concatMap sectionDependencies packageBenchmarks)
++ maybe [] sectionDependencies packageLibrary
(concatMap deps packageExecutables)
++ (concatMap deps packageTests)
++ (concatMap deps packageBenchmarks)
++ maybe [] deps packageLibrary
where
deps xs = [Dependency name version | (name, version) <- (Map.toList . sectionDependencies) xs]

section :: a -> Section a
section a = Section a [] [] [] [] [] [] [] [] [] [] [] [] [] [] [] [] Nothing [] []
section a = Section a [] mempty [] [] [] [] [] [] [] [] [] [] [] [] [] [] Nothing [] mempty

packageConfig :: FilePath
packageConfig = "package.yaml"
Expand Down Expand Up @@ -227,6 +231,9 @@ instance HasFieldNames ExecutableSection
instance FromJSON ExecutableSection where
parseJSON = genericParseJSON_

dependenciesFromList :: Maybe (List Dependency) -> Map String DependencyVersion
dependenciesFromList xs = Map.fromList [(name, version) | Dependency name version <- fromMaybeList xs]

data CommonOptions = CommonOptions {
commonOptionsSourceDirs :: Maybe (List FilePath)
, commonOptionsDependencies :: Maybe (List Dependency)
Expand Down Expand Up @@ -413,6 +420,8 @@ instance FromJSON Dependency where
subdir :: Parser (Maybe FilePath)
subdir = o .:? "subdir"

type Dependencies = Map String DependencyVersion

data DependencyVersion =
AnyVersion
| VersionRange String
Expand Down Expand Up @@ -453,7 +462,7 @@ data Package = Package {
} deriving (Eq, Show)

data CustomSetup = CustomSetup {
customSetupDependencies :: [Dependency]
customSetupDependencies :: Dependencies
} deriving (Eq, Show)

data Library = Library {
Expand All @@ -472,7 +481,7 @@ data Executable = Executable {
data Section a = Section {
sectionData :: a
, sectionSourceDirs :: [FilePath]
, sectionDependencies :: [Dependency]
, sectionDependencies :: Dependencies
, sectionDefaultExtensions :: [String]
, sectionOtherExtensions :: [String]
, sectionGhcOptions :: [GhcOption]
Expand All @@ -489,7 +498,7 @@ data Section a = Section {
, sectionLdOptions :: [LdOption]
, sectionBuildable :: Maybe Bool
, sectionConditionals :: [Conditional]
, sectionBuildTools :: [Dependency]
, sectionBuildTools :: Dependencies
} deriving (Eq, Show, Functor, Foldable, Traversable)

data Conditional = Conditional {
Expand Down Expand Up @@ -721,7 +730,7 @@ expandForeignSources dir sect = do

toCustomSetup :: CustomSetupSection -> CustomSetup
toCustomSetup CustomSetupSection{..} = CustomSetup
{ customSetupDependencies = fromMaybeList customSetupSectionDependencies }
{ customSetupDependencies = dependenciesFromList customSetupSectionDependencies }

toLibrary :: FilePath -> String -> Section global -> Section LibrarySection -> IO ([String], Section Library)
toLibrary dir name globalOptions library = traverse fromLibrarySection sect >>= expandForeignSources dir
Expand Down Expand Up @@ -783,9 +792,9 @@ mergeSections globalOptions options
, sectionInstallIncludes = sectionInstallIncludes globalOptions ++ sectionInstallIncludes options
, sectionLdOptions = sectionLdOptions globalOptions ++ sectionLdOptions options
, sectionBuildable = sectionBuildable options <|> sectionBuildable globalOptions
, sectionDependencies = sectionDependencies globalOptions ++ sectionDependencies options
, sectionDependencies = sectionDependencies options <> sectionDependencies globalOptions
, sectionConditionals = sectionConditionals globalOptions ++ sectionConditionals options
, sectionBuildTools = sectionBuildTools globalOptions ++ sectionBuildTools options
, sectionBuildTools = sectionBuildTools options <> sectionBuildTools globalOptions
}

toSection :: a -> CommonOptions -> ([FieldName], Section a)
Expand All @@ -809,9 +818,9 @@ toSection a CommonOptions{..}
, sectionInstallIncludes = fromMaybeList commonOptionsInstallIncludes
, sectionLdOptions = fromMaybeList commonOptionsLdOptions
, sectionBuildable = commonOptionsBuildable
, sectionDependencies = fromMaybeList commonOptionsDependencies
, sectionDependencies = dependenciesFromList commonOptionsDependencies
, sectionConditionals = conditionals
, sectionBuildTools = fromMaybeList commonOptionsBuildTools
, sectionBuildTools = dependenciesFromList commonOptionsBuildTools
}
)
where
Expand Down
9 changes: 5 additions & 4 deletions src/Hpack/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Data.Maybe
import Data.List.Compat
import System.Exit.Compat
import System.FilePath
import qualified Data.Map.Lazy as Map

import Hpack.Util
import Hpack.Config
Expand Down Expand Up @@ -265,11 +266,11 @@ renderOtherModules = Field "other-modules" . LineSeparatedList
renderReexportedModules :: [String] -> Element
renderReexportedModules = Field "reexported-modules" . LineSeparatedList

renderDependencies :: String -> [Dependency] -> Element
renderDependencies name = Field name . CommaSeparatedList . map renderDependency
renderDependencies :: String -> Dependencies -> Element
renderDependencies name = Field name . CommaSeparatedList . map renderDependency . Map.toList

renderDependency :: Dependency -> String
renderDependency (Dependency name version) = name ++ v
renderDependency :: (String, DependencyVersion) -> String
renderDependency (name, version) = name ++ v
where
v = case version of
AnyVersion -> ""
Expand Down
49 changes: 33 additions & 16 deletions test/Hpack/ConfigSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module Hpack.ConfigSpec (

, package
, executable
, deps
) where

import Helper
Expand All @@ -19,6 +20,7 @@ import System.Directory (createDirectory)
import Data.Yaml
import Data.Either.Compat
import Data.String
import qualified Data.Map.Lazy as Map

import Hpack.Util
import Hpack.Config hiding (package)
Expand All @@ -27,6 +29,9 @@ import qualified Hpack.Config as Config
instance IsString Dependency where
fromString name = Dependency name AnyVersion

deps :: [String] -> Dependencies
deps = Map.fromList . map (flip (,) AnyVersion)

package :: Package
package = Config.package "foo" "0.0.0"

Expand Down Expand Up @@ -64,11 +69,11 @@ spec = do
renamePackage "bar" package `shouldBe` package {packageName = "bar"}

it "renames dependencies on self" $ do
let packageWithExecutable dependencies = package {packageExecutables = [(section $ executable "main" "Main.hs") {sectionDependencies = dependencies}]}
let packageWithExecutable dependencies = package {packageExecutables = [(section $ executable "main" "Main.hs") {sectionDependencies = deps dependencies}]}
renamePackage "bar" (packageWithExecutable ["foo"]) `shouldBe` (packageWithExecutable ["bar"]) {packageName = "bar"}

describe "renameDependencies" $ do
let sectionWithDeps dependencies = (section ()) {sectionDependencies = dependencies}
let sectionWithDeps dependencies = (section ()) {sectionDependencies = deps dependencies}

it "renames dependencies" $ do
renameDependencies "bar" "baz" (sectionWithDeps ["foo", "bar"]) `shouldBe` sectionWithDeps ["foo", "baz"]
Expand All @@ -92,7 +97,7 @@ spec = do
dependencies: hpack
|]
captureUnknownFieldsValue <$> decodeEither input
`shouldBe` Right (section Empty){sectionDependencies = ["hpack"]}
`shouldBe` Right (section Empty){sectionDependencies = deps ["hpack"]}

it "accepts includes-dirs" $ do
let input = [i|
Expand Down Expand Up @@ -157,7 +162,7 @@ spec = do
|]
conditionals = [
Conditional "os(windows)"
(section ()){sectionDependencies = ["Win32"]}
(section ()){sectionDependencies = deps ["Win32"]}
Nothing
]
captureUnknownFieldsValue <$> decodeEither input
Expand Down Expand Up @@ -190,8 +195,8 @@ spec = do
|]
conditionals = [
Conditional "os(windows)"
(section ()){sectionDependencies = ["Win32"]}
(Just (section ()){sectionDependencies = ["unix"]})
(section ()){sectionDependencies = deps ["Win32"]}
(Just (section ()){sectionDependencies = deps ["unix"]})
]
r :: Either String (Section Empty)
r = captureUnknownFieldsValue <$> decodeEither input
Expand Down Expand Up @@ -738,9 +743,9 @@ spec = do
- foo > 1.0
- bar == 2.0
|]
(packageCustomSetup >>> fmap customSetupDependencies >>> (`shouldBe` Just [
Dependency "foo" (VersionRange ">1.0")
, Dependency "bar" (VersionRange "==2.0")
(packageCustomSetup >>> fmap customSetupDependencies >>> fmap Map.toList >>> (`shouldBe` Just [
("bar", VersionRange "==2.0")
, ("foo", VersionRange ">1.0")
])
)

Expand Down Expand Up @@ -784,7 +789,7 @@ spec = do
- alex
- happy
|]
(packageLibrary >>> (`shouldBe` Just (section library) {sectionBuildTools = ["alex", "happy"]}))
(packageLibrary >>> (`shouldBe` Just (section library) {sectionBuildTools = deps ["alex", "happy"]}))

it "accepts default-extensions" $ do
withPackageConfig_ [i|
Expand Down Expand Up @@ -820,7 +825,7 @@ spec = do
- happy
library: {}
|]
(packageLibrary >>> (`shouldBe` Just (section library) {sectionBuildTools = ["alex", "happy"]}))
(packageLibrary >>> (`shouldBe` Just (section library) {sectionBuildTools = deps ["alex", "happy"]}))

it "accepts c-sources" $ do
withPackageConfig [i|
Expand Down Expand Up @@ -1025,7 +1030,7 @@ spec = do
- alex
- happy
|]
(packageExecutables >>> (`shouldBe` [(section $ executable "foo" "Main.hs") {sectionBuildTools = ["alex", "happy"]}]))
(packageExecutables >>> (`shouldBe` [(section $ executable "foo" "Main.hs") {sectionBuildTools = deps ["alex", "happy"]}]))

it "accepts global source-dirs" $ do
withPackageConfig_ [i|
Expand All @@ -1047,7 +1052,7 @@ spec = do
foo:
main: Main.hs
|]
(packageExecutables >>> (`shouldBe` [(section $ executable "foo" "Main.hs") {sectionBuildTools = ["alex", "happy"]}]))
(packageExecutables >>> (`shouldBe` [(section $ executable "foo" "Main.hs") {sectionBuildTools = deps ["alex", "happy"]}]))

it "infers other-modules" $ do
withPackageConfig [i|
Expand Down Expand Up @@ -1237,7 +1242,7 @@ spec = do
main: test/Spec.hs
dependencies: hspec
|]
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = ["hspec"]}]})
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = deps ["hspec"]}]})

it "accepts list of dependencies" $ do
withPackageConfig_ [i|
Expand All @@ -1248,7 +1253,7 @@ spec = do
- hspec
- QuickCheck
|]
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = ["hspec", "QuickCheck"]}]})
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = deps ["hspec", "QuickCheck"]}]})

context "when both global and section specific dependencies are specified" $ do
it "combines dependencies" $ do
Expand All @@ -1261,7 +1266,19 @@ spec = do
main: test/Spec.hs
dependencies: hspec
|]
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = ["base", "hspec"]}]})
(`shouldBe` package {packageTests = [(section $ executable "spec" "test/Spec.hs") {sectionDependencies = deps ["base", "hspec"]}]})

it "gives section specific dependencies precedence" $ do
withPackageConfig_ [i|
dependencies:
- base

tests:
spec:
main: test/Spec.hs
dependencies: base >= 2
|]
(packageTests >>> map (Map.toList . sectionDependencies) >>> (`shouldBe` [[("base", VersionRange ">=2")]]))

context "when a specified source directory does not exist" $ do
it "warns" $ do
Expand Down
20 changes: 11 additions & 9 deletions test/Hpack/RunSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ module Hpack.RunSpec (spec) where

import Helper
import Data.List.Compat
import qualified Data.Map.Lazy as Map

import Hpack.ConfigSpec hiding (spec)
import Hpack.Config hiding (package)
Expand Down Expand Up @@ -128,7 +129,7 @@ spec = do
context "when rendering custom-setup section" $ do
it "includes setup-depends" $ do
let setup = CustomSetup
{ customSetupDependencies = ["foo >1.0", "bar ==2.0"] }
{ customSetupDependencies = deps ["foo", "bar"] }
renderPackage_ package {packageCustomSetup = Just setup} `shouldBe` unlines [
"name: foo"
, "version: 0.0.0"
Expand All @@ -137,8 +138,8 @@ spec = do
, ""
, "custom-setup"
, " setup-depends:"
, " foo >1.0"
, " , bar ==2.0"
, " bar"
, " , foo"
]

context "when rendering library section" $ do
Expand Down Expand Up @@ -225,7 +226,8 @@ spec = do

context "when rendering executable section" $ do
it "includes dependencies" $ do
renderPackage_ package {packageExecutables = [(section $ executable "foo" "Main.hs") {sectionDependencies = [Dependency "foo" (VersionRange "== 0.1.0"), Dependency "bar" AnyVersion]}]} `shouldBe` unlines [
renderPackage_ package {packageExecutables = [(section $ executable "foo" "Main.hs") {sectionDependencies = Map.fromList
[("foo", VersionRange "== 0.1.0"), ("bar", AnyVersion)]}]} `shouldBe` unlines [
"name: foo"
, "version: 0.0.0"
, "build-type: Simple"
Expand All @@ -234,8 +236,8 @@ spec = do
, "executable foo"
, " main-is: Main.hs"
, " build-depends:"
, " foo == 0.1.0"
, " , bar"
, " bar"
, " , foo == 0.1.0"
, " default-language: Haskell2010"
]

Expand Down Expand Up @@ -267,15 +269,15 @@ spec = do

describe "renderConditional" $ do
it "renders conditionals" $ do
let conditional = Conditional "os(windows)" (section ()) {sectionDependencies = ["Win32"]} Nothing
let conditional = Conditional "os(windows)" (section ()) {sectionDependencies = deps ["Win32"]} Nothing
render defaultRenderSettings 0 (renderConditional conditional) `shouldBe` [
"if os(windows)"
, " build-depends:"
, " Win32"
]

it "renders conditionals with else-branch" $ do
let conditional = Conditional "os(windows)" (section ()) {sectionDependencies = ["Win32"]} (Just $ (section ()) {sectionDependencies = ["unix"]})
let conditional = Conditional "os(windows)" (section ()) {sectionDependencies = deps ["Win32"]} (Just $ (section ()) {sectionDependencies = deps ["unix"]})
render defaultRenderSettings 0 (renderConditional conditional) `shouldBe` [
"if os(windows)"
, " build-depends:"
Expand All @@ -287,7 +289,7 @@ spec = do

it "renders nested conditionals" $ do
let conditional = Conditional "arch(i386)" (section ()) {sectionGhcOptions = ["-threaded"], sectionConditionals = [innerConditional]} Nothing
innerConditional = Conditional "os(windows)" (section ()) {sectionDependencies = ["Win32"]} Nothing
innerConditional = Conditional "os(windows)" (section ()) {sectionDependencies = deps ["Win32"]} Nothing
render defaultRenderSettings 0 (renderConditional conditional) `shouldBe` [
"if arch(i386)"
, " ghc-options: -threaded"
Expand Down

0 comments on commit 4bd0f7b

Please sign in to comment.