hnix-store-tests: init

Split from `-core` so it doesn't depend on quickcheck,
generic-arbitrary and quickcheck-instances that could propagate downstrem.
Also allows users to defined their own.

With all roundtrip property tests.

Later this should also absorb test nix-store/daemon harness from
`-remote` so it can be reused by others.
This commit is contained in:
Richard Marko 2023-11-19 18:01:55 +01:00
parent 6a6bbaadf9
commit 42f56f504f
35 changed files with 613 additions and 204 deletions

View File

@ -2,6 +2,7 @@ packages:
./hnix-store-core/hnix-store-core.cabal
./hnix-store-db/hnix-store-db.cabal
./hnix-store-remote/hnix-store-remote.cabal
./hnix-store-tests/hnix-store-tests.cabal
-- till https://github.com/obsidiansystems/dependent-sum/pull/80
allow-newer:

View File

@ -8,3 +8,6 @@ package hnix-store-db
package hnix-store-remote
ghc-options: -Wunused-packages -Wall -Werror
package hnix-store-tests
ghc-options: -Wunused-packages -Wall -Werror

View File

@ -22,7 +22,8 @@ in {
inherit (haskellPackages)
hnix-store-core
hnix-store-db
hnix-store-remote;
hnix-store-remote
hnix-store-tests;
haskellPackages = lib.dontRecurseIntoAttrs haskellPackages;
pkgs = lib.dontRecurseIntoAttrs pkgs;
}

View File

@ -89,7 +89,6 @@ library
, data-default-class
, dependent-sum > 0.7
, dependent-sum-template > 0.1.1 && < 0.3
, generic-arbitrary < 1.1
-- Required for cryptonite low-level type convertion
, memory
, cryptonite
@ -100,8 +99,6 @@ library
, monad-control
, mtl
, nix-derivation >= 1.1.1 && <2
, QuickCheck
, quickcheck-instances
, saltine >= 0.2 && < 0.3
, some > 1.0.5 && < 2
, time
@ -124,11 +121,8 @@ test-suite format-tests
main-is: Driver.hs
other-modules:
Derivation
DerivedPath
ContentAddress
NarFormat
Hash
StorePath
hs-source-dirs:
tests
build-tool-depends:
@ -147,7 +141,6 @@ test-suite format-tests
, directory
, filepath
, process
, nix-derivation >= 1.1.1 && <2
, tasty
, tasty-golden
, hspec

View File

@ -1,5 +1,3 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-|
Description : Build related types
Maintainer : srk <srk@48.io>
@ -14,15 +12,11 @@ module System.Nix.Build
import Data.Time (UTCTime)
import Data.Text (Text)
import GHC.Generics (Generic)
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import Test.QuickCheck.Instances ()
-- keep the order of these Enums to match enums from reference implementations
-- src/libstore/store-api.hh
data BuildMode = Normal | Repair | Check
deriving (Eq, Generic, Ord, Enum, Show)
deriving Arbitrary via GenericArbitrary BuildMode
data BuildStatus =
Built
@ -41,7 +35,6 @@ data BuildStatus =
| ResolvesToAlreadyValid
| NoSubstituters
deriving (Eq, Generic, Ord, Enum, Show)
deriving Arbitrary via GenericArbitrary BuildStatus
-- | Result of the build
data BuildResult = BuildResult
@ -59,7 +52,6 @@ data BuildResult = BuildResult
stopTime :: !UTCTime
}
deriving (Eq, Generic, Ord, Show)
deriving Arbitrary via GenericArbitrary BuildResult
buildSuccess :: BuildResult -> Bool
buildSuccess BuildResult {..} =

View File

