Skip to content

Commit 26c5f7a

Browse files
committed
Enable comment suppression in generated nix code
1 parent 3414c38 commit 26c5f7a

File tree

9 files changed

+45
-40
lines changed

9 files changed

+45
-40
lines changed

.last-exported-commit

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1 +1 @@
1-
Last exported commit from parent repo: 8c0dabbabd903d9c05f2745af87ec86f6f413791
1+
Last exported commit from parent repo: b4a296093f5e7ee90367d58a20e8c4c67d8f7e64

nix-bootstrap.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ cabal-version: 2.0
55
-- see: https://github.com/sol/hpack
66

77
name: nix-bootstrap
8-
version: 1.4.0.0
8+
version: 1.4.1.0
99
author: gchquser
1010
maintainer: [email protected]
1111
copyright: Crown Copyright

package.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@
1212
# See the License for the specific language governing permissions and
1313
# limitations under the License.
1414
name: nix-bootstrap
15-
version: 1.4.0.0
15+
version: 1.4.1.0
1616
author: gchquser
1717
maintainer: [email protected]
1818
copyright: Crown Copyright

src/Bootstrap/Data/Bootstrappable.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,8 @@ module Bootstrap.Data.Bootstrappable
2222
where
2323

2424
import Bootstrap.Nix.Expr
25-
( Identifier (unIdentifier),
25+
( CommentsPolicy (ShowComments),
26+
Identifier (unIdentifier),
2627
IsNixExpr (toNixExpr),
2728
isMostlyCorrectlyScoped,
2829
writeExprFormatted,
@@ -146,7 +147,7 @@ bootstrapContentNix a = do
146147
( ("Could not format nix expression: " <>)
147148
. displayException
148149
)
149-
<$> writeExprFormatted expr
150+
<$> writeExprFormatted ShowComments expr
150151
Left (i1 :| iRest) ->
151152
pure . Left $
152153
"Nix expression is incorrectly scoped; it references the out of scope "

src/Bootstrap/Nix/Expr.hs

Lines changed: 28 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -61,6 +61,7 @@ module Bootstrap.Nix.Expr
6161
writeExprForTerminal,
6262
-- | `writeBinding` writes out a `Binding` without formatting it.
6363
writeBinding,
64+
CommentsPolicy (..),
6465

6566
-- * Validation
6667

@@ -109,7 +110,6 @@ import Text.Megaparsec
109110
)
110111
import Text.Megaparsec.Char (alphaNumChar, char, letterChar, space, space1, string)
111112
import qualified Text.Megaparsec.Char.Lexer as L
112-
import Text.Regex (mkRegex, subRegex)
113113

114114
type Parser = Parsec Void Text
115115

@@ -178,31 +178,34 @@ infixl 7 |++
178178
(|++) :: Expr -> Expr -> Expr
179179
(|++) e1 = (e1 |* EListConcatOperator |*)
180180

181+
-- | Whether to include comments when formatting
182+
data CommentsPolicy = ShowComments | HideComments
183+
181184
-- | Writes out an `Expr` as Nix code
182-
writeExpr :: Expr -> Text
183-
writeExpr =
185+
writeExpr :: CommentsPolicy -> Expr -> Text
186+
writeExpr cp =
184187
\case
185-
EApplication e1 e2 -> writeExpr e1 <> " " <> writeExpr e2
186-
EFunc args e -> writeFunctionArgs args <> writeExpr e
187-
EGrouping e -> "(" <> writeExpr e <> ")"
188+
EApplication e1 e2 -> writeExpr cp e1 <> " " <> writeExpr cp e2
189+
EFunc args e -> writeFunctionArgs args <> writeExpr cp e
190+
EGrouping e -> "(" <> writeExpr cp e <> ")"
188191
EIdent (Identifier i) -> i
189192
EImport -> "import"
190-
ELetIn bindings e -> "let " <> sconcat (writeBinding <$> bindings) <> "in " <> writeExpr e
193+
ELetIn bindings e -> "let " <> sconcat (writeBinding cp <$> bindings) <> "in " <> writeExpr cp e
191194
EList exprs ->
192195
"["
193196
<> (if length exprs > 2 then "\n" else "")
194-
<> T.concat (intersperse " " (writeExpr <$> exprs))
197+
<> T.concat (intersperse " " (writeExpr cp <$> exprs))
195198
<> "]"
196199
EListConcatOperator -> "++"
197200
ELit l -> writeLiteral l
198-
EPropertyAccess e1 p -> writeExpr e1 <> "." <> writeProperty p
201+
EPropertyAccess e1 p -> writeExpr cp e1 <> "." <> writeProperty cp p
199202
ESet isRec bindings ->
200203
(if isRec then "rec " else "")
201204
<> "{"
202205
<> (if length bindings > 2 then "\n" else " ")
203-
<> mconcat (writeBinding <$> bindings)
206+
<> mconcat (writeBinding cp <$> bindings)
204207
<> "}"
205-
EWith additionalScope e -> "with " <> writeExpr additionalScope <> "; " <> writeExpr e
208+
EWith additionalScope e -> "with " <> writeExpr cp additionalScope <> "; " <> writeExpr cp e
206209
. mergeNestedLetExprs
207210

208211
-- | Recursively merges nested let expressions into a single let in block
@@ -236,19 +239,15 @@ mergeNestedLetExprs = \case
236239
PCons p1 p2 -> PCons (mergeNestedLetExprsP p1) (mergeNestedLetExprsP p2)
237240

238241
-- | Writes out an `Expr` as Nix code, formatting it with alejandra
239-
writeExprFormatted :: MonadIO m => Expr -> m (Either IOException Text)
240-
writeExprFormatted = runExceptT . (fmap toText <$> alejandra . toString . writeExpr)
242+
writeExprFormatted :: MonadIO m => CommentsPolicy -> Expr -> m (Either IOException Text)
243+
writeExprFormatted cp = runExceptT . (fmap toText <$> alejandra . toString . writeExpr cp)
241244

242245
-- | Like writeExpr, but strips out line comments,
243246
-- replaces whitespace groups with a single space,
244247
-- and escapes dollar symbols.
245248
writeExprForTerminal :: Expr -> Text
246249
writeExprForTerminal e =
247-
unwords . words . toText $
248-
subRegex
249-
(mkRegex "\n#[^\n]*\n")
250-
(toString . T.replace "$" "\\$" $ writeExpr e)
251-
" "
250+
unwords . words . T.replace "$" "\\$" $ writeExpr HideComments e
252251

253252
-- | Runs `parseE`, parsing a Nix expression
254253
parseExpr :: Text -> Either Text Expr
@@ -386,12 +385,14 @@ infixr 4 |=
386385
(|=) = BNameValue
387386

388387
-- | Writes out a `Binding` as Nix code
389-
writeBinding :: Binding -> Text
390-
writeBinding = \case
388+
writeBinding :: CommentsPolicy -> Binding -> Text
389+
writeBinding cp = \case
391390
BInherit xs -> "inherit " <> writeIdentifiers " " xs <> ";\n"
392-
BInheritFrom from xs -> "inherit (" <> writeExpr from <> ") " <> writeIdentifiers " " xs <> ";\n"
393-
BLineComment c -> "# " <> c <> "\n"
394-
BNameValue p v -> writeProperty p <> " = " <> writeExpr v <> ";\n"
391+
BInheritFrom from xs -> "inherit (" <> writeExpr cp from <> ") " <> writeIdentifiers " " xs <> ";\n"
392+
BLineComment c -> case cp of
393+
ShowComments -> "# " <> c <> "\n"
394+
HideComments -> ""
395+
BNameValue p v -> writeProperty cp p <> " = " <> writeExpr cp v <> ";\n"
395396
where
396397
writeIdentifiers :: Text -> NonEmpty Identifier -> Text
397398
writeIdentifiers sep = T.concat . intersperse sep . fmap unIdentifier . toList
@@ -605,11 +606,11 @@ parseProperty requireDot = do
605606
Nothing -> pure p
606607

607608
-- | Writes out a `Property` as Nix code
608-
writeProperty :: Property -> Text
609-
writeProperty = \case
609+
writeProperty :: CommentsPolicy -> Property -> Text
610+
writeProperty cp = \case
610611
PIdent (Identifier i) -> i
611-
PAntiquote e -> "${" <> writeExpr e <> "}"
612-
PCons p1 p2 -> writeProperty p1 <> "." <> writeProperty p2
612+
PAntiquote e -> "${" <> writeExpr cp e <> "}"
613+
PCons p1 p2 -> writeProperty cp p1 <> "." <> writeProperty cp p2
613614

614615
-- | Parses an `ESet`
615616
parseSet ::

src/Bootstrap/Nix/Expr/ReproducibleBuild/Go.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,7 @@ module Bootstrap.Nix.Expr.ReproducibleBuild.Go (reproducibleGoBuild) where
77
import Bootstrap.Data.ProjectName (ProjectName (unProjectName))
88
import Bootstrap.Nix.Expr
99
( Binding (BLineComment),
10+
CommentsPolicy (ShowComments),
1011
Expr (ELit, ESet),
1112
Literal (LString),
1213
nix,
@@ -33,5 +34,5 @@ reproducibleGoBuild projectName =
3334
|],
3435
[nixbinding|# When the build fails, it will tell you what the expected hash is.
3536
|],
36-
BLineComment (writeBinding [nixbinding|vendorSha256 = "sha256-00000000000000000000000000000000000000000000";|])
37+
BLineComment (writeBinding ShowComments [nixbinding|vendorSha256 = "sha256-00000000000000000000000000000000000000000000";|])
3738
]

