Skip to content

Commit 58e0bd1

Browse files
authored
Detect duplicate packages in stack-to-nix (input-output-hk#75)
Fixes input-output-hk#389
1 parent 66774d0 commit 58e0bd1

File tree

2 files changed

+19
-11
lines changed

2 files changed

+19
-11
lines changed

nix-tools/lib/Stack2nix.hs

Lines changed: 18 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
{-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings #-}
1+
{-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings, TupleSections #-}
22

33
module Stack2nix
44
( doStack2nix
@@ -14,6 +14,7 @@ import Control.Monad.IO.Class (liftIO)
1414
import Control.Monad (unless, forM)
1515
import Extra (unlessM)
1616

17+
import qualified Data.Map as M (fromListWith, toList)
1718
import System.FilePath ((<.>), (</>), takeDirectory, dropFileName)
1819
import System.Directory (createDirectoryIfMissing, doesDirectoryExist, doesFileExist, getCurrentDirectory)
1920
import System.IO (IOMode(..), openFile, hClose)
@@ -71,9 +72,15 @@ stack2nix args stack@(Stack resolver compiler pkgs pkgFlags ghcOpts) =
7172
_mapAttrs_ = mkSym "mapAttrs"
7273
_config_ = mkSym "config"
7374
packages <- packages2nix args pkgs
75+
let allPackages = extraDeps <> packages
76+
allPackageNames = M.fromListWith (+) ((,1 :: Int) . fst <$> allPackages)
77+
duplicates = filter ((>1) . snd) (M.toList allPackageNames)
78+
unless (null duplicates) $
79+
error $ concat ((\(name, _) ->
80+
"Duplicate definitions for package " <> show name <> "\n") <$> duplicates)
7481
return . mkNonRecSet $
7582
[ "extras" $= ("hackage" ==> mkNonRecSet
76-
([ "packages" $= mkNonRecSet (extraDeps <> packages) ]
83+
([ "packages" $= mkNonRecSet (snd <$> allPackages) ]
7784
++ [ "compiler.version" $= fromString (quoted ver)
7885
| (Just c) <- [compiler], let ver = filter (`elem` (".0123456789" :: [Char])) c]
7986
++ [ "compiler.nix-name" $= fromString (quoted name)
@@ -94,14 +101,14 @@ stack2nix args stack@(Stack resolver compiler pkgs pkgFlags ghcOpts) =
94101
--
95102
-- { name.revision = hackage.name.version.revisions.default; }
96103
--
97-
extraDeps2nix :: [Dependency] -> [Binding NExpr]
104+
extraDeps2nix :: [Dependency] -> [(T.Text, Binding NExpr)]
98105
extraDeps2nix pkgs =
99106
let extraDeps = [(pkgId, info) | PkgIndex pkgId info <- pkgs]
100-
in [ (quoted (toText pkg)) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. "default")
107+
in [ (toText pkg, quoted (toText pkg) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. "default"))
101108
| (PackageIdentifier pkg ver, Nothing) <- extraDeps ]
102-
++ [ (quoted (toText pkg)) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. quoted (T.pack sha))
109+
++ [ (toText pkg, quoted (toText pkg) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. quoted (T.pack sha)))
103110
| (PackageIdentifier pkg ver, (Just (Left sha))) <- extraDeps ]
104-
++ [ (quoted (toText pkg)) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. toText revNo)
111+
++ [ (toText pkg, quoted (toText pkg) $= (mkSym "hackage" @. toText pkg @. quoted (toText ver) @. "revisions" @. toText revNo))
105112
| (PackageIdentifier pkg ver, (Just (Right revNo))) <- extraDeps ]
106113
where parsePackageIdentifier :: String -> Maybe PackageIdentifier
107114
parsePackageIdentifier = simpleParse
@@ -137,7 +144,7 @@ writeDoc file doc =
137144

138145

139146
-- makeRelativeToCurrentDirectory
140-
packages2nix :: Args -> [Dependency] -> IO [Binding NExpr]
147+
packages2nix :: Args -> [Dependency] -> IO [(T.Text, Binding NExpr)]
141148
packages2nix args pkgs =
142149
do cwd <- getCurrentDirectory
143150
fmap concat . forM pkgs $ \case
@@ -151,7 +158,7 @@ packages2nix args pkgs =
151158
in do createDirectoryIfMissing True (takeDirectory nixFile)
152159
writeDoc nixFile =<<
153160
prettyNix <$> cabal2nix True (argDetailLevel args) src cabalFile
154-
return $ fromString pkg $= mkPath False nix
161+
return (fromString pkg, fromString pkg $= mkPath False nix)
155162
(DVCS (Git url rev) _ subdirs) ->
156163
fmap concat . forM subdirs $ \subdir ->
157164
do cacheHits <- liftIO $ cacheHits (argCacheFile args) url rev subdir
@@ -163,15 +170,15 @@ packages2nix args pkgs =
163170
_ -> return []
164171
hits ->
165172
forM hits $ \( pkg, nix ) -> do
166-
return $ fromString pkg $= mkPath False nix
173+
return (fromString pkg, fromString pkg $= mkPath False nix)
167174
_ -> return []
168175
where relPath = shortRelativePath (argOutputDir args) (dropFileName (argStackYaml args))
169176
cabalFromPath
170177
:: String -- URL
171178
-> String -- Revision
172179
-> FilePath -- Subdir
173180
-> FilePath -- Local Directory
174-
-> MaybeT IO (String -> IO [Binding NExpr])
181+
-> MaybeT IO (String -> IO [(T.Text, Binding NExpr)])
175182
cabalFromPath url rev subdir path = do
176183
d <- liftIO $ doesDirectoryExist path
177184
unless d $ fail ("not a directory: " ++ path)
@@ -188,7 +195,7 @@ packages2nix args pkgs =
188195
writeDoc nixFile =<<
189196
prettyNix <$> cabal2nix True (argDetailLevel args) src cabalFile
190197
liftIO $ appendCache (argCacheFile args) url rev subdir sha256 pkg nix
191-
return $ fromString pkg $= mkPath False nix
198+
return (fromString pkg, fromString pkg $= mkPath False nix)
192199

193200
defaultNixContents :: String
194201
defaultNixContents = unlines

nix-tools/nix-tools.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ library
3535
, base16-bytestring
3636
, bytestring
3737
, cryptohash-sha256
38+
, containers
3839
, data-fix
3940
, deepseq
4041
, directory

0 commit comments

Comments
 (0)