@ -2,6 +2,8 @@
module System.Nix.ContentAddress (
ContentAddress
, ContentAddressMethod
, FileIngestionMethod
, contentAddressBuilder
, contentAddressParser
, buildContentAddress
@ -16,9 +18,6 @@ import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import GHC.Generics (Generic)
import System.Nix.Hash (HashAlgo)
import Test.QuickCheck (Arbitrary)
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import Test.QuickCheck.Instances ()
import qualified Data.Attoparsec.Text
import qualified Data.Text.Lazy
@ -30,9 +29,6 @@ data FileIngestionMethod
| FileRecursive
deriving (Eq, Bounded, Generic, Enum, Ord, Show)
deriving via GenericArbitrary FileIngestionMethod
instance Arbitrary FileIngestionMethod
data ContentAddressMethod
= FileIngestionMethod !FileIngestionMethod
-- ^ The path was added to the store via makeFixedOutputPath or
@ -44,9 +40,6 @@ data ContentAddressMethod
-- file contents.
deriving (Eq, Generic, Ord, Show)
deriving via GenericArbitrary ContentAddressMethod
instance Arbitrary ContentAddressMethod
-- | An address for a content-addressable store path, i.e. one whose
-- store path hash is purely a function of its contents (as opposed to
-- paths that are derivation outputs, whose hashes are a function of
@ -61,9 +54,6 @@ data ContentAddress = ContentAddress
(DSum HashAlgo Digest)
deriving (Eq, Generic, Ord, Show)
deriving via GenericArbitrary ContentAddress
instance Arbitrary ContentAddress
-- | Marshall `ContentAddressableAddress` to `Text`
-- in form suitable for remote protocol usage.
buildContentAddress :: ContentAddress -> Text

View File

@ -1,6 +1,3 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -Wno-orphans -fconstraint-solver-iterations=0 #-}
module System.Nix.Derivation
( parseDerivation
, buildDerivation
@ -12,9 +9,6 @@ module System.Nix.Derivation
import Data.Attoparsec.Text.Lazy (Parser)
import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import Test.QuickCheck.Instances ()
import Nix.Derivation (Derivation(..), DerivationOutput(..))
import System.Nix.StorePath (StoreDir, StorePath)
@ -27,11 +21,6 @@ import qualified Data.Text.Lazy.Builder
import qualified Nix.Derivation
import qualified System.Nix.StorePath
deriving via GenericArbitrary (Derivation StorePath Text)
instance Arbitrary (Derivation StorePath Text)
deriving via GenericArbitrary (DerivationOutput StorePath Text)
instance Arbitrary (DerivationOutput StorePath Text)
parseDerivation :: StoreDir -> Parser (Derivation StorePath Text)
parseDerivation expectedRoot =
Nix.Derivation.parseDerivationWith

View File

@ -14,8 +14,6 @@ import GHC.Generics (Generic)
import Data.Set (Set)
import Data.Text (Text)
import System.Nix.StorePath (StoreDir, StorePath, StorePathName, InvalidPathError)
import Test.QuickCheck (Arbitrary)
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import qualified Data.Set
import qualified Data.Text
@ -26,17 +24,11 @@ data OutputsSpec =
| OutputsSpec_Names (Set StorePathName)
deriving (Eq, Generic, Ord, Show)
deriving via GenericArbitrary OutputsSpec
instance Arbitrary OutputsSpec
data DerivedPath =
DerivedPath_Opaque StorePath
| DerivedPath_Built StorePath OutputsSpec
deriving (Eq, Generic, Ord, Show)
deriving via GenericArbitrary DerivedPath
instance Arbitrary DerivedPath
data ParseOutputsError =
ParseOutputsError_InvalidPath InvalidPathError
| ParseOutputsError_NoNames

View File

@ -37,8 +37,6 @@ import Data.Some (Some(Some))
import Data.Text (Text)
import Data.Text.Lazy.Builder (Builder)
import System.Nix.Base (BaseEncoding(..))
import Test.QuickCheck (Arbitrary(arbitrary), oneof)
import Test.QuickCheck.Instances ()
import qualified Crypto.Hash
import qualified Data.ByteArray
@ -64,20 +62,6 @@ instance NamedAlgo SHA256 where
instance NamedAlgo SHA512 where
algoName = "sha512"
-- * Arbitrary @Digest@s
instance Arbitrary (Digest MD5) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA1) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA256) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA512) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
data HashAlgo :: Type -> Type where
HashAlgo_MD5 :: HashAlgo MD5
HashAlgo_SHA1 :: HashAlgo SHA1
@ -107,14 +91,6 @@ textToAlgo = \case
"sha512" -> Right $ Some HashAlgo_SHA512
name -> Left $ "Unknown hash name: " <> Data.Text.unpack name
instance Arbitrary (DSum HashAlgo Digest) where
arbitrary = oneof
[ (HashAlgo_MD5 :=>) <$> arbitrary
, (HashAlgo_SHA1 :=>) <$> arbitrary
, (HashAlgo_SHA256 :=>) <$> arbitrary
, (HashAlgo_SHA512 :=>) <$> arbitrary
]
-- | Make @DSum HashAlgo Digest@ based on provided SRI hash name
-- and its encoded form
mkNamedDigest

View File