src/Bootstrap/Nix/Flake.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@ import Bootstrap.GitPod (resetPermissionsInGitPod)
1616
import Bootstrap.Monad (MonadBootstrap)
1717
import Bootstrap.Nix.Evaluate (NixBinaryPaths, runNix)
1818
import Bootstrap.Nix.Expr
19-
( Expr (ELit, ESet),
19+
( CommentsPolicy (ShowComments),
20+
Expr (ELit, ESet),
2021
Literal (LString),
2122
nixbinding,
2223
nixproperty,
@@ -53,7 +54,7 @@ writeIntermediateFlake projectName =
5354
. try @_ @IOException
5455
. writeFileText "flake.nix"
5556
. (<> "\n")
56-
. writeExpr
57+
. writeExpr ShowComments
5758
$ intermediateFlake projectName
5859

5960
intermediateFlake :: ProjectName -> Expr

test/Bootstrap/Nix/ExprSpec.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module Bootstrap.Nix.ExprSpec (spec) where
99

1010
import Bootstrap.Nix.Expr
1111
( Binding (BInherit, BInheritFrom, BLineComment, BNameValue),
12+
CommentsPolicy (ShowComments),
1213
Expr
1314
( EApplication,
1415
EFunc,
@@ -150,12 +151,12 @@ spec = do
150151
it "backtracks if an identifier begins with \"import\"" do
151152
parseExpr "imports" `shouldBe` Right (EIdent $ Identifier "imports")
152153
it "merges nested let-in expressions" do
153-
parseExpr (writeExpr [nix|let x = 5; in let y = 4; in ""|])
154+
parseExpr (writeExpr ShowComments [nix|let x = 5; in let y = 4; in ""|])
154155
`shouldBe` Right [nix|let x = 5; y = 4; in ""|]
155156
describe "EApplication" do
156157
it "roundtrips with multiple arguments" do
157158
let expr = EApplication (EApplication EImport (EIdent $ Identifier "nixpkgs")) (ESet False [])
158-
parseExpr (writeExpr expr) `shouldBe` Right expr
159+
parseExpr (writeExpr ShowComments expr) `shouldBe` Right expr
159160
describe "EPropertyAccess" do
160161
it "correctly parses a property access expression" do
161162
parseExpr "(let a = \"hello\"; b = \"world\"; in a).b"
@@ -289,7 +290,7 @@ spec = do
289290

290291
-- | An expectation that a Nix expression is the same when written out and parsed again.
291292
roundtrips :: Expr -> Expectation
292-
roundtrips e = parseExpr (writeExpr e) `shouldBe` Right e
293+
roundtrips e = parseExpr (writeExpr ShowComments e) `shouldBe` Right e
293294

294295
-- Arbitrary Helpers
295296

test/Bootstrap/Nix/FlakeSpec.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
module Bootstrap.Nix.FlakeSpec (spec) where
55

66
import Bootstrap.Data.ProjectName (mkProjectName)
7-
import Bootstrap.Nix.Expr (writeExprFormatted)
7+
import Bootstrap.Nix.Expr (CommentsPolicy (ShowComments), writeExprFormatted)
88
import Bootstrap.Nix.Flake (intermediateFlake)
99
import qualified Relude.Unsafe as Unsafe
1010
import Test.Hspec (Spec, describe, it)
@@ -14,7 +14,7 @@ import Text.RawString.QQ (r)
1414
spec :: Spec
1515
spec = describe "intermediateFlake" do
1616
it "correctly writes the intermediate flake" do
17-
e <- writeExprFormatted (intermediateFlake $ Unsafe.fromJust $ mkProjectName "test-project")
17+
e <- writeExprFormatted ShowComments (intermediateFlake $ Unsafe.fromJust $ mkProjectName "test-project")
1818
e
1919
`shouldBe` Right
2020
[r|{

0 commit comments

Comments
 (0)