Skip to content

Commit 8a6ff07

Browse files
Merge #554: Implementation of derivationStrict primOp & use of the Store 0.4
Implement derivationStrict primOp Closes #364
2 parents e45f763 + 43be29e commit 8a6ff07

File tree

12 files changed

+545
-121
lines changed

12 files changed

+545
-121
lines changed

cabal.project

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,8 @@
11
packages:
22
./hnix.cabal
3+
4+
source-repository-package
5+
type: git
6+
location: https://github.com/Anton-Latukha/cryptohash-sha512
7+
tag: 48f827eb09a73ad5ee43dd397a06ebdbf51ab856
8+

default.nix

Lines changed: 35 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,7 @@
9191
# , nixos-20.03 # Last stable release, gets almost no updates to recipes, gets only required backports
9292
# ...
9393
# }
94-
, rev ? "24eb3f87fc610f18de7076aee7c5a84ac5591e3e"
94+
, rev ? "8ba15f6383c74e981d8038fa19cc77ed0c53ba22"
9595

9696
, pkgs ?
9797
if builtins.compareVersions builtins.nixVersion "2.0" < 0
@@ -111,30 +111,30 @@
111111

112112
let
113113

114-
getDefaultGHC = "ghc${
115-
(
116-
# Remove '.' from the string 8.8.4 -> 884
117-
pkgs.lib.stringAsChars (c: if c == "." then "" else c)
118-
# Get default GHC version,
119-
(pkgs.lib.getVersion pkgs.haskellPackages.ghc)
120-
)
121-
}";
122-
123-
compilerPackage =
124-
if ((compiler == "") || (compiler == "default"))
125-
then getDefaultGHC
126-
else compiler;
127-
128-
# 2020-05-23: NOTE: Currently HNix-store needs no overlay
129-
# hnix-store-src = pkgs.fetchFromGitHub {
130-
# owner = "haskell-nix";
131-
# repo = "hnix-store";
132-
# rev = "0.2.0.0";
133-
# sha256 = "1qf5rn43d46vgqqgmwqdkjh78rfg6bcp4kypq3z7mx46sdpzvb78";
134-
# };
114+
getDefaultGHC = "ghc${
115+
(
116+
# Remove '.' from the string 8.8.4 -> 884
117+
pkgs.lib.stringAsChars (c: if c == "." then "" else c)
118+
# Get default GHC version,
119+
(pkgs.lib.getVersion pkgs.haskellPackages.ghc)
120+
)
121+
}";
122+
123+
compilerPackage =
124+
if ((compiler == "") || (compiler == "default"))
125+
then getDefaultGHC
126+
else compiler;
127+
128+
# 2020-12-31: NOTE: Remove after `hnix-store 0.4` arrives into Nixpkgs
129+
hnix-store-src = pkgs.fetchFromGitHub {
130+
owner = "haskell-nix";
131+
repo = "hnix-store";
132+
rev = "fd09d29b8bef4904058f033d693e7d928a4a92dc";
133+
sha256 = "0fxig1ckzknm5g19jzg7rrcpz7ssn4iiv9bs9hff9gfy3ciq4zrs";
134+
};
135135

