Skip to content

Commit b036b8c

Browse files
rvlangerman
authored andcommitted
stack-to-nix: Add configurable output directory
1 parent a3d38e9 commit b036b8c

File tree

3 files changed

+48
-27
lines changed

3 files changed

+48
-27
lines changed

stack2nix/Main.hs

Lines changed: 3 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,7 @@
1-
{-# LANGUAGE RecordWildCards #-}
21
module Main where
32

4-
import Nix.Pretty (prettyNix)
5-
6-
import Stack2nix
7-
import Stack2nix.CLI
8-
9-
--------------------------------------------------------------------------------
3+
import Stack2nix (doStack2nix)
4+
import Stack2nix.CLI (parseStack2nixArgs)
105

116
main :: IO ()
12-
main = print . prettyNix =<< stackexpr =<< parseStack2nixArgs
7+
main = parseStack2nixArgs >>= doStack2nix

stack2nix/Stack2nix.hs

Lines changed: 38 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,9 @@
11
{-# LANGUAGE LambdaCase, RecordWildCards, OverloadedStrings #-}
22

33
module Stack2nix
4-
( stack2nix
4+
( doStack2nix
55
, stackexpr
6+
, stack2nix
67
) where
78

89
import qualified Data.Text as T
@@ -11,9 +12,10 @@ import Data.String (fromString)
1112
import Control.Monad.Trans.Maybe
1213
import Control.Monad.IO.Class (liftIO)
1314
import Control.Monad (unless, forM)
15+
import Extra (unlessM)
1416

1517
import System.FilePath ((<.>), (</>), takeDirectory, dropFileName)
16-
import System.Directory (createDirectoryIfMissing, doesDirectoryExist, getCurrentDirectory)
18+
import System.Directory (createDirectoryIfMissing, doesDirectoryExist, doesFileExist, getCurrentDirectory)
1719
import System.IO (IOMode(..), openFile, hClose)
1820
import Data.Yaml (decodeFileEither)
1921

@@ -37,9 +39,18 @@ import Stack2nix.Project
3739
import Stack2nix.Stack (Stack(..), Dependency(..), Location(..))
3840
import Stack2nix.External.Resolve
3941

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+
4051
stackexpr :: Args -> IO NExpr
4152
stackexpr args =
42-
do evalue <- decodeFileEither (stackFile args)
53+
do evalue <- decodeFileEither (argStackYaml args)
4354
case evalue of
4455
Left e -> error (show e)
4556
Right value -> stack2nix args
@@ -103,19 +114,19 @@ packages2nix args (Stack _ _ pkgs) =
103114
do cwd <- getCurrentDirectory
104115
fmap (mkNonRecSet . concat) . forM pkgs $ \case
105116
(LocalPath folder) ->
106-
do cabalFiles <- findCabalFiles (dropFileName (stackFile args) </> folder)
117+
do cabalFiles <- findCabalFiles (dropFileName (argStackYaml args) </> folder)
107118
forM cabalFiles $ \cabalFile ->
108119
let pkg = cabalFilePkgName cabalFile
109-
nix = ".stack.nix" </> pkg <.> "nix"
110-
nixFile = outputPath args </> nix
120+
nix = pkg <.> "nix"
121+
nixFile = argOutputDir args </> nix
111122
src = Just . C2N.Path $ relPath </> ".." </> folder
112123
in do createDirectoryIfMissing True (takeDirectory nixFile)
113124
writeDoc nixFile =<<
114125
prettyNix <$> cabal2nix src cabalFile
115126
return $ fromString pkg $= mkPath False nix
116127
(DVCS (Git url rev) subdirs) ->
117128
fmap concat . forM subdirs $ \subdir ->
118-
do cacheHits <- liftIO $ cacheHits cacheFile url rev subdir
129+
do cacheHits <- liftIO $ cacheHits (argCacheFile args) url rev subdir
119130
case cacheHits of
120131
[] -> do
121132
fetch (\dir -> cabalFromPath url rev subdir $ dir </> subdir)
@@ -126,7 +137,7 @@ packages2nix args (Stack _ _ pkgs) =
126137
forM hits $ \( pkg, nix ) -> do
127138
return $ fromString pkg $= mkPath False nix
128139
_ -> return []
129-
where relPath = shortRelativePath (outputPath args) (dropFileName (stackFile args))
140+
where relPath = shortRelativePath (argOutputDir args) (dropFileName (argStackYaml args))
130141
cabalFromPath
131142
:: String -- URL
132143
-> String -- Revision
@@ -140,16 +151,30 @@ packages2nix args (Stack _ _ pkgs) =
140151
return $ \sha256 ->
141152
forM cabalFiles $ \cabalFile -> do
142153
let pkg = cabalFilePkgName cabalFile
143-
nix = ".stack.nix" </> pkg <.> "nix"
144-
nixFile = outputPath args </> nix
154+
nix = pkg <.> "nix"
155+
nixFile = argOutputDir args </> nix
145156
subdir' = if subdir == "." then Nothing
146157
else Just subdir
147158
src = Just $ C2N.Git url rev (Just sha256) subdir'
148159
createDirectoryIfMissing True (takeDirectory nixFile)
149160
writeDoc nixFile =<<
150161
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
152163
return $ fromString pkg $= mkPath False nix
153164

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+
]

stack2nix/Stack2nix/CLI.hs

Lines changed: 7 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,20 +10,21 @@ import Data.Semigroup ((<>))
1010
--------------------------------------------------------------------------------
1111
-- CLI Arguments
1212
data Args = Args
13-
{ outputPath :: FilePath
14-
, stackFile :: FilePath
13+
{ argOutputDir :: FilePath
14+
, argStackYaml :: FilePath
15+
, argCacheFile :: FilePath
1516
} deriving Show
1617

1718
-- Argument Parser
1819
args :: Parser Args
1920
args = Args
20-
<$> strOption ( long "output" <> short 'o' <> metavar "DIR" <> value "." <> help "Generate output in DIR" )
21-
<*> argument str ( metavar "stack.yaml" )
22-
21+
<$> strOption ( long "output" <> short 'o' <> metavar "DIR" <> help "Generate output in DIR" )
22+
<*> strOption ( long "stack-yaml" <> value "stack.yaml" <> showDefault <> metavar "FILE" <> help "Override project stack.yaml" )
23+
<*> strOption ( long "cache" <> value ".stack-to-nix.cache" <> showDefault <> metavar "FILE" <> help "Dependency cache file" )
2324

2425
parseStack2nixArgs :: IO Args
2526
parseStack2nixArgs = execParser opts
2627
where opts = info (args <**> helper)
2728
( fullDesc
28-
<> progDesc "Generate a nix expression from a stack.yaml file"
29+
<> progDesc "Generate a Nix expression for a Haskell package using Stack"
2930
<> header "stack-to-nix - a stack to nix converter" )

0 commit comments

Comments
 (0)