@ -1,5 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-|
@ -32,11 +31,8 @@ module System.Nix.StorePath
, pathParser
) where
#if !MIN_VERSION_base(4,18,0)
import Control.Applicative (liftA2)
#endif
import Control.Monad.Reader.Class (MonadReader, asks)
import Crypto.Hash (HashAlgorithm, SHA256)
import Crypto.Hash (HashAlgorithm)
import Data.Attoparsec.Text.Lazy (Parser, (<?>))
import Data.ByteString (ByteString)
import Data.Default.Class (Default(def))
@ -44,7 +40,6 @@ import Data.Hashable (Hashable(hashWithSalt))
import Data.Text (Text)
import GHC.Generics (Generic)
import System.Nix.Base (BaseEncoding(NixBase32))
import Test.QuickCheck (Arbitrary(arbitrary), listOf, elements)
import qualified Data.Bifunctor
import qualified Data.ByteString.Char8
@ -81,12 +76,6 @@ instance Hashable StorePath where
hashWithSalt s StorePath{..} =
s `hashWithSalt` storePathHash `hashWithSalt` storePathName
instance Arbitrary StorePath where
arbitrary =
liftA2 StorePath
arbitrary
arbitrary
-- | The name portion of a Nix path.
--
-- 'unStorePathName' must only contain a-zA-Z0-9+._?=-, can't start
@ -97,13 +86,6 @@ newtype StorePathName = StorePathName
unStorePathName :: Text
} deriving (Eq, Generic, Hashable, Ord, Show)
instance Arbitrary StorePathName where
arbitrary = StorePathName . Data.Text.pack <$> ((:) <$> s1 <*> listOf sn)
where
alphanum = ['a' .. 'z'] <> ['A' .. 'Z'] <> ['0' .. '9']
s1 = elements $ alphanum <> "+-_?="
sn = elements $ alphanum <> "+-._?="
-- | The hash algorithm used for store path hashes.
newtype StorePathHashPart = StorePathHashPart
{ -- | Extract the contents of the hash.
@ -111,11 +93,6 @@ newtype StorePathHashPart = StorePathHashPart
}
deriving (Eq, Generic, Hashable, Ord, Show)
instance Arbitrary StorePathHashPart where
arbitrary =
mkStorePathHashPart @SHA256
. Data.ByteString.Char8.pack <$> arbitrary
-- | Make @StorePathHashPart@ from @ByteString@ (hash part of the @StorePath@)
-- using specific @HashAlgorithm@
mkStorePathHashPart
@ -183,12 +160,6 @@ newtype StoreDir = StoreDir {
unStoreDir :: RawFilePath
} deriving (Eq, Generic, Hashable, Ord, Show)
instance Arbitrary StoreDir where
arbitrary =
StoreDir
. ("/" <>) -- TODO(srk): nasty, see #237
. Data.ByteString.Char8.pack <$> arbitrary
instance Default StoreDir where
def = StoreDir "/nix/store"

View File

@ -1,18 +1,21 @@
module ContentAddress where
module ContentAddressSpec where
import Test.Tasty.QuickCheck
import System.Nix.ContentAddress (ContentAddress)
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec.QuickCheck (prop)
import System.Nix.Arbitrary ()
import qualified Data.Attoparsec.Text.Lazy
import qualified Data.Text.Lazy.Builder
import qualified System.Nix.ContentAddress
prop_caAddrRoundTrip :: ContentAddress -> Property
prop_caAddrRoundTrip = \caAddr ->
Data.Attoparsec.Text.Lazy.parseOnly
System.Nix.ContentAddress.contentAddressParser
(Data.Text.Lazy.Builder.toLazyText
(System.Nix.ContentAddress.contentAddressBuilder caAddr))
=== pure caAddr
spec :: Spec
spec = do
describe "ContentAddress" $ do
prop "roundtrips" $ \caAddr ->
Data.Attoparsec.Text.Lazy.parseOnly
System.Nix.ContentAddress.contentAddressParser
(Data.Text.Lazy.Builder.toLazyText
(System.Nix.ContentAddress.contentAddressBuilder caAddr))
`shouldBe` pure caAddr

View File

@ -1,18 +1,10 @@
module Derivation where
import Data.Text (Text)
import Test.Tasty ( TestTree
, testGroup
)
import Test.Tasty.Golden ( goldenVsFile )
import Test.Tasty.QuickCheck
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Golden (goldenVsFile)
import Nix.Derivation ( Derivation )
import System.Nix.StorePath ( StoreDir(..), StorePath )
import System.Nix.Derivation ( parseDerivation
, buildDerivation
)
import System.Nix.Derivation (parseDerivation, buildDerivation)
import Data.Default.Class (Default(def))
import qualified Data.Attoparsec.Text
@ -50,17 +42,3 @@ test_derivation =
drv = fp <> show n <> ".drv"
act = fp <> show n <> ".actual"
fp = "tests/samples/example"
-- TODO(srk): this won't roundtrip as Arbitrary Text
-- contains wild stuff like control characters and UTF8 sequences.
-- Either fix in nix-derivation or use wrapper type
-- (but we use Nix.Derivation.textParser so we need Text for now)
xprop_derivationRoundTrip :: StoreDir -> Derivation StorePath Text -> Property
xprop_derivationRoundTrip = \sd drv ->
Data.Attoparsec.Text.parseOnly (parseDerivation sd)
( Data.Text.Lazy.toStrict
$ Data.Text.Lazy.Builder.toLazyText
$ buildDerivation sd drv
)
=== pure drv

View File

