1
- {-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings #-}
1
+ {-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings, TupleSections #-}
2
2
3
3
module Stack2nix
4
4
( doStack2nix
@@ -14,6 +14,7 @@ import Control.Monad.IO.Class (liftIO)
14
14
import Control.Monad (unless , forM )
15
15
import Extra (unlessM )
16
16
17
+ import qualified Data.Map as M (fromListWith , toList )
17
18
import System.FilePath ((<.>) , (</>) , takeDirectory , dropFileName )
18
19
import System.Directory (createDirectoryIfMissing , doesDirectoryExist , doesFileExist , getCurrentDirectory )
19
20
import System.IO (IOMode (.. ), openFile , hClose )
@@ -71,9 +72,15 @@ stack2nix args stack@(Stack resolver compiler pkgs pkgFlags ghcOpts) =
71
72
_mapAttrs_ = mkSym " mapAttrs"
72
73
_config_ = mkSym " config"
73
74
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)
74
81
return . mkNonRecSet $
75
82
[ " extras" $= (" hackage" ==> mkNonRecSet
76
- ([ " packages" $= mkNonRecSet (extraDeps <> packages ) ]
83
+ ([ " packages" $= mkNonRecSet (snd <$> allPackages ) ]
77
84
++ [ " compiler.version" $= fromString (quoted ver)
78
85
| (Just c) <- [compiler], let ver = filter (`elem` (" .0123456789" :: [Char ])) c]
79
86
++ [ " compiler.nix-name" $= fromString (quoted name)
@@ -94,14 +101,14 @@ stack2nix args stack@(Stack resolver compiler pkgs pkgFlags ghcOpts) =
94
101
--
95
102
-- { name.revision = hackage.name.version.revisions.default; }
96
103
--
97
- extraDeps2nix :: [Dependency ] -> [Binding NExpr ]
104
+ extraDeps2nix :: [Dependency ] -> [( T. Text , Binding NExpr ) ]
98
105
extraDeps2nix pkgs =
99
106
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" ) )
101
108
| (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) ))
103
110
| (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) )
105
112
| (PackageIdentifier pkg ver, (Just (Right revNo))) <- extraDeps ]
106
113
where parsePackageIdentifier :: String -> Maybe PackageIdentifier
107
114
parsePackageIdentifier = simpleParse
@@ -137,7 +144,7 @@ writeDoc file doc =
137
144
138
145
139
146
-- makeRelativeToCurrentDirectory
140
- packages2nix :: Args -> [Dependency ] -> IO [Binding NExpr ]
147
+ packages2nix :: Args -> [Dependency ] -> IO [( T. Text , Binding NExpr ) ]
141
148
packages2nix args pkgs =
142
149
do cwd <- getCurrentDirectory
143
150
fmap concat . forM pkgs $ \ case
@@ -151,7 +158,7 @@ packages2nix args pkgs =
151
158
in do createDirectoryIfMissing True (takeDirectory nixFile)
152
159
writeDoc nixFile =<<
153
160
prettyNix <$> cabal2nix True (argDetailLevel args) src cabalFile
154
- return $ fromString pkg $= mkPath False nix
161
+ return (fromString pkg, fromString pkg $= mkPath False nix)
155
162
(DVCS (Git url rev) _ subdirs) ->
156
163
fmap concat . forM subdirs $ \ subdir ->
157
164
do cacheHits <- liftIO $ cacheHits (argCacheFile args) url rev subdir
@@ -163,15 +170,15 @@ packages2nix args pkgs =
163
170
_ -> return []
164
171
hits ->
165
172
forM hits $ \ ( pkg, nix ) -> do
166
- return $ fromString pkg $= mkPath False nix
173
+ return (fromString pkg, fromString pkg $= mkPath False nix)
167
174
_ -> return []
168
175
where relPath = shortRelativePath (argOutputDir args) (dropFileName (argStackYaml args))
169
176
cabalFromPath
170
177
:: String -- URL
171
178
-> String -- Revision
172
179
-> FilePath -- Subdir
173
180
-> FilePath -- Local Directory
174
- -> MaybeT IO (String -> IO [Binding NExpr ])
181
+ -> MaybeT IO (String -> IO [( T. Text , Binding NExpr ) ])
175
182
cabalFromPath url rev subdir path = do
176
183
d <- liftIO $ doesDirectoryExist path
177
184
unless d $ fail (" not a directory: " ++ path)
@@ -188,7 +195,7 @@ packages2nix args pkgs =
188
195
writeDoc nixFile =<<
189
196
prettyNix <$> cabal2nix True (argDetailLevel args) src cabalFile
190
197
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)
192
199
193
200
defaultNixContents :: String
194
201
defaultNixContents = unlines
0 commit comments