Skip to content

Commit

Permalink
Support derivations with content-addressed outputs
Browse files Browse the repository at this point in the history
Forward port of haskell-nix#26
  • Loading branch information
rickynils authored and sorki committed Dec 10, 2023
1 parent 9d7cb76 commit cbc2572
Show file tree
Hide file tree
Showing 4 changed files with 71 additions and 17 deletions.
15 changes: 14 additions & 1 deletion src/Nix/Derivation/Builder.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,15 +83,28 @@ buildDerivationWith string outputName drvOutput drvInputs (Derivation {..}) =
-- | Render a @DerivationOutput@ as a `Builder` using custom
-- renderer for filepaths
buildDerivationOutputWith
:: (fp -> Builder)
:: Monoid fp
=> (fp -> Builder)
-> DerivationOutput fp
-> Builder
buildDerivationOutputWith filepath (DerivationOutput {..}) =
filepath path
<> ","
<> string' mempty
<> ","
<> string' mempty
buildDerivationOutputWith filepath (FixedDerivationOutput {..}) =
filepath path
<> ","
<> string' hashAlgo
<> ","
<> string' hash
buildDerivationOutputWith filepath (ContentAddressedDerivationOutput {..}) =
filepath mempty
<> ","
<> string' hashAlgo
<> ","
<> string' mempty

-- | Render a @DerivationInputs@ as a `Builder` using custom
-- renderer for filepaths and output names
Expand Down
18 changes: 16 additions & 2 deletions src/Nix/Derivation/Parser.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}

Expand Down Expand Up @@ -110,14 +111,27 @@ parseDerivationWith string outputName parseOutput parseInputs = do
pure Derivation {..}

-- | Parse a derivation output
parseDerivationOutputWith :: Parser fp -> Parser (DerivationOutput fp)
parseDerivationOutputWith
:: ( Eq fp
, Monoid fp
)
=> Parser fp
-> Parser (DerivationOutput fp)
parseDerivationOutputWith filepath = do
path <- filepath
","
hashAlgo <- textParser
","
hash <- textParser
pure DerivationOutput {..}
if
| path /= mempty && hashAlgo == mempty && hash == mempty ->
pure DerivationOutput {..}
| path /= mempty && hashAlgo /= mempty && hash /= mempty ->
pure FixedDerivationOutput {..}
| path == mempty && hashAlgo /= mempty && hash == mempty ->
pure ContentAddressedDerivationOutput {..}
| otherwise ->
fail "bad output in derivation"

-- | Parse a derivation inputs
parseDerivationInputsWith
Expand Down
26 changes: 18 additions & 8 deletions src/Nix/Derivation/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,13 +54,23 @@ data DerivationInputs fp drvOutput = DerivationInputs
instance (NFData a, NFData b) => NFData (DerivationInputs a b)

-- | An output of a Nix derivation
data DerivationOutput fp = DerivationOutput
{ path :: fp
-- ^ Path where the output will be saved
, hashAlgo :: Text
-- ^ Hash used for expected hash computation
, hash :: Text
-- ^ Expected hash
} deriving (Eq, Generic, Ord, Show)
data DerivationOutput fp
= DerivationOutput
{ path :: fp
-- ^ Path where the output will be saved
}
| FixedDerivationOutput
{ path :: fp
-- ^ Path where the output will be saved
, hashAlgo :: Text
-- ^ Hash used for expected hash computation
, hash :: Text
-- ^ Expected hash
}
| ContentAddressedDerivationOutput
{ hashAlgo :: Text
-- ^ Hash used for expected hash computation
}
deriving (Eq, Generic, Ord, Show)

instance (NFData a) => NFData (DerivationOutput a)
29 changes: 23 additions & 6 deletions tests/Property.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Nix.Derivation
, DerivationOutput(..)
)
import Prelude hiding (FilePath, either)
import Test.QuickCheck (Arbitrary(..))
import Test.QuickCheck (Arbitrary(..), Gen, oneof)

import qualified Data.Attoparsec.Text.Lazy
import qualified Data.Text
Expand All @@ -37,11 +37,28 @@ instance Arbitrary (DerivationInputs FilePath Text) where
pure DerivationInputs {..}

instance Arbitrary (DerivationOutput FilePath) where
arbitrary = do
path <- arbitrary
hashAlgo <- arbitrary
hash <- arbitrary
pure DerivationOutput {..}
arbitrary = oneof
[ derivationOutput
, fixedDerivationOutput
, contentAddressedDerivationOutput
]

derivationOutput :: Gen (DerivationOutput FilePath)
derivationOutput = do
path <- arbitrary
return (DerivationOutput {..})

fixedDerivationOutput :: Gen (DerivationOutput FilePath)
fixedDerivationOutput = do
path <- arbitrary
hashAlgo <- arbitrary
hash <- arbitrary
return (FixedDerivationOutput {..})

contentAddressedDerivationOutput :: Gen (DerivationOutput FilePath)
contentAddressedDerivationOutput = do
hashAlgo <- arbitrary
return (ContentAddressedDerivationOutput {..})

instance Arbitrary (Derivation FilePath Text Text DerivationOutput DerivationInputs) where
arbitrary = do
Expand Down

0 comments on commit cbc2572

Please sign in to comment.