@ -1,19 +0,0 @@
module DerivedPath where
import Data.Default.Class (Default(def))
import Test.Tasty.QuickCheck
import System.Nix.DerivedPath (DerivedPath(..), OutputsSpec(..))
import qualified Data.Set
import qualified System.Nix.DerivedPath
prop_derivedPathRoundTrip :: Property
prop_derivedPathRoundTrip = forAll (arbitrary `suchThat` nonEmptyOutputsSpec_Names) $ \p ->
System.Nix.DerivedPath.parseDerivedPath def
(System.Nix.DerivedPath.derivedPathToText def p)
=== pure p
where
nonEmptyOutputsSpec_Names :: DerivedPath -> Bool
nonEmptyOutputsSpec_Names (DerivedPath_Built _ (OutputsSpec_Names set)) =
not $ Data.Set.null set
nonEmptyOutputsSpec_Names _ = True

View File

@ -6,23 +6,17 @@ module Hash where
import Data.ByteString (ByteString)
import Control.Monad
import Crypto.Hash (MD5, SHA1, SHA256, hash)
import qualified Data.ByteString.Base16 as B16
import qualified System.Nix.Base32 as B32
import qualified Data.ByteString.Base64.Lazy as B64
import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Lazy as BSL
import Test.Hspec
import Test.Tasty.QuickCheck
import System.Nix.Hash
import System.Nix.StorePath
import System.Nix.Base
import Crypto.Hash ( MD5
, SHA1
, SHA256
, hash
)
import System.Nix.Base
import System.Nix.Hash
import System.Nix.StorePath
import Test.Hspec
spec_hash :: Spec
spec_hash = do
@ -45,22 +39,6 @@ spec_hash = do
shouldBe (encodeWith NixBase32 $ unStorePathHashPart $ mkStorePathHashPart @SHA256 "source:sha256:2bfef67de873c54551d884fdab3055d84d573e654efa79db3c0d7b98883f9ee3:/nix/store:myfile")
"xv2iccirbrvklck36f1g7vldn5v58vck"
-- | Test that Nix-like base32 encoding roundtrips
prop_nixBase32Roundtrip :: Property
prop_nixBase32Roundtrip = forAllShrink nonEmptyString genericShrink $
\x -> pure (BSC.pack x) === (B32.decode . B32.encode . BSC.pack $ x)
where
nonEmptyString :: Gen String
nonEmptyString = listOf1 genSafeChar
genSafeChar :: Gen Char
genSafeChar = choose ('\1', '\127') -- ASCII without \NUL
-- | API variants
prop_nixBase16Roundtrip :: StorePathHashPart -> Property
prop_nixBase16Roundtrip x =
pure (unStorePathHashPart x) === decodeWith Base16 (encodeWith Base16 $ unStorePathHashPart x)
-- | Hash encoding conversion ground-truth.
-- Similiar to nix/tests/hash.sh
spec_nixhash :: Spec

View File

@ -1,22 +0,0 @@
module StorePath where
import qualified Data.Attoparsec.Text
import Test.Tasty.QuickCheck
import System.Nix.StorePath
-- | Test @StorePath@ roundtrips using @parsePath@
prop_storePathRoundtrip :: StoreDir -> StorePath -> Property
prop_storePathRoundtrip storeDir x =
parsePath storeDir (storePathToRawFilePath storeDir x) === pure x
-- | Test @StorePath@ roundtrips using @parsePathFromText@
prop_storePathFromTextRoundtrip :: StoreDir -> StorePath -> Property
prop_storePathFromTextRoundtrip storeDir x =
parsePathFromText storeDir (storePathToText storeDir x) === pure x
-- | Test @StorePath@ roundtrips using @pathParser@
prop_storePathRoundtripParser :: StoreDir -> StorePath -> Property
prop_storePathRoundtripParser storeDir x =
Data.Attoparsec.Text.parseOnly (pathParser storeDir) (storePathToText storeDir x) === pure x

View File

@ -116,6 +116,7 @@ test-suite remote
base >=4.12 && <5
, hnix-store-core
, hnix-store-remote
, hnix-store-tests
, bytestring
, cereal
, text

View File

@ -20,6 +20,7 @@ import qualified Data.HashSet
import qualified Data.Time.Clock.POSIX
import qualified System.Nix.Build
import System.Nix.Arbitrary ()
import System.Nix.Build (BuildMode, BuildStatus)
import System.Nix.Derivation (Derivation(..))
import System.Nix.StorePath (StoreDir, StorePath)

View File

@ -0,0 +1,10 @@
# Version [0.1.0.0](https://github.com/haskell-nix/hnix-store/compare/tests-0.1.0.0...tests-0.1.1.0) (2023-11-27)
* Initial release
---
`hnix-store-tests` uses [PVP Versioning][1].
[1]: https://pvp.haskell.org

201
hnix-store-tests/LICENSE Normal file
View File