136136
overlay = pkgs.lib.foldr pkgs.lib.composeExtensions (_: _: {}) [
137-
# (import "${hnix-store-src}/overlay.nix")
137+
(import "${hnix-store-src}/overlay.nix" pkgs pkgs.haskell.lib)
138138
(self: super:
139139
pkgs.lib.optionalAttrs withHoogle {
140140
ghc = super.ghc // { withPackages = super.ghc.withHoogle; };
@@ -223,6 +223,18 @@ let
223223
root = packageRoot;
224224

225225
overrides = self: super: {
226+
# 2020-12-07 We really want cryptohash-sha512, but it conflicts with
227+
# recent versions of base, for seemingly no valid reason.
228+
# As the update is slow to happen, just jailbreak here
229+
# See https://github.com/haskell-hvr/cryptohash-sha512 PRs 3, 5 and issue 4
230+
# See also https://github.com/NixOS/nixpkgs/pull/106333 for a temporary fix.
231+
cryptohash-sha512 = pkgs.haskell.lib.unmarkBroken ( pkgs.haskell.lib.doJailbreak super.cryptohash-sha512 );
232+
233+
# 2020-12-07 hnix-store-remote fails when trying to connect to a real hnix daemon.
234+
# probably due to nix sandbox restrictions.
235+
# Upstream issue @ https://github.com/haskell-nix/hnix-store/issues/80
236+
hnix-store-remote = pkgs.haskell.lib.removeConfigureFlag super.hnix-store-remote "-fio-testsuite";
237+
226238
# 2020-08-04 hnix uses custom LayoutOptions and therefore is
227239
# likely to be affected by the change in the ribbon width
228240
# calculation in prettyprinter-1.7.0.

hnix.cabal

Lines changed: 14 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,19 @@ license: BSD3
1111
license-file: LICENSE
1212
build-type: Simple
1313
cabal-version: >= 1.10
14+
data-dir: data/
15+
data-files:
16+
nix/corepkgs/buildenv.nix
17+
nix/corepkgs/unpack-channel.nix
18+
nix/corepkgs/derivation.nix
19+
nix/corepkgs/fetchurl.nix
20+
nix/corepkgs/imported-drv-to-derivation.nix
1421
extra-source-files:
1522
data/nix/corepkgs/buildenv.nix
23+
data/nix/corepkgs/unpack-channel.nix
1624
data/nix/corepkgs/derivation.nix
25+
data/nix/corepkgs/fetchurl.nix
26+
data/nix/corepkgs/imported-drv-to-derivation.nix
1727
data/nix/tests/lang/binary-data
1828
data/nix/tests/lang/data
1929
data/nix/tests/lang/dir1/a.nix
@@ -341,6 +351,7 @@ library
341351
Nix.Convert
342352
Nix.Effects
343353
Nix.Effects.Basic
354+
Nix.Effects.Derivation
344355
Nix.Eval
345356
Nix.Exec
346357
Nix.Expr
@@ -401,8 +412,9 @@ library
401412
, gitrev >= 1.1.0 && < 1.4
402413
, hashable >= 1.2.5 && < 1.4
403414
, hashing >= 0.1.0 && < 0.2
404-
, hnix-store-core >= 0.1.0 && < 0.3
405-
, http-client >= 0.5.14 && < 0.6 || >= 0.6.4 && < 0.8
415+
, hnix-store-core >= 0.4.0 && < 0.5
416+
, hnix-store-remote >= 0.4.0 && < 0.5
417+
, http-client >= 0.5.14 && < 0.6 || >= 0.6.4 && < 0.7
406418
, http-client-tls >= 0.3.5 && < 0.4
407419
, http-types >= 0.12.2 && < 0.13
408420
, lens-family >= 1.2.2 && < 2.2

src/Nix/Convert.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -151,7 +151,7 @@ instance ( Convertible e t f m
151151
NVStr' ns -> pure $ Just ns
152152
NVPath' p ->
153153
Just
154-
. hackyMakeNixStringWithoutContext
154+
. (\s -> principledMakeNixStringWithSingletonContext s (StringContext s DirectPath))
155155
. Text.pack
156156
. unStorePath
157157
<$> addPath p

src/Nix/Effects.hs

Lines changed: 55 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@
77
{-# LANGUAGE MultiParamTypeClasses #-}
88
{-# LANGUAGE OverloadedStrings #-}
99
{-# LANGUAGE TypeFamilies #-}
10+
{-# LANGUAGE DataKinds #-}
11+
{-# LANGUAGE TypeApplications #-}
1012

1113
module Nix.Effects where
1214

@@ -17,24 +19,31 @@ import Prelude hiding ( putStr
1719
import qualified Prelude
1820

1921
import Control.Monad.Trans
22+
import qualified Data.HashSet as HS
2023
import Data.Text ( Text )
2124
import qualified Data.Text as T
22-
import Network.HTTP.Client hiding ( path )
25+
import qualified Data.Text.Encoding as T
26+
import Network.HTTP.Client hiding ( path, Proxy )
2327
import Network.HTTP.Client.TLS
2428
import Network.HTTP.Types
2529
import Nix.Expr
26-
import Nix.Frames
30+
import Nix.Frames hiding ( Proxy )
2731
import Nix.Parser
2832
import Nix.Render
2933
import Nix.Utils
3034
import Nix.Value
3135
import qualified Paths_hnix
32-
import qualified System.Directory as S
3336
import System.Environment
3437
import System.Exit
38+
import System.FilePath ( takeFileName )
3539
import qualified System.Info
3640
import System.Process
3741

42+
import qualified System.Nix.Hash as Store
43+
import qualified System.Nix.Store.Remote as Store
44+
import qualified System.Nix.Store.Remote.Types as Store
45+
import qualified System.Nix.StorePath as Store
46+
3847
-- | A path into the nix store
3948
newtype StorePath = StorePath { unStorePath :: FilePath }
4049

@@ -226,36 +235,55 @@ print = putStrLn . show
226235
instance MonadPutStr IO where
227236
putStr = Prelude.putStr
228237

238+
239+
type RecursiveFlag = Bool
240+
type RepairFlag = Bool
241+
type StorePathName = Text
242+
type FilePathFilter m = FilePath -> m Bool
243+
type StorePathSet = HS.HashSet StorePath
244+
229245
class Monad m => MonadStore m where
230-
-- | Import a path into the nix store, and return the resulting path
231-
addPath' :: FilePath -> m (Either ErrorCall StorePath)
232246

233-
-- | Add a file with the given name and contents to the nix store
234-
toFile_' :: FilePath -> String -> m (Either ErrorCall StorePath)
247+
-- | Copy the contents of a local path to the store. The resulting store
248+
-- path is returned. Note: This does not support yet support the expected
249+
-- `filter` function that allows excluding some files.
250+
addToStore :: StorePathName -> FilePath -> RecursiveFlag -> RepairFlag -> m (Either ErrorCall StorePath)
251+
default addToStore :: (MonadTrans t, MonadStore m', m ~ t m') => StorePathName -> FilePath -> RecursiveFlag -> RepairFlag -> m (Either ErrorCall StorePath)
252+
addToStore a b c d = lift $ addToStore a b c d
253+
254+
-- | Like addToStore, but the contents written to the output path is a
255+
-- regular file containing the given string.
256+
addTextToStore' :: StorePathName -> Text -> Store.StorePathSet -> RepairFlag -> m (Either ErrorCall StorePath)
257+
default addTextToStore' :: (MonadTrans t, MonadStore m', m ~ t m') => StorePathName -> Text -> Store.StorePathSet -> RepairFlag -> m (Either ErrorCall StorePath)
258+
addTextToStore' a b c d = lift $ addTextToStore' a b c d
259+
260+
parseStoreResult :: Monad m => String -> (Either String a, [Store.Logger]) -> m (Either ErrorCall a)
261+
parseStoreResult name res = case res of
262+
(Left msg, logs) -> return $ Left $ ErrorCall $ "Failed to execute '" ++ name ++ "': " ++ msg ++ "\n" ++ show logs
263+
(Right result, _) -> return $ Right result
235264

236265
instance MonadStore IO where
237-
addPath' path = do
238-
(exitCode, out, _) <- readProcessWithExitCode "nix-store" ["--add", path] ""
239-
case exitCode of
240-
ExitSuccess -> do
241-
let dropTrailingLinefeed p = take (length p - 1) p
242-
pure $ Right $ StorePath $ dropTrailingLinefeed out
243-
_ ->
244-
pure
245-
$ Left
246-
$ ErrorCall
247-
$ "addPath: failed: nix-store --add "
248-
++ show path
249266

250-
--TODO: Use a temp directory so we don't overwrite anything important
251-
toFile_' filepath content = do
252-
writeFile filepath content
253-
storepath <- addPath' filepath
254-
S.removeFile filepath
255-
pure storepath
267+
addToStore name path recursive repair = case Store.makeStorePathName name of
268+
Left err -> return $ Left $ ErrorCall $ "String '" ++ show name ++ "' is not a valid path name: " ++ err
269+
Right pathName -> do
270+
-- TODO: redesign the filter parameter
271+
res <- Store.runStore $ Store.addToStore @'Store.SHA256 pathName path recursive (const False) repair
272+
parseStoreResult "addToStore" res >>= \case
273+
Left err -> return $ Left err
274+
Right storePath -> return $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath storePath
275+
276+
addTextToStore' name text references repair = do
277+
res <- Store.runStore $ Store.addTextToStore name text references repair
278+
parseStoreResult "addTextToStore" res >>= \case
279+
Left err -> return $ Left err
280+
Right path -> return $ Right $ StorePath $ T.unpack $ T.decodeUtf8 $ Store.storePathToRawFilePath path
281+
282+
addTextToStore :: (Framed e m, MonadStore m) => StorePathName -> Text -> Store.StorePathSet -> RepairFlag -> m StorePath
283+
addTextToStore a b c d = either throwError return =<< addTextToStore' a b c d
256284

257285
addPath :: (Framed e m, MonadStore m) => FilePath -> m StorePath
258-
addPath p = either throwError pure =<< addPath' p
286+
addPath p = either throwError return =<< addToStore (T.pack $ takeFileName p) p True False
259287

260288
toFile_ :: (Framed e m, MonadStore m) => FilePath -> String -> m StorePath
261-
toFile_ p contents = either throwError pure =<< toFile_' p contents
289+
toFile_ p contents = addTextToStore (T.pack p) (T.pack contents) HS.empty False

src/Nix/Effects/Basic.hs

Lines changed: 6 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,6 @@
88
{-# LANGUAGE TypeApplications #-}
99
{-# LANGUAGE ViewPatterns #-}
1010

11-
{-# OPTIONS_GHC -Wno-missing-signatures #-}
12-
{-# OPTIONS_GHC -Wno-orphans #-}
13-
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
14-
1511
module Nix.Effects.Basic where
1612

1713
import Control.Monad
@@ -20,30 +16,24 @@ import Data.HashMap.Lazy ( HashMap )
2016
import qualified Data.HashMap.Lazy as M
2117
import Data.List
2218
import Data.List.Split
23-
import Data.Maybe ( maybeToList )
2419
import Data.Text ( Text )
2520
import qualified Data.Text as Text
26-
import Nix.Atoms
21+
import Data.Text.Prettyprint.Doc
2722
import Nix.Convert
2823
import Nix.Effects
2924
import Nix.Exec ( MonadNix
30-
, callFunc
3125
, evalExprLoc
3226
, nixInstantiateExpr
3327
)
3428
import Nix.Expr
3529
import Nix.Frames
36-
import Nix.Normal
3730
import Nix.Parser
38-
import Nix.Pretty
3931
import Nix.Render
4032
import Nix.Scope
4133
import Nix.String
42-
import Nix.String.Coerce
4334
import Nix.Utils
4435
import Nix.Value
4536
import Nix.Value.Monad
46-
import Prettyprinter
4737
import System.FilePath
4838

4939
#ifdef MIN_VERSION_ghc_datasize
@@ -126,8 +116,8 @@ findPathBy
126116
-> [NValue t f m]
127117
-> FilePath
128118
-> m FilePath
129-
findPathBy finder l name = do
130-
mpath <- foldM go Nothing l
119+
findPathBy finder ls name = do
120+
mpath <- foldM go Nothing ls
131121
case mpath of
132122
Nothing ->
133123
throwError
@@ -235,13 +225,13 @@ findPathM = findPathBy existingPath
235225
pure $ if exists then Just apath else Nothing
236226

237227
defaultImportPath
238-
:: (MonadNix e t f m, MonadState (HashMap FilePath NExprLoc) m)
228+
:: (MonadNix e t f m, MonadState (HashMap FilePath NExprLoc, b) m)
239229
=> FilePath
240230
-> m (NValue t f m)
241231
defaultImportPath path = do
242232
traceM $ "Importing file " ++ path
243233
withFrame Info (ErrorCall $ "While importing file " ++ show path) $ do
244-
imports <- get
234+
imports <- gets fst
245235
evalExprLoc =<< case M.lookup path imports of
246236
Just expr -> pure expr
247237
Nothing -> do
@@ -252,7 +242,7 @@ defaultImportPath path = do
252242
$ ErrorCall
253243
. show $ fillSep ["Parse during import failed:", err]
254244
Success expr -> do
255-
modify (M.insert path expr)
245+
modify (\(a, b) -> (M.insert path expr a, b))
256246
pure expr
257247

258248
defaultPathToDefaultNix :: MonadNix e t f m => FilePath -> m FilePath
@@ -264,38 +254,5 @@ pathToDefaultNixFile p = do
264254
isDir <- doesDirectoryExist p
265255
pure $ if isDir then p </> "default.nix" else p
266256

267-
defaultDerivationStrict
268-
:: forall e t f m . MonadNix e t f m => NValue t f m -> m (NValue t f m)
269-
defaultDerivationStrict = fromValue @(AttrSet (NValue t f m)) >=> \s -> do
270-
nn <- maybe (pure False) (demand ?? fromValue) (M.lookup "__ignoreNulls" s)
271-
s' <- M.fromList <$> mapMaybeM (handleEntry nn) (M.toList s)
272-
v' <- normalForm =<< toValue @(AttrSet (NValue t f m)) @_ @(NValue t f m) s'
273-
nixInstantiateExpr $ "derivationStrict " ++ show (prettyNValue v')
274-
where
275-
mapMaybeM :: (a -> m (Maybe b)) -> [a] -> m [b]
276-
mapMaybeM op = foldr f (pure [])
277-
where f x xs = op x >>= (<$> xs) . (++) . maybeToList
278-
279-
handleEntry :: Bool -> (Text, NValue t f m) -> m (Maybe (Text, NValue t f m))
280-
handleEntry ignoreNulls (k, v) = fmap (k, ) <$> case k of
281-
-- The `args' attribute is special: it supplies the command-line
282-
-- arguments to the builder.
283-
-- TODO This use of coerceToString is probably not right and may
284-
-- not have the right arguments.
285-
"args" -> demand v $ fmap Just . coerceNixList
286-
"__ignoreNulls" -> pure Nothing
287-
_ -> demand v $ \case
288-
NVConstant NNull | ignoreNulls -> pure Nothing
289-
v' -> Just <$> coerceNix v'
290-
where
291-
coerceNix :: NValue t f m -> m (NValue t f m)
292-
coerceNix = toValue <=< coerceToString callFunc CopyToStore CoerceAny
293-
294-
coerceNixList :: NValue t f m -> m (NValue t f m)
295-
coerceNixList v = do
296-
xs <- fromValue @[NValue t f m] v
297-
ys <- traverse (`demand` coerceNix) xs
298-
toValue @[NValue t f m] ys
299-
300257
defaultTraceEffect :: MonadPutStr m => String -> m ()
301258
defaultTraceEffect = Nix.Effects.putStrLn

0 commit comments

Comments
 (0)