This commit is contained in:
Shea Levy 2019-03-10 18:11:15 -04:00
parent 0367156509
commit 974a944bf5
No known key found for this signature in database
GPG Key ID: 5C0BD6957D86FE27
14 changed files with 208 additions and 386 deletions

View File

@ -17,15 +17,11 @@ extra-source-files: ChangeLog.md, README.md
cabal-version: >=1.10
library
exposed-modules: System.Nix.Build
, System.Nix.Derivation
, System.Nix.GC
, System.Nix.Hash
exposed-modules: System.Nix.Hash
, System.Nix.Internal.Hash
, System.Nix.Nar
, System.Nix.Path
, System.Nix.StorePath
, System.Nix.Store
, System.Nix.Util
build-depends: base >=4.10
, bytestring
, binary
@ -41,6 +37,7 @@ library
, regex-base
, regex-tdfa-text
, text
, time
, unix
, unordered-containers
, vector

View File

@ -1,50 +0,0 @@
{-# LANGUAGE RecordWildCards #-}
{-|
Description : Build related types
Maintainer : srk <srk@48.io>
|-}
module System.Nix.Build (
BuildMode(..)
, BuildStatus(..)
, BuildResult(..)
, buildSuccess
) where
import Data.Text (Text)
import Data.HashSet (HashSet)
import System.Nix.Path (Path)
data BuildMode = Normal | Repair | Check
deriving (Eq, Ord, Enum, Show)
data BuildStatus =
Built
| Substituted
| AlreadyValid
| PermanentFailure
| InputRejected
| OutputRejected
| TransientFailure -- possibly transient
| CachedFailure -- no longer used
| TimedOut
| MiscFailure
| DependencyFailed
| LogLimitExceeded
| NotDeterministic
deriving (Eq, Ord, Enum, Show)
-- | Result of the build
data BuildResult = BuildResult
{ -- | build status, MiscFailure should be default
status :: !BuildStatus
, -- | possible build error message
error :: !(Maybe Text)
, -- | How many times this build was performed
timesBuilt :: !Integer
, -- | If timesBuilt > 1, whether some builds did not produce the same result
isNonDeterministic :: !Bool
-- XXX: | startTime stopTime time_t
} deriving (Eq, Ord, Show)
buildSuccess BuildResult{..} = status == Built || status == Substituted || status == AlreadyValid

View File

@ -1,30 +0,0 @@
{-|
Description : Derivation types
Maintainer : srk <srk@48.io>
|-}
module System.Nix.Derivation where
import Data.Text (Text)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import System.Nix.Path
type OutputName = Text
newtype DerivationInputs = DerivationInputs
{ _unDerivationInputs :: HashMap Path (HashSet OutputName)
} deriving (Eq, Ord, Show)
data Derivation = Derivation
{ _derivationInputs :: DerivationInputs
, _derivationOutputs :: !(HashMap OutputName Path)
-- | Inputs that are sources
, _derivationInputSrcs :: !PathSet
, _derivationPlatform :: !Text
-- | Path to builder
, _derivationBuilder :: !Path
, _derivationArgs :: ![Text]
, _derivationEnv :: ![HashMap Text Text]
} deriving (Eq, Ord, Show)

View File

@ -1,47 +0,0 @@
{-|
Description : Garbage collection actions / options
Maintainer : srk <srk@48.io>
|-}
module System.Nix.GC (
Action(..)
, Options(..)
, Result(..)
) where
import System.Nix.Path (PathSet)
{- Garbage collector operation:
- ReturnLive: return the set of paths reachable from
(i.e. in the closure of) the roots.
- ReturnDead: return the set of paths not reachable from
the roots.
- DeleteDead: actually delete the latter set.
- DeleteSpecific: delete the paths listed in
`pathsToDelete', insofar as they are not reachable.
-}
data Action = ReturnLive | ReturnDead | DeleteDead | DeleteSpecific
deriving (Eq, Ord, Enum, Show)
-- | Garbage collector operation options
data Options = Options
{ -- | operation
operation :: !Action
-- | If `ignoreLiveness' is set, then reachability from the roots is
-- ignored (dangerous!). However, the paths must still be
-- unreferenced *within* the store (i.e., there can be no other
-- store paths that depend on them).
, ignoreLiveness :: !Bool
-- | For DeleteSpecific, the paths to delete
, pathsToDelete :: !PathSet
, -- | Stop after at least `maxFreed` bytes have been freed
maxFreed :: !Integer
} deriving (Eq, Ord, Show)
data Result = Result
{ -- | Depending on the action, the GC roots, or the paths that would be or have been deleted
paths :: !PathSet
, -- | For ReturnDead, DeleteDead and DeleteSpecific, the number of bytes that would be or was freed
bytesFreed :: !Integer
} deriving (Eq, Ord, Show)

View File

@ -1,19 +1,12 @@
{-|
Description : Cryptographic hashes for hnix-store.
Maintainer : Shea Levy <shea@shealevy.com>; Greg Hale <imalsogreg@gmail.com>
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE CPP #-}
module System.Nix.Hash (
HNix.Digest
, HNix.HashAlgorithm(..)
, HNix.NamedAlgorithm(..)
, HNix.NamedDigest(..)
, HNix.HasDigest(..)
, HNix.hash
, HNix.hashLazy
@ -22,4 +15,3 @@ module System.Nix.Hash (
) where
import qualified System.Nix.Internal.Hash as HNix

View File

@ -2,18 +2,22 @@
Description : Cryptographic hashes for hnix-store.
Maintainer : Greg Hale <imalsogreg@gmail.com>
-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE StandaloneDeriving #-}
module System.Nix.Internal.Hash where
import Data.Text (Text)
import qualified Crypto.Hash.MD5 as MD5
import qualified Crypto.Hash.SHA1 as SHA1
import qualified Crypto.Hash.SHA256 as SHA256
@ -40,6 +44,17 @@ data HashAlgorithm
| SHA256
| Truncated Nat HashAlgorithm
class NamedAlgorithm (a :: HashAlgorithm) where
algorithmName :: Text
instance NamedAlgorithm 'MD5 where
algorithmName = "md5"
instance NamedAlgorithm 'SHA1 where
algorithmName = "sha1"
instance NamedAlgorithm 'SHA256 where
algorithmName = "sha256"
-- | Types with kind @HashAlgorithm@ may be a @HasDigest@ instance
-- if they are able to hash bytestrings via the init/update/finalize
@ -114,6 +129,9 @@ newtype Digest (a :: HashAlgorithm) = Digest
-- not some particular text encoding.
} deriving (Show, Eq, Ord, DataHashable.Hashable)
-- | A digest from a named hash algorithm.
data NamedDigest =
forall a . NamedAlgorithm a => NamedDigest (Digest a)
-- instance DataHashable.Hashable (Digest a) where
-- hashWithSalt a (Digest bs) = DataHashable.hashWithSalt a bs

View File

@ -7,7 +7,6 @@
{-|
Description : Allowed effects for interacting with Nar files.
Maintainer : Shea Levy <shea@shealevy.com>
|-}
module System.Nix.Nar (
FileSystemObject(..)
@ -18,6 +17,7 @@ module System.Nix.Nar (
, localUnpackNar
, narEffectsIO
, putNar
, FilePathPart(..)
) where
import Control.Applicative
@ -42,8 +42,6 @@ import System.FilePath
import System.Posix.Files (createSymbolicLink, fileSize, getFileStatus,
isDirectory, readSymbolicLink)
import System.Nix.Path
data NarEffects (m :: * -> *) = NarEffects {
narReadFile :: FilePath -> m BSL.ByteString
, narWriteFile :: FilePath -> BSL.ByteString -> m ()
@ -65,6 +63,13 @@ data NarEffects (m :: * -> *) = NarEffects {
data Nar = Nar { narFile :: FileSystemObject }
deriving (Eq, Show)
newtype FilePathPart = FilePathPart { unFilePathPart :: BSC.ByteString } deriving (Eq, Ord, Show)
filePathPart :: BSC.ByteString -> Maybe FilePathPart
filePathPart p = case BSC.any (`elem` ['/', '\NUL']) p of
False -> Just $ FilePathPart p
True -> Nothing
-- | A FileSystemObject (FSO) is an anonymous entity that can be NAR archived
data FileSystemObject =
Regular IsExecutable Int64 BSL.ByteString

View File

@ -1,121 +0,0 @@
{-|
Description : Types and effects for interacting with the Nix store.
Maintainer : Shea Levy <shea@shealevy.com>
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module System.Nix.Path
( FilePathPart(..)
, PathHashAlgo
, Path(..)
, PathSet
, SubstitutablePathInfo(..)
, ValidPathInfo(..)
, PathName(..)
, filePathPart
, pathName
, Roots
) where
import System.Nix.Hash (Digest(..),
HashAlgorithm(Truncated, SHA256))
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import Data.Hashable (Hashable (..), hashPtrWithSalt)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import Data.Map.Strict (Map)
import Data.Text (Text)
import qualified Data.Text as T
import System.IO.Unsafe (unsafeDupablePerformIO)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)
-- | The hash algorithm used for store path hashes.
type PathHashAlgo = Truncated 20 SHA256
-- | The name portion of a Nix path.
--
-- Must be composed of a-z, A-Z, 0-9, +, -, ., _, ?, and =, can't
-- start with a ., and must have at least one character.
newtype PathName = PathName
{ pathNameContents :: Text -- ^ The contents of the path name
} deriving (Eq, Ord, Show, Hashable)
-- | A regular expression for matching a valid 'PathName'
nameRegex :: Regex
nameRegex =
makeRegex "[a-zA-Z0-9\\+\\-\\_\\?\\=][a-zA-Z0-9\\+\\-\\.\\_\\?\\=]*"
-- | Construct a 'PathName', assuming the provided contents are valid.
pathName :: Text -> Maybe PathName
pathName n = case matchTest nameRegex n of
True -> Just $ PathName n
False -> Nothing
-- | A path in a store.
data Path = Path !(Digest PathHashAlgo) !PathName
deriving (Eq, Ord, Show)
type PathSet = HashSet Path
-- | Information about substitutes for a 'Path'.
data SubstitutablePathInfo = SubstitutablePathInfo
{ -- | The .drv which led to this 'Path'.
deriver :: !(Maybe Path)
, -- | The references of the 'Path'
references :: !PathSet
, -- | The (likely compressed) size of the download of this 'Path'.
downloadSize :: !Integer
, -- | The size of the uncompressed NAR serialization of this
-- 'Path'.
narSize :: !Integer
} deriving (Eq, Ord, Show)
-- | Information about @Path@
data ValidPathInfo = ValidPathInfo
{ -- | Path itself
path :: !Path
, -- | The .drv which led to this 'Path'.
deriverVP :: !(Maybe Path)
, -- | NAR hash
narHash :: !Text
, -- | The references of the 'Path'
referencesVP :: !PathSet
, -- | Registration time should be time_t
registrationTime :: !Integer
, -- | The size of the uncompressed NAR serialization of this
-- 'Path'.
narSizeVP :: !Integer
, -- | Whether the path is ultimately trusted, that is, it's a
-- derivation output that was built locally.
ultimate :: !Bool
, -- | Signatures
sigs :: ![Text]
, -- | Content-addressed
-- Store path is computed from a cryptographic hash
-- of the contents of the path, plus some other bits of data like
-- the "name" part of the path.
--
-- ca has one of the following forms:
-- * text:sha256:<sha256 hash of file contents> (paths by makeTextPath() / addTextToStore())
-- * fixed:<r?>:<ht>:<h> (paths by makeFixedOutputPath() / addToStore())
ca :: !Text
} deriving (Eq, Ord, Show)
-- | A valid filename or directory name
newtype FilePathPart = FilePathPart { unFilePathPart :: BSC.ByteString }
deriving (Eq, Ord, Show)
-- | Construct FilePathPart from Text by checking that there
-- are no '/' or '\\NUL' characters
filePathPart :: BSC.ByteString -> Maybe FilePathPart
filePathPart p = case BSC.any (`elem` ['/', '\NUL']) p of
False -> Just $ FilePathPart p
True -> Nothing
type Roots = Map Path Path
instance Hashable Path where
hashWithSalt s (Path hash name) = s `hashWithSalt` hash `hashWithSalt` name

View File

@ -1,66 +1,63 @@
{-|
Description : Types and effects for interacting with the Nix store.
Maintainer : Shea Levy <shea@shealevy.com>
Description : Effects for interacting with the Nix store.
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module System.Nix.Store
( PathName, pathNameContents, pathName
, PathHashAlgo, Path(..)
, StoreEffects(..)
, SubstitutablePathInfo(..)
) where
{-# LANGUAGE RankNTypes #-}
module System.Nix.Store where
import qualified Data.ByteString.Lazy as BS
import Data.Text (Text)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)
import Data.Hashable (Hashable(..), hashPtrWithSalt)
import Data.HashSet (HashSet)
import Data.HashMap.Strict (HashMap)
import System.IO.Unsafe (unsafeDupablePerformIO)
import Data.ByteString.Lazy (ByteString)
import System.Nix.Hash (NamedAlgorithm)
import System.Nix.StorePath
import System.Nix.Nar (Nar)
import System.Nix.Hash (Digest)
import System.Nix.Path
import System.Nix.Nar
-- | Interactions with the Nix store.
-- | Effect for interactions with the Nix store.
--
-- @rootedPath@: A path plus a witness to the fact that the path is
-- reachable from a root whose liftime is at least as long as the
-- @rootedPath@ reference itself, when the implementation supports
-- this.
--
-- @validPath@: A @rootedPath@ plus a witness to the fact that the
-- path is valid. On implementations that support temporary roots,
-- this implies that the path will remain valid so long as the
-- reference is held.
-- @root@: The root path of the store (e.g. "/nix/store").
--
-- @m@: The monad the effects operate in.
data StoreEffects rootedPath validPath m =
StoreEffects
{ -- | Project out the underlying 'Path' from a 'rootedPath'
fromRootedPath :: !(rootedPath -> Path)
, -- | Project out the underlying 'rootedPath' from a 'validPath'
fromValidPath :: !(validPath -> rootedPath)
, -- | Which of the given paths are valid?
validPaths :: !(HashSet rootedPath -> m (HashSet validPath))
, -- | Get the paths that refer to a given path.
referrers :: !(validPath -> m (HashSet Path))
, -- | Get a root to the 'Path'.
rootedPath :: !(Path -> m rootedPath)
, -- | Get information about substituters of a set of 'Path's
substitutablePathInfos ::
!(HashSet Path -> m (HashMap Path SubstitutablePathInfo))
, -- | Get the currently valid derivers of a 'Path'.
validDerivers :: !(Path -> m (HashSet Path))
, -- | Get the outputs of the derivation at a 'Path'.
derivationOutputs :: !(validPath -> m (HashSet Path))
, -- | Get the output names of the derivation at a 'Path'.
derivationOutputNames :: !(validPath -> m (HashSet Text))
, -- | Get a full 'Path' corresponding to a given 'Digest'.
pathFromHashPart :: !(Digest PathHashAlgo -> m Path)
, -- | Add a non-nar file to the store
addFile :: !(BS.ByteString -> m validPath)
}
--
-- A valid instance should follow the appropriate hashing algorithms
-- for effects which add a new path to the store.
data StoreEffects root m = StoreEffects
{ -- | Add a regular file to the store with the given references,
-- hashed with 'SHA256'.
regularFileToStore
:: StorePathName
-> ByteString
-> StorePathSet root
-> m (StorePath root)
, -- ^ Add a fixed file (possibly not regular) to the store with a
-- given hash algorithm.
--
-- Note that conceptually this functionality overlaps with
-- 'regularFileToStore' (when the 'HashMode' is 'Flat @SHA256' and
-- the references set is empty), but for legacy reasons these
-- follow a different underlying algorithm for getting the store
-- path.
--
-- If the 'HashMode' is 'Fixed', the top level FSO of the 'Nar'
-- must be a 'Regular' object.
fixedFileToStore
:: forall a . (NamedAlgorithm a)
=> StorePathName
-> HashMode a
-> Nar
-> m (StorePath root)
, -- ^ Import a serialization of a valid path into the store.
--
-- 'CheckSigs' is ignored if not a trusted user.
importPath
:: StorePathInfo root
-> Nar
-> Repair
-> CheckSigs
-> m ()
}
-- | Flag to indicate whether a command should overwrite a specified
-- path if it already exists (in an attempt to fix issues).
data Repair = Repair | DontRepair
-- | Flag to indicate whether signatures should be validated on an
-- imported archive.
data CheckSigs = CheckSigs | DontCheckSigs

View File

@ -0,0 +1,109 @@
{-|
Description : Creating and manipulating Nix store paths.
-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RecordWildCards #-}
module System.Nix.StorePath
( StorePathHashAlgo
, StorePathName
, storePathNameText
, storePathName
, StorePath(..)
, StorePathSet
, StorePathInfo(..)
, ContentAddressedHash(..)
, HashMode(..)
) where
import Data.Word (Word64)
import GHC.TypeLits (Symbol)
import System.Nix.Hash
import Data.Time (UTCTime)
import Data.Hashable (Hashable (..))
import Data.HashSet (HashSet)
import Data.Text (Text)
import Text.Regex.Base.RegexLike (makeRegex, matchTest)
import Text.Regex.TDFA.Text (Regex)
-- | The hash algorithm used for store path hashes.
type StorePathHashAlgo = 'Truncated 20 'SHA256
-- | The name portion of a Nix path.
--
-- Must be composed of a-z, A-Z, 0-9, +, -, ., _, ?, and =, can't
-- start with a ., and must have at least one character.
newtype StorePathName = StorePathName
{ storePathNameText :: Text
-- ^ The contents of the path name
} deriving (Eq, Ord, Show, Hashable)
-- | A regular expression for matching a valid 'StorePathName'
nameRegex :: Regex
nameRegex =
makeRegex "[a-zA-Z0-9\\+\\-\\_\\?\\=][a-zA-Z0-9\\+\\-\\.\\_\\?\\=]*"
-- | Construct a 'StorePathName', checking that the provided contents are valid.
storePathName :: Text -> Maybe StorePathName
storePathName n = case matchTest nameRegex n of
True -> Just $ StorePathName n
False -> Nothing
-- | A path in a store.
--
-- @root@: The root path of the store (e.g. "/nix/store").
data StorePath (root :: Symbol) = StorePath
{ pathHash :: !(Digest StorePathHashAlgo)
, pathName :: !StorePathName
} deriving (Eq, Ord, Show)
type StorePathSet root = HashSet (StorePath root)
-- | Metadata about a valid @Path@ in the store.
data StorePathInfo store = StorePathInfo
{ -- |The path itself
path :: !(StorePath store)
, -- | The .drv which led to this 'Path', if any/known.
deriver :: !(Maybe (StorePath store))
, -- | The hash of the serialization of this path.
narHash :: !NamedDigest
, -- | The references of the 'Path'.
references :: !(StorePathSet store)
, -- | When this store path was registered valid.
registrationTime :: !UTCTime
, -- | The size of the uncompressed NAR serialization of this
-- 'StorePath'.
narSize :: !Word64
, -- | Whether the path is ultimately trusted, that is, it's a
-- derivation output that was built locally.
ultimate :: !Bool
, -- | Signatures attesting to the validity of this registration.
sigs :: ![Text] -- TODO better type?
, -- | Whether or not the store path is content-addressed, and if so
-- what is the hash that gives its address?
ca :: !(Maybe ContentAddressedHash)
}
-- | The different types of content-addressed hashing we have in Nix.
data ContentAddressedHash
= RegularFile (Digest 'SHA256)
-- ^ A regular file hashed like sha256sum.
| forall algo . NamedAlgorithm algo =>
FixedFile (HashMode algo) (Digest algo)
-- ^ A file hashed via the add-fixed-file-to-store approach.
-- This can in fact overlap with RegularFile (if the 'HashMode'
-- is 'Flat @SHA256'), but the resulting Nix store hash is
-- different for stupid legacy reasons.
-- | A specification of how to hash a file.
data HashMode (a :: HashAlgorithm)
= Flat -- ^ Normal hashing of a regular file.
| Recursive -- ^ Hashing of a serialization of a file, compatible
-- with directories and executable files as well as
-- regular files.
instance Hashable (StorePath store) where
hashWithSalt s (StorePath {..}) =
s `hashWithSalt` pathHash `hashWithSalt` pathName

View File

@ -1,48 +0,0 @@
{-|
Description : Utilities for packing stuff
Maintainer : srk <srk@48.io>
|-}
module System.Nix.Util where
import Control.Monad
import Data.Binary.Get
import Data.Binary.Put
import qualified Data.ByteString.Lazy as LBS
putInt :: Integral a => a -> Put
putInt = putWord64le . fromIntegral
getInt :: Integral a => Get a
getInt = fromIntegral <$> getWord64le
-- length prefixed string packing with padding to 8 bytes
putByteStringLen :: LBS.ByteString -> Put
putByteStringLen x = do
putInt $ fromIntegral $ len
putLazyByteString x
when (len `mod` 8 /= 0) $
pad $ fromIntegral $ 8 - (len `mod` 8)
where len = LBS.length x
pad x = forM_ (take x $ cycle [0]) putWord8
putByteStrings :: Foldable t => t LBS.ByteString -> Put
putByteStrings xs = do
putInt $ fromIntegral $ length xs
mapM_ putByteStringLen xs
getByteStringLen :: Get LBS.ByteString
getByteStringLen = do
len <- getInt
st <- getLazyByteString len
when (len `mod` 8 /= 0) $ do
pads <- unpad $ fromIntegral $ 8 - (len `mod` 8)
unless (all (==0) pads) $ fail $ "No zeroes" ++ show (st, len, pads)
return st
where unpad x = sequence $ replicate x getWord8
getByteStrings :: Get [LBS.ByteString]
getByteStrings = do
count <- getInt
res <- sequence $ replicate count getByteStringLen
return res

View File

@ -23,7 +23,7 @@ import Test.Tasty.QuickCheck
import Text.Read (readMaybe)
import System.Nix.Hash
import System.Nix.Path
import System.Nix.StorePath
import NarFormat -- TODO: Move the fixtures into a common module
spec_hash :: Spec
@ -41,5 +41,5 @@ spec_hash = do
let exampleStr =
"source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3"
<> "c0d7b98883f9ee3:/nix/store:myfile"
shouldBe (printAsBase32 @PathHashAlgo (hash exampleStr))
shouldBe (printAsBase32 @StorePathHashAlgo (hash exampleStr))
"xv2iccirbrvklck36f1g7vldn5v58vck"

View File

@ -33,7 +33,7 @@ import Test.Tasty.QuickCheck
import Text.Read (readMaybe)
import System.Nix.Nar
import System.Nix.Path
import System.Nix.StorePath

View File

@ -9,7 +9,7 @@ let
(map extract-external-inputs packages));
package-envs = builtins.listToAttrs (map (p: {
name = p;
value = haskellPackages.${p}.env;
value = (hslib.doCheck haskellPackages.${p}).env;
}) packages);
in (haskellPackages.mkDerivation {
pname = "hnix-store-core";