@ -0,0 +1,201 @@
Apache License
Version 2.0, January 2004
http://www.apache.org/licenses/
TERMS AND CONDITIONS FOR USE, REPRODUCTION, AND DISTRIBUTION
1. Definitions.
"License" shall mean the terms and conditions for use, reproduction,
and distribution as defined by Sections 1 through 9 of this document.
"Licensor" shall mean the copyright owner or entity authorized by
the copyright owner that is granting the License.
"Legal Entity" shall mean the union of the acting entity and all
other entities that control, are controlled by, or are under common
control with that entity. For the purposes of this definition,
"control" means (i) the power, direct or indirect, to cause the
direction or management of such entity, whether by contract or
otherwise, or (ii) ownership of fifty percent (50%) or more of the
outstanding shares, or (iii) beneficial ownership of such entity.
"You" (or "Your") shall mean an individual or Legal Entity
exercising permissions granted by this License.
"Source" form shall mean the preferred form for making modifications,
including but not limited to software source code, documentation
source, and configuration files.
"Object" form shall mean any form resulting from mechanical
transformation or translation of a Source form, including but
not limited to compiled object code, generated documentation,
and conversions to other media types.
"Work" shall mean the work of authorship, whether in Source or
Object form, made available under the License, as indicated by a
copyright notice that is included in or attached to the work
(an example is provided in the Appendix below).
"Derivative Works" shall mean any work, whether in Source or Object
form, that is based on (or derived from) the Work and for which the
editorial revisions, annotations, elaborations, or other modifications
represent, as a whole, an original work of authorship. For the purposes
of this License, Derivative Works shall not include works that remain
separable from, or merely link (or bind by name) to the interfaces of,
the Work and Derivative Works thereof.
"Contribution" shall mean any work of authorship, including
the original version of the Work and any modifications or additions
to that Work or Derivative Works thereof, that is intentionally
submitted to Licensor for inclusion in the Work by the copyright owner
or by an individual or Legal Entity authorized to submit on behalf of
the copyright owner. For the purposes of this definition, "submitted"
means any form of electronic, verbal, or written communication sent
to the Licensor or its representatives, including but not limited to
communication on electronic mailing lists, source code control systems,
and issue tracking systems that are managed by, or on behalf of, the
Licensor for the purpose of discussing and improving the Work, but
excluding communication that is conspicuously marked or otherwise
designated in writing by the copyright owner as "Not a Contribution."
"Contributor" shall mean Licensor and any individual or Legal Entity
on behalf of whom a Contribution has been received by Licensor and
subsequently incorporated within the Work.
2. Grant of Copyright License. Subject to the terms and conditions of
this License, each Contributor hereby grants to You a perpetual,
worldwide, non-exclusive, no-charge, royalty-free, irrevocable
copyright license to reproduce, prepare Derivative Works of,
publicly display, publicly perform, sublicense, and distribute the
Work and such Derivative Works in Source or Object form.
3. Grant of Patent License. Subject to the terms and conditions of
this License, each Contributor hereby grants to You a perpetual,
worldwide, non-exclusive, no-charge, royalty-free, irrevocable
(except as stated in this section) patent license to make, have made,
use, offer to sell, sell, import, and otherwise transfer the Work,
where such license applies only to those patent claims licensable
by such Contributor that are necessarily infringed by their
Contribution(s) alone or by combination of their Contribution(s)
with the Work to which such Contribution(s) was submitted. If You
institute patent litigation against any entity (including a
cross-claim or counterclaim in a lawsuit) alleging that the Work
or a Contribution incorporated within the Work constitutes direct
or contributory patent infringement, then any patent licenses
granted to You under this License for that Work shall terminate
as of the date such litigation is filed.
4. Redistribution. You may reproduce and distribute copies of the
Work or Derivative Works thereof in any medium, with or without
modifications, and in Source or Object form, provided that You
meet the following conditions:
(a) You must give any other recipients of the Work or
Derivative Works a copy of this License; and
(b) You must cause any modified files to carry prominent notices
stating that You changed the files; and
(c) You must retain, in the Source form of any Derivative Works
that You distribute, all copyright, patent, trademark, and
attribution notices from the Source form of the Work,
excluding those notices that do not pertain to any part of
the Derivative Works; and
(d) If the Work includes a "NOTICE" text file as part of its
distribution, then any Derivative Works that You distribute must
include a readable copy of the attribution notices contained
within such NOTICE file, excluding those notices that do not
pertain to any part of the Derivative Works, in at least one
of the following places: within a NOTICE text file distributed
as part of the Derivative Works; within the Source form or
documentation, if provided along with the Derivative Works; or,
within a display generated by the Derivative Works, if and
wherever such third-party notices normally appear. The contents
of the NOTICE file are for informational purposes only and
do not modify the License. You may add Your own attribution
notices within Derivative Works that You distribute, alongside
or as an addendum to the NOTICE text from the Work, provided
that such additional attribution notices cannot be construed
as modifying the License.
You may add Your own copyright statement to Your modifications and
may provide additional or different license terms and conditions
for use, reproduction, or distribution of Your modifications, or
for any such Derivative Works as a whole, provided Your use,
reproduction, and distribution of the Work otherwise complies with
the conditions stated in this License.
5. Submission of Contributions. Unless You explicitly state otherwise,
any Contribution intentionally submitted for inclusion in the Work
by You to the Licensor shall be under the terms and conditions of
this License, without any additional terms or conditions.
Notwithstanding the above, nothing herein shall supersede or modify
the terms of any separate license agreement you may have executed
with Licensor regarding such Contributions.
6. Trademarks. This License does not grant permission to use the trade
names, trademarks, service marks, or product names of the Licensor,
except as required for reasonable and customary use in describing the
origin of the Work and reproducing the content of the NOTICE file.
7. Disclaimer of Warranty. Unless required by applicable law or
agreed to in writing, Licensor provides the Work (and each
Contributor provides its Contributions) on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or
implied, including, without limitation, any warranties or conditions
of TITLE, NON-INFRINGEMENT, MERCHANTABILITY, or FITNESS FOR A
PARTICULAR PURPOSE. You are solely responsible for determining the
appropriateness of using or redistributing the Work and assume any
risks associated with Your exercise of permissions under this License.
8. Limitation of Liability. In no event and under no legal theory,
whether in tort (including negligence), contract, or otherwise,
unless required by applicable law (such as deliberate and grossly
negligent acts) or agreed to in writing, shall any Contributor be
liable to You for damages, including any direct, indirect, special,
incidental, or consequential damages of any character arising as a
result of this License or out of the use or inability to use the
Work (including but not limited to damages for loss of goodwill,
work stoppage, computer failure or malfunction, or any and all
other commercial damages or losses), even if such Contributor
has been advised of the possibility of such damages.
9. Accepting Warranty or Additional Liability. While redistributing
the Work or Derivative Works thereof, You may choose to offer,
and charge a fee for, acceptance of support, warranty, indemnity,
or other liability obligations and/or rights consistent with this
License. However, in accepting such obligations, You may act only
on Your own behalf and on Your sole responsibility, not on behalf
of any other Contributor, and only if You agree to indemnify,
defend, and hold each Contributor harmless for any liability
incurred by, or claims asserted against, such Contributor by reason
of your accepting any such warranty or additional liability.
END OF TERMS AND CONDITIONS
APPENDIX: How to apply the Apache License to your work.
To apply the Apache License to your work, attach the following
boilerplate notice, with the fields enclosed by brackets "[]"
replaced with your own identifying information. (Don't include
the brackets!) The text should be enclosed in the appropriate
comment syntax for the file format. We also recommend that a
file or class name and description of purpose be included on the
same "printed page" as the copyright notice for easier
identification within third-party archives.
Copyright 2018 Shea Levy.
Licensed under the Apache License, Version 2.0 (the "License");
you may not use this file except in compliance with the License.
You may obtain a copy of the License at
http://www.apache.org/licenses/LICENSE-2.0
Unless required by applicable law or agreed to in writing, software
distributed under the License is distributed on an "AS IS" BASIS,
WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
See the License for the specific language governing permissions and
limitations under the License.

