Skip to content

Commit

Permalink
Add support for building remote imports as FOD to dhall-nixpkgs (#2318)
Browse files Browse the repository at this point in the history
  • Loading branch information
cdepillabout authored Oct 22, 2021
1 parent 705ad21 commit dc31e3c
Show file tree
Hide file tree
Showing 2 changed files with 142 additions and 29 deletions.
169 changes: 140 additions & 29 deletions dhall-nixpkgs/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

{-| @dhall-to-nixpkgs@ is essentially the Dhall analog of @cabal2nix@.
Expand Down Expand Up @@ -75,9 +76,12 @@ import Control.Monad.Morph (hoist)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State.Strict (StateT)
import Data.Aeson (FromJSON)
import Data.ByteArray.Encoding (Base (Base16, Base64), convertToBase)
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (mapMaybe)
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Crypto (SHA256Digest (..))
import Dhall.Import (Status (..), stack)
import Dhall.Parser (Src)
import GHC.Generics (Generic)
Expand All @@ -104,6 +108,7 @@ import Dhall.Core
import qualified Control.Foldl as Foldl
import qualified Control.Monad.Trans.State.Strict as State
import qualified Data.Aeson as Aeson
import qualified Data.ByteString.Char8 as ByteString.Char8
import qualified Data.Foldable as Foldable
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Text as Text
Expand Down Expand Up @@ -149,6 +154,7 @@ data Directory = Directory
, file :: FilePath
, source :: Bool
, document :: Bool
, fixedOutputDerivations :: Bool
}

data NixPrefetchGit = NixPrefetchGit
Expand Down Expand Up @@ -206,6 +212,13 @@ parseDocument =
<> Options.help "Generate documentation for the Nix package"
)

parseFixedOutputDerivations :: Parser Bool
parseFixedOutputDerivations =
Options.switch
( Options.long "fixed-output-derivations"
<> Options.help "Translate Dhall remote imports to Nix fixed-output derivations"
)

parseName :: Parser (Maybe Text)
parseName =
optional
Expand Down Expand Up @@ -271,6 +284,8 @@ parseDirectory = do

document <- parseDocument

fixedOutputDerivations <- parseFixedOutputDerivations

return Directory{..}

parserInfoOptions :: ParserInfo Options
Expand Down Expand Up @@ -306,11 +321,12 @@ nub = Foldl.fold Foldl.nub
This function finds all remote imports that are transitive dependencies of
the given expression, failing if any of them are missing integrity checks.
-}
findExternalDependencies :: Expr Src Import -> StateT Status Shell URL
findExternalDependencies :: Expr Src Import -> StateT Status Shell (URL, SHA256Digest)
findExternalDependencies expression = do
-- This is a best-effort attempt to pick an import alternative if there is
-- more than one
let pickAlt (ImportAlt e0 e1)
let pickAlt :: Expr Src Import -> Maybe (Expr Src Import)
pickAlt (ImportAlt e0 e1)
-- If only the latter import has an integrity check, then select
-- that
| Embed Import{ importHashed = ImportHashed{ hash = Nothing } } <- Dhall.Core.shallowDenote e0
Expand All @@ -322,7 +338,8 @@ findExternalDependencies expression = do
pickAlt _ =
Nothing

let rewrittenExpression =
let rewrittenExpression :: Expr Src Import
rewrittenExpression =
Dhall.Optics.rewriteOf Dhall.Core.subExpressions pickAlt expression

import_ <- lift (Turtle.select (Foldable.toList rewrittenExpression))
Expand All @@ -349,8 +366,8 @@ findExternalDependencies expression = do

Remote url ->
case hash of
Just _ ->
return url
Just sha256 ->
return (url, sha256)
Nothing ->
die (MissingSemanticIntegrityCheck url)

Expand All @@ -366,16 +383,69 @@ findExternalDependencies expression = do
findExternalDependencies parsedExpression

