Skip to content

Commit

Permalink
remote: fix handling of BuildResult.builtOutputs
Browse files Browse the repository at this point in the history
  • Loading branch information
sorki committed Dec 6, 2023
1 parent a2ab4b3 commit 7806a97
Show file tree
Hide file tree
Showing 4 changed files with 35 additions and 13 deletions.
19 changes: 17 additions & 2 deletions hnix-store-json/src/System/Nix/JSON.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ which is required for `-remote`.
module System.Nix.JSON where

import Data.Aeson
import Data.Aeson.Types (toJSONKeyText)
import Deriving.Aeson
import System.Nix.Base (BaseEncoding(NixBase32))
import System.Nix.OutputName (OutputName)
Expand Down Expand Up @@ -90,7 +91,13 @@ instance ToJSON (DerivationOutput OutputName) where
. System.Nix.Realisation.derivationOutputBuilder
System.Nix.OutputName.unOutputName

instance ToJSONKey (DerivationOutput OutputName)
instance ToJSONKey (DerivationOutput OutputName) where
toJSONKey =
toJSONKeyText
$ Data.Text.Lazy.toStrict
. Data.Text.Lazy.Builder.toLazyText
. System.Nix.Realisation.derivationOutputBuilder
System.Nix.OutputName.unOutputName

instance FromJSON (DerivationOutput OutputName) where
parseJSON =
Expand All @@ -102,7 +109,15 @@ instance FromJSON (DerivationOutput OutputName) where
System.Nix.OutputName.mkOutputName
)

instance FromJSONKey (DerivationOutput OutputName)
instance FromJSONKey (DerivationOutput OutputName) where
fromJSONKey =
FromJSONKeyTextParser
( either
(fail . show)
pure
. System.Nix.Realisation.derivationOutputParser
System.Nix.OutputName.mkOutputName
)

instance ToJSON Signature where
toJSON = toJSON . System.Nix.Signature.signatureToText
Expand Down
4 changes: 2 additions & 2 deletions hnix-store-json/tests/JSONSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,10 +95,10 @@ spec = do
encode sampleDerivationOutput `shouldBe` "\"sha256:1b4sb93wp679q4zx9k1ignby1yna3z7c4c2ri3wphylbc2dwsys0!foo\""

it "sampleRealisation0 matches preimage" $
encode sampleRealisation0 `shouldBe` "{\"outPath\":\"cdips4lakfk1qbf1x68fq18wnn3r5r14-builder.sh\",\"signatures\":[],\"dependentRealisations\":[]}"
encode sampleRealisation0 `shouldBe` "{\"outPath\":\"cdips4lakfk1qbf1x68fq18wnn3r5r14-builder.sh\",\"signatures\":[],\"dependentRealisations\":{}}"

it "sampleRealisation1 matches preimage" $
encode sampleRealisation1 `shouldBe` "{\"outPath\":\"5rwxzi7pal3qhpsyfc16gzkh939q1np6-curl-7.82.0.drv\",\"signatures\":[\"SMjnB3mPgXYjXacU+xN24BdzXlAgGAuFnYwPddU3bhjfHBeQus/OimdIPMgR/JMKFPHXORrk7pbjv68vecTEBA==\",\"fW3iEMfyx6IZzGNswD54BjclfkXiYzh0xRXddrXfJ1rp1l8p1xTi9/0g2EibbwLFb6p83cwIJv5KtTGksC54CQ==\"],\"dependentRealisations\":[[\"sha256:1b4sb93wp679q4zx9k1ignby1yna3z7c4c2ri3wphylbc2dwsys0!foo\",\"9472ijanf79nlkb5n1yh57s7867p1930-testFixed\"]]}"
encode sampleRealisation1 `shouldBe` "{\"outPath\":\"5rwxzi7pal3qhpsyfc16gzkh939q1np6-curl-7.82.0.drv\",\"signatures\":[\"SMjnB3mPgXYjXacU+xN24BdzXlAgGAuFnYwPddU3bhjfHBeQus/OimdIPMgR/JMKFPHXORrk7pbjv68vecTEBA==\",\"fW3iEMfyx6IZzGNswD54BjclfkXiYzh0xRXddrXfJ1rp1l8p1xTi9/0g2EibbwLFb6p83cwIJv5KtTGksC54CQ==\"],\"dependentRealisations\":{\"sha256:1b4sb93wp679q4zx9k1ignby1yna3z7c4c2ri3wphylbc2dwsys0!foo\":\"9472ijanf79nlkb5n1yh57s7867p1930-testFixed\"}}"

forceRight
:: Show a
Expand Down
2 changes: 2 additions & 0 deletions hnix-store-remote/hnix-store-remote.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -107,8 +107,10 @@ library
build-depends:
base >=4.12 && <5
, hnix-store-core >= 0.8 && <0.9
, hnix-store-json >= 0.1
, hnix-store-nar >= 0.1
, hnix-store-tests >= 0.1
, aeson
, attoparsec
, bytestring
, cereal
Expand Down
23 changes: 14 additions & 9 deletions hnix-store-remote/src/System/Nix/Store/Remote/Serializer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ import qualified Control.Monad.Reader
import qualified Data.Attoparsec.Text
import qualified Data.Bits
import qualified Data.ByteString
import qualified Data.ByteString.Lazy
import qualified Data.HashSet
import qualified Data.Map.Strict
import qualified Data.Maybe
Expand All @@ -133,6 +134,7 @@ import System.Nix.ContentAddress (ContentAddress)
import System.Nix.Derivation (Derivation(..), DerivationOutput(..))
import System.Nix.DerivedPath (DerivedPath, ParseOutputsError)
import System.Nix.Hash (HashAlgo(..))
import System.Nix.JSON ()
import System.Nix.OutputName (OutputName)
import System.Nix.Realisation (DerivationOutputError, Realisation(..))
import System.Nix.Signature (Signature, NarSignature)
Expand All @@ -141,6 +143,7 @@ import System.Nix.StorePath (HasStoreDir(..), InvalidNameError, InvalidPathError
import System.Nix.StorePath.Metadata (Metadata(..), StorePathTrust(..))
import System.Nix.Store.Remote.Types

import qualified Data.Aeson
import qualified Data.Coerce
import qualified Data.Bifunctor
import qualified Data.Some
Expand Down Expand Up @@ -616,14 +619,11 @@ realisation
=> NixSerializer r SError Realisation
realisation = Serializer
{ getS = do
realisationOutPath <- getS storePath
realisationSignatures <- getS (set signature)
realisationDependencies <- getS (mapS derivationOutputTyped storePath)
pure Realisation{..}
, putS = \Realisation{..} -> do
putS storePath realisationOutPath
putS (set signature) realisationSignatures
putS (mapS derivationOutputTyped storePath) realisationDependencies
rb <- getS byteString