View File

@ -0,0 +1,7 @@
# hnix-store-tests
Arbitrary instances for core types, roundtrip property tests, utility functions
and a harness for running tests that require nix-store
with nix-daemon.
[Test.Hspec.Nix]: ./src/Test/Hspec/Nix.hs

View File

@ -0,0 +1,81 @@
cabal-version: 2.2
name: hnix-store-tests
version: 0.1.0.0
synopsis: Test utilities and instances
description:
This package contains Arbitrary instances for core
types, roundtrip property tests, utility functions
and a harness for running tests that require nix-store
with nix-daemon.
homepage: https://github.com/haskell-nix/hnix-store
license: Apache-2.0
license-file: LICENSE
author: Richard Marko
maintainer: srk@48.io
copyright: 2023 Richard Marko
category: Nix
build-type: Simple
extra-source-files:
CHANGELOG.md
, README.md
common commons
ghc-options: -Wall
default-extensions:
DerivingStrategies
, DerivingVia
, FlexibleInstances
, ScopedTypeVariables
, StandaloneDeriving
, RecordWildCards
, TypeApplications
, LambdaCase
default-language: Haskell2010
library
import: commons
exposed-modules:
System.Nix.Arbitrary
, System.Nix.Arbitrary.Build
, System.Nix.Arbitrary.ContentAddress
, System.Nix.Arbitrary.Derivation
, System.Nix.Arbitrary.DerivedPath
, System.Nix.Arbitrary.Hash
, System.Nix.Arbitrary.StorePath
build-depends:
base >=4.12 && <5
, hnix-store-core
, bytestring
, cryptonite
, dependent-sum > 0.7
, generic-arbitrary < 1.1
, QuickCheck
, quickcheck-instances
, text
hs-source-dirs: src
test-suite props
import: commons
type: exitcode-stdio-1.0
main-is: Spec.hs
other-modules:
BaseEncodingSpec
ContentAddressSpec
DerivationSpec
DerivedPathSpec
StorePathSpec
hs-source-dirs:
tests
build-tool-depends:
hspec-discover:hspec-discover
build-depends:
base
, hnix-store-core
, hnix-store-tests
, attoparsec
, bytestring
, containers
, data-default-class
, QuickCheck
, text
, hspec

