1
1
{-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings #-}
2
2
3
3
module Stack2nix
4
- ( stack2nix
4
+ ( doStack2nix
5
5
, stackexpr
6
+ , stack2nix
6
7
) where
7
8
8
9
import qualified Data.Text as T
@@ -11,9 +12,10 @@ import Data.String (fromString)
11
12
import Control.Monad.Trans.Maybe
12
13
import Control.Monad.IO.Class (liftIO )
13
14
import Control.Monad (unless , forM )
15
+ import Extra (unlessM )
14
16
15
17
import System.FilePath ((<.>) , (</>) , takeDirectory , dropFileName )
16
- import System.Directory (createDirectoryIfMissing , doesDirectoryExist , getCurrentDirectory )
18
+ import System.Directory (createDirectoryIfMissing , doesDirectoryExist , doesFileExist , getCurrentDirectory )
17
19
import System.IO (IOMode (.. ), openFile , hClose )
18
20
import Data.Yaml (decodeFileEither )
19
21
@@ -37,9 +39,18 @@ import Stack2nix.Project
37
39
import Stack2nix.Stack (Stack (.. ), Dependency (.. ), Location (.. ))
38
40
import Stack2nix.External.Resolve
39
41
42
+ doStack2nix :: Args -> IO ()
43
+ doStack2nix args = do
44
+ let pkgsNix = argOutputDir args </> " pkgs.nix"
45
+ defaultNix = argOutputDir args </> " default.nix"
46
+ pkgs <- stackexpr args
47
+ writeDoc pkgsNix (prettyNix pkgs)
48
+ unlessM (doesFileExist defaultNix) $ do
49
+ writeFile defaultNix defaultNixContents
50
+
40
51
stackexpr :: Args -> IO NExpr
41
52
stackexpr args =
42
- do evalue <- decodeFileEither (stackFile args)
53
+ do evalue <- decodeFileEither (argStackYaml args)
43
54
case evalue of
44
55
Left e -> error (show e)
45
56
Right value -> stack2nix args
@@ -103,19 +114,19 @@ packages2nix args (Stack _ _ pkgs) =
103
114
do cwd <- getCurrentDirectory
104
115
fmap (mkNonRecSet . concat ) . forM pkgs $ \ case
105
116
(LocalPath folder) ->
106
- do cabalFiles <- findCabalFiles (dropFileName (stackFile args) </> folder)
117
+ do cabalFiles <- findCabalFiles (dropFileName (argStackYaml args) </> folder)
107
118
forM cabalFiles $ \ cabalFile ->
108
119
let pkg = cabalFilePkgName cabalFile
109
- nix = " .stack.nix " </> pkg <.> " nix"
110
- nixFile = outputPath args </> nix
120
+ nix = pkg <.> " nix"
121
+ nixFile = argOutputDir args </> nix
111
122
src = Just . C2N. Path $ relPath </> " .." </> folder
112
123
in do createDirectoryIfMissing True (takeDirectory nixFile)
113
124
writeDoc nixFile =<<
114
125
prettyNix <$> cabal2nix src cabalFile
115
126
return $ fromString pkg $= mkPath False nix
116
127
(DVCS (Git url rev) subdirs) ->
117
128
fmap concat . forM subdirs $ \ subdir ->
118
- do cacheHits <- liftIO $ cacheHits cacheFile url rev subdir
129
+ do cacheHits <- liftIO $ cacheHits (argCacheFile args) url rev subdir
119
130
case cacheHits of
120
131
[] -> do
121
132
fetch (\ dir -> cabalFromPath url rev subdir $ dir </> subdir)
@@ -126,7 +137,7 @@ packages2nix args (Stack _ _ pkgs) =
126
137
forM hits $ \ ( pkg, nix ) -> do
127
138
return $ fromString pkg $= mkPath False nix
128
139
_ -> return []
129
- where relPath = shortRelativePath (outputPath args) (dropFileName (stackFile args))
140
+ where relPath = shortRelativePath (argOutputDir args) (dropFileName (argStackYaml args))
130
141
cabalFromPath
131
142
:: String -- URL
132
143
-> String -- Revision
@@ -140,16 +151,30 @@ packages2nix args (Stack _ _ pkgs) =
140
151
return $ \ sha256 ->
141
152
forM cabalFiles $ \ cabalFile -> do
142
153
let pkg = cabalFilePkgName cabalFile
143
- nix = " .stack.nix " </> pkg <.> " nix"
144
- nixFile = outputPath args </> nix
154
+ nix = pkg <.> " nix"
155
+ nixFile = argOutputDir args </> nix
145
156
subdir' = if subdir == " ." then Nothing
146
157
else Just subdir
147
158
src = Just $ C2N. Git url rev (Just sha256) subdir'
148
159
createDirectoryIfMissing True (takeDirectory nixFile)
149
160
writeDoc nixFile =<<
150
161
prettyNix <$> cabal2nix src cabalFile
151
- liftIO $ appendCache cacheFile url rev subdir sha256 pkg nix
162
+ liftIO $ appendCache (argCacheFile args) url rev subdir sha256 pkg nix
152
163
return $ fromString pkg $= mkPath False nix
153
164
154
- cacheFile :: FilePath
155
- cacheFile = " .stack-to-nix.cache"
165
+ defaultNixContents :: String
166
+ defaultNixContents = unlines
167
+ [ " { pkgs ? import <nixpkgs> {} }:"
168
+ , " "
169
+ , " let"
170
+ , " haskell = import (builtins.fetchTarball https://github.com/input-output-hk/haskell.nix/archive/master.tar.gz) { inherit pkgs; };"
171
+ , " "
172
+ , " pkgSet = haskell.mkStackPkgSet {"
173
+ , " stack-pkgs = import ./pkgs.nix;"
174
+ , " pkg-def-overlays = [];"
175
+ , " modules = [];"
176
+ , " };"
177
+ , " "
178
+ , " in"
179
+ , " pkgSet.config.hsPkgs"
180
+ ]
0 commit comments