Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 0 additions & 2 deletions src/Stack2nix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,10 +29,8 @@ stack2nix args@Args{..} = do
ensureExecutableExists "cabal" "cabal-install"
ensureExecutableExists "git" "git"
ensureExecutableExists "nix-prefetch-git" "nix-prefetch-scripts"
ensureExecutableExists "ghc" "haskell.compiler.ghc802"
assertMinVer "git" "2"
assertMinVer "cabal" "2"
assertMinVer "ghc" "8.0"
updateCabalPackageIndex
-- cwd <- getCurrentDirectory
-- let projRoot = if isAbsolute argUri then argUri else cwd </> argUri
Expand Down
37 changes: 28 additions & 9 deletions src/Stack2nix/External/Stack.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DataKinds #-}

module Stack2nix.External.Stack
( PackageRef(..), runPlan
Expand All @@ -15,11 +16,15 @@ import Stack.Build.Source (loadSourceMapFull)
import Stack.Build.Target (NeedTargets (..))
import Stack.Options.BuildParser
import Stack.Options.GlobalParser
import Stack.Config
import Path (parseAbsFile)
import Stack.Types.Compiler (CVType(..), CompilerVersion, getGhcVersion)
import Stack.Options.Utils (GlobalOptsContext (..))
import Stack.Prelude hiding (mapConcurrently, logDebug)
import Stack.Prelude hiding (logDebug)
import Stack.Types.BuildPlan (Repo (..), PackageLocation (..))
import Stack.Runners (withBuildConfig)
import Stack.Runners (withBuildConfig, loadCompilerVersion)
import Stack.Types.Config
import Stack.Types.Runner
import Stack.Types.Config.Build (BuildCommand (..))
import Stack.Types.Nix
import Stack.Types.Package (PackageSource (..), lpPackage,
Expand All @@ -30,16 +35,14 @@ import Stack.Types.PackageIdentifier (PackageIdentifier (..),
packageIdentifierString,
PackageIdentifierRevision (..))
import Stack2nix.External.Cabal2nix (cabal2nix)
import Stack2nix.External.Util (failHard, runCmd)
import Stack2nix.Render (render)
import Stack2nix.Types (Args (..))
import Stack2nix.Util (mapPool, logDebug)
import Stack2nix.Util (mapPool, logDebug, ensureExecutable)
import System.Directory (canonicalizePath,
createDirectoryIfMissing,
getCurrentDirectory,
makeRelativeToCurrentDirectory)
import System.FilePath (makeRelative, (</>))
import System.IO (hPutStrLn, stderr)
import qualified Distribution.Nixpkgs.Haskell.Hackage as DB
import Distribution.Nixpkgs.Haskell.Derivation (Derivation)
import Text.PrettyPrint.HughesPJClass (Doc)
Expand All @@ -55,7 +58,7 @@ genNixFile args baseDir uri argRev hackageDB pkgRef = do
cwd <- getCurrentDirectory
case pkgRef of
NonHackagePackage _ident PLArchive {} -> error "genNixFile: No support for archive package locations"
HackagePackage (PackageIdentifierRevision pkg _) -> do
HackagePackage (PackageIdentifierRevision pkg _) ->
cabal2nix args ("cabal://" <> packageIdentifierString pkg) Nothing Nothing hackageDB
NonHackagePackage _ident (PLRepo repo) ->
cabal2nix args (unpack $ repoUrl repo) (Just $ repoCommit repo) (Just (repoSubdirs repo)) hackageDB
Expand All @@ -82,16 +85,17 @@ planAndGenerate :: HasEnvConfig env
-> FilePath
-> Maybe String
-> Args
-> String
-> RIO env ()
planAndGenerate boptsCli baseDir remoteUri args@Args{..} = do
planAndGenerate boptsCli baseDir remoteUri args@Args{..} ghcnixversion = do
(_targets, _mbp, _locals, _extraToBuild, sourceMap) <- loadSourceMapFull NeedTargets boptsCli
let pkgs = sourceMapToPackages sourceMap
liftIO $ logDebug args $ "plan:\n" ++ show pkgs

hackageDB <- liftIO $ loadHackageDB Nothing argHackageSnapshot
drvs <- liftIO $ mapPool argThreads (genNixFile args baseDir remoteUri argRev hackageDB) pkgs
let locals = map (\l -> show (packageName (lpPackage l))) _locals
liftIO $ render drvs args locals
liftIO $ render drvs args locals ghcnixversion

runPlan :: FilePath
-> Maybe String
Expand All @@ -101,7 +105,22 @@ runPlan baseDir remoteUri args@Args{..} = do
let stackRoot = "/tmp/s2n"
createDirectoryIfMissing True stackRoot
let globals = globalOpts baseDir stackRoot args
withBuildConfig globals $ planAndGenerate buildOpts baseDir remoteUri args
let stackFile = baseDir </> "stack.yaml"

ghcVersion <- getGhcVersionIO globals stackFile
let ghcnixversion = filter (/= '.') $ show (getGhcVersion ghcVersion)
ensureExecutable ("haskell.compiler.ghc" ++ ghcnixversion)
withBuildConfig globals $ planAndGenerate buildOpts baseDir remoteUri args ghcnixversion


getGhcVersionIO :: GlobalOpts -> FilePath -> IO (CompilerVersion 'CVWanted)
getGhcVersionIO go stackFile = do
cp <- canonicalizePath stackFile
fp <- parseAbsFile cp
lc <- withRunner LevelError True False ColorAuto Nothing False $ \runner ->
-- https://www.fpcomplete.com/blog/2017/07/the-rio-monad
runRIO runner $ loadConfig mempty Nothing (SYLOverride fp)
loadCompilerVersion go lc

{-
TODO:
Expand Down
12 changes: 6 additions & 6 deletions src/Stack2nix/Render.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,8 @@ basePackages = S.fromList
, "xhtml"
]

render :: [Either Doc Derivation] -> Args -> [String]-> IO ()
render results args locals = do
render :: [Either Doc Derivation] -> Args -> [String] -> String -> IO ()
render results args locals ghcnixversion = do
let docs = lefts results
when (length docs > 0) $ do
hPutStrLn stderr $ show docs
Expand All @@ -69,7 +69,7 @@ render results args locals = do
let missing = sort $ S.toList $ S.difference basePackages $ S.fromList (map drvToName drvs)
let renderedMissing = map (\b -> nest 6 (text (b <> " = null;"))) missing

let out = defaultNix $ renderedMissing ++ map (renderOne args locals) drvs
let out = defaultNix ghcnixversion $ renderedMissing ++ map (renderOne args locals) drvs

case argOutFile args of
Just fname -> writeFile fname out
Expand Down Expand Up @@ -99,14 +99,14 @@ renderOne args locals drv' =
drvToName :: Derivation -> String
drvToName drv = unPackageName $ pkgName $ view pkgid drv

defaultNix :: [Doc] -> String
defaultNix drvs = unlines $
defaultNix :: String -> [Doc] -> String
defaultNix ghcnixversion drvs = unlines $
[ "# Generated using stack2nix " <> display version <> "."
, "#"
, "# Only works with sufficiently recent nixpkgs, e.g. \"NIX_PATH=nixpkgs=https://github.com/NixOS/nixpkgs/archive/21a8239452adae3a4717772f4e490575586b2755.tar.gz\"."
, ""
, "{ pkgs ? (import <nixpkgs> {})"
, ", compiler ? pkgs.haskell.packages.ghc802"
, ", compiler ? pkgs.haskell.packages.ghc" ++ ghcnixversion
, "}:"
, ""
, "with pkgs.haskell.lib;"
Expand Down
22 changes: 14 additions & 8 deletions src/Stack2nix/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ module Stack2nix.Util
, mapPool
, logDebug
, ensureExecutableExists
, ensureExecutable
) where

import Control.Concurrent.Async
Expand Down Expand Up @@ -58,16 +59,21 @@ logDebug args msg
| otherwise = return ()


-- check if executable is present, if not provision it with nix
ensureExecutableExists :: String -> String -> IO ()
ensureExecutableExists executable nixAttr = do
exec <- findExecutable executable
case exec of
Just _ -> return ()
Nothing -> do
(exitcode2, stdout, err2) <- readProcessWithExitCode "nix-build" ["-A", nixAttr, "<nixpkgs>"] mempty
case exitcode2 of
ExitSuccess -> do
hPutStrLn stderr $ err2
path <- getEnv "PATH"
setEnv "PATH" (path ++ ":" ++ unpack (strip (pack stdout)) ++ "/bin")
ExitFailure _ -> error $ nixAttr ++ " failed to build via nix"
Nothing -> ensureExecutable nixAttr

-- given nixAttr, build it and add $out/bin to $PATH
ensureExecutable :: String -> IO ()
ensureExecutable nixAttr = do
(exitcode2, stdout, err2) <- readProcessWithExitCode "nix-build" ["-A", nixAttr, "<nixpkgs>", "--no-build-output", "--no-out-link"] mempty
case exitcode2 of
ExitSuccess -> do
hPutStrLn stderr $ err2
path <- getEnv "PATH"
setEnv "PATH" (unpack (strip (pack stdout)) ++ "/bin" ++ ":" ++ path)
ExitFailure _ -> error $ nixAttr ++ " failed to build via nix"
1 change: 1 addition & 0 deletions stack2nix.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ library
, microlens
, optparse-applicative >= 0.13.2 && < 0.14
, pretty
, path
, language-nix
, process >= 1.4.3 && < 1.5
, regex-pcre >= 0.94.4 && < 0.95
Expand Down
8 changes: 4 additions & 4 deletions stack2nix.nix
Original file line number Diff line number Diff line change
Expand Up @@ -34614,8 +34614,8 @@ inherit (pkgs) which;};
"stack2nix" = callPackage
({ mkDerivation, async, base, Cabal, cabal2nix, containers
, directory, distribution-nixpkgs, filepath, language-nix
, microlens, optparse-applicative, pretty, process, regex-pcre
, SafeSemaphore, stack, stdenv, temporary, text, time
, microlens, optparse-applicative, path, pretty, process
, regex-pcre, SafeSemaphore, stack, stdenv, temporary, text, time
}:
mkDerivation {
pname = "stack2nix";
Expand All @@ -34626,8 +34626,8 @@ inherit (pkgs) which;};
libraryHaskellDepends = [
async base Cabal cabal2nix containers directory
distribution-nixpkgs filepath language-nix microlens
optparse-applicative pretty process regex-pcre SafeSemaphore stack
temporary text time
optparse-applicative path pretty process regex-pcre SafeSemaphore
stack temporary text time
];
executableHaskellDepends = [
base Cabal optparse-applicative time
Expand Down