View File

@ -0,0 +1,8 @@
module System.Nix.Arbitrary where
import System.Nix.Arbitrary.Build ()
import System.Nix.Arbitrary.ContentAddress ()
import System.Nix.Arbitrary.Derivation ()
import System.Nix.Arbitrary.DerivedPath ()
import System.Nix.Arbitrary.Hash ()
import System.Nix.Arbitrary.StorePath ()

View File

@ -0,0 +1,19 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.Build where
import System.Nix.Build
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import Test.QuickCheck.Instances ()
deriving via GenericArbitrary BuildMode
instance Arbitrary BuildMode
deriving via GenericArbitrary BuildStatus
instance Arbitrary BuildStatus
deriving via GenericArbitrary BuildResult
instance Arbitrary BuildResult

View File

@ -0,0 +1,19 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.ContentAddress where
import System.Nix.Arbitrary.Hash ()
import System.Nix.ContentAddress (FileIngestionMethod, ContentAddress, ContentAddressMethod)
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
deriving via GenericArbitrary FileIngestionMethod
instance Arbitrary FileIngestionMethod
deriving via GenericArbitrary ContentAddressMethod
instance Arbitrary ContentAddressMethod
deriving via GenericArbitrary ContentAddress
instance Arbitrary ContentAddress

View File

@ -0,0 +1,18 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.Derivation where
import Data.Text (Text)
import System.Nix.Derivation
import System.Nix.StorePath (StorePath)
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import Test.QuickCheck.Instances ()
import System.Nix.Arbitrary.StorePath ()
deriving via GenericArbitrary (Derivation StorePath Text)
instance Arbitrary (Derivation StorePath Text)
deriving via GenericArbitrary (DerivationOutput StorePath Text)
instance Arbitrary (DerivationOutput StorePath Text)

View File

@ -0,0 +1,15 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.DerivedPath where
import Test.QuickCheck (Arbitrary)
import Test.QuickCheck.Arbitrary.Generic (GenericArbitrary(..))
import System.Nix.Arbitrary.StorePath ()
import System.Nix.DerivedPath (DerivedPath, OutputsSpec)
deriving via GenericArbitrary OutputsSpec
instance Arbitrary OutputsSpec
deriving via GenericArbitrary DerivedPath
instance Arbitrary DerivedPath

View File

@ -0,0 +1,38 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.Hash where
import Data.ByteString (ByteString)
import Crypto.Hash (Digest, MD5(..), SHA1(..), SHA256(..), SHA512(..))
import Data.Dependent.Sum (DSum((:=>)))
import System.Nix.Hash (HashAlgo(..))
import Test.QuickCheck (Arbitrary(arbitrary), oneof)
import Test.QuickCheck.Instances ()
import qualified Crypto.Hash
-- * Arbitrary @Digest@s
instance Arbitrary (Digest MD5) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA1) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA256) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
instance Arbitrary (Digest SHA512) where
arbitrary = Crypto.Hash.hash @ByteString <$> arbitrary
-- * Arbitrary @DSum HashAlgo Digest@s
instance Arbitrary (DSum HashAlgo Digest) where
arbitrary = oneof
[ (HashAlgo_MD5 :=>) <$> arbitrary
, (HashAlgo_SHA1 :=>) <$> arbitrary
, (HashAlgo_SHA256 :=>) <$> arbitrary
, (HashAlgo_SHA512 :=>) <$> arbitrary
]

View File

@ -0,0 +1,45 @@
-- due to recent generic-arbitrary
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module System.Nix.Arbitrary.StorePath where
#if !MIN_VERSION_base(4,18,0)
import Control.Applicative (liftA2)
#endif
import Crypto.Hash (SHA256)
import qualified Data.ByteString.Char8
import qualified Data.Text
import System.Nix.StorePath (StoreDir(..)
, StorePath(..)
, StorePathName(..)
, StorePathHashPart(..)
)
import qualified System.Nix.StorePath
import Test.QuickCheck (Arbitrary(arbitrary), listOf, elements)
instance Arbitrary StoreDir where
arbitrary =
StoreDir
. (Data.ByteString.Char8.singleton '/' <>) -- TODO(srk): nasty, see #237
. Data.ByteString.Char8.pack <$> arbitrary
instance Arbitrary StorePath where
arbitrary =
liftA2 StorePath
arbitrary
arbitrary
instance Arbitrary StorePathName where
arbitrary = StorePathName . Data.Text.pack <$> ((:) <$> s1 <*> listOf sn)
where
alphanum = ['a' .. 'z'] <> ['A' .. 'Z'] <> ['0' .. '9']
s1 = elements $ alphanum <> "+-_?="
sn = elements $ alphanum <> "+-._?="
instance Arbitrary StorePathHashPart where
arbitrary =
-- TODO(srk): other hashes
System.Nix.StorePath.mkStorePathHashPart @SHA256
. Data.ByteString.Char8.pack <$> arbitrary

