Skip to content

Commit

Permalink
Merge pull request #231 from sorki/srk/cereal
Browse files Browse the repository at this point in the history
remote: start transitioning from binary to cereal
  • Loading branch information
sorki authored Nov 17, 2023
2 parents 4734067 + cefbca3 commit 3b06982
Show file tree
Hide file tree
Showing 31 changed files with 920 additions and 274 deletions.
8 changes: 7 additions & 1 deletion cabal.project
Original file line number Diff line number Diff line change
@@ -1 +1,7 @@
packages: ./hnix-store-core/*.cabal ./hnix-store-remote/*.cabal
packages:
./hnix-store-core/hnix-store-core.cabal
./hnix-store-remote/hnix-store-remote.cabal

package hnix-store-remote
flags: +build-readme +io-testsuite

2 changes: 0 additions & 2 deletions cabal.project.local.ci
Original file line number Diff line number Diff line change
@@ -1,7 +1,5 @@
tests: True

flags: +io-testsuite

package hnix-store-core
ghc-options: -Wunused-packages -Wall

Expand Down
16 changes: 16 additions & 0 deletions hnix-store-core/CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,16 +1,32 @@
# Next

* Changes:
* `StorePathMetadata` converted to `Metadata a` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* Constructors of `StorePathName` and `StorePathHashPart` are no longer
exported. Use respective `mkStorePath..` functions. [#230](https://github.com/haskell-nix/hnix-store/pull/230)
* `StorePathSet` type alias is no more, use `HashSet StorePath` [#230](https://github.com/haskell-nix/hnix-store/pull/230)
* `makeStorePath` and `parsePath` now returns `Either InvalidPathError StorePath` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* `BuildResult`s `timesBuild` field changes type from `Integer` to `Int` [#231](https://github.com/haskell-nix/hnix-store/pull/231)

* Additions:
* `Default StoreDir` instance [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* `System.Nix.StorePath.storePathHashPartToText` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* Added `Generic` and `Show` instances for
`Signature` and `NarSignature` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* Added `Eq` and `Ord` instances for `SomeNamedDigest` [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* `BuildStatus` grows `NoSubstituters` and `ResolvesToAlreadyValid` constructors [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* `InvalidPathError` replacing previous stringy error [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* Added `Arbitrary` instances for (exported by default) [#230](https://github.com/haskell-nix/hnix-store/pull/230)
* `StorePath`
* `StorePathName`
* `StorePathHashPart`
* `StoreDir`
* Added `Arbitrary` instances for [#231](https://github.com/haskell-nix/hnix-store/pull/231)
* `BuildMode`
* `BuildStatus`
* `BuildResult`
* `Derivation StorePath Text`
* `DerivationOutput StorePath Text`

# [0.7.0.0](https://github.com/haskell-nix/hnix-store/compare/core-0.6.1.0...core-0.7.0.0) 2023-11-15

Expand Down
1 change: 0 additions & 1 deletion hnix-store-core/cabal.project

This file was deleted.

10 changes: 10 additions & 0 deletions hnix-store-core/hnix-store-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -60,6 +60,8 @@ library
, case-insensitive
, cereal
, containers
, data-default-class
, generic-arbitrary < 1.1
-- Required for cryptonite low-level type convertion
, memory
, cryptonite
Expand All @@ -71,6 +73,7 @@ library
, mtl
, nix-derivation >= 1.1.1 && <2
, QuickCheck
, quickcheck-instances
, saltine
, time
, text
Expand All @@ -89,9 +92,13 @@ library
, DeriveFoldable
, DeriveTraversable
, DeriveLift
, DerivingStrategies
, DerivingVia
, FlexibleContexts
, FlexibleInstances
, StandaloneDeriving
, ScopedTypeVariables
, RecordWildCards
, TypeApplications
, TypeSynonymInstances
, InstanceSigs
Expand All @@ -116,6 +123,7 @@ test-suite format-tests
main-is: Driver.hs
other-modules:
Derivation
ContentAddressableAddress
NarFormat
Hash
StorePath
Expand All @@ -134,9 +142,11 @@ test-suite format-tests
, bytestring
, containers
, cryptonite
, data-default-class
, directory
, filepath
, process
, nix-derivation >= 1.1.1 && <2
, tasty
, tasty-golden
, hspec
Expand Down
25 changes: 16 additions & 9 deletions hnix-store-core/src/System/Nix/Build.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# language RecordWildCards #-}
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -fconstraint-solver-iterations=0 #-}
{-|
Description : Build related types
Maintainer : srk <srk@48.io>
Expand All @@ -8,15 +9,18 @@ module System.Nix.Build
, BuildStatus(..)
, BuildResult(..)
, buildSuccess
)
where
) where

import Data.Time ( UTCTime )
import Data.Time (UTCTime)
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, Ord, Enum, Show)
deriving (Eq, Generic, Ord, Enum, Show)
deriving Arbitrary via GenericArbitrary BuildMode

data BuildStatus =
Built
Expand All @@ -32,8 +36,10 @@ data BuildStatus =
| DependencyFailed
| LogLimitExceeded
| NotDeterministic
deriving (Eq, Ord, Enum, Show)

| ResolvesToAlreadyValid
| NoSubstituters
deriving (Eq, Generic, Ord, Enum, Show)
deriving Arbitrary via GenericArbitrary BuildStatus

-- | Result of the build
data BuildResult = BuildResult
Expand All @@ -42,15 +48,16 @@ data BuildResult = BuildResult
, -- | possible build error message
errorMessage :: !(Maybe Text)
, -- | How many times this build was performed
timesBuilt :: !Integer
timesBuilt :: !Int
, -- | If timesBuilt > 1, whether some builds did not produce the same result
isNonDeterministic :: !Bool
, -- Start time of this build
startTime :: !UTCTime
, -- Stop time of this build
stopTime :: !UTCTime
}
deriving (Eq, Ord, Show)
deriving (Eq, Generic, Ord, Show)
deriving Arbitrary via GenericArbitrary BuildResult

buildSuccess :: BuildResult -> Bool
buildSuccess BuildResult {..} =
Expand Down
56 changes: 36 additions & 20 deletions hnix-store-core/src/System/Nix/Derivation.hs
Original file line number Diff line number Diff line change
@@ -1,32 +1,48 @@
-- due to recent generic-arbitrary
{-# OPTIONS_GHC -Wno-orphans -fconstraint-solver-iterations=0 #-}

module System.Nix.Derivation
( parseDerivation
, buildDerivation
)
where
) where

import qualified Data.Text.Lazy.Builder as Text.Lazy
( Builder )
import qualified Data.Attoparsec.Text.Lazy as Text.Lazy
( Parser )
import Nix.Derivation ( Derivation )
import qualified Nix.Derivation as Derivation
import System.Nix.StorePath ( StoreDir
, StorePath
, storePathToFilePath
)
import qualified System.Nix.StorePath as StorePath
import Data.Attoparsec.Text.Lazy (Parser)
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)

import qualified Data.Attoparsec.Text.Lazy
import qualified Data.Text.Lazy

parseDerivation :: StoreDir -> Text.Lazy.Parser (Derivation StorePath Text)
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 =
Derivation.parseDerivationWith
("\"" *> StorePath.pathParser expectedRoot <* "\"")
Derivation.textParser
Nix.Derivation.parseDerivationWith
pathParser
Nix.Derivation.textParser
where
pathParser = do
text <- Nix.Derivation.textParser
case Data.Attoparsec.Text.Lazy.parseOnly
(System.Nix.StorePath.pathParser expectedRoot)
(Data.Text.Lazy.fromStrict text)
of
Right p -> pure p
Left e -> fail e

buildDerivation :: StoreDir -> Derivation StorePath Text -> Text.Lazy.Builder
buildDerivation :: StoreDir -> Derivation StorePath Text -> Builder
buildDerivation storeDir =
Derivation.buildDerivationWith
(show . storePathToFilePath storeDir)
Nix.Derivation.buildDerivationWith
(show . System.Nix.StorePath.storePathToText storeDir)
show
17 changes: 15 additions & 2 deletions hnix-store-core/src/System/Nix/Internal/Hash.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module System.Nix.Internal.Hash
)
where

import Crypto.Hash (Digest)
import qualified Text.Show
import qualified Crypto.Hash as C
import qualified Data.ByteString as BS
Expand All @@ -45,11 +46,23 @@ instance NamedAlgo C.SHA512 where
algoName = "sha512"

-- | A digest whose 'NamedAlgo' is not known at compile time.
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (C.Digest a)
data SomeNamedDigest = forall a . NamedAlgo a => SomeDigest (Digest a)

instance Show SomeNamedDigest where
show sd = case sd of
SomeDigest (digest :: C.Digest hashType) -> toString $ "SomeDigest " <> algoName @hashType <> ":" <> encodeDigestWith NixBase32 digest
SomeDigest (digest :: Digest hashType) -> toString $ "SomeDigest " <> algoName @hashType <> ":" <> encodeDigestWith NixBase32 digest

instance Eq SomeNamedDigest where
(==) (SomeDigest (a :: Digest aType))
(SomeDigest (b :: Digest bType))
= algoName @aType == algoName @bType
&& encodeDigestWith NixBase32 a == encodeDigestWith NixBase32 b

instance Ord SomeNamedDigest where
(<=) (SomeDigest (a :: Digest aType))
(SomeDigest (b :: Digest bType))
= algoName @aType <= algoName @bType
&& encodeDigestWith NixBase32 a <= encodeDigestWith NixBase32 b

mkNamedDigest :: Text -> Text -> Either String SomeNamedDigest
mkNamedDigest name sriHash =
Expand Down
11 changes: 4 additions & 7 deletions hnix-store-core/src/System/Nix/Internal/Nar/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ import qualified System.Nix.Internal.Nar.Options as Nar
-- of the actions the parser can take, and @ParserState@ for the
-- internals of the parser
newtype NarParser m a = NarParser
{ runNarParser ::
{ _runNarParser ::
State.StateT
ParserState
(Except.ExceptT
Expand Down Expand Up @@ -554,15 +554,12 @@ testParser' :: (m ~ IO) => FilePath -> IO (Either String ())
testParser' fp =
withFile fp ReadMode $ \h -> runParser Nar.narEffectsIO parseNar h "tmp"




-- | Distance to the next multiple of 8
padLen :: Int -> Int
padLen n = (8 - n) `mod` 8


dbgState :: IO.MonadIO m => NarParser m ()
dbgState = do
-- | Debugging helper
_dbgState :: IO.MonadIO m => NarParser m ()
_dbgState = do
s <- State.get
IO.liftIO $ print (tokenStack s, directoryStack s)
4 changes: 2 additions & 2 deletions hnix-store-core/src/System/Nix/Internal/Signature.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import qualified Crypto.Saltine.Internal.ByteSizes as NaClSizes

-- | A NaCl signature.
newtype Signature = Signature ByteString
deriving (Eq, Ord)
deriving (Eq, Generic, Ord, Show)

instance IsEncoding Signature where
decode s
Expand All @@ -42,4 +42,4 @@ data NarSignature = NarSignature
, -- | The archive's signature.
sig :: Signature
}
deriving (Eq, Ord)
deriving (Eq, Generic, Ord, Show)
Loading

0 comments on commit 3b06982

Please sign in to comment.