data Dependency = Dependency
{ functionParameter :: (Text, Maybe NExpr)
{ functionParameter :: Maybe (Text, Maybe NExpr)
-- ^ Function parameter used to bring the dependency into scope for the
-- Nix package. The @`Maybe` `NExpr`@ is always `Nothing`, but we
-- Nix package.
--
-- This is 'Nothing' when 'fixedOutputDerivations' is enabled, since these
-- dependencies don't need to passed in as arguments. This is 'Just'
-- when 'fixedOutputDerivations' is not enabled.
--
-- The @'Maybe' 'NExpr'@ is always 'Nothing', but we
-- include it here for convenience
, dependencyExpression :: NExpr
-- ^ The dependency expression to include in the dependency list. This
-- will be an expression of the form:
-- ^ The dependency expression to include in the dependency list.
--
-- 'dependencyToNix' will create an expression of the following form.
-- This is called when 'fixedOutputDerivations' is 'False':
--
-- > someDependency.override { file = "./someFile.dhall" }
--
-- 'dependencyToNixAsFOD' will create an expression of the following form.
-- This is called when 'fixedOutputDerivations' is 'True':
--
-- > buildDhallUrl {
-- > url = "https://some.url.to/a/dhall/file.dhall";
-- > hash = "sha256-ZTSiQUXpPbPfPvS8OeK6dDQE6j6NbP27ho1cg9YfENI=";
-- > dhall-hash =
-- > "sha256:6534a24145e93db3df3ef4bc39e2ba743404ea3e8d6cfdbb868d5c83d61f10d2";
-- > }
}
deriving stock Show

-- | Convert a 'URL' and integrity check to a Nix 'Dependency' that uses the
-- Nix function @buildDhallUrl@ to build.
--
-- This function will create a Nix dependency of the form:
--
-- > buildDhallUrl {
-- > url = "https://some.url.to/a/dhall/file.dhall";
-- > hash = "sha256-ZTSiQUXpPbPfPvS8OeK6dDQE6j6NbP27ho1cg9YfENI=";
-- > dhall-hash =
-- > "sha256:6534a24145e93db3df3ef4bc39e2ba743404ea3e8d6cfdbb868d5c83d61f10d2";
-- > }
--
-- The @hash@ argument is an SRI hash that Nix understands. The @dhall-hash@
-- argument is a base-16-encoded hash that Dhall understands.
dependencyToNixAsFOD :: URL -> SHA256Digest -> IO Dependency
dependencyToNixAsFOD url (SHA256Digest shaBytes) = do
let functionParameter = Nothing

let dhallHash =
"sha256:" <> ByteString.Char8.unpack (convertToBase Base16 shaBytes)

let nixSRIHash =
"sha256-" <> ByteString.Char8.unpack (convertToBase Base64 shaBytes)

let dependencyExpression =
"buildDhallUrl"
@@ Nix.attrsE
[ ("url", Nix.mkStr $ Dhall.Core.pretty url)
, ("hash", Nix.mkStr $ Text.pack nixSRIHash)
, ("dhall-hash", Nix.mkStr $ Text.pack dhallHash)
]

return Dependency{..}

{-| The Nixpkgs support for Dhall implements two conventions that
@dhall-to-nixpkgs@ depends on:
Expand Down Expand Up @@ -409,7 +479,7 @@ dependencyToNix url@URL{ authority, path } = do
"dhall-lang" : "dhall-lang" : _rev : "Prelude" : rest -> do
let fileArgument = Text.intercalate "/" rest

let functionParameter = (prelude, Nothing)
let functionParameter = Just (prelude, Nothing)

let dependencyExpression =
(Nix.mkSym prelude @. "overridePackage")
Expand All @@ -421,7 +491,7 @@ dependencyToNix url@URL{ authority, path } = do
_owner : repo : _rev : rest -> do
let fileArgument = Text.intercalate "/" rest

let functionParameter = (repo, Nothing)
let functionParameter = Just (repo, Nothing)

let dependencyExpression =
(Nix.mkSym repo @. "overridePackage")
Expand Down Expand Up @@ -460,10 +530,10 @@ dependencyToNix url@URL{ authority, path } = do
rest
rest ->
rest

let fileArgument = Text.intercalate "/" pathComponents

let functionParameter = (prelude, Nothing)
let functionParameter = Just (prelude, Nothing)

let dependencyExpression =
(Nix.mkSym prelude @. "overridePackage")
Expand All @@ -475,6 +545,45 @@ dependencyToNix url@URL{ authority, path } = do
_ -> do
die (UnsupportedDomainDependency url authority)

-- | Turn a list of 'Dependency's into an argument list for the generated Nix
-- function.
--
-- The following 'makeNixFunctionParams' call:
--
-- @@
-- 'makeNixFunctionParams'
-- \"buildDhallDirectoryPackage\"
-- [ 'Dependency' ('Just' (\"Prelude\", 'Nothing')) ...
-- , 'Dependency' ('Just' (\"Prelude\", 'Nothing')) ...
-- , 'Dependency' 'Nothing' ...
-- , 'Dependency' ('Just' (\"example-repo\", 'Nothing')) ...
-- ]
-- @@
--
-- will generate an argument list like the following:
--
-- > { buildDhallDirectoryPackage, buildDhallUrl, Prelude, example-repo }:
--
-- Note that identical 'functionParameter's will be collapsed into a single
-- parameter (like @Prelude@ above).
--
-- @buildDhallUrl@ will be added as an argument only if there is a 'Dependency'
-- with a 'Nothing' value for 'functionalParameter'.
makeNixFunctionParams :: Text -> [Dependency] -> [(Text, Maybe NExpr)]
makeNixFunctionParams buildDhallFuncName nixDependencies =
let containsBuildDhallUrlDependency =
any (\dep -> functionParameter dep == Nothing) nixDependencies

buildDhallUrlParam =
if containsBuildDhallUrlDependency
then [ ("buildDhallUrl", Nothing) ]
else [ ]

in ( [ (buildDhallFuncName, Nothing) ]
<> buildDhallUrlParam
<> nub (mapMaybe functionParameter nixDependencies)
)

githubToNixpkgs :: GitHub -> IO ()
githubToNixpkgs GitHub{ name, uri, rev = maybeRev, hash, fetchSubmodules, directory, file, source, document } = do
URI{ uriScheme, uriAuthority = Just URIAuth{ uriUserInfo, uriRegName, uriPort }, uriPath, uriQuery, uriFragment } <- do
Expand Down Expand Up @@ -600,18 +709,16 @@ githubToNixpkgs GitHub{ name, uri, rev = maybeRev, hash, fetchSubmodules, direct

dependencies <- Turtle.reduce Foldl.nub (State.evalStateT (findExternalDependencies expression) status)

nixDependencies <- traverse dependencyToNix dependencies
nixDependencies <- traverse (\(url, _sha256) -> dependencyToNix url) dependencies

let buildDhallGitHubPackage = "buildDhallGitHubPackage"

let functionParams =
makeNixFunctionParams buildDhallGitHubPackage nixDependencies

let nixExpression =
Nix.mkFunction
(Nix.mkParamset
( [ (buildDhallGitHubPackage, Nothing) ]
<> nub (fmap functionParameter nixDependencies)
)
False
)
(Nix.mkParamset functionParams False)
( Nix.mkSym buildDhallGitHubPackage
@@ Nix.attrsE
[ ("name", Nix.mkStr finalName)
Expand All @@ -633,7 +740,7 @@ githubToNixpkgs GitHub{ name, uri, rev = maybeRev, hash, fetchSubmodules, direct
Prettyprint.Text.putDoc ((Nix.Pretty.prettyNix nixExpression) <> "\n")

directoryToNixpkgs :: Directory -> IO ()
directoryToNixpkgs Directory{ name, directory, file, source, document } = do
directoryToNixpkgs Directory{ name, directory, file, source, document, fixedOutputDerivations } = do
let finalName =
case name of
Nothing -> Turtle.format fp (Turtle.dirname directory)
Expand Down Expand Up @@ -661,7 +768,13 @@ directoryToNixpkgs Directory{ name, directory, file, source, document } = do

dependencies <- Turtle.reduce Foldl.nub (State.evalStateT (findExternalDependencies expression) status)

nixDependencies <- traverse dependencyToNix dependencies
let depToNix :: (URL, SHA256Digest) -> IO Dependency
depToNix (url, sha256) =
if fixedOutputDerivations
then dependencyToNixAsFOD url sha256
else dependencyToNix url

nixDependencies <- traverse depToNix dependencies

let buildDhallDirectoryPackage = "buildDhallDirectoryPackage"

Expand All @@ -671,14 +784,12 @@ directoryToNixpkgs Directory{ name, directory, file, source, document } = do
where
directoryString = Turtle.encodeString directory

let functionParams =
makeNixFunctionParams buildDhallDirectoryPackage nixDependencies

let nixExpression =
Nix.mkFunction
(Nix.mkParamset
( [ (buildDhallDirectoryPackage, Nothing) ]
<> nub (fmap functionParameter nixDependencies)
)
False
)
(Nix.mkParamset functionParams False)
( Nix.mkSym buildDhallDirectoryPackage
@@ Nix.attrsE
[ ("name", Nix.mkStr finalName)
Expand Down Expand Up @@ -942,7 +1053,7 @@ The following command:
, rev : Text
, path : Text
, sha256 : Text
, fetchSubmodules : Bool
, fetchSubmodules : Bool
}

... but JSON decoding failed with the following error:
Expand Down
2 changes: 2 additions & 0 deletions dhall-nixpkgs/dhall-nixpkgs.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -18,13 +18,15 @@ Executable dhall-to-nixpkgs
Main-Is: Main.hs
Build-Depends: base >= 4.11 && < 5
, aeson >= 1.0.0.0 && < 1.6
, bytestring < 0.12
, data-fix
, dhall >= 1.32.0 && < 1.41
, foldl < 1.5
, hnix >= 0.10.1 && < 0.15
, lens-family-core >= 1.0.0 && < 2.2
-- megaparsec follows SemVer: https://github.com/mrkkrp/megaparsec/issues/469#issuecomment-927918469
, megaparsec >= 7.0.0 && < 10
, memory >= 0.14 && < 0.17
, mmorph < 1.3
, neat-interpolation < 0.6
, optparse-applicative >= 0.14.0.0 && < 0.17
Expand Down

0 comments on commit dc31e3c

Please sign in to comment.