View File

@ -0,0 +1,33 @@
module BaseEncodingSpec where
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Gen, choose, listOf1, forAllShrink, genericShrink)
import System.Nix.Base
import System.Nix.Arbitrary ()
import System.Nix.StorePath (StorePathHashPart(..))
import qualified Data.ByteString.Char8
import qualified System.Nix.Base32
spec :: Spec
spec = do
describe "Hash" $ do
prop "Nix-like Base32 roundtrips" $
-- TODO(srk): use decodeWith
forAllShrink nonEmptyString genericShrink $ \x ->
(System.Nix.Base32.decode
. System.Nix.Base32.encode
. Data.ByteString.Char8.pack $ x)
`shouldBe`
pure (Data.ByteString.Char8.pack x)
prop "Base16 roundtrips" $ \x ->
decodeWith Base16 (encodeWith Base16 $ unStorePathHashPart x)
`shouldBe`
pure (unStorePathHashPart x)
where
nonEmptyString :: Gen String
nonEmptyString = listOf1 genSafeChar
genSafeChar :: Gen Char
genSafeChar = choose ('\1', '\127') -- ASCII without \NUL

View File

@ -0,0 +1,27 @@
module DerivationSpec where
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec.QuickCheck (xprop)
import System.Nix.Arbitrary ()
import System.Nix.Derivation (parseDerivation, buildDerivation)
import qualified Data.Attoparsec.Text
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Builder
-- TODO(srk): this won't roundtrip as Arbitrary Text
-- contains wild stuff like control characters and UTF8 sequences.
-- Either fix in nix-derivation or use wrapper type
-- (but we use Nix.Derivation.textParser so we need Text for now)
spec :: Spec
spec = do
describe "Derivation" $ do
xprop "roundtrips via Text" $ \sd drv ->
Data.Attoparsec.Text.parseOnly (parseDerivation sd)
( Data.Text.Lazy.toStrict
$ Data.Text.Lazy.Builder.toLazyText
$ buildDerivation sd drv
)
`shouldBe` pure drv

View File

@ -0,0 +1,26 @@
module DerivedPathSpec where
import Data.Default.Class (Default(def))
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (Arbitrary(arbitrary), forAll, suchThat)
import System.Nix.Arbitrary ()
import System.Nix.DerivedPath (DerivedPath(..), OutputsSpec(..))
import qualified Data.Set
import qualified System.Nix.DerivedPath
spec :: Spec
spec = do
describe "DerivedPath" $ do
prop "roundtrips" $
forAll (arbitrary `suchThat` nonEmptyOutputsSpec_Names) $ \p ->
System.Nix.DerivedPath.parseDerivedPath def
(System.Nix.DerivedPath.derivedPathToText def p)
`shouldBe` pure p
where
nonEmptyOutputsSpec_Names :: DerivedPath -> Bool
nonEmptyOutputsSpec_Names (DerivedPath_Built _ (OutputsSpec_Names set)) =
not $ Data.Set.null set
nonEmptyOutputsSpec_Names _ = True

View File

@ -0,0 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover #-}

View File

@ -0,0 +1,26 @@
module StorePathSpec where
import Test.Hspec (Spec, describe, shouldBe)
import Test.Hspec.QuickCheck (prop)
import System.Nix.Arbitrary ()
import System.Nix.StorePath
import qualified Data.Attoparsec.Text
spec :: Spec
spec = do
describe "StorePath" $ do
prop "roundtrips using parsePath . storePathToRawFilePath" $
\storeDir x ->
parsePath storeDir (storePathToRawFilePath storeDir x) `shouldBe` pure x
prop "roundtrips using parsePathFromText . storePathToText" $
\storeDir x ->
parsePathFromText storeDir (storePathToText storeDir x) `shouldBe` pure x
prop "roundtrips using pathParser . storePathToText" $
\storeDir x ->
Data.Attoparsec.Text.parseOnly
(pathParser storeDir)
(storePathToText storeDir x) `shouldBe` pure x

View File

@ -76,4 +76,10 @@ in
];
}))
];
hnix-store-tests =
lib.pipe
(hself.callCabal2nix "hnix-store-tests" ./hnix-store-tests {})
[
haskellLib.compose.buildFromSdist
];
}

View File

@ -7,6 +7,7 @@ let
"hnix-store-core"
"hnix-store-db"
"hnix-store-remote"
"hnix-store-tests"
];
extract-external-inputs = p:
builtins.filter